GRIDMAN
grid managment library
test_template.f
Go to the documentation of this file.
1 C> @file tests/test_template.f
2 C> Unit tests of subroutines from formats/template.f and convert/template.f
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_template
24 
25  USE gridman
26  USE gridman_lib
27  IMPLICIT NONE
28 
29  INTEGER(GRIDMAN_SP) :: m,l
30  INTEGER :: ierr,res
31  INTEGER(GRIDMAN_SP),ALLOCATABLE :: n(:)
32  REAL(GRIDMAN_DP),ALLOCATABLE :: x(:),y(:)
33  INTEGER(GRIDMAN_SP),PARAMETER :: m0=3
34  INTEGER(GRIDMAN_SP),PARAMETER :: l0=11
35  INTEGER(GRIDMAN_SP) :: n0(m0)
36  REAL(GRIDMAN_DP) :: x0(l0),y0(l0)
37  TYPE(gridman_grid) :: grid1,grid2
38 
39  gridman_check=.true.
40  gridman_dbg=.false.
41 
42  n0(1)=4
43  x0(1)=1.
44  y0(1)=1.
45  x0(2)=5.
46  y0(2)=1.
47  x0(3)=5.
48  y0(3)=5.
49  x0(4)=1.
50  y0(4)=1.
51 
52  n0(2)=2
53  x0(5)=3.
54  y0(5)=5.
55  x0(6)=1.
56  y0(6)=3.
57 
58  n0(3)=5
59  x0(7)=0.
60  y0(7)=0.
61  x0(8)=0.
62  y0(8)=6.
63  x0(9)=6.
64  y0(9)=6.
65  x0(10)=6.
66  y0(10)=0.
67  x0(11)=0.
68  y0(11)=0
69 
70  CALL gridman_template2grid(grid1,m0,n0,l0,x0,y0,ierr)
71  IF(ierr.NE.0) stop "TEST_TEMPLATE TERMINATED"
72 
73  CALL gridman_grid2template(grid1,m,n,l,x,y,ierr)
74  IF(ierr.NE.0) stop "TEST_TEMPLATE TERMINATED"
75 
76 cc IL=0
77 cc WRITE(*,*)
78 cc DO IP=1,M
79 cc DO IV=1,N(IP)
80 cc IL=IL+1
81 cc WRITE(*,*) X(IL),Y(IL)
82 cc END DO
83 cc WRITE(*,*)
84 cc END DO
85 
86  CALL gridman_template_write('tmp.txt',m0,n0,l0,x0,y0,ierr)
87  IF(ierr.NE.0) stop "TEST_TEMPLATE TERMINATED"
88 
89  CALL gridman_template_read(grid2,'tmp.txt',ierr)
90  IF(ierr.NE.0) stop "TEST_TEMPLATE TERMINATED"
91 
92  CALL gridman_grid_compare(grid1,grid2,res,ierr)
93  IF(ierr.NE.0) stop "TEST_TEMPLATE TERMINATED"
94  IF(res.NE.0) THEN
95  WRITE(*,*) "ERROR after GRIDMAN_GRID_COMPARE"
96  WRITE(*,*) "Grids are different, RES ",res
97  stop "TEST_TEMPLATE TERMINATED"
98  END IF
99 
100  CALL gridman_template_read(grid2,'./input/54001.wall',ierr)
101  IF(ierr.NE.0) stop "TEST_TEMPLATE TERMINATED"
102 
103 cc IL=0
104 cc WRITE(*,*)
105 cc DO IP=1,M
106 cc DO IV=1,N(IP)
107 cc IL=IL+1
108 cc WRITE(*,*) X(IL),Y(IL)
109 cc END DO
110 cc WRITE(*,*)
111 cc END DO
112 
113  CALL gridman_template_write(grid2,'tmp2.txt',ierr)
114  IF(ierr.NE.0) stop "TEST_TEMPLATE TERMINATED"
115 
116  CALL gridman_grid_write(grid1,'tmp1.grd',ierr)
117  IF(ierr.NE.0) stop "TEST_TEMPLATE TERMINATED"
118 
119  CALL gridman_grid_write(grid2,'tmp2.grd',ierr)
120  IF(ierr.NE.0) stop "TEST_TEMPLATE TERMINATED"
121 
122  CALL gridman_grid_deallocate(grid1,ierr)
123  CALL gridman_grid_deallocate(grid2,ierr)
124 
125  WRITE(*,*) "TEST_TEMPLATE COMPLETED"
126 
127  END PROGRAM test_template
128 
129 
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
subroutine gridman_grid2template(GRID, M, N, L, X, Y, IERR)
Convert GRIDMAN_GRID object into arrays which can be stored in simple template format (DG template) ...
Definition: template.f:239
logical, save, public gridman_dbg
Switch for debugging mode.
Definition: gridman.f:122
Definition of data types, global constants and variables.
Definition: gridman.f:83
subroutine gridman_template2grid(GRID, M, N, L, X, Y, IERR)
Convert data read from a file in simple template format (DG template) into GRIDMAN_GRID object...
Definition: template.f:35
subroutine gridman_grid_compare(GRID1, GRID2, RES, IERR)
Compare two grid objects.
Definition: grid1.f:1068