Skip to content

Navigation Menu

Sign in
Appearance settings

Search code, repositories, users, issues, pull requests...

Provide feedback

We read every piece of feedback, and take your input very seriously.

Saved searches

Use saved searches to filter your results more quickly

Sign up
Appearance settings

Commit 21c888e

Browse files
authored
Merge pull request #441 from Aman-Godara/pad
implemented pad function
2 parents c2b8338 + 74bb5ba commit 21c888e

File tree

3 files changed

+330
-3
lines changed

3 files changed

+330
-3
lines changed

‎doc/specs/stdlib_strings.md

Lines changed: 108 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -384,6 +384,114 @@ end program demo_replace_all
384384
```
385385

386386

387+
<!-- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -->
388+
### `padl`
389+
390+
#### Description
391+
392+
Returns a string of length `output_length` left padded with `pad_with` character if it is provided, otherwise with `" "` (1 whitespace).
393+
If `output_length` is less than or equal to the length of `string`, padding is not performed.
394+
395+
#### Syntax
396+
397+
`string = [[stdlib_strings(module):padl(interface)]] (string, output_length [, pad_with])`
398+
399+
#### Status
400+
401+
Experimental
402+
403+
#### Class
404+
405+
Pure function
406+
407+
#### Argument
408+
409+
- `string`: Character scalar or [[stdlib_string_type(module):string_type(type)]].
410+
This argument is intent(in).
411+
- `output_length`: integer.
412+
This argument is intent(in).
413+
- `pad_with`: Character scalar of length 1.
414+
This argument is intent(in) and optional.
415+
416+
#### Result value
417+
418+
The result is of the same type as `string`.
419+
420+
#### Example
421+
422+
```fortran
423+
program demo_padl
424+
use stdlib_string_type, only: string_type, assignment(=)
425+
use stdlib_strings, only : padl
426+
implicit none
427+
string_type :: string
428+
429+
string = "left pad this string"
430+
! string <-- "left pad this string"
431+
432+
print *, padl(string, 25, "$") ! "$$$$$left pad this string"
433+
434+
string = padl(string, 25)
435+
! string <-- " left pad this string"
436+
437+
end program demo_padl
438+
```
439+
440+
441+
<!-- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -->
442+
### `padr`
443+
444+
#### Description
445+
446+
Returns a string of length `output_length` right padded with `pad_with` character if it is provided, otherwise with `" "` (1 whitespace).
447+
If `output_length` is less than or equal to the length of `string`, padding is not performed.
448+
449+
#### Syntax
450+
451+
`string = [[stdlib_strings(module):padr(interface)]] (string, output_length [, pad_with])`
452+
453+
#### Status
454+
455+
Experimental
456+
457+
#### Class
458+
459+
Pure function
460+
461+
#### Argument
462+
463+
- `string`: Character scalar or [[stdlib_string_type(module):string_type(type)]].
464+
This argument is intent(in).
465+
- `output_length`: integer.
466+
This argument is intent(in).
467+
- `pad_with`: Character scalar of length 1.
468+
This argument is intent(in) and optional.
469+
470+
#### Result value
471+
472+
The result is of the same type as `string`.
473+
474+
#### Example
475+
476+
```fortran
477+
program demo_padr
478+
use stdlib_string_type, only: string_type, assignment(=)
479+
use stdlib_strings, only : padr
480+
implicit none
481+
string_type :: string
482+
483+
string = "right pad this string"
484+
! string <-- "right pad this string"
485+
486+
print *, padr(string, 25, "$") ! "right pad this string$$$$"
487+
488+
string = padr(string, 25)
489+
! string <-- "right pad this string "
490+
491+
end program demo_padr
492+
```
493+
494+
387495
<!-- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -->
388496
### `count`
389497

‎src/stdlib_strings.f90

Lines changed: 145 additions & 2 deletions
Original file line numberDiff line numberDiff line change
@@ -5,14 +5,14 @@
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, len
99
use stdlib_optval, only: optval
1010
implicit none
1111
private
1212

1313
public :: strip, chomp
1414
public :: starts_with, ends_with
15-
public :: slice, find, replace_all, count
15+
public :: slice, find, replace_all, padl, padr, count
1616

1717

1818
!> Remove leading and trailing whitespace characters.
@@ -93,6 +93,28 @@ module stdlib_strings
9393
module procedure :: replace_all_char_char_char
9494
end interface replace_all
9595

96+
!> Version: experimental
97+
!>
98+
!> Left pad the input string
99+
!> [Specifications](../page/specs/stdlib_strings.html#padl)
100+
interface padl
101+
module procedure :: padl_string_default
102+
module procedure :: padl_string_pad_with
103+
module procedure :: padl_char_default
104+
module procedure :: padl_char_pad_with
105+
end interface padl
106+
107+
!> Version: experimental
108+
!>
109+
!> Right pad the input string
110+
!> [Specifications](../page/specs/stdlib_strings.html#padr)
111+
interface padr
112+
module procedure :: padr_string_default
113+
module procedure :: padr_string_pad_with
114+
module procedure :: padr_char_default
115+
module procedure :: padr_char_pad_with
116+
end interface padr
117+
96118
!> Version: experimental
97119
!>
98120
!> Returns the number of times substring 'pattern' has appeared in the
@@ -659,6 +681,127 @@ pure function replace_all_char_char_char(string, pattern, replacement) result(re
659681

660682
end function replace_all_char_char_char
661683

684+
!> Left pad the input string with " " (1 whitespace)
685+
!>
686+
!> Returns a new string
687+
pure function padl_string_default(string, output_length) result(res)
688+
type(string_type), intent(in) :: string
689+
integer, intent(in) :: output_length
690+
type(string_type) :: res
691+
692+
res = string_type(padl(char(string), output_length, " "))
693+
694+
end function padl_string_default
695+
696+
!> Left pad the input string with the 'pad_with' character
697+
!>
698+
!> Returns a new string
699+
pure function padl_string_pad_with(string, output_length, pad_with) result(res)
700+
type(string_type), intent(in) :: string
701+
integer, intent(in) :: output_length
702+
character(len=1), intent(in) :: pad_with
703+
type(string_type) :: res
704+
705+
res = string_type(padl(char(string), output_length, pad_with))
706+
707+
end function padl_string_pad_with
708+
709+
!> Left pad the input string with " " (1 whitespace)
710+
!>
711+
!> Returns a new string
712+
pure function padl_char_default(string, output_length) result(res)
713+
character(len=*), intent(in) :: string
714+
integer, intent(in) :: output_length
715+
character(len=max(len(string), output_length)) :: res
716+
717+
res = padl(string, output_length, " ")
718+
719+
end function padl_char_default
720+
721+
!> Left pad the input string with the 'pad_with' character
722+
!>
723+
!> Returns a new string
724+
pure function padl_char_pad_with(string, output_length, pad_with) result(res)
725+
character(len=*), intent(in) :: string
726+
integer, intent(in) :: output_length
727+
character(len=1), intent(in) :: pad_with
728+
character(len=max(len(string), output_length)) :: res
729+
integer :: string_length
730+
731+
string_length = len(string)
732+
733+
if (string_length < output_length) then
734+
res = repeat(pad_with, output_length - string_length)
735+
res(output_length - string_length + 1 : output_length) = string
736+
else
737+
res = string
738+
end if
739+
740+
end function padl_char_pad_with
741+
742+
!> Right pad the input string with " " (1 whitespace)
743+
!>
744+
!> Returns a new string
745+
pure function padr_string_default(string, output_length) result(res)
746+
type(string_type), intent(in) :: string
747+
integer, intent(in) :: output_length
748+
character(len=max(len(string), output_length)) :: char_output
749+
type(string_type) :: res
750+
751+
! We're taking advantage of `char_output` being longer than `string` and
752+
! initialized with whitespaces. By casting `string` to a `character`
753+
! type and back to `string_type`, we're effectively right-padding
754+
! `string` with spaces, so we don't need to pad explicitly.
755+
char_output = char(string)
756+
res = string_type(char_output)
757+
758+
end function padr_string_default
759+
760+
!> Right pad the input string with the 'pad_with' character
761+
!>
762+
!> Returns a new string
763+
pure function padr_string_pad_with(string, output_length, pad_with) result(res)
764+
type(string_type), intent(in) :: string
765+
integer, intent(in) :: output_length
766+
character(len=1), intent(in) :: pad_with
767+
type(string_type) :: res
768+
769+
res = string_type(padr(char(string), output_length, pad_with))
770+
771+
end function padr_string_pad_with
772+
773+
!> Right pad the input string with " " (1 whitespace)
774+
!>
775+
!> Returns a new string
776+
pure function padr_char_default(string, output_length) result(res)
777+
character(len=*), intent(in) :: string
778+
integer, intent(in) :: output_length
779+
character(len=max(len(string), output_length)) :: res
780+
781+
res = string
782+
783+
end function padr_char_default
784+
785+
!> Right pad the input string with the 'pad_with' character
786+
!>
787+
!> Returns a new string
788+
pure function padr_char_pad_with(string, output_length, pad_with) result(res)
789+
character(len=*), intent(in) :: string
790+
integer, intent(in) :: output_length
791+
character(len=1), intent(in) :: pad_with
792+
character(len=max(len(string), output_length)) :: res
793+
integer :: string_length
794+
795+
string_length = len(string)
796+
797+
res = string
798+
if (string_length < output_length) then
799+
res(string_length + 1 : output_length) = &
800+
repeat(pad_with, output_length - string_length)
801+
end if
802+
803+
end function padr_char_pad_with
804+
662805
!> Returns the number of times substring 'pattern' has appeared in the
663806
!> input string 'string'
664807
!> Returns an integer

‎src/tests/string/test_string_functions.f90

Lines changed: 77 additions & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -4,7 +4,7 @@ module test_string_functions
44
use stdlib_error, only : check
55
use stdlib_string_type, only : string_type, assignment(=), operator(==), &
66
to_lower, to_upper, to_title, to_sentence, reverse
7-
use stdlib_strings, only: slice, find, replace_all, count
7+
use stdlib_strings, only: slice, find, replace_all, padl, padr, count
88
use stdlib_optval, only: optval
99
use stdlib_ascii, only : to_string
1010
implicit none
@@ -378,6 +378,80 @@ subroutine test_replace_all
378378

379379
end subroutine test_replace_all
380380

381+
subroutine test_padl
382+
type(string_type) :: test_string
383+
character(len=:), allocatable :: test_char
384+
385+
test_string = "left pad this string"
386+
test_char = " left pad this string "
387+
388+
! output_length > len(string)
389+
call check(padl(test_string, 25, "#") == "#####left pad this string", &
390+
& 'padl: output_length > len(string), test_case 1')
391+
call check(padl(test_string, 22, "$") == "$$left pad this string", &
392+
& 'padl: output_length > len(string), test_case 2')
393+
call check(padl(test_string, 23) == " left pad this string", &
394+
& 'padl: output_length > len(string), test_case 3')
395+
call check(padl(test_char, 26) == " left pad this string ", &
396+
& 'padl: output_length > len(string), test_case 4')
397+
call check(padl(test_char, 26, "&") == "&& left pad this string ", &
398+
& 'padl: output_length > len(string), test_case 5')
399+
call check(padl("", 10, "!") == "!!!!!!!!!!", &
400+
& 'padl: output_length > len(string), test_case 6')
401+
402+
! output_length <= len(string)
403+
call check(padl(test_string, 18, "#") == "left pad this string", &
404+
& 'padl: output_length <= len(string), test_case 1')
405+
call check(padl(test_string, -4, "@") == "left pad this string", &
406+
& 'padl: output_length <= len(string), test_case 2')
407+
call check(padl(test_char, 20, "0") == " left pad this string ", &
408+
& 'padl: output_length <= len(string), test_case 3')
409+
call check(padl(test_char, 17) == " left pad this string ", &
410+
& 'padl: output_length <= len(string), test_case 4')
411+
call check(padl("", 0, "!") == "", &
412+
& 'padl: output_length <= len(string), test_case 5')
413+
call check(padl("", -12, "!") == "", &
414+
& 'padl: output_length <= len(string), test_case 6')
415+
416+
end subroutine test_padl
417+
418+
subroutine test_padr
419+
type(string_type) :: test_string
420+
character(len=:), allocatable :: test_char
421+
422+
test_string = "right pad this string"
423+
test_char = " right pad this string "
424+
425+
! output_length > len(string)
426+
call check(padr(test_string, 25, "#") == "right pad this string####", &
427+
& 'padr: output_length > len(string), test_case 1')
428+
call check(padr(test_string, 22, "$") == "right pad this string$", &
429+
& 'padr: output_length > len(string), test_case 2')
430+
call check(padr(test_string, 24) == "right pad this string ", &
431+
& 'padr: output_length > len(string), test_case 3')
432+
call check(padr(test_char, 27) == " right pad this string ", &
433+
& 'padr: output_length > len(string), test_case 4')
434+
call check(padr(test_char, 27, "&") == " right pad this string &&", &
435+
& 'padr: output_length > len(string), test_case 5')
436+
call check(padr("", 10, "!") == "!!!!!!!!!!", &
437+
& 'padr: output_length > len(string), test_case 6')
438+
439+
! output_length <= len(string)
440+
call check(padr(test_string, 18, "#") == "right pad this string", &
441+
& 'padr: output_length <= len(string), test_case 1')
442+
call check(padr(test_string, -4, "@") == "right pad this string", &
443+
& 'padr: output_length <= len(string), test_case 2')
444+
call check(padr(test_char, 20, "0") == " right pad this string ", &
445+
& 'padr: output_length <= len(string), test_case 3')
446+
call check(padr(test_char, 17) == " right pad this string ", &
447+
& 'padr: output_length <= len(string), test_case 4')
448+
call check(padr("", 0, "!") == "", &
449+
& 'padr: output_length <= len(string), test_case 5')
450+
call check(padr("", -12, "!") == "", &
451+
& 'padr: output_length <= len(string), test_case 6')
452+
453+
end subroutine test_padr
454+
381455
subroutine test_count
382456
type(string_type) :: test_string_1, test_string_2, test_pattern_1, test_pattern_2
383457
test_string_1 = "DNA sequence: AGAGAGAGTCCTGTCGAGA"
@@ -437,6 +511,8 @@ program tester
437511
call test_slice_gen
438512
call test_find
439513
call test_replace_all
514+
call test_padl
515+
call test_padr
440516
call test_count
441517

442518
end program tester

0 commit comments

Comments
(0)

AltStyle によって変換されたページ (->オリジナル) /