MONC
conversions.F90
Go to the documentation of this file.
1 
7  implicit none
8 
9 #ifndef TEST_MODE
10  private
11 #endif
12 
13  ! logical to determine whether to use the original rounding method
14  logical :: l_original_rounding = .false.
15  ! This is the rounding applied when going from single to double precision numbers
16  integer, parameter :: real_rounding_precision=int(1e8)
17 
25  interface conv_to_generic
27  end interface conv_to_generic
28 
38  interface conv_to_string
40  end interface conv_to_string
41 
49  interface conv_to_integer
51  end interface conv_to_integer
52 
60  interface conv_to_real
62  end interface conv_to_real
63 
71  interface conv_to_logical
73  end interface conv_to_logical
74 
81  interface conv_is_integer
82  module procedure string_is_integer
83  end interface conv_is_integer
84 
91  interface conv_is_real
92  module procedure string_is_real
93  end interface conv_is_real
94 
100  interface conv_is_logical
101  module procedure string_is_logical
102  end interface conv_is_logical
103 
106 
107 contains
108 
113  real(kind=double_precision) function conv_single_real_to_double(input_real)
114  real(kind=single_precision), intent(in) :: input_real
115 
116  if (l_original_rounding) then
117  ! This rounding methods only works for values than 1.e-8. Aerosol masses
118  ! are smaller than this value and hence this rounding method can cause
119  ! issues
120  conv_single_real_to_double=dnint(real(input_real, kind=default_precision)* &
122  else
123  ! This method will round to the precision of the machine.
124  conv_single_real_to_double=real(input_real, kind=default_precision)
125  if (abs(conv_single_real_to_double) < epsilon(1.0_default_precision)) &
126  conv_single_real_to_double = 0.0_default_precision
127  endif
128  end function conv_single_real_to_double
129 
130 
134  logical function string_is_integer(string)
135  character(len=*), intent(in) :: string
136 
137  integer :: integer_value, ierr
138 
139  if (len(trim(string)) .ne. 0) then
140  read(string, '(i11)', iostat=ierr ) integer_value
141  string_is_integer = ierr == 0
142  else
143  string_is_integer=.false.
144  end if
145  end function string_is_integer
146 
150  logical function string_is_real(string)
151  character(len=*), intent(in) :: string
152 
153  integer :: ierr
154  real :: real_value
155 
156  if (len(trim(string)) .ne. 0) then
157  read(string, '(f12.2)', iostat=ierr ) real_value
158  string_is_real = ierr == 0
159  else
160  string_is_real=.false.
161  end if
162  end function string_is_real
163 
167  logical function string_is_logical(string)
168  character(len=*), intent(in) :: string
169 
170  string_is_logical = .false.
171  if (trim(adjustl(string)) .eq. "true" .or. trim(adjustl(string)) .eq. "false" .or. &
172  trim(adjustl(string)) .eq. ".true." .or. trim(adjustl(string)) .eq. ".false." .or. &
173  trim(adjustl(string)) .eq. ".true" .or. trim(adjustl(string)) .eq. "true." .or. &
174  trim(adjustl(string)) .eq. ".false" .or. trim(adjustl(string)) .eq. "false.") string_is_logical = .true.
175  end function string_is_logical
176 
182  function generic_to_string(generic, makecopy, str_length)
183  class(*), pointer, intent(in) :: generic
184  logical, intent(in) :: makecopy
185  integer, intent(in) :: str_length
186  character(len=str_length), pointer :: generic_to_string, temporary_generic_ptr
187 
188  select type(generic)
189  type is (character(len=*))
190  if (makecopy) then
191  ! Need to do this to enforce string length information
192  temporary_generic_ptr=>generic
193  allocate(generic_to_string, source=temporary_generic_ptr)
194  else
195  generic_to_string=>generic
196  end if
197  class default
198  generic_to_string=>null()
199  end select
200  end function generic_to_string
201 
205  function integer_to_string(input)
206  integer, intent(in) :: input
207  character(len=15) :: integer_to_string
208 
209  write(integer_to_string, '(i15)' ) input
210  integer_to_string = trim(adjustl(integer_to_string))
211  end function integer_to_string
212 
216  function real_single_to_string(input, decimal_places, exponent, exponent_small_numbers)
217  real(kind=single_precision), intent(in) :: input
218  character(len=30) :: real_single_to_string
219  integer, optional :: decimal_places
220  logical, optional :: exponent, exponent_small_numbers
221 
222  logical :: transformed
223  transformed=.false.
224 
225  if (present(exponent)) then
226  if (exponent) then
227  write(real_single_to_string, '(es30.10)' ) input
228  transformed=.true.
229  end if
230  end if
231  if (present(exponent_small_numbers)) then
232  if (exponent_small_numbers) then
233  write(real_single_to_string, '(g30.10)' ) input
234  transformed=.true.
235  end if
236  end if
237  if (.not. transformed) then
238  write(real_single_to_string, '(f30.10)' ) input
239  if (scan(real_single_to_string, "*") .ne. 0) write(real_single_to_string, '(es30.10)' ) input
240  end if
242  if (present(decimal_places)) call limit_to_decimal_places(real_single_to_string, decimal_places)
243 
245  end function real_single_to_string
246 
250  function real_double_to_string(input, decimal_places, exponent, exponent_small_numbers)
251  real(kind=double_precision), intent(in) :: input
252  character(len=30) :: real_double_to_string
253  integer, optional :: decimal_places
254  logical, optional :: exponent, exponent_small_numbers
255 
256  logical :: transformed
257  transformed=.false.
258 
259  if (present(exponent)) then
260  if (exponent) then
261  write(real_double_to_string, '(es30.10)' ) input
262  transformed=.true.
263  end if
264  end if
265  if (present(exponent_small_numbers)) then
266  if (exponent_small_numbers) then
267  write(real_double_to_string, '(g30.10)' ) input
268  transformed=.true.
269  end if
270  end if
271  if (.not. transformed) then
272  write(real_double_to_string, '(f30.10)' ) input
273  if (scan(real_double_to_string, "*") .ne. 0) write(real_double_to_string, '(es30.10)' ) input
274  end if
276  if (present(decimal_places)) then
277  call limit_to_decimal_places(real_double_to_string, decimal_places)
278  end if
279 
281  end function real_double_to_string
282 
287  subroutine limit_to_decimal_places(string_to_parse, decimal_places)
288  character(len=*), intent(inout) :: string_to_parse
289  integer, intent(in) :: decimal_places
290 
291  integer :: decimal_posn, exp_posn
292 
293  string_to_parse=adjustl(string_to_parse)
294  decimal_posn=index(string_to_parse, ".")
295  exp_posn=index(string_to_parse, "E")
296  if (decimal_posn .ne. 0 .and. decimal_posn+decimal_places+1 .le. len(string_to_parse)) then
297  if (exp_posn .eq. 0) then
298  string_to_parse(decimal_posn+decimal_places+1:)=" "
299  else
300  string_to_parse(decimal_posn+decimal_places+1:)=string_to_parse(exp_posn:)
301  string_to_parse(decimal_posn+decimal_places+1+(len(string_to_parse)-exp_posn)+1:)=" "
302  end if
303  end if
304  end subroutine limit_to_decimal_places
305 
310  subroutine trim_trailing_zeros(string_to_parse, zeros_to_retain)
311  character(len=*), intent(inout) :: string_to_parse
312  integer, intent(in) :: zeros_to_retain
313 
314  integer :: decimal_posn, i, zero_count, nonzero_hit
315 
316  zero_count=0
317 
318  decimal_posn=index(string_to_parse, ".")
319  if (decimal_posn .ne. 0 .and. decimal_posn .lt. len(string_to_parse)) then
320  do i=len(trim(string_to_parse)), decimal_posn, -1
321  if (string_to_parse(i:i) .ne. "0") then
322  nonzero_hit=i
323  exit
324  else
325  zero_count=zero_count+1
326  end if
327  end do
328  if (zero_count .gt. zeros_to_retain) then
329  string_to_parse(nonzero_hit+zeros_to_retain:)=""
330  end if
331  end if
332  end subroutine trim_trailing_zeros
333 
337  function logical_to_string(input)
338  logical, intent(in) :: input
339  character(len=5) :: logical_to_string
340 
341  if (input) then
342  logical_to_string = "true"
343  else
344  logical_to_string = "false"
345  end if
346  end function logical_to_string
347 
352  function generic_to_logical(generic, makecopy)
353  class(*), pointer, intent(in) :: generic
354  logical, intent(in) :: makecopy
355  logical, pointer :: generic_to_logical
356 
357  select type(generic)
358  type is (logical)
359  if (makecopy) then
360  allocate(generic_to_logical, source=generic)
361  else
362  generic_to_logical=>generic
363  end if
364  class default
365  generic_to_logical=>null()
366  end select
367  end function generic_to_logical
368 
372  logical function string_to_logical(string)
373  character(len=*), intent(in) :: string
374 
375  if (trim(adjustl(string)) .eq. "true" .or. trim(adjustl(string)) .eq. ".true." .or. &
376  trim(adjustl(string)) .eq. ".true" .or. trim(adjustl(string)) .eq. "true.") then
377  string_to_logical = .true.
378  else
379  string_to_logical = .false.
380  end if
381  end function string_to_logical
382 
386  logical function integer_to_logical(input)
387  integer, intent(in) :: input
388 
389  if (input .ge. 1) then
390  integer_to_logical = .true.
391  else
392  integer_to_logical = .false.
393  end if
394  end function integer_to_logical
395 
399  logical function real_to_logical(input)
400  real, intent(in) :: input
401 
402  if (input .ge. 1.0) then
403  real_to_logical = .true.
404  else
405  real_to_logical = .false.
406  end if
407  end function real_to_logical
408 
413  function generic_to_double_real(generic, makecopy)
414  class(*), pointer, intent(in) :: generic
415  logical, intent(in) :: makecopy
416  real(kind=default_precision), pointer :: generic_to_double_real
417 
418  select type(generic)
419  type is (real(kind=default_precision))
420  if (makecopy) then
421  allocate(generic_to_double_real, source=generic)
422  else
423  generic_to_double_real=>generic
424  end if
425  class default
426  generic_to_double_real=>null()
427  end select
428  end function generic_to_double_real
429 
434  function generic_to_real(generic, makecopy)
435  class(*), pointer, intent(in) :: generic
436  logical, intent(in) :: makecopy
437  real, pointer :: generic_to_real
438 
439  select type(generic)
440  type is (real)
441  if (makecopy) then
442  allocate(generic_to_real, source=generic)
443  else
444  generic_to_real=>generic
445  end if
446  type is (integer)
447  allocate(generic_to_real)
448  generic_to_real=conv_to_real(generic)
449  class default
450  generic_to_real=>null()
451  end select
452  end function generic_to_real
453 
457  real function string_to_real(string)
458  character(len=*), intent(in) :: string
459 
460  if (scan(string, "E") .ne. 0 .or. scan(string, "e") .ne. 0) then
461  read(string, '(es30.10)' ) string_to_real
462  else
463  read(string, '(f11.2)' ) string_to_real
464  end if
465  end function string_to_real
466 
470  real function integer_to_real(input)
471  integer, intent(in) :: input
472 
473  integer_to_real = real(input)
474  end function integer_to_real
475 
479  real function logical_to_real(input)
480  logical, intent(in) :: input
481 
482  if (input) then
483  logical_to_real = 1.0
484  else
485  logical_to_real = 0.0
486  end if
487  end function logical_to_real
488 
493  function generic_to_integer(generic, makecopy)
494  class(*), pointer, intent(in) :: generic
495  logical, intent(in) :: makecopy
496  integer, pointer :: generic_to_integer
497 
498  select type(generic)
499  type is (integer)
500  if (makecopy) then
501  allocate(generic_to_integer, source=generic)
502  else
503  generic_to_integer=>generic
504  end if
505  class default
506  generic_to_integer=>null()
507  end select
508  end function generic_to_integer
509 
513  integer function string_to_integer(string)
514  character(len=*), intent(in) :: string
515 
516  read(string, '(i15)' ) string_to_integer
517  end function string_to_integer
518 
522  integer function real_to_integer(input)
523  real, intent(in) :: input
524 
525  real_to_integer = int(input)
526  end function real_to_integer
527 
531  integer function logical_to_integer(input)
532  logical, intent(in) :: input
533 
534  if (input) then
536  else
538  end if
539  end function logical_to_integer
540 
545  function string_to_generic(string, makecopy)
546  character(len=*), target, intent(in) :: string
547  logical, intent(in) :: makecopy
548  class(*), pointer :: string_to_generic
549 
550  if (makecopy) then
551  allocate(string_to_generic, source=string)
552  else
553  string_to_generic=>string
554  end if
555  end function string_to_generic
556 
561  function integer_to_generic(input, makecopy)
562  integer, target , intent(in) :: input
563  logical, intent(in) :: makecopy
564  class(*), pointer :: integer_to_generic
565 
566  if (makecopy) then
567  allocate(integer_to_generic, source=input)
568  else
569  integer_to_generic=>input
570  end if
571  end function integer_to_generic
572 
577  function real_single_to_generic(input, makecopy)
578  real(kind=single_precision), target, intent(in) :: input
579  logical, intent(in) :: makecopy
580  class(*), pointer :: real_single_to_generic
581 
582  if (makecopy) then
583  allocate(real_single_to_generic, source=input)
584  else
586  end if
587  end function real_single_to_generic
588 
593  function real_double_to_generic(input, makecopy)
594  real(kind=double_precision), target, intent(in) :: input
595  logical, intent(in) :: makecopy
596  class(*), pointer :: real_double_to_generic
597 
598  if (makecopy) then
599  allocate(real_double_to_generic, source=input)
600  else
602  end if
603  end function real_double_to_generic
604 
609  function logical_to_generic(input, makecopy)
610  logical, target, intent(in) :: input
611  logical, intent(in) :: makecopy
612  class(*), pointer :: logical_to_generic
613 
614  if (makecopy) then
615  allocate(logical_to_generic, source=input)
616  else
617  logical_to_generic=>input
618  end if
619  end function logical_to_generic
620 end module conversions_mod
conversions_mod
Conversion between common inbuilt FORTRAN data types.
Definition: conversions.F90:5
conversions_mod::limit_to_decimal_places
subroutine limit_to_decimal_places(string_to_parse, decimal_places)
Helper subroutine which trims the string down to an upper limit of decimal places,...
Definition: conversions.F90:288
conversions_mod::generic_to_string
character(len=str_length) function, pointer generic_to_string(generic, makecopy, str_length)
Converts a generic to a string.
Definition: conversions.F90:183
conversions_mod::logical_to_generic
class(*) function, pointer logical_to_generic(input, makecopy)
Converts a logical into its generic data representation.
Definition: conversions.F90:610
conversions_mod::integer_to_logical
logical function integer_to_logical(input)
Converts an integer to a logical.
Definition: conversions.F90:387
conversions_mod::conv_is_logical
Determines whether a data item can be represented as a logical or not.
Definition: conversions.F90:100
conversions_mod::string_is_integer
logical function string_is_integer(string)
Determines whether a string is an integer or not.
Definition: conversions.F90:135
conversions_mod::conv_to_integer
Converts data types to integers.
Definition: conversions.F90:49
conversions_mod::generic_to_real
real function, pointer generic_to_real(generic, makecopy)
Converts a generic to a real. If this is infact an integer then will do a conversion and allocate poi...
Definition: conversions.F90:435
conversions_mod::string_is_logical
logical function string_is_logical(string)
Determines whether a string is a logical or not.
Definition: conversions.F90:168
conversions_mod::conv_to_logical
Converts data types to logical.
Definition: conversions.F90:71
conversions_mod::integer_to_real
real function integer_to_real(input)
Converts an integer to a real.
Definition: conversions.F90:471
conversions_mod::conv_to_generic
Converts a data type into the generic (class *) form.
Definition: conversions.F90:25
conversions_mod::generic_to_double_real
real(kind=default_precision) function, pointer, public generic_to_double_real(generic, makecopy)
Converts a generic to a double real.
Definition: conversions.F90:414
conversions_mod::integer_to_generic
class(*) function, pointer integer_to_generic(input, makecopy)
Converts an integer into its generic data representation.
Definition: conversions.F90:562
conversions_mod::generic_to_logical
logical function, pointer generic_to_logical(generic, makecopy)
Converts a generic to a logical.
Definition: conversions.F90:353
conversions_mod::string_to_integer
integer function string_to_integer(string)
Converts a string to an integer.
Definition: conversions.F90:514
conversions_mod::real_single_to_string
character(len=30) function real_single_to_string(input, decimal_places, exponent, exponent_small_numbers)
Converts a single precision real to a string.
Definition: conversions.F90:217
datadefn_mod::single_precision
integer, parameter, public single_precision
Single precision (32 bit) kind.
Definition: datadefn.F90:13
conversions_mod::conv_to_string
Converts data types to strings.
Definition: conversions.F90:38
conversions_mod::string_is_real
logical function string_is_real(string)
Determines whether a string is a real or not.
Definition: conversions.F90:151
conversions_mod::real_double_to_string
character(len=30) function real_double_to_string(input, decimal_places, exponent, exponent_small_numbers)
Converts a double precision real to a string.
Definition: conversions.F90:251
conversions_mod::conv_is_real
Determines whether a data item can be represented as a real or not.
Definition: conversions.F90:91
conversions_mod::real_to_logical
logical function real_to_logical(input)
Converts a real to a logical.
Definition: conversions.F90:400
conversions_mod::logical_to_integer
integer function logical_to_integer(input)
Converts a logical to an integer.
Definition: conversions.F90:532
conversions_mod::conv_is_integer
Determines whether a data item can be represented as an integer or not.
Definition: conversions.F90:81
conversions_mod::real_rounding_precision
integer, parameter real_rounding_precision
Definition: conversions.F90:16
conversions_mod::logical_to_string
character(len=5) function logical_to_string(input)
Converts a logical to a string.
Definition: conversions.F90:338
conversions_mod::string_to_generic
class(*) function, pointer string_to_generic(string, makecopy)
Converts a string into its generic data representation.
Definition: conversions.F90:546
conversions_mod::real_to_integer
integer function real_to_integer(input)
Converts a real to an integer.
Definition: conversions.F90:523
datadefn_mod::double_precision
integer, parameter, public double_precision
Double precision (64 bit) kind.
Definition: datadefn.F90:14
datadefn_mod
Contains common definitions for the data and datatypes used by MONC.
Definition: datadefn.F90:2
conversions_mod::logical_to_real
real function logical_to_real(input)
Converts a logical to a real.
Definition: conversions.F90:480
conversions_mod::l_original_rounding
logical l_original_rounding
Definition: conversions.F90:14
conversions_mod::integer_to_string
character(len=15) function integer_to_string(input)
Converts an integer to a string.
Definition: conversions.F90:206
conversions_mod::string_to_logical
logical function string_to_logical(string)
Converts a string to a logical.
Definition: conversions.F90:373
conversions_mod::string_to_real
real function string_to_real(string)
Converts a string to a real.
Definition: conversions.F90:458
conversions_mod::real_double_to_generic
class(*) function, pointer real_double_to_generic(input, makecopy)
Converts a double real into its generic data representation.
Definition: conversions.F90:594
conversions_mod::trim_trailing_zeros
subroutine trim_trailing_zeros(string_to_parse, zeros_to_retain)
A helper subroutine which trims training zeros from the string after a decimal place this is to make ...
Definition: conversions.F90:311
conversions_mod::conv_to_real
Converts data types to real.
Definition: conversions.F90:60
conversions_mod::real_single_to_generic
class(*) function, pointer real_single_to_generic(input, makecopy)
Converts a single real into its generic data representation.
Definition: conversions.F90:578
conversions_mod::generic_to_integer
integer function, pointer generic_to_integer(generic, makecopy)
Converts a generic to an integer.
Definition: conversions.F90:494
datadefn_mod::default_precision
integer, parameter, public default_precision
MPI communication type which we use for the prognostic and calculation data.
Definition: datadefn.F90:17
conversions_mod::conv_single_real_to_double
real(kind=double_precision) function, public conv_single_real_to_double(input_real)
Converts from a single to double precision real. This applies some rounding to a certain number of de...
Definition: conversions.F90:114