extension Function

private elemental function extension(self)

Arguments

Type IntentOptional AttributesName
class(string), intent(in) :: self

The string.

Return Value type(string)

Extension file name.

Description

Return the extension of a string containing a file name.


Variables

TypeVisibility AttributesNameInitial
integer, public :: pos

Character position.

character(kind=CK,len=:), public, allocatable:: temporary

Temporary storage, workaround for GNU bug.


Source Code

  elemental function basename(self, sep, extension, strip_last_extension)
  !---------------------------------------------------------------------------------------------------------------------------------
  !< Return the base file name of a string containing a file name.
  !<
  !< Optionally, the extension is also stripped if provided or the last one if required, e.g.
  !<
  !<### Example
  !<
  !<```fortran
  !< type(string) :: astring
  !< astring = 'bar/foo.tar.bz2'
  !< print '(A)', astring%basename(extension='.tar.bz2')//''        ! print "foo"
  !< print '(A)', astring%basename(strip_last_extension=.true.)//'' ! print "foo.tar"
  !<```
  !---------------------------------------------------------------------------------------------------------------------------------
  class(string),             intent(in)           :: self                 !< The string.
  character(kind=CK, len=*), intent(in), optional :: sep                  !< Directory separator.
  character(kind=CK, len=*), intent(in), optional :: extension            !< File extension.
  logical,                   intent(in), optional :: strip_last_extension !< Flag to enable the stripping of last extension.
  type(string)                                    :: basename             !< Base file name.
  character(kind=CK, len=:), allocatable          :: sep_                 !< Separator, default value.
  integer                                         :: pos                  !< Character position.
#ifdef __GFORTRAN__
  character(kind=CK, len=:), allocatable          :: temporary            !< Temporary storage, workaround for GNU bug.
#endif
  !---------------------------------------------------------------------------------------------------------------------------------

  !---------------------------------------------------------------------------------------------------------------------------------
  if (allocated(self%raw)) then
    sep_ = UIX_DIR_SEP ; if (present(sep)) sep_ = sep
    basename = self
#ifdef __GFORTRAN__
    temporary = basename%raw
    pos = index(temporary, sep_, back=.true.)
    if (pos>0) basename%raw = temporary(pos+1:)
#else
    pos = index(basename%raw, sep_, back=.true.)
    if (pos>0) basename%raw = self%raw(pos+1:)
#endif
    if (present(extension)) then
#ifdef __GFORTRAN__
      temporary = basename%raw
      pos = index(temporary, extension, back=.true.)
      if (pos>0) basename%raw = temporary(1:pos-1)
#else
      pos = index(basename%raw, extension, back=.true.)
      if (pos>0) basename%raw = basename%raw(1:pos-1)
#endif
    elseif (present(strip_last_extension)) then
      if (strip_last_extension) then
#ifdef __GFORTRAN__
        temporary = basename%raw
        pos = index(temporary, '.', back=.true.)
        basename%raw = temporary(1:pos-1)
#else
        pos = index(basename%raw, '.', back=.true.)
        basename%raw = basename%raw(1:pos-1)
#endif
      endif
    endif
  endif
  return
  !---------------------------------------------------------------------------------------------------------------------------------
  endfunction basename

  elemental function camelcase(self, sep)
  !---------------------------------------------------------------------------------------------------------------------------------
  !< Return a string with all words capitalized without spaces.
  !<
  !< @note Multiple subsequent separators are collapsed to one occurence.
  !<
  !<### Example
  !<
  !<```fortran
  !< type(string) :: astring
  !< astring = 'caMeL caSe var'
  !< print '(A)', astring%camelcase()//'' ! print "CamelCaseVar"
  !---------------------------------------------------------------------------------------------------------------------------------
  class(string),             intent(in)           :: self      !< The string.
  character(kind=CK, len=*), intent(in), optional :: sep       !< Separator.
  type(string)                                    :: camelcase !< Camel case string.
  type(string), allocatable                       :: tokens(:) !< String tokens.
  !---------------------------------------------------------------------------------------------------------------------------------

  !---------------------------------------------------------------------------------------------------------------------------------
  if (allocated(self%raw)) then
    call self%split(tokens=tokens, sep=sep)
    tokens = tokens%capitalize()
    camelcase = camelcase%join(array=tokens)
  endif
  return
  !---------------------------------------------------------------------------------------------------------------------------------
  endfunction camelcase

  elemental function capitalize(self) result(capitalized)
  !---------------------------------------------------------------------------------------------------------------------------------
  !< Return a string with its first character capitalized and the rest lowercased.
  !---------------------------------------------------------------------------------------------------------------------------------
  class(string), intent(in) :: self        !< The string.
  type(string)              :: capitalized !< Upper case string.
  integer                   :: c           !< Character counter.
  !---------------------------------------------------------------------------------------------------------------------------------

  !---------------------------------------------------------------------------------------------------------------------------------
  if (allocated(self%raw)) then
    capitalized = self%lower()
    c = index(LOWER_ALPHABET, capitalized%raw(1:1))
    if (c>0) capitalized%raw(1:1) = UPPER_ALPHABET(c:c)
  endif
  return
  !---------------------------------------------------------------------------------------------------------------------------------
  endfunction capitalize

  pure function chars(self) result(raw)
  !---------------------------------------------------------------------------------------------------------------------------------
  !< Return the raw characters data.
  !---------------------------------------------------------------------------------------------------------------------------------
  class(string), intent(in)              :: self !< The string.
  character(kind=CK, len=:), allocatable :: raw  !< Raw characters data.
  !---------------------------------------------------------------------------------------------------------------------------------

  !---------------------------------------------------------------------------------------------------------------------------------
  if (allocated(self%raw)) then
    raw = self%raw
  else
    raw = ''
  endif
  return
  !---------------------------------------------------------------------------------------------------------------------------------
  endfunction chars

  elemental function decode(self, codec) result(decoded)
  !---------------------------------------------------------------------------------------------------------------------------------
  !< Return a string decoded accordingly the codec.
  !<
  !< @note Only BASE64 codec is currently available.
  !<
  !<### Example
  !<
  !<```fortran
  !< type(string) :: astring
  !< astring = 'SG93IGFyZSB5b3U/'
  !< print '(A)', astring%decode(codec='base64')//'' ! print "How are you?"
  !---------------------------------------------------------------------------------------------------------------------------------
  class(string),             intent(in) :: self    !< The string.
  character(kind=CK, len=*), intent(in) :: codec   !< Encoding codec.
  type(string)                          :: decoded !< Decoded string.
  type(string)                          :: codec_u !< Encoding codec in upper case string.
  !---------------------------------------------------------------------------------------------------------------------------------

  !---------------------------------------------------------------------------------------------------------------------------------
  if (allocated(self%raw)) then
    decoded = self
    codec_u = codec
    select case(codec_u%upper()//'')
    case('BASE64')
      call b64_decode(code=self%raw, s=decoded%raw)
    endselect
    decoded = decoded%strip(remove_nulls=.true.)
  endif
  return
  !---------------------------------------------------------------------------------------------------------------------------------
  endfunction decode

  elemental function encode(self, codec) result(encoded)
  !---------------------------------------------------------------------------------------------------------------------------------
  !< Return a string encoded accordingly the codec.
  !<
  !< @note Only BASE64 codec is currently available.
  !<
  !<### Example
  !<
  !<```fortran
  !< type(string) :: astring
  !< astring = 'How are you?'
  !< print '(A)', astring%encode(codec='base64')//'' ! print "SG93IGFyZSB5b3U/"
  !---------------------------------------------------------------------------------------------------------------------------------
  class(string),             intent(in) :: self    !< The string.
  character(kind=CK, len=*), intent(in) :: codec   !< Encoding codec.
  type(string)                          :: encoded !< Encoded string.
  !---------------------------------------------------------------------------------------------------------------------------------

  !---------------------------------------------------------------------------------------------------------------------------------
  if (allocated(self%raw)) then
    encoded = codec
    select case(encoded%upper()//'')
    case('BASE64')
      call b64_encode(s=self%raw, code=encoded%raw)
    endselect
  endif
  return
  !---------------------------------------------------------------------------------------------------------------------------------
  endfunction encode

  elemental function escape(self, to_escape, esc) result(escaped)
  !---------------------------------------------------------------------------------------------------------------------------------
  !< Escape backslashes (or custom escape character).
  !---------------------------------------------------------------------------------------------------------------------------------
  class(string),             intent(in)           :: self      !< The string.
  character(kind=CK, len=1), intent(in)           :: to_escape !< Character to be escaped.
  character(kind=CK, len=*), intent(in), optional :: esc       !< Character used to escape.
  type(string)                                    :: escaped   !< Escaped string.
  character(kind=CK, len=:), allocatable          :: esc_      !< Character to escape, local variable.
  integer                                         :: c         !< Character counter.
  !---------------------------------------------------------------------------------------------------------------------------------

  !---------------------------------------------------------------------------------------------------------------------------------
  if (allocated(self%raw)) then
    esc_ = BACKSLASH ; if (present(esc)) esc_ = esc
    escaped%raw = ''
    do c=1, len(self%raw)
      if (self%raw(c:c)==to_escape) then
        escaped%raw = escaped%raw//esc_//to_escape
      else
        escaped%raw = escaped%raw//self%raw(c:c)
      endif
    enddo
  endif
  return
  !---------------------------------------------------------------------------------------------------------------------------------
  endfunction escape

  elemental function extension(self)
  !---------------------------------------------------------------------------------------------------------------------------------
  !< Return the extension of a string containing a file name.
  !---------------------------------------------------------------------------------------------------------------------------------
  class(string), intent(in)              :: self      !< The string.
  type(string)                           :: extension !< Extension file name.
  integer                                :: pos       !< Character position.
#ifdef __GFORTRAN__
  character(kind=CK, len=:), allocatable :: temporary !< Temporary storage, workaround for GNU bug.
#endif
  !---------------------------------------------------------------------------------------------------------------------------------

  !---------------------------------------------------------------------------------------------------------------------------------
  if (allocated(self%raw)) then
    extension = ''
    pos = index(self%raw, '.', back=.true.)
#ifdef __GFORTRAN__
    temporary = self%raw
    if (pos>0) extension%raw = temporary(pos:)
#else
    if (pos>0) extension%raw = self%raw(pos:)
#endif
  endif
  return
  !---------------------------------------------------------------------------------------------------------------------------------
  endfunction extension