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

gyrokinetics / gs2 / 1821477209

16 May 2025 02:50PM UTC coverage: 8.139% (+0.2%) from 7.92%
1821477209

push

gitlab-ci

David Dickinson
Merged in bugfix/use_uv_in_coverage_test_to_install_packages (pull request #1142)

3704 of 45511 relevant lines covered (8.14%)

122643.73 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, 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
   contains
81
     procedure, public :: read => read_normalisations_config
82
     procedure, public :: write => write_normalisations_config
83
     procedure, public :: reset => reset_normalisations_config
84
     procedure, public :: broadcast => broadcast_normalisations_config
85
     procedure, public, nopass :: get_default_name => get_default_name_normalisations_config
86
     procedure, public, nopass :: get_default_requires_index => get_default_requires_index_normalisations_config
87
  end type normalisations_config_type
88
  
89
  type(normalisations_config_type) :: normalisations_config  
90
contains
91
  !/////////////////////////////
92
  !// TYPE BOUND PROCEDURES
93
  !/////////////////////////////
94

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

250
  !> Decide if a given normalisation has been set
251
  function norms_check_if_set(self,val_name)
×
252
    use warning_helpers, only: not_exactly_equal
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 = not_exactly_equal(self%get_value(val_name), 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
  !> Read input file and populate the norms object
305
  subroutine init_normalisations(normalisations_config_in)
×
306
    implicit none
307
    type(normalisations_config_type), intent(in), optional :: normalisations_config_in
308
    if(initialized) return
×
309
    initialized = .true.
×
310
    call norms%init(normalisations_config_in)
×
311
  end subroutine init_normalisations
312

313
  !> Free memory etc. associated with normalisations
314
  subroutine finish_normalisations
×
315
    implicit none
316
    initialized = .false.
×
317
    call norms%finish
×
318
    call normalisations_config%reset()
×
319
  end subroutine finish_normalisations
×
320

321
#include "normalisations_auto_gen.inc"
322
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