SUBROUTINE import_mesh(msh,mesh_file)
USE tools_mesh
IMPLICIT NONE
!
TYPE(mesh), INTENT(INOUT) :: msh
CHARACTER(len=*), INTENT(INOUT) :: mesh_file
!
INTEGER :: i, intbuf(2)
INTEGER :: icontxt, mypnum
CHARACTER(len=4) :: fmt
icontxt = icontxt_()
mypnum = mypnum_()
CALL sw_msh%tic()
! Reads the mesh object on P0...
IF(mypnum == 0) THEN
! Sets mesh format
mesh_file = ADJUSTR(mesh_file)
i = SCAN(mesh_file,'.',back=.TRUE.)
IF(i == 0) THEN
WRITE(*,100)
WRITE(*,'(a24,a80)')'Expected to find file: ',mesh_file
CALL abort_psblas
END IF
i = i + 1
fmt = mesh_file(i:LEN(mesh_file))
SELECT CASE (fmt)
CASE('cgns')
#ifdef HAVE_CGNS
CALL rd_cgns_mesh(mesh_file, msh%id, msh%nbc, msh%ncd, &
& msh%verts, msh%faces, msh%cells, &
& msh%v2f, msh%v2c, msh%f2c, msh%c2g)
#else
ERROR STOP "MORFEUS built without CNGS support! Unable to continue."
#endif
CASE('e')
#ifdef HAVE_EXODUS
CALL rd_exodus_mesh(mesh_file, msh%id, msh%nbc, msh%ncd, &
& msh%verts, msh%faces, msh%cells, &
& msh%v2f, msh%v2c, msh%f2c, msh%c2g)
#else
ERROR STOP "MORFEUS built without exodus support! Unable to continue."
#endif
CASE('msh')
CALL rd_gmsh_mesh(mesh_file, msh%id, msh%nbc, msh%ncd, &
& msh%verts, msh%faces, msh%cells, &
& msh%v2f, msh%v2c, msh%f2c, msh%c2g)
CASE('neu')
CALL rd_gambit_mesh(mesh_file, msh%id, msh%nbc, msh%ncd, &
& msh%verts, msh%faces, msh%cells, &
& msh%v2f, msh%v2c, msh%f2c, msh%c2g)
CASE DEFAULT
WRITE(*,200)
CALL abort_psblas
END SELECT
END IF
! ... then bcast msh%(id,nbc,ncd)
IF(mypnum == 0) THEN
CALL psb_bcast(icontxt,msh%id)
intbuf(1) = msh%nbc
intbuf(2) = msh%ncd
CALL psb_bcast(icontxt,intbuf)
ELSE
CALL psb_bcast(icontxt,msh%id)
CALL psb_bcast(icontxt,intbuf)
msh%nbc = intbuf(1)
msh%ncd = intbuf(2)
END IF
CALL sw_msh%toc()
100 FORMAT('ERROR! Unsupported mesh filename in IMPORT_MESH')
200 FORMAT('ERROR! Unsupported mesh format in IMPORT_MESH')
END SUBROUTINE import_mesh