Skip to content

Commit 2083f32

Browse files
committed
implemented pad function with optional pad_with argument
1 parent e325c2b commit 2083f32

File tree

1 file changed

+141
-1
lines changed

1 file changed

+141
-1
lines changed

src/stdlib_strings.f90

Lines changed: 141 additions & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -5,7 +5,7 @@
55
!> The specification of this module is available [here](../page/specs/stdlib_strings.html).
66
module stdlib_strings
77
use stdlib_ascii, only: whitespace
8-
use stdlib_string_type, only: string_type, char, verify
8+
use stdlib_string_type, only: string_type, char, verify, repeat
99
use stdlib_optval, only: optval
1010
implicit none
1111
private
@@ -93,6 +93,26 @@ module stdlib_strings
9393
module procedure :: replace_all_char_char_char
9494
end interface replace_all
9595

96+
!> Left pad the input string
97+
!> [Specifications](link to the specs - to be completed)
98+
!> Version: experimental
99+
interface padl
100+
module procedure :: padl_string_string
101+
module procedure :: padl_string_char
102+
module procedure :: padl_char_string
103+
module procedure :: padl_char_char
104+
end interface padl
105+
106+
!> Right pad the input string
107+
!> [Specifications](link to the specs - to be completed)
108+
!> Version: experimental
109+
interface padr
110+
module procedure :: padr_string_string
111+
module procedure :: padr_string_char
112+
module procedure :: padr_char_string
113+
module procedure :: padr_char_char
114+
end interface padr
115+
96116
contains
97117

98118

@@ -564,4 +584,124 @@ pure function replace_all_char_char_char(string, pattern, replacement, replace_o
564584

565585
end function replace_all_char_char_char
566586

587+
!> Left pad the input string with the 'pad_with' string
588+
!>
589+
!> Returns a new string
590+
pure function padl_string_string(string, output_length, pad_with) result(res)
591+
type(string_type), intent(in) :: string
592+
integer, intent(in) :: output_length
593+
type(string_type), intent(in), optional :: pad_with
594+
type(string_type) :: res
595+
596+
res = string_type(padl_char_char(char(string), output_length, char(pad_with)))
597+
end function padl_string_string
598+
599+
!> Left pad the input string with the 'pad_with' string
600+
!>
601+
!> Returns a new string
602+
pure function padl_string_char(string, output_length, pad_with) result(res)
603+
type(string_type), intent(in) :: string
604+
integer, intent(in) :: output_length
605+
character(len=1), intent(in), optional :: pad_with
606+
type(string_type) :: res
607+
608+
res = string_type(padl_char_char(char(string), output_length, pad_with))
609+
end function padl_string_char
610+
611+
!> Left pad the input string with the 'pad_with' string
612+
!>
613+
!> Returns a new string
614+
pure function padl_char_string(string, output_length, pad_with) result(res)
615+
character(len=*), intent(in) :: string
616+
integer, intent(in) :: output_length
617+
type(string_type), intent(in), optional :: pad_with
618+
character(len=max(len(string), output_length)) :: res
619+
620+
res = padl_char_char(string, output_length, char(pad_with))
621+
end function padl_char_string
622+
623+
!> Left pad the input string with the 'pad_with' string
624+
!>
625+
!> Returns a new string
626+
pure function padl_char_char(string, output_length, pad_with) result(res)
627+
character(len=*), intent(in) :: string
628+
integer, intent(in) :: output_length
629+
character(len=1), intent(in), optional :: pad_with
630+
integer :: string_length
631+
character(len=max(string_length, output_length)) :: res
632+
633+
string_length = len(string)
634+
if (.not. present(pad_with)) then
635+
pad_with = ' '
636+
end if
637+
638+
if (string_length < output_length) then
639+
res = repeat(pad_with, output_length - string_length)
640+
res(output_length - string_length + 1 : output_length) = string
641+
else
642+
res = string
643+
end if
644+
645+
end function padl_char_char
646+
647+
!> Right pad the input string with the 'pad_with' string
648+
!>
649+
!> Returns a new string
650+
pure function padr_string_string(string, output_length, pad_with) result(res)
651+
type(string_type), intent(in) :: string
652+
integer, intent(in) :: output_length
653+
type(string_type), intent(in), optional :: pad_with
654+
type(string_type) :: res
655+
656+
res = string_type(padr_char_char(char(string), output_length, char(pad_with)))
657+
end function padr_string_string
658+
659+
!> Right pad the input string with the 'pad_with' string
660+
!>
661+
!> Returns a new string
662+
pure function padr_string_char(string, output_length, pad_with) result(res)
663+
type(string_type), intent(in) :: string
664+
integer, intent(in) :: output_length
665+
character(len=1), intent(in), optional :: pad_with
666+
type(string_type) :: res
667+
668+
res = string_type(padr_char_char(char(string), output_length, pad_with))
669+
end function padr_string_char
670+
671+
!> Right pad the input string with the 'pad_with' string
672+
!>
673+
!> Returns a new string
674+
pure function padr_char_string(string, output_length, pad_with) result(res)
675+
character(len=*), intent(in) :: string
676+
integer, intent(in) :: output_length
677+
type(string_type), intent(in), optional :: pad_with
678+
character(len=max(len(string), output_length)) :: res
679+
680+
res = padr_char_char(string, output_length, char(pad_with))
681+
end function padr_char_string
682+
683+
!> Right pad the input string with the 'pad_with' character
684+
!>
685+
!> Returns a new string
686+
pure function padr_char_char(string, output_length, pad_with) result(res)
687+
character(len=*), intent(in) :: string
688+
integer, intent(in) :: output_length
689+
character(len=1), intent(in), optional :: pad_with
690+
integer :: string_length
691+
character(len=max(string_length, output_length)) :: res
692+
693+
string_length = len(string)
694+
if (.not. present(pad_with)) then
695+
pad_with = ' '
696+
end if
697+
698+
res = string
699+
if (string_length < output_length) then
700+
res(string_length + 1 : output_length) = repeat(pad_with, &
701+
& output_length - string_length)
702+
end if
703+
704+
end function padr_char_char
705+
706+
567707
end module stdlib_strings

0 commit comments

Comments
 (0)