MONC
Data Types | Functions/Subroutines | Variables
conversions_mod Module Reference

Conversion between common inbuilt FORTRAN data types. More...

Data Types

interface  conv_is_integer
 Determines whether a data item can be represented as an integer or not. More...
 
interface  conv_is_logical
 Determines whether a data item can be represented as a logical or not. More...
 
interface  conv_is_real
 Determines whether a data item can be represented as a real or not. More...
 
interface  conv_to_generic
 Converts a data type into the generic (class *) form. More...
 
interface  conv_to_integer
 Converts data types to integers. More...
 
interface  conv_to_logical
 Converts data types to logical. More...
 
interface  conv_to_real
 Converts data types to real. More...
 
interface  conv_to_string
 Converts data types to strings. More...
 

Functions/Subroutines

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 decimal places to ignore very small fractions. More...
 
logical function string_is_integer (string)
 Determines whether a string is an integer or not. More...
 
logical function string_is_real (string)
 Determines whether a string is a real or not. More...
 
logical function string_is_logical (string)
 Determines whether a string is a logical or not. More...
 
character(len=str_length) function, pointer generic_to_string (generic, makecopy, str_length)
 Converts a generic to a string. More...
 
character(len=15) function integer_to_string (input)
 Converts an integer to a string. More...
 
character(len=30) function real_single_to_string (input, decimal_places, exponent, exponent_small_numbers)
 Converts a single precision real to a string. More...
 
character(len=30) function real_double_to_string (input, decimal_places, exponent, exponent_small_numbers)
 Converts a double precision real to a string. More...
 
subroutine limit_to_decimal_places (string_to_parse, decimal_places)
 Helper subroutine which trims the string down to an upper limit of decimal places, with all numbers beyond this point removed. More...
 
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 the string more readable when printed out. More...
 
character(len=5) function logical_to_string (input)
 Converts a logical to a string. More...
 
logical function, pointer generic_to_logical (generic, makecopy)
 Converts a generic to a logical. More...
 
logical function string_to_logical (string)
 Converts a string to a logical. More...
 
logical function integer_to_logical (input)
 Converts an integer to a logical. More...
 
logical function real_to_logical (input)
 Converts a real to a logical. More...
 
real(kind=default_precision) function, pointer, public generic_to_double_real (generic, makecopy)
 Converts a generic to a double real. More...
 
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 pointed to this. More...
 
real function string_to_real (string)
 Converts a string to a real. More...
 
real function integer_to_real (input)
 Converts an integer to a real. More...
 
real function logical_to_real (input)
 Converts a logical to a real. More...
 
integer function, pointer generic_to_integer (generic, makecopy)
 Converts a generic to an integer. More...
 
integer function string_to_integer (string)
 Converts a string to an integer. More...
 
integer function real_to_integer (input)
 Converts a real to an integer. More...
 
integer function logical_to_integer (input)
 Converts a logical to an integer. More...
 
class(*) function, pointer string_to_generic (string, makecopy)
 Converts a string into its generic data representation. More...
 
class(*) function, pointer integer_to_generic (input, makecopy)
 Converts an integer into its generic data representation. More...
 
class(*) function, pointer real_single_to_generic (input, makecopy)
 Converts a single real into its generic data representation. More...
 
class(*) function, pointer real_double_to_generic (input, makecopy)
 Converts a double real into its generic data representation. More...
 
class(*) function, pointer logical_to_generic (input, makecopy)
 Converts a logical into its generic data representation. More...
 

Variables

integer, parameter real_rounding_precision =int(1e8)
 

Detailed Description

Conversion between common inbuilt FORTRAN data types.

The user will still need to supply conversions between their derived types but this makes it easier when handling common inbuilt type conversions.

Function/Subroutine Documentation

◆ conv_single_real_to_double()

real(kind=double_precision) function, public conversions_mod::conv_single_real_to_double ( real(kind=single_precision), intent(in)  input_real)

Converts from a single to double precision real. This applies some rounding to a certain number of decimal places to ignore very small fractions.

Parameters
input_realThe single precision real to convert
Returns
Double precision representation which is smoothed to a specific rounding precision

Definition at line 112 of file conversions.F90.

112  real(kind=SINGLE_PRECISION), intent(in) :: input_real
113 
114  conv_single_real_to_double=dnint(real(input_real, kind=DEFAULT_PRECISION) * &
115  real_rounding_precision) / real_rounding_precision
Here is the caller graph for this function:

◆ generic_to_double_real()

real(kind=default_precision) function, pointer, public conversions_mod::generic_to_double_real ( class(*), intent(in), pointer  generic,
logical, intent(in)  makecopy 
)

Converts a generic to a double real.

Parameters
genericThe generic to convert into a double real
makecopyWhether to use a copy of the generic data or not
Returns
A pointer to the double real or null if generic conversion not possible

Definition at line 402 of file conversions.F90.

402  class(*), pointer, intent(in) :: generic
403  logical, intent(in) :: makecopy
404  real(kind=DEFAULT_PRECISION), pointer :: generic_to_double_real
405 
406  select type(generic)
407  type is (real(kind=default_precision))
408  if (makecopy) then
409  allocate(generic_to_double_real, source=generic)
410  else
411  generic_to_double_real=>generic
412  end if
413  class default
414  generic_to_double_real=>null()
415  end select

◆ generic_to_integer()

integer function, pointer conversions_mod::generic_to_integer ( class(*), intent(in), pointer  generic,
logical, intent(in)  makecopy 
)
private

Converts a generic to an integer.

Parameters
genericThe generic to convert into an integer
makecopyWhether to use a copy of the generic data or not
Returns
A pointer to the integer or null if generic conversion not possible

Definition at line 482 of file conversions.F90.

482  class(*), pointer, intent(in) :: generic
483  logical, intent(in) :: makecopy
484  integer, pointer :: generic_to_integer
485 
486  select type(generic)
487  type is (integer)
488  if (makecopy) then
489  allocate(generic_to_integer, source=generic)
490  else
491  generic_to_integer=>generic
492  end if
493  class default
494  generic_to_integer=>null()
495  end select

◆ generic_to_logical()

logical function, pointer conversions_mod::generic_to_logical ( class(*), intent(in), pointer  generic,
logical, intent(in)  makecopy 
)
private

Converts a generic to a logical.

Parameters
genericThe generic to convert into a logical
makecopyWhether to use a copy of the generic data or not
Returns
A pointer to the logical or null if generic conversion not possible

Definition at line 341 of file conversions.F90.

341  class(*), pointer, intent(in) :: generic
342  logical, intent(in) :: makecopy
343  logical, pointer :: generic_to_logical
344 
345  select type(generic)
346  type is (logical)
347  if (makecopy) then
348  allocate(generic_to_logical, source=generic)
349  else
350  generic_to_logical=>generic
351  end if
352  class default
353  generic_to_logical=>null()
354  end select

◆ generic_to_real()

real function, pointer conversions_mod::generic_to_real ( class(*), intent(in), pointer  generic,
logical, intent(in)  makecopy 
)
private

Converts a generic to a real. If this is infact an integer then will do a conversion and allocate pointed to this.

Parameters
genericThe generic to convert into a real
makecopyWhether to use a copy of the generic data or not
Returns
A pointer to the real or null if generic conversion not possible

Definition at line 423 of file conversions.F90.

423  class(*), pointer, intent(in) :: generic
424  logical, intent(in) :: makecopy
425  real, pointer :: generic_to_real
426 
427  select type(generic)
428  type is (real)
429  if (makecopy) then
430  allocate(generic_to_real, source=generic)
431  else
432  generic_to_real=>generic
433  end if
434  type is (integer)
435  allocate(generic_to_real)
436  generic_to_real=conv_to_real(generic)
437  class default
438  generic_to_real=>null()
439  end select

◆ generic_to_string()

character(len=str_length) function, pointer conversions_mod::generic_to_string ( class(*), intent(in), pointer  generic,
logical, intent(in)  makecopy,
integer, intent(in)  str_length 
)
private

Converts a generic to a string.

Parameters
genericThe generic to convert into a string
makecopyWhether to use a copy of the generic data or not
str_lengthLength of the resulting string
Returns
A pointer to the string or null if generic conversion not possible

Definition at line 171 of file conversions.F90.

171  class(*), pointer, intent(in) :: generic
172  logical, intent(in) :: makecopy
173  integer, intent(in) :: str_length
174  character(len=str_length), pointer :: generic_to_string, temporary_generic_ptr
175 
176  select type(generic)
177  type is (character(len=*))
178  if (makecopy) then
179  ! Need to do this to enforce string length information
180  temporary_generic_ptr=>generic
181  allocate(generic_to_string, source=temporary_generic_ptr)
182  else
183  generic_to_string=>generic
184  end if
185  class default
186  generic_to_string=>null()
187  end select

◆ integer_to_generic()

class(*) function, pointer conversions_mod::integer_to_generic ( integer, intent(in), target  input,
logical, intent(in)  makecopy 
)
private

Converts an integer into its generic data representation.

Parameters
inputThe integer to convert into its generic representation
makecopyWhether make a copy of the underlying data or just return a simple pointer
Returns
A pointer to the generic data

Definition at line 550 of file conversions.F90.

550  integer, target , intent(in) :: input
551  logical, intent(in) :: makecopy
552  class(*), pointer :: integer_to_generic
553 
554  if (makecopy) then
555  allocate(integer_to_generic, source=input)
556  else
557  integer_to_generic=>input
558  end if

◆ integer_to_logical()

logical function conversions_mod::integer_to_logical ( integer, intent(in)  input)
private

Converts an integer to a logical.

Parameters
inputThe integer to convert into a logical
Returns
The logical

Definition at line 375 of file conversions.F90.

375  integer, intent(in) :: input
376 
377  if (input .ge. 1) then
378  integer_to_logical = .true.
379  else
380  integer_to_logical = .false.
381  end if

◆ integer_to_real()

real function conversions_mod::integer_to_real ( integer, intent(in)  input)
private

Converts an integer to a real.

Parameters
inputThe integer to convert into a real
Returns
The real

Definition at line 459 of file conversions.F90.

459  integer, intent(in) :: input
460 
461  integer_to_real = real(input)

◆ integer_to_string()

character(len=15) function conversions_mod::integer_to_string ( integer, intent(in)  input)
private

Converts an integer to a string.

Parameters
inputThe integer to convert into a string
Returns
The string of length 15 characters

Definition at line 194 of file conversions.F90.

194  integer, intent(in) :: input
195  character(len=15) :: integer_to_string
196 
197  write(integer_to_string, '(i15)' ) input
198  integer_to_string = trim(adjustl(integer_to_string))

◆ limit_to_decimal_places()

subroutine conversions_mod::limit_to_decimal_places ( character(len=*), intent(inout)  string_to_parse,
integer, intent(in)  decimal_places 
)
private

Helper subroutine which trims the string down to an upper limit of decimal places, with all numbers beyond this point removed.

Parameters
stringToParseThe raw, uncropped, string to processess which is modified
decimalPlacesNumber of decimal places to keep

Definition at line 276 of file conversions.F90.

276  character(len=*), intent(inout) :: string_to_parse
277  integer, intent(in) :: decimal_places
278 
279  integer :: decimal_posn, exp_posn
280 
281  string_to_parse=adjustl(string_to_parse)
282  decimal_posn=index(string_to_parse, ".")
283  exp_posn=index(string_to_parse, "E")
284  if (decimal_posn .ne. 0 .and. decimal_posn+decimal_places+1 .le. len(string_to_parse)) then
285  if (exp_posn .eq. 0) then
286  string_to_parse(decimal_posn+decimal_places+1:)=" "
287  else
288  string_to_parse(decimal_posn+decimal_places+1:)=string_to_parse(exp_posn:)
289  string_to_parse(decimal_posn+decimal_places+1+(len(string_to_parse)-exp_posn)+1:)=" "
290  end if
291  end if
Here is the caller graph for this function:

◆ logical_to_generic()

class(*) function, pointer conversions_mod::logical_to_generic ( logical, intent(in), target  input,
logical, intent(in)  makecopy 
)
private

Converts a logical into its generic data representation.

Parameters
inputThe logical to convert into its generic representation
makecopyWhether make a copy of the underlying data or just return a simple pointer
Returns
A pointer to the generic data

Definition at line 598 of file conversions.F90.

598  logical, target, intent(in) :: input
599  logical, intent(in) :: makecopy
600  class(*), pointer :: logical_to_generic
601 
602  if (makecopy) then
603  allocate(logical_to_generic, source=input)
604  else
605  logical_to_generic=>input
606  end if

◆ logical_to_integer()

integer function conversions_mod::logical_to_integer ( logical, intent(in)  input)
private

Converts a logical to an integer.

Parameters
inputThe logical to convert into an integer
Returns
The integer

Definition at line 520 of file conversions.F90.

520  logical, intent(in) :: input
521 
522  if (input) then
523  logical_to_integer = 1
524  else
525  logical_to_integer = 0
526  end if

◆ logical_to_real()

real function conversions_mod::logical_to_real ( logical, intent(in)  input)
private

Converts a logical to a real.

Parameters
inputThe logical to convert into a real
Returns
The real

Definition at line 468 of file conversions.F90.

468  logical, intent(in) :: input
469 
470  if (input) then
471  logical_to_real = 1.0
472  else
473  logical_to_real = 0.0
474  end if

◆ logical_to_string()

character(len=5) function conversions_mod::logical_to_string ( logical, intent(in)  input)
private

Converts a logical to a string.

Parameters
inputThe logical to convert into a string
Returns
The string of length 5 characters

Definition at line 326 of file conversions.F90.

326  logical, intent(in) :: input
327  character(len=5) :: logical_to_string
328 
329  if (input) then
330  logical_to_string = "true"
331  else
332  logical_to_string = "false"
333  end if

◆ real_double_to_generic()

class(*) function, pointer conversions_mod::real_double_to_generic ( real(kind=double_precision), intent(in), target  input,
logical, intent(in)  makecopy 
)
private

Converts a double real into its generic data representation.

Parameters
inputThe real to convert into its generic representation
makecopyWhether make a copy of the underlying data or just return a simple pointer
Returns
A pointer to the generic data

Definition at line 582 of file conversions.F90.

582  real(kind=DOUBLE_PRECISION), target, intent(in) :: input
583  logical, intent(in) :: makecopy
584  class(*), pointer :: real_double_to_generic
585 
586  if (makecopy) then
587  allocate(real_double_to_generic, source=input)
588  else
589  real_double_to_generic=>input
590  end if

◆ real_double_to_string()

character(len=30) function conversions_mod::real_double_to_string ( real(kind=double_precision), intent(in)  input,
integer, optional  decimal_places,
logical, optional  exponent,
logical, optional  exponent_small_numbers 
)
private

Converts a double precision real to a string.

Parameters
inputThe real to convert into a string
Returns
The string of length 30 characters

Definition at line 239 of file conversions.F90.

239  real(kind=DOUBLE_PRECISION), intent(in) :: input
240  character(len=30) :: real_double_to_string
241  integer, optional :: decimal_places
242  logical, optional :: exponent, exponent_small_numbers
243 
244  logical :: transformed
245  transformed=.false.
246 
247  if (present(exponent)) then
248  if (exponent) then
249  write(real_double_to_string, '(es30.10)' ) input
250  transformed=.true.
251  end if
252  end if
253  if (present(exponent_small_numbers)) then
254  if (exponent_small_numbers) then
255  write(real_double_to_string, '(g30.10)' ) input
256  transformed=.true.
257  end if
258  end if
259  if (.not. transformed) then
260  write(real_double_to_string, '(f30.10)' ) input
261  if (scan(real_double_to_string, "*") .ne. 0) write(real_double_to_string, '(es30.10)' ) input
262  end if
263  call trim_trailing_zeros(real_double_to_string, 2)
264  if (present(decimal_places)) then
265  call limit_to_decimal_places(real_double_to_string, decimal_places)
266  end if
267 
268  real_double_to_string = trim(adjustl(real_double_to_string))
Here is the call graph for this function:

◆ real_single_to_generic()

class(*) function, pointer conversions_mod::real_single_to_generic ( real(kind=single_precision), intent(in), target  input,
logical, intent(in)  makecopy 
)
private

Converts a single real into its generic data representation.

Parameters
inputThe real to convert into its generic representation
makecopyWhether make a copy of the underlying data or just return a simple pointer
Returns
A pointer to the generic data

Definition at line 566 of file conversions.F90.

566  real(kind=SINGLE_PRECISION), target, intent(in) :: input
567  logical, intent(in) :: makecopy
568  class(*), pointer :: real_single_to_generic
569 
570  if (makecopy) then
571  allocate(real_single_to_generic, source=input)
572  else
573  real_single_to_generic=>input
574  end if

◆ real_single_to_string()

character(len=30) function conversions_mod::real_single_to_string ( real(kind=single_precision), intent(in)  input,
integer, optional  decimal_places,
logical, optional  exponent,
logical, optional  exponent_small_numbers 
)
private

Converts a single precision real to a string.

Parameters
inputThe real to convert into a string
Returns
The string of length 30 characters

Definition at line 205 of file conversions.F90.

205  real(kind=SINGLE_PRECISION), intent(in) :: input
206  character(len=30) :: real_single_to_string
207  integer, optional :: decimal_places
208  logical, optional :: exponent, exponent_small_numbers
209 
210  logical :: transformed
211  transformed=.false.
212 
213  if (present(exponent)) then
214  if (exponent) then
215  write(real_single_to_string, '(es30.10)' ) input
216  transformed=.true.
217  end if
218  end if
219  if (present(exponent_small_numbers)) then
220  if (exponent_small_numbers) then
221  write(real_single_to_string, '(g30.10)' ) input
222  transformed=.true.
223  end if
224  end if
225  if (.not. transformed) then
226  write(real_single_to_string, '(f30.10)' ) input
227  if (scan(real_single_to_string, "*") .ne. 0) write(real_single_to_string, '(es30.10)' ) input
228  end if
229  call trim_trailing_zeros(real_single_to_string, 2)
230  if (present(decimal_places)) call limit_to_decimal_places(real_single_to_string, decimal_places)
231 
232  real_single_to_string = trim(adjustl(real_single_to_string))
Here is the call graph for this function:

◆ real_to_integer()

integer function conversions_mod::real_to_integer ( real, intent(in)  input)
private

Converts a real to an integer.

Parameters
inputThe real to convert into an integer
Returns
The integer

Definition at line 511 of file conversions.F90.

511  real, intent(in) :: input
512 
513  real_to_integer = int(input)

◆ real_to_logical()

logical function conversions_mod::real_to_logical ( real, intent(in)  input)
private

Converts a real to a logical.

Parameters
inputThe real to convert into a logical
Returns
The logical

Definition at line 388 of file conversions.F90.

388  real, intent(in) :: input
389 
390  if (input .ge. 1.0) then
391  real_to_logical = .true.
392  else
393  real_to_logical = .false.
394  end if

◆ string_is_integer()

logical function conversions_mod::string_is_integer ( character(len=*), intent(in)  string)
private

Determines whether a string is an integer or not.

Parameters
stringThe string to test
Returns
Logical whether or not the string can be represented as an integer

Definition at line 123 of file conversions.F90.

123  character(len=*), intent(in) :: string
124 
125  integer :: integer_value, ierr
126 
127  if (len(trim(string)) .ne. 0) then
128  read(string, '(i10)', iostat=ierr ) integer_value
129  string_is_integer = ierr == 0
130  else
131  string_is_integer=.false.
132  end if

◆ string_is_logical()

logical function conversions_mod::string_is_logical ( character(len=*), intent(in)  string)
private

Determines whether a string is a logical or not.

Parameters
stringThe string to test
Returns
Logical whether or not the string can be represented as a logical

Definition at line 156 of file conversions.F90.

156  character(len=*), intent(in) :: string
157 
158  string_is_logical = .false.
159  if (trim(adjustl(string)) .eq. "true" .or. trim(adjustl(string)) .eq. "false" .or. &
160  trim(adjustl(string)) .eq. ".true." .or. trim(adjustl(string)) .eq. ".false." .or. &
161  trim(adjustl(string)) .eq. ".true" .or. trim(adjustl(string)) .eq. "true." .or. &
162  trim(adjustl(string)) .eq. ".false" .or. trim(adjustl(string)) .eq. "false.") string_is_logical = .true.

◆ string_is_real()

logical function conversions_mod::string_is_real ( character(len=*), intent(in)  string)
private

Determines whether a string is a real or not.

Parameters
stringThe string to test
Returns
Logical whether or not the string can be represented as a real

Definition at line 139 of file conversions.F90.

139  character(len=*), intent(in) :: string
140 
141  integer :: ierr
142  real :: real_value
143 
144  if (len(trim(string)) .ne. 0) then
145  read(string, '(f10.2)', iostat=ierr ) real_value
146  string_is_real = ierr == 0
147  else
148  string_is_real=.false.
149  end if

◆ string_to_generic()

class(*) function, pointer conversions_mod::string_to_generic ( character(len=*), intent(in), target  string,
logical, intent(in)  makecopy 
)
private

Converts a string into its generic data representation.

Parameters
stringThe string to convert into its generic representation
makecopyWhether make a copy of the underlying data or just return a simple pointer
Returns
A pointer to the generic data

Definition at line 534 of file conversions.F90.

534  character(len=*), target, intent(in) :: string
535  logical, intent(in) :: makecopy
536  class(*), pointer :: string_to_generic
537 
538  if (makecopy) then
539  allocate(string_to_generic, source=string)
540  else
541  string_to_generic=>string
542  end if

◆ string_to_integer()

integer function conversions_mod::string_to_integer ( character(len=*), intent(in)  string)
private

Converts a string to an integer.

Parameters
stringThe string to convert into an integer
Returns
The integer

Definition at line 502 of file conversions.F90.

502  character(len=*), intent(in) :: string
503 
504  read(string, '(i15)' ) string_to_integer

◆ string_to_logical()

logical function conversions_mod::string_to_logical ( character(len=*), intent(in)  string)
private

Converts a string to a logical.

Parameters
stringThe string to convert into a logical (case sensitive)
Returns
The logical

Definition at line 361 of file conversions.F90.

361  character(len=*), intent(in) :: string
362 
363  if (trim(adjustl(string)) .eq. "true" .or. trim(adjustl(string)) .eq. ".true." .or. &
364  trim(adjustl(string)) .eq. ".true" .or. trim(adjustl(string)) .eq. "true.") then
365  string_to_logical = .true.
366  else
367  string_to_logical = .false.
368  end if

◆ string_to_real()

real function conversions_mod::string_to_real ( character(len=*), intent(in)  string)
private

Converts a string to a real.

Parameters
stringThe string to convert into a real
Returns
The real

Definition at line 446 of file conversions.F90.

446  character(len=*), intent(in) :: string
447 
448  if (scan(string, "E") .ne. 0 .or. scan(string, "e") .ne. 0) then
449  read(string, '(es30.10)' ) string_to_real
450  else
451  read(string, '(f10.0)' ) string_to_real
452  end if

◆ trim_trailing_zeros()

subroutine conversions_mod::trim_trailing_zeros ( character(len=*), intent(inout)  string_to_parse,
integer, intent(in)  zeros_to_retain 
)
private

A helper subroutine which trims training zeros from the string after a decimal place this is to make the string more readable when printed out.

Parameters
stringToParseThe string to parse which is modified to replace trailing zeros
zerosToRetainThe number of trailing (after decimal) zeros to retain

Definition at line 299 of file conversions.F90.

299  character(len=*), intent(inout) :: string_to_parse
300  integer, intent(in) :: zeros_to_retain
301 
302  integer :: decimal_posn, i, zero_count, nonzero_hit
303 
304  zero_count=0
305 
306  decimal_posn=index(string_to_parse, ".")
307  if (decimal_posn .ne. 0 .and. decimal_posn .lt. len(string_to_parse)) then
308  do i=len(trim(string_to_parse)), decimal_posn, -1
309  if (string_to_parse(i:i) .ne. "0") then
310  nonzero_hit=i
311  exit
312  else
313  zero_count=zero_count+1
314  end if
315  end do
316  if (zero_count .gt. zeros_to_retain) then
317  string_to_parse(nonzero_hit+zeros_to_retain:)=""
318  end if
319  end if
Here is the caller graph for this function:

Variable Documentation

◆ real_rounding_precision

integer, parameter conversions_mod::real_rounding_precision =int(1e8)
private

Definition at line 14 of file conversions.F90.

14  integer, parameter :: real_rounding_precision=int(1e8)