GRIDMAN
grid managment library
test_grid3d.f
Go to the documentation of this file.
1 C> @file tests/test_grid3d.f
2 C> Unit tests of subroutines reletaed to the 3D grid type
3 C GRIDMAN, grid managment library. Author: Vladislav Kotov, v.kotov@fz-juelich.de
4 
5 ! Copyright (c) 2017 Forschungszentrum Juelich GmbH
6 ! Vladislav Kotov
7 !
8 ! This file is part of GRIDMAN.
9 !
10 ! GRIDMAN is free software: you can redistribute it and/or modify
11 ! it under the terms of the GNU General Public License as published by
12 ! the Free Software Foundation, either version 3 of the License, or
13 ! (at your option) any later version.
14 !
15 ! GRIDMAN is distributed in the hope that it will be useful,
16 ! but WITHOUT ANY WARRANTY; without even the implied warranty of
17 ! MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the
18 ! GNU General Public License for more details.
19 !
20 ! You should have received a copy of the GNU General Public License
21 ! along with GRIDMAN. If not, see <http://www.gnu.org/licenses/>.
22 
23  PROGRAM test_grid3d
24  USE gridman
25  USE gridman_lib
26  IMPLICIT NONE
27 
28  TYPE(gridman_grid) :: grid
29  INTEGER :: ierr,st
30  REAL(GRIDMAN_DP),ALLOCATABLE :: data(:,:)
31  INTEGER(GRIDMAN_SP) :: ie,iedge,isrf
32 
33  gridman_check=.true.
34 
35  CALL gridman_addsurf3d_read(grid,'input/input.eir.3D',ierr)
36  IF(ierr.NE.0) stop 'TEST_GRID3D TERMINATED'
37 
38  CALL gridman_grid_write(grid,'grid3d.grd',ierr)
39  IF(ierr.NE.0) stop 'TEST_GRID3D TERMINATED'
40 
41  WRITE(*,*) 'eirene3D.vtk'
42  CALL gridman_vtk_grid3d_write('eirene3D.vtk','VTK 3D test',
43  s grid,grid%NEDGES,0,0,0,0,ierr)
44  IF(ierr.NE.0) stop 'TEST_GRID3D TERMINATED'
45 
46 C cell scalar added
47  WRITE(*,*) 'eirene3D-2.vtk'
48  ALLOCATE(DATA(grid%NEDGES,1),stat=st)
49  IF(st.NE.0) THEN
50  WRITE(*,*) "Cannot allocate memory"
51  stop 'TEST_GRID3D TERMINATED'
52  END IF
53  DATA(:,1)=0
54  DO ie=1,grid%EDGEINDEX(1)%NELEMENTS
55  iedge=grid%EDGEINDEX(1)%INDEXES(0,ie)
56  isrf=grid%EDGEINDEX(1)%INDEXES(1,ie)
57  DATA(iedge,1)=isrf
58  END DO
59 
60  CALL gridman_vtk_grid3d_write('eirene3D_2.vtk','VTK 3D test',
61  s grid,grid%NEDGES,
62  s 1,0,0,0,ierr,
63  s cell_scalar=DATA,csname='ADDSURF')
64  IF(ierr.NE.0) stop 'TEST_GRID3D TERMINATED'
65 
66 C index removed
67  WRITE(*,*) 'eirene3D-3.vtk'
68  CALL gridman_index_deallocate(grid%EDGEINDEX(1),ierr)
69  IF(ierr.NE.0) stop 'TEST_GRID3D TERMINATED'
70  DEALLOCATE(grid%EDGEINDEX)
71  grid%NEDGEINDEX=0
72 
73  CALL gridman_vtk_grid3d_write('eirene3D_3.vtk','VTK 3D test',
74  s grid,grid%NEDGES,
75  s 1,0,0,0,ierr,
76  s cell_scalar=DATA,csname='ADDSURF')
77  IF(ierr.NE.0) stop 'TEST_GRID3D TERMINATED'
78 
79 C w/o cell scalar
80  WRITE(*,*) 'eirene3D-4.vtk'
81  CALL gridman_vtk_grid3d_write('eirene3D_4.vtk','VTK 3D test',
82  s grid,grid%NEDGES,
83  s 0,0,0,0,ierr)
84  IF(ierr.NE.0) stop 'TEST_GRID3D TERMINATED'
85 
86 
87  DEALLOCATE(DATA,stat=st)
88  IF(st.NE.0) THEN
89  WRITE(*,*) "Cannot deallocate memory"
90  stop 'TEST_GRID3D ERMINATED'
91  END IF
92 
93  CALL gridman_grid_deallocate(grid,ierr)
94  IF(ierr.NE.0) stop 'TEST_GRID3D TERMINATED'
95 
96  WRITE(*,*) "TEST_GRID3D COMPLETED"
97 
98  END PROGRAM test_grid3d
logical, save, public gridman_check
Switch to enforce extra checks of input parameters.
Definition: gridman.f:133
Explicit interfaces to GRIDMAN subroutines and functions.
Definition: gridman.f:251
Data-type which describes a grid as a set of edges, methods in grid.f.
Definition: gridman.f:168
subroutine gridman_grid_deallocate(GRID, IERR)
Deallocate grid object.
Definition: grid1.f:184
Definition of data types, global constants and variables.
Definition: gridman.f:83
subroutine gridman_index_deallocate(INDEX, IERR)
Allocate index object.
Definition: index.f:98
subroutine gridman_vtk_grid3d_write(FNAME, HEADER, GRID, NELEMENTS, NCS, NCV, NPS, NPV, IERR, CELL_SCALAR, CSNAME, CELL_VECTOR, CVNAME, POINT_SCALAR, PSNAME, POINT_VECTOR, PVNAME)
Write 3D grid and data in VTK ASCII legacy format. Only grid w/o cells is implemented at the moment !...
Definition: vtk.f:1048