wr_vtk_mesh Subroutine

subroutine wr_vtk_mesh(ncd, verts, cells, v2c, points, cell_ids, v2cconn, icverts)

Uses

  • proc~~wr_vtk_mesh~~UsesGraph proc~wr_vtk_mesh wr_vtk_mesh module~class_vertex class_vertex proc~wr_vtk_mesh->module~class_vertex module~class_cell class_cell proc~wr_vtk_mesh->module~class_cell module~class_psblas class_psblas proc~wr_vtk_mesh->module~class_psblas module~class_connectivity class_connectivity proc~wr_vtk_mesh->module~class_connectivity module~class_vertex->module~class_psblas module~class_vector class_vector module~class_vertex->module~class_vector module~class_cell->module~class_psblas module~class_stopwatch class_stopwatch module~class_psblas->module~class_stopwatch module~tools_psblas tools_psblas module~class_psblas->module~tools_psblas module~class_connectivity->module~class_psblas module~class_stopwatch->module~tools_psblas psb_base_mod psb_base_mod module~class_stopwatch->psb_base_mod module~class_vector->module~class_psblas psb_prec_mod psb_prec_mod module~tools_psblas->psb_prec_mod module~tools_psblas->psb_base_mod psb_krylov_mod psb_krylov_mod module~tools_psblas->psb_krylov_mod

Set x,y,z positions

Arguments

Type IntentOptional AttributesName
integer, intent(in) :: ncd
type(vertex), intent(in) :: verts(:)
type(cell), intent(in) :: cells(:)
type(connectivity), intent(in) :: v2c
real(kind=psb_dpk_), intent(out), dimension(:,:), allocatable:: points
integer, intent(out), dimension(:), allocatable:: cell_ids
integer, intent(out), dimension(:), allocatable:: v2cconn
integer, intent(out), dimension(:), allocatable:: icverts

Calls

proc~~wr_vtk_mesh~~CallsGraph proc~wr_vtk_mesh wr_vtk_mesh interface~abort_psblas abort_psblas proc~wr_vtk_mesh->interface~abort_psblas proc~abort_psblas abort_psblas interface~abort_psblas->proc~abort_psblas psb_abort psb_abort proc~abort_psblas->psb_abort

Called by

proc~~wr_vtk_mesh~~CalledByGraph proc~wr_vtk_mesh wr_vtk_mesh proc~write_vtk_mesh write_vtk_mesh proc~write_vtk_mesh->proc~wr_vtk_mesh proc~write_vtk_morfeus write_vtk_morfeus proc~write_vtk_morfeus->proc~write_vtk_mesh interface~write_vtk_morfeus write_vtk_morfeus interface~write_vtk_morfeus->proc~write_vtk_morfeus

Contents

Source Code


Source Code

    SUBROUTINE wr_vtk_mesh(ncd, verts, cells, v2c, points, cell_ids, v2cconn, icverts)
        USE class_psblas
        USE class_cell
        USE class_connectivity
        USE class_vertex
        IMPLICIT NONE

        ! Input parameters
        INTEGER,            INTENT(IN) :: ncd
        TYPE(vertex),       INTENT(IN) :: verts(:)
        TYPE(cell),         INTENT(IN) :: cells(:)
        TYPE(connectivity), INTENT(IN) :: v2c
        INTEGER, DIMENSION(:), ALLOCATABLE, INTENT(OUT) :: cell_ids
        INTEGER, DIMENSION(:), ALLOCATABLE, INTENT(OUT) :: v2cconn
        INTEGER, DIMENSION(:), ALLOCATABLE, INTENT(OUT) :: icverts
        REAL(psb_dpk_), DIMENSION(:,:), ALLOCATABLE, INTENT(OUT) :: points

        ! Local variables
        INTEGER :: i, info
        INTEGER, ALLOCATABLE :: v2clookup(:)             ! CSR data for v2c connectivity
        INTEGER :: v2cnconn                              ! number of connections to faces
        INTEGER :: nverts, ncells                        ! number of vertices & cells
        REAL(psb_dpk_), ALLOCATABLE :: xpos(:), ypos(:), zpos(:)

        nverts = SIZE(verts)
        ncells = SIZE(cells)

!        IF(mypnum_() /= 0) RETURN ! this need only be done by one processor

        ! pack up the data into arrays and pass it off to a C function to handle the IO
        ALLOCATE(xpos(nverts),ypos(nverts),zpos(nverts),icverts(ncells),stat=info)
        IF(info /= 0) THEN
            WRITE(*,300)
            CALL abort_psblas
        END IF

        ! use the getters to pack position arrays
        xpos = verts(:)%x_()
        ypos = verts(:)%y_()
        zpos = verts(:)%z_()

        ALLOCATE(points(3,1:SIZE(xpos)),source=0.0_r8k)
        points(1,:) = xpos; points(2,:) = ypos; points(3,:) = zpos  !! Set x,y,z positions

        ! VTK format needs v2c connectivity
        CALL v2c%get_conn_csr(v2clookup,v2cconn)
        v2cnconn = SIZE(v2cconn)

        icverts(:) = cells%nv_()

        ! passing:
        ! (0) nverts
        ! (1) vertex positions
        ! (2) ncells
        ! (3) size of v2c array (see next)
        ! (4) connectivity array for v2c
        ! (5) array listing number of vertices for each cell

        ! Set the cells IDs
        ALLOCATE(cell_ids(ncells),stat=info)
        IF(info /= 0) THEN
            WRITE(*,300)
            CALL abort_psblas
        ELSE
            cell_ids=[ (i,i=1,ncells) ]
        END IF

300     FORMAT(' ERROR! Memory allocation failure in WR_VTK_MESH')

    END SUBROUTINE wr_vtk_mesh