Skip to content

Commit 3c9f8bb

Browse files
committed
implemented pad function with optional pad_with argument
1 parent 7d38373 commit 3c9f8bb

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

@@ -649,4 +669,124 @@ pure function replace_all_char_char_char(string, pattern, replacement) result(re
649669

650670
end function replace_all_char_char_char
651671

672+
!> Left pad the input string with the 'pad_with' string
673+
!>
674+
!> Returns a new string
675+
pure function padl_string_string(string, output_length, pad_with) result(res)
676+
type(string_type), intent(in) :: string
677+
integer, intent(in) :: output_length
678+
type(string_type), intent(in), optional :: pad_with
679+
type(string_type) :: res
680+
681+
res = string_type(padl_char_char(char(string), output_length, char(pad_with)))
682+
end function padl_string_string
683+
684+
!> Left pad the input string with the 'pad_with' string
685+
!>
686+
!> Returns a new string
687+
pure function padl_string_char(string, output_length, pad_with) result(res)
688+
type(string_type), intent(in) :: string
689+
integer, intent(in) :: output_length
690+
character(len=1), intent(in), optional :: pad_with
691+
type(string_type) :: res
692+
693+
res = string_type(padl_char_char(char(string), output_length, pad_with))
694+
end function padl_string_char
695+
696+
!> Left pad the input string with the 'pad_with' string
697+
!>
698+
!> Returns a new string
699+
pure function padl_char_string(string, output_length, pad_with) result(res)
700+
character(len=*), intent(in) :: string
701+
integer, intent(in) :: output_length
702+
type(string_type), intent(in), optional :: pad_with
703+
character(len=max(len(string), output_length)) :: res
704+
705+
res = padl_char_char(string, output_length, char(pad_with))
706+
end function padl_char_string
707+
708+
!> Left pad the input string with the 'pad_with' string
709+
!>
710+
!> Returns a new string
711+
pure function padl_char_char(string, output_length, pad_with) result(res)
712+
character(len=*), intent(in) :: string
713+
integer, intent(in) :: output_length
714+
character(len=1), intent(in), optional :: pad_with
715+
integer :: string_length
716+
character(len=max(string_length, output_length)) :: res
717+
718+
string_length = len(string)
719+
if (.not. present(pad_with)) then
720+
pad_with = ' '
721+
end if
722+
723+
if (string_length < output_length) then
724+
res = repeat(pad_with, output_length - string_length)
725+
res(output_length - string_length + 1 : output_length) = string
726+
else
727+
res = string
728+
end if
729+
730+
end function padl_char_char
731+
732+
!> Right pad the input string with the 'pad_with' string
733+
!>
734+
!> Returns a new string
735+
pure function padr_string_string(string, output_length, pad_with) result(res)
736+
type(string_type), intent(in) :: string
737+
integer, intent(in) :: output_length
738+
type(string_type), intent(in), optional :: pad_with
739+
type(string_type) :: res
740+
741+
res = string_type(padr_char_char(char(string), output_length, char(pad_with)))
742+
end function padr_string_string
743+
744+
!> Right pad the input string with the 'pad_with' string
745+
!>
746+
!> Returns a new string
747+
pure function padr_string_char(string, output_length, pad_with) result(res)
748+
type(string_type), intent(in) :: string
749+
integer, intent(in) :: output_length
750+
character(len=1), intent(in), optional :: pad_with
751+
type(string_type) :: res
752+
753+
res = string_type(padr_char_char(char(string), output_length, pad_with))
754+
end function padr_string_char
755+
756+
!> Right pad the input string with the 'pad_with' string
757+
!>
758+
!> Returns a new string
759+
pure function padr_char_string(string, output_length, pad_with) result(res)
760+
character(len=*), intent(in) :: string
761+
integer, intent(in) :: output_length
762+
type(string_type), intent(in), optional :: pad_with
763+
character(len=max(len(string), output_length)) :: res
764+
765+
res = padr_char_char(string, output_length, char(pad_with))
766+
end function padr_char_string
767+
768+
!> Right pad the input string with the 'pad_with' character
769+
!>
770+
!> Returns a new string
771+
pure function padr_char_char(string, output_length, pad_with) result(res)
772+
character(len=*), intent(in) :: string
773+
integer, intent(in) :: output_length
774+
character(len=1), intent(in), optional :: pad_with
775+
integer :: string_length
776+
character(len=max(string_length, output_length)) :: res
777+
778+
string_length = len(string)
779+
if (.not. present(pad_with)) then
780+
pad_with = ' '
781+
end if
782+
783+
res = string
784+
if (string_length < output_length) then
785+
res(string_length + 1 : output_length) = repeat(pad_with, &
786+
& output_length - string_length)
787+
end if
788+
789+
end function padr_char_char
790+
791+
652792
end module stdlib_strings

0 commit comments

Comments
 (0)