The ParaMonte Documentation Website
Current view: top level - kernel - String_mod.f90 (source / functions) Hit Total Coverage
Test: ParaMonte 1.5.1 :: Coarray Parallel Kernel - Code Coverage Report Lines: 263 265 99.2 %
Date: 2021-01-08 12:59:07 Functions: 21 21 100.0 %
Legend: Lines: hit not hit

          Line data    Source code
       1             : !!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
       2             : !!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
       3             : !!!!
       4             : !!!!   MIT License
       5             : !!!!
       6             : !!!!   ParaMonte: plain powerful parallel Monte Carlo library.
       7             : !!!!
       8             : !!!!   Copyright (C) 2012-present, The Computational Data Science Lab
       9             : !!!!
      10             : !!!!   This file is part of the ParaMonte library.
      11             : !!!!
      12             : !!!!   Permission is hereby granted, free of charge, to any person obtaining a
      13             : !!!!   copy of this software and associated documentation files (the "Software"),
      14             : !!!!   to deal in the Software without restriction, including without limitation
      15             : !!!!   the rights to use, copy, modify, merge, publish, distribute, sublicense,
      16             : !!!!   and/or sell copies of the Software, and to permit persons to whom the
      17             : !!!!   Software is furnished to do so, subject to the following conditions:
      18             : !!!!
      19             : !!!!   The above copyright notice and this permission notice shall be
      20             : !!!!   included in all copies or substantial portions of the Software.
      21             : !!!!
      22             : !!!!   THE SOFTWARE IS PROVIDED "AS IS", WITHOUT WARRANTY OF ANY KIND,
      23             : !!!!   EXPRESS OR IMPLIED, INCLUDING BUT NOT LIMITED TO THE WARRANTIES OF
      24             : !!!!   MERCHANTABILITY, FITNESS FOR A PARTICULAR PURPOSE AND NONINFRINGEMENT.
      25             : !!!!   IN NO EVENT SHALL THE AUTHORS OR COPYRIGHT HOLDERS BE LIABLE FOR ANY CLAIM,
      26             : !!!!   DAMAGES OR OTHER LIABILITY, WHETHER IN AN ACTION OF CONTRACT, TORT OR
      27             : !!!!   OTHERWISE, ARISING FROM, OUT OF OR IN CONNECTION WITH THE SOFTWARE
      28             : !!!!   OR THE USE OR OTHER DEALINGS IN THE SOFTWARE.
      29             : !!!!
      30             : !!!!   ACKNOWLEDGMENT
      31             : !!!!
      32             : !!!!   ParaMonte is an honor-ware and its currency is acknowledgment and citations.
      33             : !!!!   As per the ParaMonte library license agreement terms, if you use any parts of
      34             : !!!!   this library for any purposes, kindly acknowledge the use of ParaMonte in your
      35             : !!!!   work (education/research/industry/development/...) by citing the ParaMonte
      36             : !!!!   library as described on this page:
      37             : !!!!
      38             : !!!!       https://github.com/cdslaborg/paramonte/blob/main/ACKNOWLEDGMENT.md
      39             : !!!!
      40             : !!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
      41             : !!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
      42             : 
      43             : !> \brief This module contains the classes and procedures for various string manipulations.
      44             : !> \author Amir Shahmoradi
      45             : 
      46             : module String_mod
      47             : 
      48             :     use, intrinsic :: iso_fortran_env, only: int8
      49             :     use Constants_mod, only: IK, RK
      50             :     use JaggedArray_mod, only: CharVec_type
      51             :     implicit none
      52             : 
      53             :     public
      54             : 
      55             :     character(*), parameter :: MODULE_NAME = "@String_mod"
      56             : 
      57             :     integer(int8) :: NUM2STR_MAXLEN = 63_int8
      58             : 
      59             :     !> The `IntStr_type` class for converting integers to strings.
      60             :     type :: IntStr_type
      61             :         integer(IK)                 :: val !< The integer value.
      62             :         character(:), allocatable   :: str !< The integer value in string format.
      63             :     contains
      64             :         procedure, nopass           :: int322str, int642str
      65             :         generic                     :: int2str => int322str, int642str
      66             :     end type IntStr_type
      67             : 
      68             :     !> The `RealStr_type` class for converting real numbers to strings.
      69             :     type :: RealStr_type
      70             :         integer(IK)                 :: val !< The real value.
      71             :         character(:), allocatable   :: str !< The real value in string format.
      72             :     contains
      73             :         procedure, nopass           :: real322str, real642str
      74             :         generic                     :: real2str => real322str, real642str
      75             :     end type RealStr_type
      76             : 
      77             :     !> The `String_type` class for manipulating strings.
      78             :     type :: String_type
      79             :         character(:)      , allocatable   :: value          !< The string value.
      80             :         type(CharVec_type), allocatable   :: Parts(:)       !< The string parts.
      81             :         integer(IK)                       :: nPart = 0_IK   !< The number of parts in the string.
      82             :     contains
      83             :         procedure, nopass :: split, replaceStr, getLowerCase, getUpperCase, isInteger, isDigit
      84             :         procedure, nopass :: str2int, str2real, str2int32, str2int64, str2real32, str2real64
      85             :         procedure, nopass :: pad => padString
      86             :     end type String_type
      87             : 
      88             :     interface int2str
      89             :         module procedure int322str, int642str
      90             :     end interface
      91             : 
      92             :     interface real2str
      93             :         module procedure real322str, real642str, real642str_1D, real642str_2D
      94             :     end interface
      95             : 
      96             :     interface num2str
      97             :         module procedure int322str, int642str, real642str, real642str_1D, real642str_2D, real322str, log2str
      98             :     end interface
      99             : 
     100             : !%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
     101             : 
     102             : contains
     103             : 
     104             : !%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
     105             : 
     106             :     !> \brief
     107             :     !> Replace the input `search` string with the input `substitute` in the input `string` and return the result.
     108             :     !>
     109             :     !> \param[in]       string      :   The input string whose subparts will have to replaced.
     110             :     !> \param[in]       search      :   The input substring pattern that will have to replaced.
     111             :     !> \param[in]       substitute  :   The input substitute substring that will replace the `search` pattern in the input string.
     112             :     !>
     113             :     !> \return
     114             :     !> `modifiedString` : The modified input `string` such that with all
     115             :     !> instances of `search` are replaced with the input `substitute` string.
     116             :     !>
     117             :     !> \remark
     118             :     !> This procedure is a static method of the class [String_type](@ref string_type).
     119             :     !>
     120             :     !> \author
     121             :     ! Amir Shahmoradi, Sep 1, 2017, 12:00 AM, ICES, UT Austin
     122       12012 :     pure recursive function replaceStr(string,search,substitute) result(modifiedString)
     123             : #if INTEL_COMPILER_ENABLED && defined DLL_ENABLED && (OS_IS_WINDOWS || defined OS_IS_DARWIN)
     124             :         !DEC$ ATTRIBUTES DLLEXPORT :: replaceStr
     125             : #endif
     126             :         implicit none
     127             :         character(len=*), intent(in)  :: string, search, substitute
     128             :         character(len=:), allocatable :: modifiedString
     129             :         integer(IK)                   :: i, stringLen, searchLen
     130       12012 :         stringLen = len(string)
     131       12012 :         searchLen = len(search)
     132       12012 :         if (stringLen==0 .or. searchLen==0) then
     133         156 :             modifiedString = ""
     134         156 :             return
     135       11856 :         elseif (stringLen<searchLen) then
     136          12 :             modifiedString = string
     137          12 :             return
     138             :         end if
     139       11844 :         i = 1
     140      191984 :         do
     141      203828 :             if (string(i:i+searchLen-1)==search) then
     142        6156 :                 modifiedString = string(1:i-1) // substitute // replaceStr(string(i+searchLen:stringLen),search,substitute)
     143        6156 :                 exit
     144             :             end if
     145      197672 :             if (i+searchLen>stringLen) then
     146        5688 :                 modifiedString = string
     147        5688 :                 exit
     148             :             end if
     149      191984 :             i = i + 1
     150      191984 :             cycle
     151             :         end do
     152       24024 :     end function replaceStr
     153             : 
     154             : !%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
     155             : 
     156             :     !> \brief
     157             :     !> Split the input string string with the input `substitute` in the input `string` and return the result.
     158             :     !>
     159             :     !> \param[in]       string  :   The input string.
     160             :     !> \param[in]       delim   :   The delimiter to be used to split the input string.
     161             :     !> \param[out]      npart   :   The number of substrings resulting from splitting the string (**optional**).
     162             :     !>
     163             :     !> \return
     164             :     !> `Parts` : An allocatable array of type [CharVec_type](@ref jaggedarray_mod::charvec_type)
     165             :     !> containing the split parts of the input string.
     166             :     !>
     167             :     !> \remark
     168             :     !> When `delim = ""`, this routine returns a jagged array of strings, each element of which is one
     169             :     !> character of the input string.
     170             :     !>
     171             :     !> \remark
     172             :     !> This procedure is a static method of the class [String_type](@ref string_type).
     173             :     !>
     174             :     !> \remark
     175             :     !> This procedure should be preferred over the the legacy implementation [splitStr()](@ref splitstr)
     176             :     !> that is kept only for legacy support. This routine is significantly faster than the legacy implementation
     177             :     !> and its semantic behavior is identical to the Python3's `split()` string method, except when `delim` is empty.
     178             :     !>
     179             :     !> \author
     180             :     ! Amir Shahmoradi, Friday Dec 4, 2020, 11:40 PM, Dallas, TX
     181      295140 :     function split(string,delim,npart) result(Parts)
     182             : #if INTEL_COMPILER_ENABLED && defined DLL_ENABLED && (OS_IS_WINDOWS || defined OS_IS_DARWIN)
     183             :         !DEC$ ATTRIBUTES DLLEXPORT :: split
     184             : #endif
     185             :         implicit none
     186             :         character(len=*)    , intent(in)            :: string, delim
     187             :         integer(IK)         , intent(out), optional :: npart
     188             :         type(CharVec_type)  , allocatable           :: Parts(:)
     189             :         integer(IK)         , allocatable           :: PartEnd(:)
     190             :         integer(IK)         , allocatable           :: PartBegin(:)
     191             :         integer(IK)                                 :: dlmlenMinusOne
     192             :         integer(IK)                                 :: strlen, dlmlen, npartMax, ipart, ibeg, iend, i
     193             :         logical                                     :: npartIsPresent
     194             : 
     195      295140 :         dlmlen = len(delim)
     196      295140 :         strlen = len(string)
     197      295140 :         npartIsPresent = present(npart)
     198             : 
     199             :         ! if dlm is empty, return the whole string split character by character
     200             : 
     201      295140 :         if (dlmlen==0_IK) then
     202          30 :             allocate(Parts(strlen))
     203          30 :             do ipart = 1, strlen
     204          30 :                 Parts(ipart)%record = string(ipart:ipart)
     205             :             end do
     206           3 :             if (npartIsPresent) npart = strlen
     207           3 :             return
     208             :         end if
     209             : 
     210      295137 :         npartMax = 1_IK + strlen / dlmlen ! There can be at most strlen + 1 splits
     211      295137 :         allocate(PartBegin(npartMax), PartEnd(npartMax)) ! This will contain the beginning and the ends of the splits.
     212      295137 :         dlmlenMinusOne = dlmlen - 1_IK
     213             : 
     214      295137 :         ibeg = 0_IK
     215      295137 :         ipart = 1_IK
     216      295137 :         PartBegin(ipart) = 1_IK
     217    36055700 :         loopParseString: do
     218             : 
     219    36350900 :             ibeg = ibeg + 1_IK
     220    36350900 :             iend = ibeg + dlmlenMinusOne
     221             : 
     222    36350900 :             if (strlen<iend) then ! the remaining part of the string is shorter than the delim
     223      295137 :                 PartEnd(ipart) = strlen
     224      295137 :                 exit loopParseString
     225    36055700 :             elseif ( string(ibeg:iend) == delim ) then
     226      842607 :                 PartEnd(ipart) = ibeg - 1_IK
     227      842607 :                 ipart = ipart + 1_IK
     228      842607 :                 PartBegin(ipart) = iend + 1_IK
     229      842607 :                 ibeg = iend
     230             :             end if
     231             : 
     232             :         end do loopParseString
     233             : 
     234     1432880 :         allocate(Parts(ipart))
     235     1432880 :         do i = 1, ipart
     236     1432880 :             Parts(i)%record = string(PartBegin(i):PartEnd(i))
     237             :         end do
     238      295137 :         if (present(npart)) npart = ipart
     239             : 
     240      295137 :         deallocate(PartBegin, PartEnd)
     241             : 
     242      295140 :     end function split
     243             : 
     244             : !%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
     245             : 
     246             :     !> \brief
     247             :     !> Split the input string string with the input `substitute` in the input `string` and return the result.
     248             :     !>
     249             :     !> \param[in]       string      :   The input string.
     250             :     !> \param[in]       delimiter   :   The delimiter to be used to split the input string.
     251             :     !> \param[out]      nPart       :   The number of substrings resulting from splitting the string (**optional**).
     252             :     !>
     253             :     !> \return
     254             :     !> `Parts` : An allocatable array of type [CharVec_type](@ref jaggedarray_mod::charvec_type)
     255             :     !> containing the split parts of the input string.
     256             :     !>
     257             :     !> \remark
     258             :     !> This procedure is a static method of the class [String_type](@ref string_type).
     259             :     !>
     260             :     !> \warning
     261             :     !> This algorithm is only kept for archival purposes and should not be used in new development, unless the
     262             :     !> implications and the behavior of this algorithm are fully understood. Use instead [split()](@ref split).
     263             :     !>
     264             :     !> \warning
     265             :     !> The semantic behavior of this algorithm is different from [split()](@ref split).
     266             :     !> Furthermore, this algorithm is slower than the alternative implementation in [split()](@ref split).
     267             :     !>
     268             :     !> \author
     269             :     ! Amir Shahmoradi, Sep 1, 2017, 12:00 AM, ICES, UT Austin
     270          15 :     function splitStr(string,delimiter,nPart) result(Parts)
     271             : #if INTEL_COMPILER_ENABLED && defined DLL_ENABLED && (OS_IS_WINDOWS || defined OS_IS_DARWIN)
     272             :         !DEC$ ATTRIBUTES DLLEXPORT :: splitStr
     273             : #endif
     274             : 
     275             :         implicit none
     276             :         character(len=*)    , intent(in)            :: string, delimiter
     277             :         integer(IK)         , intent(out), optional :: nPart
     278          15 :         character(len=:)    , allocatable           :: dummyStr
     279             :         type(CharVec_type)  , allocatable           :: Parts(:)
     280             :         integer(IK)                                 :: maxNumSplit
     281             :         integer(IK)                                 :: stringLen, delimLen, splitCounter, currentPos
     282             : 
     283          15 :         dummyStr  = string
     284          15 :         delimLen  = len(delimiter)
     285          15 :         stringLen = len(dummyStr)
     286             : 
     287          15 :         if (delimLen==0) then
     288           6 :             allocate(Parts(1))
     289           3 :             Parts(1)%record = string
     290           3 :             if (present(nPart)) nPart = 1_IK
     291           3 :             return
     292             :         end if
     293             : 
     294          12 :         maxNumSplit = 1 + stringLen / delimLen
     295          63 :         allocate(Parts(maxNumSplit))
     296          12 :         splitCounter = 1
     297          21 :         loopParseString: do
     298          33 :             if (stringLen<delimLen) then
     299           3 :                 Parts(splitCounter)%record = dummyStr
     300           3 :                 exit loopParseString
     301          30 :             elseif (stringLen==delimLen) then
     302             :                 ! Note that in Fortran: 'amir '=='amir' = .true.
     303             :                 ! https://software.intel.com/en-us/forums/intel-visual-fortran-compiler-for-windows/topic/275823)
     304           6 :                 if (dummyStr==delimiter) then
     305           6 :                     Parts(splitCounter)%record = ""
     306             :                 else
     307           0 :                     Parts(splitCounter)%record = dummyStr
     308             :                 end if
     309           6 :                 exit loopParseString
     310          24 :             elseif (dummyStr(1:delimLen)==delimiter) then
     311          15 :                 dummyStr = dummyStr(delimLen+1:stringLen)
     312          15 :                 stringLen = len(dummyStr)
     313          15 :                 cycle loopParseString
     314             :             else
     315           9 :                 currentPos = 2
     316          24 :                 loopSearchString: do
     317          33 :                     if (dummyStr(currentPos:currentPos+delimLen-1)==delimiter) then
     318           6 :                         Parts(splitCounter)%record = dummyStr(1:currentPos-1)
     319           6 :                         if (currentPos+delimLen>stringLen) then
     320           0 :                             exit loopParseString
     321             :                         else
     322           6 :                             splitCounter = splitCounter + 1
     323           6 :                             dummyStr = dummyStr(currentPos+delimLen:stringLen)
     324           6 :                             stringLen = len(dummyStr)
     325           6 :                             cycle loopParseString
     326             :                         end if
     327             :                     else
     328          27 :                         currentPos = currentPos + 1
     329          27 :                         if (stringLen<currentPos+delimLen-1) then
     330           3 :                             Parts(splitCounter)%record = dummyStr
     331           3 :                             exit loopParseString
     332             :                         end if
     333          24 :                         cycle loopSearchString
     334             :                     end if
     335             :                 end do loopSearchString
     336             :             end if
     337             :         end do loopParseString
     338         141 :         Parts = Parts(1:splitCounter)
     339          12 :         if (present(nPart)) nPart = splitCounter
     340             : 
     341      295155 :     end function splitStr
     342             : 
     343             : !%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
     344             : 
     345             :     !> \brief
     346             :     !> Return `.true.` if the input single character is a digit: `["0","1","2","3","4","5","6","7","8","9"]`.
     347             :     !>
     348             :     !> \param[in]       singleChar  :   The input single character.
     349             :     !>
     350             :     !> \return
     351             :     !> `stringIsDigit` : A logical value indicating whether the input character is a digit or not.
     352             :     !>
     353             :     !> \remark
     354             :     !> This procedure is a static method of the class [String_type](@ref string_type).
     355             :     !>
     356             :     !> \author
     357             :     ! Amir Shahmoradi, Sep 1, 2017, 12:00 AM, ICES, UT Austin
     358        1212 :     pure function isDigit(singleChar) result(stringIsDigit)
     359             : #if INTEL_COMPILER_ENABLED && defined DLL_ENABLED && (OS_IS_WINDOWS || defined OS_IS_DARWIN)
     360             :         !DEC$ ATTRIBUTES DLLEXPORT :: isDigit
     361             : #endif
     362             :         character(1), intent(in)    :: singleChar
     363             :         logical                     :: stringIsDigit
     364             :         character(*), parameter     :: Digit(10) = ["0","1","2","3","4","5","6","7","8","9"]
     365             :         integer                     :: j
     366        1212 :         stringIsDigit = .false.
     367       13056 :         loopOverDigit: do j = 1,10
     368       13056 :             if (singleChar==Digit(j)) then
     369          42 :                 stringIsDigit = .true.
     370          42 :                 exit loopOverDigit
     371             :             end if
     372             :         end do loopOverDigit
     373        1227 :     end function isDigit
     374             : 
     375             : !%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
     376             : 
     377             :     !> \brief
     378             :     !> Return `.true.` if the input string is an integer containing only: `["0","1","2","3","4","5","6","7","8","9"]`.
     379             :     !>
     380             :     !> \param[in]       string  :   The input string.
     381             :     !>
     382             :     !> \return
     383             :     !> `stringIsInteger` : A logical value indicating whether the input string is an integer.
     384             :     !>
     385             :     !> \remark
     386             :     !> This procedure is a static method of the class [String_type](@ref string_type).
     387             :     !>
     388             :     !> \author
     389             :     ! Amir Shahmoradi, Sep 1, 2017, 12:00 AM, ICES, UT Austin
     390        2601 :     pure function isInteger(string) result(stringIsInteger)
     391             : #if INTEL_COMPILER_ENABLED && defined DLL_ENABLED && (OS_IS_WINDOWS || defined OS_IS_DARWIN)
     392             :         !DEC$ ATTRIBUTES DLLEXPORT :: isInteger
     393             : #endif
     394             :         character(*), intent(in)    :: string
     395             :         logical                     :: stringIsInteger
     396             :         character(*), parameter     :: Digit(10) = ["0","1","2","3","4","5","6","7","8","9"]
     397             :         integer                     :: i, j
     398        5256 :         do i = 1,len(string)
     399        2721 :             stringIsInteger = .false.
     400        9705 :             loopOverDigit: do j = 1,10
     401        9705 :                 if (string(i:i)==Digit(j)) then
     402        2655 :                     stringIsInteger = .true.
     403        2655 :                     exit loopOverDigit
     404             :                 end if
     405             :             end do loopOverDigit
     406        5256 :             if (.not.stringIsInteger) return
     407             :         end do
     408        3813 :     end function isInteger
     409             : 
     410             : !%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
     411             : 
     412             :     !> \brief
     413             :     !> Return the lowercase of the input string.
     414             :     !>
     415             :     !> \param[in]       string  :   The input string.
     416             :     !>
     417             :     !> \return
     418             :     !> `output` : The lowercase string.
     419             :     !>
     420             :     !> \remark
     421             :     !> This procedure is a static method of the class [String_type](@ref string_type).
     422             :     !>
     423             :     !> \author
     424             :     ! Amir Shahmoradi, Sep 1, 2017, 12:00 AM, ICES, UT Austin
     425       20810 :     pure function getLowerCase(string) result(output)
     426             : #if INTEL_COMPILER_ENABLED && defined DLL_ENABLED && (OS_IS_WINDOWS || defined OS_IS_DARWIN)
     427             :         !DEC$ ATTRIBUTES DLLEXPORT :: getLowerCase
     428             : #endif
     429             :         character(*), intent(in) :: string
     430             :         integer(IK), parameter   :: DUC = ichar('A') - ichar('a')
     431             :         character(len(string))   :: output
     432             :         character                :: ch
     433             :         integer(IK)              :: i
     434      277116 :         do i = 1,len(string)
     435      256306 :             ch = string(i:i)
     436      256306 :             if (ch>='A' .and. ch<='Z') ch = char(ichar(ch)-DUC)
     437      277116 :             output(i:i) = ch
     438             :         end do
     439        2601 :     end function getLowerCase
     440             : 
     441             : !%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
     442             : 
     443             :     !> \brief
     444             :     !> Return the uppercase of the input string.
     445             :     !>
     446             :     !> \param[in]       string  :   The input string.
     447             :     !>
     448             :     !> \return
     449             :     !> `output` : The uppercase string.
     450             :     !>
     451             :     !> \remark
     452             :     !> This procedure is a static method of the class [String_type](@ref string_type).
     453             :     !>
     454             :     !> \author
     455             :     ! Amir Shahmoradi, Sep 1, 2017, 12:00 AM, ICES, UT Austin
     456           6 :     pure function getUpperCase(string) result(output)
     457             : #if INTEL_COMPILER_ENABLED && defined DLL_ENABLED && (OS_IS_WINDOWS || defined OS_IS_DARWIN)
     458             :         !DEC$ ATTRIBUTES DLLEXPORT :: getUpperCase
     459             : #endif
     460             :         character(*), intent(in) :: string
     461             :         integer(IK), parameter   :: DUC = ichar('A') - ichar('a')
     462             :         character(len(string))   :: output
     463             :         character                :: ch
     464             :         integer(IK)              :: i
     465          63 :         do i = 1,len(string)
     466          57 :             ch = string(i:i)
     467          57 :             if (ch>='a' .and. ch<='z') ch = char(ichar(ch)+DUC)
     468          63 :             output(i:i) = ch
     469             :         end do
     470       20810 :     end function getUpperCase
     471             : 
     472             : !%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
     473             : 
     474             : !    ! ATTN: legacy code, do not use. The substitute functions are >1 order of magnitude faster. Changes a string to lower case
     475             : !    pure function getLowerCaseOld(string)
     476             : !#if INTEL_COMPILER_ENABLED && defined DLL_ENABLED && (OS_IS_WINDOWS || defined OS_IS_DARWIN)
     477             : !        !DEC$ ATTRIBUTES DLLEXPORT :: getLowerCaseOld
     478             : !#endif
     479             : !        implicit None
     480             : !        character(*), intent(in) :: string
     481             : !        character(len(string))   :: getLowerCaseOld
     482             : !        character(26), parameter :: lowerCase = 'abcdefghijklmnopqrstuvwxyz', upperCase = 'ABCDEFGHIJKLMNOPQRSTUVWXYZ'
     483             : !        integer(IK)              :: ic, i
     484             : !        getLowerCaseOld = string
     485             : !        do i = 1, len(string)
     486             : !            ic = INDEX(upperCase, string(i:i))
     487             : !            if (ic > 0) getLowerCaseOld(i:i) = lowerCase(ic:ic)
     488             : !        end do
     489             : !    end function getLowerCaseOld
     490             : !
     491             : !!%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
     492             : !
     493             : !    ! ATTN: legacy code, do not use. The substitute functions are >1 order of magnitude faster. Changes a string to upper case
     494             : !    pure function getUpperCaseOld(string)
     495             : !#if INTEL_COMPILER_ENABLED && defined DLL_ENABLED && (OS_IS_WINDOWS || defined OS_IS_DARWIN)
     496             : !        !DEC$ ATTRIBUTES DLLEXPORT :: getUpperCaseOld
     497             : !#endif
     498             : !        implicit None
     499             : !        character(*), intent(in) :: string
     500             : !        character(len(string))   :: getUpperCaseOld
     501             : !        character(26), parameter :: lowerCase = 'abcdefghijklmnopqrstuvwxyz', upperCase = 'ABCDEFGHIJKLMNOPQRSTUVWXYZ'
     502             : !        integer(IK)              :: ic, i
     503             : !        getUpperCaseOld = string
     504             : !        do i = 1, len(string)
     505             : !            ic = INDEX(lowerCase, string(i:i))
     506             : !            if (ic > 0) getUpperCaseOld(i:i) = upperCase(ic:ic)
     507             : !        end do
     508             : !    end function getUpperCaseOld
     509             : 
     510             : !%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
     511             : 
     512             :     !> \brief
     513             :     !> Convert the input logical value to string and return the result.
     514             :     !>
     515             :     !> \param[in]   logicalIn   :   The input logical value.
     516             :     !>
     517             :     !> \return
     518             :     !> `log2str` : The logical value in string format. Depending on the logical value, it can be either `"TRUE"` or `"FALSE"`.
     519             :     !>
     520             :     !> \remark
     521             :     !> This procedure is a static method of the class [String_type](@ref string_type).
     522             :     !>
     523             :     !> \author
     524             :     ! Amir Shahmoradi, Sep 1, 2017, 12:00 AM, ICES, UT Austin
     525        5241 :     pure function log2str(logicalIn)
     526             : #if INTEL_COMPILER_ENABLED && defined DLL_ENABLED && (OS_IS_WINDOWS || defined OS_IS_DARWIN)
     527             :         !DEC$ ATTRIBUTES DLLEXPORT :: log2str
     528             : #endif
     529             :         implicit none
     530             :         logical     , intent(in)           :: logicalIn
     531             :         character(:), allocatable          :: log2str
     532        5241 :         allocate(character(NUM2STR_MAXLEN) :: log2str)
     533        5241 :         if (logicalIn) then
     534        1050 :             log2str = "TRUE"
     535             :         else
     536        4191 :             log2str = "FALSE"
     537             :         end if
     538           6 :     end function log2str
     539             : 
     540             : !%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
     541             : 
     542             :     !> \brief
     543             :     !> Convert the input 32-bit integer value to string, with the requested format, if provided.
     544             :     !>
     545             :     !> \param[in]   integerIn   :   The input integer value.
     546             :     !> \param[in]   formatIn    :   The Fortran IO format to be used when writing the integer value to the string (**optional**).
     547             :     !> \param[in]   minLen      :   The minimum length of the output string, adjusted to the left.
     548             :     !>
     549             :     !> \return
     550             :     !> `int322str` : The integer value as a string.
     551             :     !>
     552             :     !> \remark
     553             :     !> This procedure is a static method of the class [String_type](@ref string_type).
     554             :     !>
     555             :     !> \todo
     556             :     !> Currently, `minLen` must be smaller than `NUM2STR_MAXLEN`, for the code to function properly.
     557             :     !> This has to be improved, similar to the `real2str` procedures.
     558             :     !>
     559             :     !> \author
     560             :     ! Amir Shahmoradi, Sep 1, 2017, 12:00 AM, ICES, UT Austin
     561       37412 :     pure function int322str(integerIn,formatIn,minLen)
     562             : #if INTEL_COMPILER_ENABLED && defined DLL_ENABLED && (OS_IS_WINDOWS || defined OS_IS_DARWIN)
     563             :         !DEC$ ATTRIBUTES DLLEXPORT :: int322str
     564             : #endif
     565             :         use, intrinsic :: iso_fortran_env, only: int32
     566             :         implicit none
     567             :         integer(int32) , intent(in)           :: integerIn
     568             :         character(*)   , intent(in), optional :: formatIn
     569             :         integer(IK)    , intent(in), optional :: minLen
     570             :         character(:)   , allocatable          :: int322str
     571       37412 :         allocate(character(NUM2STR_MAXLEN) :: int322str)
     572       37412 :         if (present(formatIn)) then
     573         324 :             write(int322str,formatIn) integerIn
     574             :         else
     575       37088 :             write(int322str,"(I0)") integerIn
     576             :         end if
     577       37412 :         if (present(minLen)) then
     578        2634 :             int322str = adjustl(int322str)
     579        2634 :             int322str = int322str(1:minLen)
     580             :         else
     581       34778 :             int322str = trim(adjustl(int322str))
     582             :         end if
     583        5241 :     end function int322str
     584             : 
     585             : !%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
     586             : 
     587             :     !> \brief
     588             :     !> Convert the input 64-bit integer value to string, with the requested format, if provided.
     589             :     !>
     590             :     !> \param[in]   integerIn   :   The input integer value.
     591             :     !> \param[in]   formatIn    :   The Fortran IO format to be used when writing the integer value to the string (**optional**).
     592             :     !> \param[in]   minLen      :   The minimum length of the output string, adjusted to the left.
     593             :     !>
     594             :     !> \return
     595             :     !> `int322str` : The integer value as a string.
     596             :     !>
     597             :     !> \remark
     598             :     !> This procedure is a static method of the class [String_type](@ref string_type).
     599             :     !>
     600             :     !> \todo
     601             :     !> Currently, `minLen` must be smaller than `NUM2STR_MAXLEN`, for the code to function properly.
     602             :     !> This has to be improved, similar to the `real2str` procedures.
     603             :     !>
     604             :     !> \author
     605             :     ! Amir Shahmoradi, Sep 1, 2017, 12:00 AM, ICES, UT Austin
     606          12 :     pure function int642str(integerIn,formatIn,minLen)
     607             : #if INTEL_COMPILER_ENABLED && defined DLL_ENABLED && (OS_IS_WINDOWS || defined OS_IS_DARWIN)
     608             :         !DEC$ ATTRIBUTES DLLEXPORT :: int642str
     609             : #endif
     610             :         use, intrinsic :: iso_fortran_env, only: int64
     611             :         implicit none
     612             :         integer(int64), intent(in)           :: integerIn
     613             :         character(*)  , intent(in), optional :: formatIn
     614             :         integer(IK)   , intent(in), optional :: minLen
     615             :         character(:)  , allocatable          :: int642str
     616          12 :         allocate(character(NUM2STR_MAXLEN) :: int642str)
     617          12 :         if (present(formatIn)) then
     618           3 :             write(int642str,formatIn) integerIn
     619             :         else
     620           9 :             write(int642str,*) integerIn
     621             :         end if
     622          12 :         if (present(minLen)) then
     623           3 :             int642str = adjustl(int642str)
     624           3 :             int642str = int642str(1:minLen)
     625             :         else
     626           9 :             int642str = trim(adjustl(int642str))
     627             :         end if
     628       37412 :     end function int642str
     629             : 
     630             : !%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
     631             : 
     632             :     !> \brief
     633             :     !> Convert the input 32-bit real value to string, with the requested format, if provided.
     634             :     !>
     635             :     !> \param[in]   realIn      :   The input real value.
     636             :     !> \param[in]   formatIn    :   The Fortran IO format to be used when writing the real value to the string (**optional**).
     637             :     !> \param[in]   minLen      :   The minimum length of the output string, adjusted to the left.
     638             :     !>
     639             :     !> \return
     640             :     !> `int322str` : The real value as a string.
     641             :     !>
     642             :     !> \remark
     643             :     !> This procedure is a static method of the class [String_type](@ref string_type).
     644             :     !>
     645             :     !> \author
     646             :     ! Amir Shahmoradi, Sep 1, 2017, 12:00 AM, ICES, UT Austin
     647          15 :     pure function real322str(realIn,formatIn,minLen)
     648             : #if INTEL_COMPILER_ENABLED && defined DLL_ENABLED && (OS_IS_WINDOWS || defined OS_IS_DARWIN)
     649             :         !DEC$ ATTRIBUTES DLLEXPORT :: real322str
     650             : #endif
     651             :         use, intrinsic :: iso_fortran_env, only: real32
     652             :         implicit none
     653             :         real(real32), intent(in)            :: realIn
     654             :         character(*), intent(in), optional  :: formatIn
     655             :         integer(IK) , intent(in), optional  :: minLen
     656          15 :         character(:), allocatable           :: dumstr
     657             :         character(:), allocatable           :: real322str
     658             :         integer(IK)                         :: len_real322str
     659          15 :         allocate(character(NUM2STR_MAXLEN)  :: real322str)
     660          15 :         if (present(formatIn)) then
     661          12 :             write(real322str,formatIn) realIn
     662             :         else
     663           3 :             write(real322str,*) realIn
     664             :         end if
     665          15 :         if (present(minLen)) then
     666           9 :             real322str = adjustl(real322str)
     667           9 :             len_real322str = len(real322str)
     668           9 :             if (minLen>len_real322str) then
     669           3 :                 allocate(character(minLen) :: dumstr)
     670           3 :                 dumstr(1:len_real322str) = real322str
     671           3 :                 call move_alloc(from = dumstr, to = real322str)
     672             :             else
     673           6 :                 real322str = real322str(1:minLen)
     674             :             end if
     675             :         else
     676           6 :             real322str = trim(adjustl(real322str))
     677             :         end if
     678          27 :     end function real322str
     679             : 
     680             : !%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
     681             : 
     682             :     !> \brief
     683             :     !> Convert the input 64-bit real value to string, with the requested format, if provided.
     684             :     !>
     685             :     !> \param[in]   realIn      :   The input real value.
     686             :     !> \param[in]   formatIn    :   The Fortran IO format to be used when writing the real value to the string (**optional**).
     687             :     !> \param[in]   minLen      :   The minimum length of the output string, adjusted to the left.
     688             :     !>
     689             :     !> \return
     690             :     !> `int322str` : The real value as a string.
     691             :     !>
     692             :     !> \remark
     693             :     !> This procedure is a static method of the class [String_type](@ref string_type).
     694             :     !>
     695             :     !> \author
     696             :     ! Amir Shahmoradi, Sep 1, 2017, 12:00 AM, ICES, UT Austin
     697        9853 :     pure function real642str(realIn,formatIn,minLen)
     698             : #if INTEL_COMPILER_ENABLED && defined DLL_ENABLED && (OS_IS_WINDOWS || defined OS_IS_DARWIN)
     699             :         !DEC$ ATTRIBUTES DLLEXPORT :: real642str
     700             : #endif
     701             :         use, intrinsic :: iso_fortran_env, only: real64
     702             :         implicit none
     703             :         real(real64), intent(in)            :: realIn
     704             :         character(*), intent(in), optional  :: formatIn
     705             :         integer(IK) , intent(in), optional  :: minLen
     706        9853 :         character(:), allocatable           :: dumstr
     707             :         character(:), allocatable           :: real642str
     708             :         integer(IK)                         :: len_real642str
     709        9853 :         allocate(character(NUM2STR_MAXLEN)  :: real642str)
     710        9853 :         if (present(formatIn)) then
     711        4343 :             write(real642str,formatIn) realIn
     712             :         else
     713        5510 :             write(real642str,*) realIn
     714             :         end if
     715        9853 :         if (present(minLen)) then
     716        2640 :             real642str = adjustl(real642str)
     717        2640 :             len_real642str = len(real642str)
     718        2640 :             if (minLen>len_real642str) then
     719           3 :                 allocate(character(minLen) :: dumstr)
     720           3 :                 dumstr(1:len_real642str) = real642str
     721           3 :                 call move_alloc(from = dumstr, to = real642str)
     722             :             else
     723        2637 :                 real642str = real642str(1:minLen)
     724             :             end if
     725             :         else
     726        7213 :             real642str = trim(adjustl(real642str))
     727             :         end if
     728        9868 :     end function real642str
     729             : 
     730             : !%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
     731             : 
     732             :     !> \brief
     733             :     !> Convert an input vector of  64-bit real values to string, with the requested format, if provided.
     734             :     !>
     735             :     !> \param[in]   RealIn      :   The input vector of real values.
     736             :     !> \param[in]   formatIn    :   The Fortran IO format to be used when writing the real value to the string (**optional**).
     737             :     !> \param[in]   minLen      :   The minimum length of the output string, adjusted to the left.
     738             :     !>
     739             :     !> \return
     740             :     !> `real642str_1D` : The output vector of strings each representing one real value in the input vector.
     741             :     !>
     742             :     !> \remark
     743             :     !> This procedure is a static method of the class [String_type](@ref string_type).
     744             :     !>
     745             :     !> \author
     746             :     ! Amir Shahmoradi, Sep 1, 2017, 12:00 AM, ICES, UT Austin
     747         132 :     pure function real642str_1D(RealIn,formatIn,minLen)
     748             : #if INTEL_COMPILER_ENABLED && defined DLL_ENABLED && (OS_IS_WINDOWS || defined OS_IS_DARWIN)
     749             :         !DEC$ ATTRIBUTES DLLEXPORT :: real642str_1D
     750             : #endif
     751             :         use, intrinsic :: iso_fortran_env, only: real64
     752             :         implicit none
     753             :         real(real64), intent(in)            :: RealIn(:)
     754             :         character(*), intent(in), optional  :: formatIn
     755             :         integer(IK) , intent(in), optional  :: minLen
     756          66 :         character(:), allocatable           :: dumstr
     757             :         character(:), allocatable           :: real642str_1D
     758             :         integer(IK)                         :: len_real642str_1D
     759          66 :         allocate(character(NUM2STR_MAXLEN*size(RealIn)) :: real642str_1D)
     760          66 :         if (present(formatIn)) then
     761           9 :             write(real642str_1D,formatIn) RealIn
     762             :         else
     763          57 :             write(real642str_1D,"(*(g0.15,:,','))") RealIn
     764             :         end if
     765          66 :         if (present(minLen)) then
     766           6 :             real642str_1D = adjustl(real642str_1D)
     767           6 :             len_real642str_1D = len(real642str_1D)
     768           6 :             if (minLen>len_real642str_1D) then
     769           3 :                 allocate(character(minLen) :: dumstr)
     770           3 :                 dumstr(1:len_real642str_1D) = real642str_1D
     771           3 :                 call move_alloc(from = dumstr, to = real642str_1D)
     772             :             else
     773           3 :                 real642str_1D = real642str_1D(1:minLen)
     774             :             end if
     775             :         else
     776          60 :             real642str_1D = trim(adjustl(real642str_1D))
     777             :         end if
     778        9919 :     end function real642str_1D
     779             : 
     780             : !%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
     781             : 
     782             :     !> \brief
     783             :     !> Convert an input 2D matrix of  64-bit real values to string, with the requested format, if provided.
     784             :     !>
     785             :     !> \param[in]   RealIn      :   The input 2D matrix of real values.
     786             :     !> \param[in]   formatIn    :   The Fortran IO format to be used when writing the real value to the string (**optional**).
     787             :     !> \param[in]   minLen      :   The minimum length of the output string, adjusted to the left.
     788             :     !>
     789             :     !> \return
     790             :     !> `real642str_2D` : The output 2D array of strings each representing one real value in the input 2D matrix.
     791             :     !>
     792             :     !> \remark
     793             :     !> This procedure is a static method of the class [String_type](@ref string_type).
     794             :     !>
     795             :     !> \author
     796             :     ! Amir Shahmoradi, Sep 1, 2017, 12:00 AM, ICES, UT Austin
     797         108 :     pure function real642str_2D(RealIn,formatIn,minLen)
     798             : #if INTEL_COMPILER_ENABLED && defined DLL_ENABLED && (OS_IS_WINDOWS || defined OS_IS_DARWIN)
     799             :         !DEC$ ATTRIBUTES DLLEXPORT :: real642str_2D
     800             : #endif
     801             :         use, intrinsic :: iso_fortran_env, only: real64
     802             :         implicit none
     803             :         real(real64), intent(in)            :: RealIn(:,:)
     804             :         character(*), intent(in), optional  :: formatIn
     805             :         integer(IK) , intent(in), optional  :: minLen
     806             :         character(:), allocatable           :: real642str_2D
     807          54 :         character(:), allocatable           :: dumstr
     808             :         integer(IK)                         :: len_real642str_2D
     809          54 :         allocate(character(NUM2STR_MAXLEN*size(RealIn,1)*size(RealIn,2)) :: real642str_2D)
     810          54 :         if (present(formatIn)) then
     811           9 :             write(real642str_2D,formatIn) RealIn
     812             :         else
     813          45 :             write(real642str_2D,"(*(g0.15,:,','))") RealIn
     814             :         end if
     815          54 :         if (present(minLen)) then
     816           6 :             real642str_2D = adjustl(real642str_2D)
     817           6 :             len_real642str_2D = len(real642str_2D)
     818           6 :             if (minLen>len_real642str_2D) then
     819           3 :                 allocate(character(minLen) :: dumstr)
     820           3 :                 dumstr(1:len_real642str_2D) = real642str_2D
     821           3 :                 call move_alloc(from = dumstr, to = real642str_2D)
     822             :             else
     823           3 :                 real642str_2D = real642str_2D(1:minLen)
     824             :             end if
     825             :         else
     826          48 :             real642str_2D = trim(adjustl(real642str_2D))
     827             :         end if
     828         120 :     end function real642str_2D
     829             : 
     830             : !%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
     831             : 
     832             :     !> \brief
     833             :     !> Convert an input string to integer.
     834             :     !>
     835             :     !> \param[in]   str         :   The input string.
     836             :     !> \param[in]   iostat      :   The Fortran IO status integer of default kind. Refer to the Fortran `read/write` functions
     837             :     !>                              for the meaning of different output values for `iostat`.
     838             :     !>
     839             :     !> \return
     840             :     !> `str2int` : The inferred integer from the input string.
     841             :     !>
     842             :     !> \remark
     843             :     !> This procedure is a static method of the class [String_type](@ref string_type).
     844             :     !>
     845             :     !> \author
     846             :     ! Amir Shahmoradi, Sep 1, 2017, 12:00 AM, ICES, UT Austin
     847           6 :     function str2int(str,iostat)
     848             : #if INTEL_COMPILER_ENABLED && defined DLL_ENABLED && (OS_IS_WINDOWS || defined OS_IS_DARWIN)
     849             :         !DEC$ ATTRIBUTES DLLEXPORT :: str2int
     850             : #endif
     851          54 :         use Constants_mod, only: IK
     852             :         implicit none
     853             :         character(*), intent(in)        :: str
     854             :         integer, intent(out), optional  :: iostat
     855             :         integer(IK)                     :: str2int
     856           6 :         if (present(iostat)) then
     857           3 :             iostat = 0
     858           3 :             read(str,*,iostat=iostat) str2int
     859             :         else
     860           3 :             read(str,*) str2int
     861             :         endif
     862           6 :     end function str2int
     863             : 
     864             : !%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
     865             : 
     866             :     !> \brief
     867             :     !> Convert an input string to 32-bit integer.
     868             :     !>
     869             :     !> \param[in]   str         :   The input string.
     870             :     !> \param[in]   iostat      :   The Fortran IO status integer of default kind. Refer to the Fortran `read/write` functions
     871             :     !>                              for the meaning of different output values for `iostat`.
     872             :     !>
     873             :     !> \return
     874             :     !> `str2int` : The inferred 32-bit integer from the input string.
     875             :     !>
     876             :     !> \remark
     877             :     !> This procedure is a static method of the class [String_type](@ref string_type).
     878             :     !>
     879             :     !> \author
     880             :     ! Amir Shahmoradi, Sep 1, 2017, 12:00 AM, ICES, UT Austin
     881           6 :     function str2int32(str,iostat)
     882             : #if INTEL_COMPILER_ENABLED && defined DLL_ENABLED && (OS_IS_WINDOWS || defined OS_IS_DARWIN)
     883             :         !DEC$ ATTRIBUTES DLLEXPORT :: str2int32
     884             : #endif
     885             :         use, intrinsic :: iso_fortran_env, only: int32
     886             :         implicit none
     887             :         character(*), intent(in)        :: str
     888             :         integer, intent(out), optional  :: iostat
     889             :         integer(int32)                  :: str2int32
     890           6 :         if (present(iostat)) then
     891           3 :             iostat = 0
     892           3 :             read(str,*,iostat=iostat) str2int32
     893             :         else
     894           3 :             read(str,*) str2int32
     895             :         endif
     896          12 :     end function str2int32
     897             : 
     898             : !%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
     899             : 
     900             :     !> \brief
     901             :     !> Convert an input string to 64-bit integer.
     902             :     !>
     903             :     !> \param[in]   str         :   The input string.
     904             :     !> \param[in]   iostat      :   The Fortran IO status integer of default kind. Refer to the Fortran `read/write` functions
     905             :     !>                              for the meaning of different output values for `iostat`.
     906             :     !>
     907             :     !> \return
     908             :     !> `str2int` : The inferred 64-bit integer from the input string.
     909             :     !>
     910             :     !> \remark
     911             :     !> This procedure is a static method of the class [String_type](@ref string_type).
     912             :     !>
     913             :     !> \author
     914             :     ! Amir Shahmoradi, Sep 1, 2017, 12:00 AM, ICES, UT Austin
     915           6 :     function str2int64(str,iostat)
     916             : #if INTEL_COMPILER_ENABLED && defined DLL_ENABLED && (OS_IS_WINDOWS || defined OS_IS_DARWIN)
     917             :         !DEC$ ATTRIBUTES DLLEXPORT :: str2int64
     918             : #endif
     919             :         use, intrinsic :: iso_fortran_env, only: int64
     920             :         implicit none
     921             :         character(*), intent(in)        :: str
     922             :         integer, intent(out), optional  :: iostat
     923             :         integer(int64)                  :: str2int64
     924           6 :         if (present(iostat)) then
     925           3 :             iostat = 0
     926           3 :             read(str,*,iostat=iostat) str2int64
     927             :         else
     928           3 :             read(str,*) str2int64
     929             :         endif
     930          12 :     end function str2int64
     931             : 
     932             : !%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
     933             : 
     934             :     !> \brief
     935             :     !> Convert an input string to real value.
     936             :     !>
     937             :     !> \param[in]   str         :   The input string.
     938             :     !> \param[in]   iostat      :   The Fortran IO status integer of default kind. Refer to the Fortran `read/write` functions
     939             :     !>                              for the meaning of different output values for `iostat`.
     940             :     !>
     941             :     !> \return
     942             :     !> `str2int` : The inferred real value from the input string.
     943             :     !>
     944             :     !> \remark
     945             :     !> This procedure is a static method of the class [String_type](@ref string_type).
     946             :     !>
     947             :     !> \author
     948             :     ! Amir Shahmoradi, Sep 1, 2017, 12:00 AM, ICES, UT Austin
     949           6 :     function str2real(str,iostat)
     950             : #if INTEL_COMPILER_ENABLED && defined DLL_ENABLED && (OS_IS_WINDOWS || defined OS_IS_DARWIN)
     951             :         !DEC$ ATTRIBUTES DLLEXPORT :: str2real
     952             : #endif
     953             :         use Constants_mod, only: RK ! LCOV_EXCL_LINE
     954             :         implicit none
     955             :         character(*), intent(in)        :: str
     956             :         integer, optional, intent(out)  :: iostat
     957             :         real(RK)                        :: str2real
     958           6 :         if (present(iostat)) then
     959           3 :             iostat = 0
     960           3 :             read(str,*,iostat=iostat) str2real
     961             :         else
     962           3 :             read(str,*) str2real
     963             :         endif
     964           6 :     end function str2real
     965             : 
     966             : !%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
     967             : 
     968             :     !> \brief
     969             :     !> Convert an input string to 32-bit real value.
     970             :     !>
     971             :     !> \param[in]   str         :   The input string.
     972             :     !> \param[in]   iostat      :   The Fortran IO status integer of default kind. Refer to the Fortran `read/write` functions
     973             :     !>                              for the meaning of different output values for `iostat`.
     974             :     !>
     975             :     !> \return
     976             :     !> `str2int` : The inferred 32-bit real value from the input string.
     977             :     !>
     978             :     !> \remark
     979             :     !> This procedure is a static method of the class [String_type](@ref string_type).
     980             :     !>
     981             :     !> \author
     982             :     ! Amir Shahmoradi, Sep 1, 2017, 12:00 AM, ICES, UT Austin
     983          18 :     function str2real32(str,iostat)
     984             : #if INTEL_COMPILER_ENABLED && defined DLL_ENABLED && (OS_IS_WINDOWS || defined OS_IS_DARWIN)
     985             :         !DEC$ ATTRIBUTES DLLEXPORT :: str2real32
     986             : #endif
     987             :         use, intrinsic :: iso_fortran_env, only: real32
     988             :         implicit none
     989             :         character(*), intent(in)        :: str
     990             :         integer, optional, intent(out)  :: iostat
     991             :         real(real32)                    :: str2real32
     992          18 :         if (present(iostat)) then
     993           3 :             iostat = 0
     994           3 :             read(str,*,iostat=iostat) str2real32
     995             :         else
     996          15 :             read(str,*) str2real32
     997             :         endif
     998          24 :     end function str2real32
     999             : 
    1000             : !%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
    1001             : 
    1002             :     !> \brief
    1003             :     !> Convert an input string to 64-bit real value.
    1004             :     !>
    1005             :     !> \param[in]   str         :   The input string.
    1006             :     !> \param[in]   iostat      :   The optional output Fortran IO status integer of default kind. Refer to the Fortran `read/write`
    1007             :     !>                              functions for the meaning of different output values for `iostat` (**optional**).
    1008             :     !>
    1009             :     !> \return
    1010             :     !> `str2int` : The inferred 64-bit real value from the input string.
    1011             :     !>
    1012             :     !> \remark
    1013             :     !> This procedure is a static method of the class [String_type](@ref string_type).
    1014             :     !>
    1015             :     !> \author
    1016             :     ! Amir Shahmoradi, Sep 1, 2017, 12:00 AM, ICES, UT Austin
    1017         108 :     function str2real64(str,iostat)
    1018             : #if INTEL_COMPILER_ENABLED && defined DLL_ENABLED && (OS_IS_WINDOWS || defined OS_IS_DARWIN)
    1019             :         !DEC$ ATTRIBUTES DLLEXPORT :: str2real64
    1020             : #endif
    1021             :         use, intrinsic :: iso_fortran_env, only: real64
    1022             :         implicit none
    1023             :         character(*), intent(in)        :: str
    1024             :         integer, optional, intent(out)  :: iostat
    1025             :         real(real64)                    :: str2real64
    1026         108 :         if (present(iostat)) then
    1027          93 :             iostat = 0
    1028          93 :             read(str,*,iostat=iostat) str2real64
    1029          93 :             if (iostat/=0) str2real64 = -huge(1._real64)
    1030             :         else
    1031          15 :             read(str,*) str2real64
    1032             :         endif
    1033         126 :     end function str2real64
    1034             : 
    1035             : !%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
    1036             : 
    1037             :     !> \brief
    1038             :     !> Pad the input `string` with the input `symbol` string for a length of `paddedLen` and return the resulting new string.
    1039             :     !> @param[in]   string      :   The input string to be padded.
    1040             :     !> @param[in]   symbol      :   The symbol to be used for padding.
    1041             :     !> @param[in]   paddedLen   :   The length of the resulting final string.
    1042             :     !>
    1043             :     !> \return
    1044             :     !> `paddedString` : The output string padded with `symbol`.
    1045             :     !>
    1046             :     !> \remark
    1047             :     !> Note that `symbol` can be a string of any length. However, if the full lengths of symbols do not fit
    1048             :     !> at the end of the padded output string, the symbol will be cut at the end of the output padded string.
    1049        2640 :     pure function padString(string, symbol, paddedLen) result(paddedString)
    1050             : #if INTEL_COMPILER_ENABLED && defined DLL_ENABLED && (OS_IS_WINDOWS || defined OS_IS_DARWIN)
    1051             :         !DEC$ ATTRIBUTES DLLEXPORT :: padString
    1052             : #endif
    1053         108 :         use Constants_mod, only: IK
    1054             :         implicit none
    1055             :         character(*), intent(in)            :: string
    1056             :         character(*), intent(in)            :: symbol
    1057             :         integer(IK) , intent(in)            :: paddedLen
    1058             :         character(paddedLen)                :: paddedString
    1059        2640 :         character(:), allocatable           :: pad
    1060             :         integer(IK)                         :: stringLen, symbolLen, symbolCount, diff ! LCOV_EXCL_LINE
    1061             :         stringLen = len(string) ! LCOV_EXCL_LINE
    1062        2640 :         if (stringLen>=paddedLen) then
    1063           6 :             paddedString = string
    1064           6 :             return
    1065             :         end if
    1066        2634 :         symbolLen = len(symbol)
    1067        2634 :         diff = paddedLen - stringLen
    1068        2634 :         symbolCount = diff / symbolLen + 1
    1069      117247 :         pad = repeat(symbol,symbolCount)
    1070        2634 :         paddedString = string // pad(1:diff)
    1071        2640 :     end function padString
    1072             : 
    1073             : !%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
    1074             : 
    1075             : end module String_mod ! LCOV_EXCL_LINE

ParaMonte: Plain Powerful Parallel Monte Carlo Library 
The Computational Data Science Lab
© Copyright 2012 - 2021