• Home
  • Features
  • Pricing
  • Docs
  • Announcements
  • Sign In

gyrokinetics / gs2 / 1640171109

24 Jan 2025 07:04PM UTC coverage: 7.915% (-0.03%) from 7.943%
1640171109

push

gitlab-ci

David Dickinson
Merged in experimental/generate_config_collection_module (pull request #1070)

3691 of 46631 relevant lines covered (7.92%)

99785.8 hits per line

Source File
Press 'n' to go to next uncovered line, 'b' for previous

0.0
/src/normalisations.f90
1
!> FIXME : Add documentation
2
module normalisations
3
  use abstract_config, only: abstract_config_type, CONFIG_MAX_NAME_LEN
4
  
5
  implicit none
6
  
7
  private
8

9
  public :: norms
10
  public :: init_normalisations, finish_normalisations
11
  public :: check_normalisations, wnml_normalisations
12

13
  public :: normalisations_config_type
14
  public :: set_normalisations_config
15
  public :: get_normalisations_config
16
  
17
  real, parameter :: default_value = -999.0
18
  
19
  !> Define a type to hold the set of normalisations, we
20
  !> could imagine extending this in the future to provide
21
  !> a normalise/denormalise routine which can be used to
22
  !> automatically convert quantities
23
  type norms_type
24
     private
25
     !Internal parameters
26
     real :: def_val = default_value !Default value, used to check if parameter has been set.
27

28
     !Note def_val is really a parameter, but not allowed to define params in derived type
29
     logical :: some_norms_set=.false.
30
     logical :: all_norms_set=.false.
31
     logical :: initialised = .false.
32

33
     !The following is used to help automate loops over normalisations
34
     integer :: nnorm
35
     character(len=6), dimension(:), allocatable, public :: names
36

37
     !The normalisations
38
     real :: mref !< Reference mass in atomic mass units
39
     real :: zref !< Reference charge in units of the elementary charge
40
     real :: nref !< Reference density in \(m^{-3}\)
41
     real :: tref !< Reference temperature in \(eV\)
42
     real :: aref !< Reference length in \(m\)
43
     real :: vref !< Reference (thermal) velocity in \(m/s\)
44
     real :: bref !< Reference magnetic field in Tesla, \(T\)
45
     real :: rhoref !< Reference Larmor radius in \(m\)
46
   contains
47
     private
48
     procedure, public :: init => norms_init
49
     procedure, public :: finish => norms_finish
50
     procedure, public :: reset => norms_reset
51
     procedure :: read_parameters => norms_read_parameters
52
     procedure :: set_value => norms_set_value
53
     procedure, public :: get_value => norms_get_value
54
     procedure :: check_if_set => norms_check_if_set
55
     procedure :: set_logicals => norms_set_logicals
56
  end type norms_type
57

58
  type(norms_type) :: norms !The normalisation object, there should only be one of these
59
  logical :: initialized = .false. !Have we setup the module yet?
60

61
  !> Used to represent the input configuration of
62
  !> normalisations. These values are not used for anything but will
63
  !> be written to the output file to aid post processing etc.
64
  type, extends(abstract_config_type) :: normalisations_config_type
65
     ! namelist : normalisations_knobs
66
     !> Reference length in \(m\)
67
     real :: aref = default_value
68
     !> Reference magnetic field in \(T\)
69
     real :: bref = default_value
70
     !> Reference mass in atomic mass units
71
     real :: mref = default_value
72
     !> Reference density in \(m^{-3}\)
73
     real :: nref = default_value
74
     !> Reference Larmor radius in \(m\)
75
     real :: rhoref = default_value
76
     !> Reference temperature in \(eV\)
77
     real :: tref = default_value
78
     !> Reference (thermal) velocity in \(m/s\)
79
     real :: vref = default_value
80
     !> Reference charge in units of the elementary charge
81
     real :: zref = default_value
82
   contains
83
     procedure, public :: read => read_normalisations_config
84
     procedure, public :: write => write_normalisations_config
85
     procedure, public :: reset => reset_normalisations_config
86
     procedure, public :: broadcast => broadcast_normalisations_config
87
     procedure, public, nopass :: get_default_name => get_default_name_normalisations_config
88
     procedure, public, nopass :: get_default_requires_index => get_default_requires_index_normalisations_config
89
  end type normalisations_config_type
90
  
91
  type(normalisations_config_type) :: normalisations_config  
92
contains
93
  !/////////////////////////////
94
  !// TYPE BOUND PROCEDURES
95
  !/////////////////////////////
96

97
  !> Sets the value of a particular normalisation, determined by the
98
  !> passed `val_name` string. Unknown `val_name` values result in a
99
  !> warning message on `proc0`.
100
  subroutine norms_set_value(self, val_name, val)
×
101
    use runtime_tests, only: verbosity
102
    use mp, only: proc0
103
    implicit none
104
    class(norms_type), intent(in out) :: self
105
    character(len=*), intent(in) :: val_name
106
    real, intent(in) :: val
107
    
108
    !Here we can have a message in very verbose runs
109
    if((verbosity().gt.5).and.proc0)then
×
110
       if(val.eq.self%def_val)then
×
111
          write(6,'("The ",A," normalisation has not been set. This may prevent conversion of some quantities.")') trim(val_name)
×
112
       else
113
          write(6,'("Setting the ",A," normalisation to ",F12.5)') trim(val_name), val
×
114
       endif
115
    endif
116

117
    !Should probably convert to lower case here, but until we
118
    !add some string utils to do this sort of stuff we'll rely
119
    !on developer doing the right thing.
120
    select case (trim(val_name))
×
121
    case("mref")
122
       self%mref=val
×
123
    case("zref")
124
       self%zref=val
×
125
    case("nref")
126
       self%nref=val
×
127
    case("tref")
128
       self%tref=val
×
129
    case("aref")
130
       self%aref=val
×
131
    case("vref")
132
       self%vref=val
×
133
    case("bref")
134
       self%bref=val
×
135
    case("rhoref")
136
       self%rhoref=val
×
137
    case default
138
       if(proc0) write(6,'("Warning : Attempt to set unknown normalisation ",A," --> Ignoring")')
×
139
    end select
140
  end subroutine norms_set_value
×
141

142
  !> Get the value of the normalisation associated with `val_name`.
143
  !> Unknown values of `val_name` result in a call to `mp_abort`.
144
  function norms_get_value(self, val_name)
×
145
    use mp, only: mp_abort
146
    implicit none
147
    class(norms_type), intent(in) :: self
148
    character(len=*), intent(in) :: val_name
149
    real :: norms_get_value
150

151
    !Should probably convert to lower case here, but until we
152
    !add some string utils to do this sort of stuff we'll rely
153
    !on developer doing the right thing.
154
    select case (trim(val_name))
×
155
    case("mref")
156
       norms_get_value=self%mref
×
157
    case("zref")
158
       norms_get_value=self%zref
×
159
    case("nref")
160
       norms_get_value=self%nref
×
161
    case("tref")
162
       norms_get_value=self%tref
×
163
    case("aref")
164
       norms_get_value=self%aref
×
165
    case("vref")
166
       norms_get_value=self%vref
×
167
    case("bref")
168
       norms_get_value=self%bref
×
169
    case("rhoref")
170
       norms_get_value=self%rhoref
×
171
    case default
172
      call mp_abort("Invalid normalisation requested")
×
173
    end select
174
  end function norms_get_value
×
175

176
  !> FIXME : Add documentation  
177
  subroutine norms_read_parameters(self, normalisations_config_in)
×
178
    implicit none
179
    class(norms_type), intent(in out) :: self
180
    type(normalisations_config_type), intent(in), optional :: normalisations_config_in
181
    real :: mref,zref,nref,tref,aref,vref,bref,rhoref
182

183
    if (present(normalisations_config_in)) normalisations_config = normalisations_config_in
×
184

185
    call normalisations_config%init(name = 'normalisations_knobs', requires_index = .false.)
×
186

187
    ! Copy out internal values into module level parameters
188
    associate(self => normalisations_config)
189
#include "normalisations_copy_out_auto_gen.inc"
190
    end associate
191

192
    !Now copy parameters into holder type
193
    call self%set_value("mref",mref)
×
194
    call self%set_value("zref",zref)
×
195
    call self%set_value("nref",nref)
×
196
    call self%set_value("tref",tref)
×
197
    call self%set_value("aref",aref)
×
198
    call self%set_value("vref",vref)
×
199
    call self%set_value("bref",bref)
×
200
    call self%set_value("rhoref",rhoref)
×
201
  end subroutine norms_read_parameters
×
202

203
  !> Initialise the norms object
204
  subroutine norms_init(self, normalisations_config_in)
×
205
    implicit none
206
    class(norms_type), intent(in out) :: self
207
    type(normalisations_config_type), intent(in), optional :: normalisations_config_in
208

209
    !First setup allowed normalisations
210
    self%nnorm=8
×
211
    if(.not.allocated(self%names)) allocate(self%names(self%nnorm))
×
212
    self%names(1)="mref"
×
213
    self%names(2)="zref"
×
214
    self%names(3)="nref"
×
215
    self%names(4)="tref"
×
216
    self%names(5)="aref"
×
217
    self%names(6)="vref"
×
218
    self%names(7)="bref"
×
219
    self%names(8)="rhoref"
×
220

221
    if(self%initialised) return
×
222
    self%initialised = .true.
×
223

224
    call self%read_parameters(normalisations_config_in)
×
225
  end subroutine norms_init
226

227
  !> Reset the properties
228
  subroutine norms_reset(self)
×
229
    implicit none
230
    class(norms_type), intent(in out) :: self
231
    integer :: i
232
    
233
    !Loop over parameters and set them to def_val
234
    do i=1,len(self%names)
×
235
       call self%set_value(self%names(i),self%def_val)
×
236
    enddo
237

238
    !Set the logical vars
239
    self%initialised=.false.
×
240
    call self%set_logicals
×
241
  end subroutine norms_reset
×
242

243
  !> Reset and free memory
244
  subroutine norms_finish(self)
×
245
    implicit none
246
    class(norms_type), intent(in out) :: self
247
    call self%reset
×
248
    if(allocated(self%names)) deallocate(self%names)
×
249
  end subroutine norms_finish
×
250

251
  !> Decide if a given normalisation has been set
252
  function norms_check_if_set(self,val_name)
×
253
    implicit none
254
    class(norms_type), intent(in) :: self
255
    character(len=*), intent(in) :: val_name
256
    logical :: norms_check_if_set
257
    norms_check_if_set = self%get_value(val_name).ne.self%def_val
×
258
  end function norms_check_if_set
×
259

260
  !> Decide if all/some of the normalisations have been set
261
  subroutine norms_set_logicals(self)
×
262
    implicit none
263
    class(norms_type), intent(in out) :: self
264
    integer :: i
265
    logical :: some_set, all_set
266

267
    !Init internals
268
    some_set=.false.
×
269
    all_set=.true.
×
270

271
    !Loop over parameters and set them to def_val
272
    do i=1,len(self%names)
×
273
       all_set=all_set.and.self%check_if_set(self%names(i))
×
274
       some_set=some_set.or.self%check_if_set(self%names(i))
×
275
    enddo
276

277
    !Update object parameters
278
    self%some_norms_set=some_set
×
279
    self%all_norms_set=all_set
×
280
  end subroutine norms_set_logicals
×
281

282
  !/////////////////////////////
283
  !// MODULE LEVEL PROCDURES
284
  !/////////////////////////////
285
  
286
  !> FIXME : Add documentation
287
  subroutine check_normalisations(report_unit)
×
288
    implicit none
289
    integer, intent(in) :: report_unit
290
    character(len=7) :: msg
291
    if(norms%all_norms_set)then
×
292
       msg = "All of"
×
293
    else
294
       if(norms%some_norms_set)then
×
295
          msg = "Some of"
×
296
       else
297
          msg = "None of"
×
298
       endif
299
    endif
300

301
    write(report_unit,fmt='(A," the normalisation parameters have been provided.")') trim(msg)
×
302
  end subroutine check_normalisations
×
303

304
  !> FIXME : Add documentation  
305
  subroutine wnml_normalisations(unit)
×
306
    implicit none
307
    integer, intent(in) :: unit
308
    integer :: i
309
    write(unit,*)
×
310
    do i=1,len(norms%names)
×
311
       write(unit,fmt='(A," = ", F12.5)') trim(norms%names(i)),norms%get_value(norms%names(i))
×
312
    enddo
313
    write(unit,'("/")')
×
314
  end subroutine wnml_normalisations
×
315

316
  !> Read input file and populate the norms object
317
  subroutine init_normalisations(normalisations_config_in)
×
318
    implicit none
319
    type(normalisations_config_type), intent(in), optional :: normalisations_config_in
320
    if(initialized) return
×
321
    initialized = .true.
×
322
    call norms%init(normalisations_config_in)
×
323
  end subroutine init_normalisations
324

325
  !> Free memory etc. associated with normalisations
326
  subroutine finish_normalisations
×
327
    implicit none
328
    initialized = .false.
×
329
    call norms%finish
×
330
    call normalisations_config%reset()
×
331
  end subroutine finish_normalisations
×
332

333
#include "normalisations_auto_gen.inc"
334
end module normalisations
×
STATUS · Troubleshooting · Open an Issue · Sales · Support · CAREERS · ENTERPRISE · START FREE · SCHEDULE DEMO
ANNOUNCEMENTS · TWITTER · TOS & SLA · Supported CI Services · What's a CI service? · Automated Testing

© 2026 Coveralls, Inc