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

gyrokinetics / gs2 / 1998640042

22 Aug 2025 01:50PM UTC coverage: 10.577% (-0.1%) from 10.718%
1998640042

push

gitlab-ci

David Dickinson
Merged in feature/dont_reset_configs_when_finishing_modules (pull request #1160)

4700 of 44434 relevant lines covered (10.58%)

125622.86 hits per line

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

82.29
/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, init_normalisations, finish_normalisations, check_normalisations
10

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

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

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

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

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

59
  !> Used to represent the input configuration of
60
  !> normalisations. These values are not used for anything but will
61
  !> be written to the output file to aid post processing etc.
62
  type, extends(abstract_config_type) :: normalisations_config_type
63
     ! namelist : normalisations_knobs
64
     !> Reference length in \(m\)
65
     real :: aref = default_value
66
     !> Reference magnetic field in \(T\)
67
     real :: bref = default_value
68
     !> Reference mass in atomic mass units
69
     real :: mref = default_value
70
     !> Reference density in \(m^{-3}\)
71
     real :: nref = default_value
72
     !> Reference Larmor radius in \(m\)
73
     real :: rhoref = default_value
74
     !> Reference temperature in \(eV\)
75
     real :: tref = default_value
76
     !> Reference (thermal) velocity in \(m/s\)
77
     real :: vref = default_value
78
     !> Reference charge in units of the elementary charge
79
     real :: zref = default_value
80
#include "normalisations_overrides_and_bound_auto_gen.inc"
81
  end type normalisations_config_type
82
  
83
  type(normalisations_config_type) :: normalisations_config  
84
contains
85
  !/////////////////////////////
86
  !// TYPE BOUND PROCEDURES
87
  !/////////////////////////////
88

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

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

135
  !> Get the value of the normalisation associated with `val_name`.
136
  !> Unknown values of `val_name` result in a call to `mp_abort`.
137
  function norms_get_value(self, val_name)
336✔
138
    use mp, only: mp_abort
139
    implicit none
140
    class(norms_type), intent(in) :: self
141
    character(len=*), intent(in) :: val_name
142
    real :: norms_get_value
143

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

169
  !> FIXME : Add documentation  
170
  subroutine norms_read_parameters(self, normalisations_config_in)
28✔
171
    implicit none
172
    class(norms_type), intent(in out) :: self
173
    type(normalisations_config_type), intent(in), optional :: normalisations_config_in
174
    real :: mref,zref,nref,tref,aref,vref,bref,rhoref
175

176
    if (present(normalisations_config_in)) normalisations_config = normalisations_config_in
28✔
177

178
    call normalisations_config%init(name = 'normalisations_knobs', requires_index = .false.)
28✔
179

180
    ! Copy out internal values into module level parameters
181
    associate(self => normalisations_config)
182
#include "normalisations_copy_out_auto_gen.inc"
183
    end associate
184

185
    !Now copy parameters into holder type
186
    call self%set_value("mref",mref)
28✔
187
    call self%set_value("zref",zref)
28✔
188
    call self%set_value("nref",nref)
28✔
189
    call self%set_value("tref",tref)
28✔
190
    call self%set_value("aref",aref)
28✔
191
    call self%set_value("vref",vref)
28✔
192
    call self%set_value("bref",bref)
28✔
193
    call self%set_value("rhoref",rhoref)
28✔
194
  end subroutine norms_read_parameters
28✔
195

196
  !> Initialise the norms object
197
  subroutine norms_init(self, normalisations_config_in)
28✔
198
    implicit none
199
    class(norms_type), intent(in out) :: self
200
    type(normalisations_config_type), intent(in), optional :: normalisations_config_in
201

202
    !First setup allowed normalisations
203
    self%nnorm=8
28✔
204
    if(.not.allocated(self%names)) allocate(self%names(self%nnorm))
28✔
205
    self%names(1)="mref"
28✔
206
    self%names(2)="zref"
28✔
207
    self%names(3)="nref"
28✔
208
    self%names(4)="tref"
28✔
209
    self%names(5)="aref"
28✔
210
    self%names(6)="vref"
28✔
211
    self%names(7)="bref"
28✔
212
    self%names(8)="rhoref"
28✔
213

214
    if(self%initialised) return
28✔
215
    self%initialised = .true.
28✔
216

217
    call self%read_parameters(normalisations_config_in)
28✔
218
  end subroutine norms_init
219

220
  !> Reset the properties
221
  subroutine norms_reset(self)
28✔
222
    implicit none
223
    class(norms_type), intent(in out) :: self
224
    integer :: i
225
    
226
    !Loop over parameters and set them to def_val
227
    do i=1,len(self%names)
196✔
228
       call self%set_value(self%names(i),self%def_val)
196✔
229
    enddo
230

231
    !Set the logical vars
232
    self%initialised=.false.
28✔
233
    call self%set_logicals
28✔
234
  end subroutine norms_reset
28✔
235

236
  !> Reset and free memory
237
  subroutine norms_finish(self)
28✔
238
    implicit none
239
    class(norms_type), intent(in out) :: self
240
    call self%reset
28✔
241
    if(allocated(self%names)) deallocate(self%names)
28✔
242
  end subroutine norms_finish
28✔
243

244
  !> Decide if a given normalisation has been set
245
  function norms_check_if_set(self,val_name)
336✔
246
    use warning_helpers, only: not_exactly_equal
247
    implicit none
248
    class(norms_type), intent(in) :: self
249
    character(len=*), intent(in) :: val_name
250
    logical :: norms_check_if_set
251
    norms_check_if_set = not_exactly_equal(self%get_value(val_name), self%def_val)
672✔
252
  end function norms_check_if_set
336✔
253

254
  !> Decide if all/some of the normalisations have been set
255
  subroutine norms_set_logicals(self)
28✔
256
    implicit none
257
    class(norms_type), intent(in out) :: self
258
    integer :: i
259
    logical :: some_set, all_set
260

261
    !Init internals
262
    some_set=.false.
28✔
263
    all_set=.true.
28✔
264

265
    !Loop over parameters and set them to def_val
266
    do i=1,len(self%names)
196✔
267
       all_set=all_set.and.self%check_if_set(self%names(i))
168✔
268
       some_set=some_set.or.self%check_if_set(self%names(i))
196✔
269
    enddo
270

271
    !Update object parameters
272
    self%some_norms_set=some_set
28✔
273
    self%all_norms_set=all_set
28✔
274
  end subroutine norms_set_logicals
28✔
275

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

295
    write(report_unit,fmt='(A," the normalisation parameters have been provided.")') trim(msg)
×
296
  end subroutine check_normalisations
×
297

298
  !> Read input file and populate the norms object
299
  subroutine init_normalisations(normalisations_config_in)
28✔
300
    implicit none
301
    type(normalisations_config_type), intent(in), optional :: normalisations_config_in
302
    if(initialized) return
28✔
303
    initialized = .true.
28✔
304
    call norms%init(normalisations_config_in)
28✔
305
  end subroutine init_normalisations
306

307
  !> Free memory etc. associated with normalisations
308
  subroutine finish_normalisations
28✔
309
    implicit none
310
    initialized = .false.
28✔
311
    call norms%finish
28✔
312
  end subroutine finish_normalisations
28✔
313

314
#include "normalisations_auto_gen.inc"
315
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