V3FIT
siesta_file.f
Go to the documentation of this file.
1 !*******************************************************************************
4 !
5 ! Note separating the Doxygen comment block here so detailed decription is
6 ! found in the Module not the file.
7 !
10 !*******************************************************************************
11  MODULE siesta_file
12  USE stel_kinds, ONLY: rprec
13  USE profiler
14 
15  IMPLICIT NONE
16 
17 !*******************************************************************************
18 ! siesta file module parameters
19 !*******************************************************************************
21  INTEGER, PARAMETER :: siesta_lasym_flag = 31
22 
23 !*******************************************************************************
24 ! DERIVED-TYPE DECLARATIONS
25 ! 1) primed grid base class
26 !
27 !*******************************************************************************
28 !-------------------------------------------------------------------------------
30 !-------------------------------------------------------------------------------
32 ! State flags.
33  INTEGER :: flags
34 
35 ! Number of radial points.
36  INTEGER :: nrad
37 ! Number of toroidal modes.
38  INTEGER :: ntor
39 ! Number of poloidal modes.
40  INTEGER :: mpol
41 
42 ! Magnetic field scaling factor.
43  REAL (rprec) :: b_factor
44 
45 ! J^s current density half parity.
46  REAL (rprec), DIMENSION(:,:,:), POINTER :: jksupsmnsf => null()
47 ! J^u current density half parity.
48  REAL (rprec), DIMENSION(:,:,:), POINTER :: jksupumncf => null()
49 ! J^v current density half parity.
50  REAL (rprec), DIMENSION(:,:,:), POINTER :: jksupvmncf => null()
51 ! J^s current density full parity.
52  REAL (rprec), DIMENSION(:,:,:), POINTER :: jksupsmncf => null()
53 ! J^u current density full parity.
54  REAL (rprec), DIMENSION(:,:,:), POINTER :: jksupumnsf => null()
55 ! J^v current density full parity.
56  REAL (rprec), DIMENSION(:,:,:), POINTER :: jksupvmnsf => null()
57  END TYPE
58 
59  CONTAINS
60 !*******************************************************************************
61 ! CONSTRUCTION SUBROUTINES
62 !*******************************************************************************
63 !-------------------------------------------------------------------------------
71 !-------------------------------------------------------------------------------
72  FUNCTION siesta_file_construct(siesta_file_name)
73  USE ezcdf
74 
75  IMPLICIT NONE
76 
77 ! Declare Arguments
78  TYPE (siesta_file_class), POINTER :: siesta_file_construct
79  CHARACTER (len=*), INTENT(in) :: siesta_file_name
80 
81 ! local variables
82  REAL (rprec) :: start_time
83  INTEGER :: siesta_ncid
84  INTEGER :: status
85 
86 ! Start of executable code
87  start_time = profiler_get_start_time()
88 
89  ALLOCATE(siesta_file_construct)
90 
91  CALL cdf_open(siesta_ncid, trim(siesta_file_name), 'r', status)
92 
93  CALL cdf_read(siesta_ncid, 'state_flags', &
94  & siesta_file_construct%flags)
95 
96  CALL cdf_read(siesta_ncid, 'nrad', siesta_file_construct%nrad)
97  CALL cdf_read(siesta_ncid, 'ntor', siesta_file_construct%ntor)
98  CALL cdf_read(siesta_ncid, 'mpol', siesta_file_construct%mpol)
99 
100  CALL cdf_read(siesta_ncid, 'b_factor', &
101  & siesta_file_construct%b_factor)
102 
103  ALLOCATE(siesta_file_construct%jksupsmnsf( &
104  & 0:siesta_file_construct%mpol, &
106  & siesta_file_construct%nrad))
107  ALLOCATE(siesta_file_construct%jksupumncf( &
108  & 0:siesta_file_construct%mpol, &
110  & siesta_file_construct%nrad))
111  ALLOCATE(siesta_file_construct%jksupvmncf( &
112  & 0:siesta_file_construct%mpol, &
114  & siesta_file_construct%nrad))
115 
116  CALL cdf_read(siesta_ncid, 'jksupsmnsf(m,n,r)', &
117  & siesta_file_construct%jksupsmnsf)
118  CALL cdf_read(siesta_ncid, 'jksupumncf(m,n,r)', &
119  & siesta_file_construct%jksupumncf)
120  CALL cdf_read(siesta_ncid, 'jksupvmncf(m,n,r)', &
121  & siesta_file_construct%jksupvmncf)
122 
123  IF (btest(siesta_file_construct%flags, siesta_lasym_flag)) THEN
124  ALLOCATE(siesta_file_construct%jksupsmncf( &
125  & 0:siesta_file_construct%mpol, &
127  & siesta_file_construct%nrad))
128  ALLOCATE(siesta_file_construct%jksupumnsf( &
129  & 0:siesta_file_construct%mpol, &
131  & siesta_file_construct%nrad))
132  ALLOCATE(siesta_file_construct%jksupvmnsf( &
133  & 0:siesta_file_construct%mpol, &
135  & siesta_file_construct%nrad))
136 
137  CALL cdf_read(siesta_ncid, 'jksupsmncf(m,n,r)', &
138  & siesta_file_construct%jksupsmncf)
139  CALL cdf_read(siesta_ncid, 'jksupumnsf(m,n,r)', &
140  & siesta_file_construct%jksupumnsf)
141  CALL cdf_read(siesta_ncid, 'jksupvmnsf(m,n,r)', &
142  & siesta_file_construct%jksupvmnsf)
143  END IF
144 
145  CALL cdf_close(siesta_ncid)
146 
147  CALL profiler_set_stop_time('siesta_file_construct', start_time)
148 
149  END FUNCTION
150 
151 !*******************************************************************************
152 ! DESTRUCTION SUBROUTINES
153 !*******************************************************************************
154 !-------------------------------------------------------------------------------
160 !-------------------------------------------------------------------------------
161  SUBROUTINE siesta_file_destruct(this)
162 
163  IMPLICIT NONE
164 
165 ! Declare Arguments
166  TYPE (siesta_file_class), POINTER :: this
167 
168 ! Start of executable code
169  IF (ASSOCIATED(this%jksupsmncf)) THEN
170  DEALLOCATE(this%jksupsmncf)
171  this%jksupsmncf => null()
172  END IF
173 
174  IF (ASSOCIATED(this%jksupsmnsf)) THEN
175  DEALLOCATE(this%jksupsmnsf)
176  this%jksupsmnsf => null()
177  END IF
178 
179  IF (ASSOCIATED(this%jksupumncf)) THEN
180  DEALLOCATE(this%jksupumncf)
181  this%jksupumncf => null()
182  END IF
183 
184  IF (ASSOCIATED(this%jksupumnsf)) THEN
185  DEALLOCATE(this%jksupumnsf)
186  this%jksupumnsf => null()
187  END IF
188 
189  IF (ASSOCIATED(this%jksupvmncf)) THEN
190  DEALLOCATE(this%jksupvmncf)
191  this%jksupvmncf => null()
192  END IF
193 
194  IF (ASSOCIATED(this%jksupvmnsf)) THEN
195  DEALLOCATE(this%jksupvmnsf)
196  this%jksupvmnsf => null()
197  END IF
198 
199  DEALLOCATE(this)
200 
201  END SUBROUTINE
202 
203  END MODULE
siesta_file::siesta_file_construct
type(siesta_file_class) function, pointer siesta_file_construct(siesta_file_name)
Construct a siesta_file_class object.
Definition: siesta_file.f:73
profiler
Defines functions for measuring an tabulating performance of function and subroutine calls....
Definition: profiler.f:13
siesta_file
Defines the base class of the type siesta_file_class. This contains the output of a siesta equilibriu...
Definition: siesta_file.f:11
siesta_file::siesta_lasym_flag
integer, parameter siesta_lasym_flag
Version number.
Definition: siesta_file.f:21
siesta_file::siesta_file_class
Base class representing a siesta output.
Definition: siesta_file.f:31
profiler::profiler_get_start_time
real(rprec) function profiler_get_start_time()
Gets the start time of profiled function.
Definition: profiler.f:194
siesta_file::siesta_file_destruct
subroutine siesta_file_destruct(this)
Deconstruct a siesta_file_class object.
Definition: siesta_file.f:162
profiler::profiler_set_stop_time
subroutine profiler_set_stop_time(symbol_name, start_time)
Gets the end time of profiled function.
Definition: profiler.f:121