M_anything Module

NAME

M_anything(3fm) - [M_anything::INTRO] procedures that use polymorphism to allow arguments of different types generically
(LICENSE:MIT)

SYNOPSIS

  use M_anything,only : anyscalar_to_string
  use M_anything,only : anyscalar_to_int64
  use M_anything,only : anyscalar_to_real
  use M_anything,only : anyscalar_to_real128
  use M_anything,only : anyscalar_to_double
  use M_anything,only : anything_to_bytes
  use M_anything,only : anyinteger_to_string
  use M_anything,only : get_type
  use M_anything,only : bytes_to_anything
  use M_anything,only : empty, assignment(=)

DESCRIPTION

   anyscalar_to_string     convert intrinsic type to string
   anyscalar_to_int64      convert integer or real of any kind to 64-bit integer
   anyscalar_to_real       convert integer or real of any kind to real
   anyscalar_to_real128    convert integer or real of any kind to real128
   anyscalar_to_double     convert integer or real of any kind to doubleprecision
   anything_to_bytes       convert anything to bytes
   anyinteger_to_string    convert integer to string
   get_type                return array of strings containing type names of arguments
   empty                   create an empty array

EXAMPLE

At the cost of casting to a different type these functions can (among other uses such as in linked lists) allow for an alternative to duplicating code using generic procedure methods. For example, the following SQUAREALL function can take many input types and return a DOUBLEPRECISION value (it is a trivial example for demonstration purposes, and does not check for overflow, etc.).:

Sample program

 program demo_M_anything
 use, intrinsic :: iso_fortran_env, only : int8, int16, int32, int64
 use, intrinsic :: iso_fortran_env, only : real32, real64, real128
 implicit none
    ! call same function with many scalar input types
    write(*,*)squareall(2_int8)
    write(*,*)squareall(2_int16)
    write(*,*)squareall(2_int32)
    write(*,*)squareall(2_int64)
    write(*,*)squareall(2.0_real32)
    write(*,*)squareall(2.0_real64)
    write(*,*)squareall(2.0_real128)
 contains

 function squareall(invalue) result (dvalue)
 use M_anything, only : anyscalar_to_double
 class(*),intent(in)  :: invalue
 doubleprecision      :: invalue_local
 doubleprecision      :: dvalue
    invalue_local=anyscalar_to_double(invalue)
    dvalue=invalue_local*invalue_local
 end function squareall

 end program demo_M_anything

Results:

   4.00000000000000
   4.00000000000000
   4.00000000000000
   4.00000000000000
   4.00000000000000
   4.00000000000000
   4.00000000000000

AUTHOR

John S. Urban

LICENSE

MIT

,input_unit,output_unit public setany

subroutine setany(anything,default,answer)

$@(#) M_anything::setany(3fp): set absent parameter to default value

class(),intent(in),optional :: anything class(),intent(in) :: default class(*),intent(out),allocatable :: answer if(present(anything))then answer=anything else answer=default endif end subroutine setany



Variables

Type Visibility Attributes Name Initial
type(Empty_t), public :: empty

singleton


Interfaces

public interface anything_to_bytes

  • private function anything_to_bytes_arr(anything) result(chars)

    NAME

    anything_to_bytes(3f) - [M_anything] convert standard types to bytes (character(len=1):: array(:))
    (LICENSE:MIT)
    

    SYNOPSIS

    function anything_to_bytes(anything) result(chars)
    
     class(*),intent(in)  :: anything
             or
     class(*),intent(in)  :: anything(:)
    
     character(len=1),allocatable :: chars(:)
    

    DESCRIPTION

    This function uses polymorphism to allow input arguments of different
    types. It is used to create other procedures that can take many
    argument types as input options and convert them to a single type
    to simplify storing arbitrary data, to simplify generating data
    hashes, ...
    

    OPTIONS

    VALUEIN  input array or scalar to convert to type CHARACTER(LEN=1).
             May be of KIND INTEGER(kind=int8), INTEGER(kind=int16),
             INTEGER(kind=int32), INTEGER(kind=int64),
             REAL(kind=real32, REAL(kind=real64),
             REAL(kind=real128), complex, or CHARACTER(len=*)
    

    RETURN

    CHARS    The returned value is an array of bytes (character(len=1)).
    

    EXAMPLE

    Sample program

    program demo_anything_to_bytes
    use M_anything,      only : anything_to_bytes
    implicit none
    integer :: i
       write(*,'(/,4(1x,z2.2))')anything_to_bytes([(i*i,i=1,10)])
       write(*,'(/,4(1x,z2.2))')anything_to_bytes([11.11,22.22,33.33])
       write(*,'(/,4(1x,z2.2))')anything_to_bytes('This is a string')
    end program demo_anything_to_bytes
    

    Expected output

        01 00 00 00
        04 00 00 00
        09 00 00 00
        10 00 00 00
        19 00 00 00
        24 00 00 00
        31 00 00 00
        40 00 00 00
        51 00 00 00
        64 00 00 00
    
        8F C2 31 41
        8F C2 B1 41
        EC 51 05 42
    
        54 68 69 73
        20 69 73 20
        61 20 73 74
        72 69 6E 67
    

    AUTHOR

    John S. Urban
    

    LICENSE

    MIT
    

    Arguments

    Type IntentOptional Attributes Name
    class(*), intent(in) :: anything(:)

    Return Value character(len=1), allocatable, (:)

  • private function anything_to_bytes_scalar(anything) result(chars)

    Arguments

    Type IntentOptional Attributes Name
    class(*), intent(in) :: anything

    Return Value character(len=1), allocatable, (:)

public interface assignment(=)

  • private subroutine ints_empty_(x, emp)

    NAME

    empty(3f) - [M_anything] set an allocatable array to zero
    (LICENSE:MIT)
    

    SYNOPSIS

    use M_anything, only : empty, assignment(=)
    

    DESCRIPTION

    A convenience routine that sets an array to an empty set.
    

    EXAMPLE

    Sample program:

    program demo_empty_
    use M_anything, only : empty, assignment(=)
    integer, allocatable      :: ints(:)
    character(:), allocatable :: strs(:)
    real, allocatable      :: reals(:)
       ints=empty
       write(*,*)size(ints)
    
       write(*,*)'give them some size ...'
       reals = [1.0,2.0,3.0]
       ints = [1,2,3]
       strs = [character(len=10) :: "one","two","three","four"]
       write(*,*)size(ints)
       write(*,*)size(reals)
       write(*,*)size(strs)
    
       ints=empty
       reals=empty
       strs=empty
       write(*,*)'back to empty ...'
       write(*,*)size(ints)
       write(*,*)size(reals)
       write(*,*)size(strs)
    
    end program demo_empty_
    

    Expected output:

    >             0
    >   give them some size ...
    >             3
    >             3
    >             4
    >   back to empty ...
    >             0
    >             0
    >             0
    

    AUTHOR

    John S. Urban
    

    LICENSE

    MIT
    

    Arguments

    Type IntentOptional Attributes Name
    integer, intent(inout), allocatable :: x(:)
    type(Empty_t), intent(in) :: emp
  • private subroutine reals_empty_(x, emp)

    Arguments

    Type IntentOptional Attributes Name
    real, intent(inout), allocatable :: x(:)
    type(Empty_t), intent(in) :: emp
  • private subroutine doubles_empty_(x, emp)

    Arguments

    Type IntentOptional Attributes Name
    doubleprecision, intent(inout), allocatable :: x(:)
    type(Empty_t), intent(in) :: emp
  • private subroutine strings_empty_(x, emp)

    Arguments

    Type IntentOptional Attributes Name
    character(len=:), intent(inout), allocatable :: x(:)
    type(Empty_t), intent(in) :: emp

public interface get_type

  • private function get_type_arr(anything) result(chars)

    NAME

    get_type(3f) - [M_anything] return array of strings containing type
    names of arguments
    (LICENSE:MIT)
    

    SYNOPSIS

    function get_type(anything) result(chars)
    
     class(*),intent(in)  :: anything
             or
     class(*),intent(in)  :: anything(..)
    
     character(len=:),allocatable :: chars
    

    DESCRIPTION

    This function uses polymorphism to allow input arguments of different
    types. It is used by other procedures that can take many
    argument types as input options.
    

    OPTIONS

    VALUEIN  input array or scalar to return type of
             May be of KIND INTEGER(kind=int8), INTEGER(kind=int16),
             INTEGER(kind=int32), INTEGER(kind=int64),
             REAL(kind=real32, REAL(kind=real64),
             REAL(kind=real128), complex, or CHARACTER(len=*)
    

    RETURN

    CHARS    The returned value is an array of names
    

    EXAMPLE

    Sample program

    program demo_get_type
    use M_anything,      only : get_type
    implicit none
    integer :: i
       write(*,*)get_type([(i*i,i=1,10)])
       write(*,*)get_type([11.11,22.22,33.33])
       write(*,*)get_type('This is a string')
       write(*,*)get_type(30.0d0)
    end program demo_get_type
    

    Results:

     int32
     real32
     character
     real64
    

    AUTHOR

    John S. Urban
    

    LICENSE

    MIT
    

    Arguments

    Type IntentOptional Attributes Name
    class(*), intent(in) :: anything(:)

    Return Value character(len=20)

  • private impure elemental function get_type_scalar(anything) result(chars)

    Arguments

    Type IntentOptional Attributes Name
    class(*), intent(in) :: anything

    Return Value character(len=20)


Functions

public impure function anyinteger_to_string(int) result(out)

Sample program

Read more…

Arguments

Type IntentOptional Attributes Name
class(*), intent(in) :: int

Return Value character(len=:), allocatable

public pure elemental function anyscalar_to_double(valuein) result(d_out)

Sample program

Read more…

Arguments

Type IntentOptional Attributes Name
class(*), intent(in) :: valuein

Return Value doubleprecision

public impure elemental function anyscalar_to_int64(valuein) result(ii38)

Results

Read more…

Arguments

Type IntentOptional Attributes Name
class(*), intent(in) :: valuein

Return Value integer(kind=int64)

public pure elemental function anyscalar_to_real(valuein) result(r_out)

Sample program

Read more…

Arguments

Type IntentOptional Attributes Name
class(*), intent(in) :: valuein

Return Value real

public pure elemental function anyscalar_to_real128(valuein) result(d_out)

Sample program

Read more…

Arguments

Type IntentOptional Attributes Name
class(*), intent(in) :: valuein

Return Value real(kind=real128)

public pure function anyscalar_to_string(gen0, gen1, gen2, gen3, gen4, gen5, gen6, gen7, gen8, gen9, gena, genb, genc, gend, gene, genf, geng, genh, geni, genj, sep)

Sample program:

Read more…

Arguments

Type IntentOptional Attributes Name
class(*), intent(in), optional :: gen0
class(*), intent(in), optional :: gen1
class(*), intent(in), optional :: gen2
class(*), intent(in), optional :: gen3
class(*), intent(in), optional :: gen4
class(*), intent(in), optional :: gen5
class(*), intent(in), optional :: gen6
class(*), intent(in), optional :: gen7
class(*), intent(in), optional :: gen8
class(*), intent(in), optional :: gen9
class(*), intent(in), optional :: gena
class(*), intent(in), optional :: genb
class(*), intent(in), optional :: genc
class(*), intent(in), optional :: gend
class(*), intent(in), optional :: gene
class(*), intent(in), optional :: genf
class(*), intent(in), optional :: geng
class(*), intent(in), optional :: genh
class(*), intent(in), optional :: geni
class(*), intent(in), optional :: genj
character(len=*), intent(in), optional :: sep

Return Value character(len=:), allocatable


Subroutines

public subroutine bytes_to_anything(chars, anything)

subroutine bytes_to_anything(chars,anything)

Read more…

Arguments

Type IntentOptional Attributes Name
character(len=1), allocatable :: chars(:)
class(*) :: anything(:)