GRIDMAN
grid managment library
test_carre_DN.f
Go to the documentation of this file.
1 C> @file tests/test_carre_DN.f
2 C> Unit tests of subroutines from formats/carre.f and convert/carre.f
3 C> for Double Null topolgy
4 C GRIDMAN, grid managment library. Author: Vladislav Kotov, v.kotov@fz-juelich.de
5 
6 ! Copyright (c) 2017 Forschungszentrum Juelich GmbH
7 ! Vladislav Kotov
8 !
9 ! This file is part of GRIDMAN.
10 !
11 ! GRIDMAN is free software: you can redistribute it and/or modify
12 ! it under the terms of the GNU General Public License as published by
13 ! the Free Software Foundation, either version 3 of the License, or
14 ! (at your option) any later version.
15 !
16 ! GRIDMAN is distributed in the hope that it will be useful,
17 ! but WITHOUT ANY WARRANTY; without even the implied warranty of
18 ! MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the
19 ! GNU General Public License for more details.
20 !
21 ! You should have received a copy of the GNU General Public License
22 ! along with GRIDMAN. If not, see <http://www.gnu.org/licenses/>.
23 
24  PROGRAM test_carre_dn
25  USE gridman
26  USE gridman_lib
27  IMPLICIT NONE
28 
29  TYPE(gridman_grid) :: sonnet_grid,fort30_grid
30  REAL(GRIDMAN_DP),ALLOCATABLE :: vol1(:),vol2(:)
31  REAL(GRIDMAN_DP) :: v1,v2
32  INTEGER :: ierr
33 
34  gridman_check=.true.
35 
36  WRITE(gridman_unit,*) "READ30"
37  CALL gridman_carre_read30_grid(fort30_grid,
38  c './input/fort.30.kstar',ierr,.true.)
39  IF(ierr.NE.0) stop "TEST_CARRE_DN TERMINATED"
40 
41  WRITE(gridman_unit,*) "READSONNET"
42  CALL gridman_carre_readsonnet_grid(sonnet_grid,
43  c './input/kstar.carre.082_2',ierr,.true.)
44  IF(ierr.NE.0) stop "TEST_CARRE_DN TERMINATED"
45 
46  WRITE(gridman_unit,*) "CYLVOLUMES"
47  ALLOCATE(vol1(sonnet_grid%NCELLS),vol2(fort30_grid%NCELLS))
48  CALL gridman_grid2d_cylvolumes(sonnet_grid,vol1,ierr)
49  IF(ierr.NE.0) stop "TEST_CARRE_DN TERMINATED"
50  CALL gridman_grid2d_cylvolumes(fort30_grid,vol2,ierr)
51  IF(ierr.NE.0) stop "TEST_CARRE_DN TERMINATED"
52 
53  v1=sum(vol1)*sonnet_grid%UNIT2SI**3
54  v2=sum(vol2)*fort30_grid%UNIT2SI**3
55  IF(abs(v1-v2).GT.gridman_tol*(abs(v1)+abs(v2))) THEN
56  WRITE(gridman_unit,*) "ERROR detected in TEST_CARRE_DDN: ",
57  w "mismatch of grid volumes between SONNET and FORT.30"
58  WRITE(gridman_unit,*) "V_SONNET, V_FORT30 ",v1,v2
59  stop "TEST_CARRE_DDN TERMINATED"
60  END IF
61 
62  WRITE(gridman_unit,*) "WRITE"
63  CALL gridman_grid_write(sonnet_grid,'sonnetDN.grd',ierr)
64  IF(ierr.NE.0) stop "TEST_CARRE_DN TERMINATED"
65  CALL gridman_grid_write(fort30_grid,'fort30DN.grd',ierr)
66  IF(ierr.NE.0) stop "TEST_CARRE_DN TERMINATED"
67 
68  WRITE(*,*) "TEST_CARRE_DN COMPLETED"
69 
70  END PROGRAM test_carre_dn
logical, save, public gridman_check
Switch to enforce extra checks of input parameters.
Definition: gridman.f:133
integer, save, public gridman_unit
Index of the standard output unit.
Definition: gridman.f:116
real(gridman_dp), save, public gridman_tol
Tolerance parameter which is used to compare two real numbers.
Definition: gridman.f:127
subroutine gridman_grid2d_cylvolumes(GRID, VCELLS, IERR, ANGLE)
Calculate cylindrical cell volumes.
Definition: grid2d.f:1018
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_carre_readsonnet_grid(GRID, FNAME, IERR, LEIR)
Read CARRE grid in SONNET format, return GRID object.
Definition: carre.f:927
Definition of data types, global constants and variables.
Definition: gridman.f:83
subroutine gridman_carre_read30_grid(GRID, FNAME, IERR, LEIR)
Read B2 (CARRE, SONNET) grid from fort.30, return GRID object.
Definition: carre.f:853