Skip to content

Commit 8f7ac8d

Browse files
ecasglezecasglezmilancurcic
authored
New zfill function to left-pad a string with zeros (#689)
* New zfill function to left-pad a string with zeros * Minor edit --------- Co-authored-by: ecasglez <ecasglez@protonmail.com> Co-authored-by: Milan Curcic <caomaco@gmail.com>
1 parent 4da9933 commit 8f7ac8d

File tree

5 files changed

+140
-3
lines changed

5 files changed

+140
-3
lines changed

doc/specs/stdlib_strings.md

Lines changed: 39 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -421,6 +421,45 @@ The result is a scalar of integer type or an integer array of rank equal to the
421421
{!example/strings/example_count.f90!}
422422
```
423423

424+
425+
<!-- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -->
426+
### `zfill`
427+
428+
#### Description
429+
430+
Returns a string of length `output_length` left-padded with zeros.
431+
If `output_length` is less than or equal to the length of `string`, padding is not performed.
432+
433+
#### Syntax
434+
435+
`string = [[stdlib_strings(module):zfill(interface)]] (string, output_length)`
436+
437+
#### Status
438+
439+
Experimental
440+
441+
#### Class
442+
443+
Pure function
444+
445+
#### Argument
446+
447+
- `string`: Character scalar or [[stdlib_string_type(module):string_type(type)]].
448+
This argument is intent(in).
449+
- `output_length`: integer.
450+
This argument is intent(in).
451+
452+
#### Result value
453+
454+
The result is of the same type as `string`.
455+
456+
#### Example
457+
458+
```fortran
459+
{!example/strings/example_zfill.f90!}
460+
```
461+
462+
424463
<!-- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -->
425464
### `to_string`
426465

example/strings/CMakeLists.txt

Lines changed: 1 addition & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -9,3 +9,4 @@ ADD_EXAMPLE(slice)
99
ADD_EXAMPLE(starts_with)
1010
ADD_EXAMPLE(strip)
1111
ADD_EXAMPLE(to_string)
12+
ADD_EXAMPLE(zfill)

example/strings/example_zfill.f90

Lines changed: 15 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -0,0 +1,15 @@
1+
program example_zfill
2+
use stdlib_string_type, only: string_type, assignment(=), write (formatted)
3+
use stdlib_strings, only: zfill
4+
implicit none
5+
type(string_type) :: string
6+
7+
string = "left pad this string with zeros"
8+
! string <-- "left pad this string with zeros"
9+
10+
print '(dt)', zfill(string, 36) ! "00000left pad this string with zeros"
11+
12+
string = zfill(string, 36)
13+
! string <-- "00000left pad this string with zeros"
14+
15+
end program example_zfill

src/stdlib_strings.fypp

Lines changed: 34 additions & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -14,7 +14,7 @@ module stdlib_strings
1414
public :: to_string
1515
public :: strip, chomp
1616
public :: starts_with, ends_with
17-
public :: slice, find, replace_all, padl, padr, count
17+
public :: slice, find, replace_all, padl, padr, count, zfill
1818

1919
!> Version: experimental
2020
!>
@@ -155,6 +155,15 @@ module stdlib_strings
155155
module procedure :: count_char_char
156156
end interface count
157157

158+
!> Version: experimental
159+
!>
160+
!> Left pad the input string with zeros.
161+
!> [Specifications](../page/specs/stdlib_strings.html#zfill)
162+
interface zfill
163+
module procedure :: zfill_string
164+
module procedure :: zfill_char
165+
end interface zfill
166+
158167
contains
159168

160169

@@ -909,6 +918,30 @@ contains
909918
end if
910919

911920
end function count_char_char
921+
922+
!> Left pad the input string with zeros
923+
!>
924+
!> Returns a new string
925+
pure function zfill_string(string, output_length) result(res)
926+
type(string_type), intent(in) :: string
927+
integer, intent(in) :: output_length
928+
type(string_type) :: res
929+
930+
res = string_type(padl(char(string), output_length, "0"))
931+
932+
end function zfill_string
933+
934+
!> Left pad the input string with zeros
935+
!>
936+
!> Returns a new string
937+
pure function zfill_char(string, output_length) result(res)
938+
character(len=*), intent(in) :: string
939+
integer, intent(in) :: output_length
940+
character(len=max(len(string), output_length)) :: res
941+
942+
res = padl(string, output_length, "0")
943+
944+
end function zfill_char
912945

913946

914947
end module stdlib_strings

test/string/test_string_functions.f90

Lines changed: 51 additions & 2 deletions
Original file line numberDiff line numberDiff line change
@@ -4,7 +4,7 @@ module test_string_functions
44
use testdrive, only : new_unittest, unittest_type, error_type, 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, padl, padr, count
7+
use stdlib_strings, only: slice, find, replace_all, padl, padr, count, zfill
88
use stdlib_optval, only: optval
99
use stdlib_strings, only : to_string
1010
implicit none
@@ -29,7 +29,8 @@ subroutine collect_string_functions(testsuite)
2929
new_unittest("replace_all", test_replace_all), &
3030
new_unittest("padl", test_padl), &
3131
new_unittest("padr", test_padr), &
32-
new_unittest("count", test_count) &
32+
new_unittest("count", test_count), &
33+
new_unittest("zfill", test_zfill) &
3334
]
3435
end subroutine collect_string_functions
3536

@@ -659,6 +660,54 @@ subroutine test_count(error)
659660

660661
end subroutine test_count
661662

663+
subroutine test_zfill(error)
664+
!> Error handling
665+
type(error_type), allocatable, intent(out) :: error
666+
667+
type(string_type) :: test_string
668+
character(len=:), allocatable :: test_char
669+
670+
test_string = "left pad this string"
671+
test_char = " left pad this string "
672+
673+
! output_length > len(string)
674+
call check(error, zfill(test_string, 25) == "00000left pad this string", &
675+
& 'zfill: output_length > len(string), test_case 1')
676+
if (allocated(error)) return
677+
call check(error, zfill(test_string, 22) == "00left pad this string", &
678+
& 'zfill: output_length > len(string), test_case 2')
679+
if (allocated(error)) return
680+
call check(error, zfill(test_string, 23) == "000left pad this string", &
681+
& 'zfill: output_length > len(string), test_case 3')
682+
if (allocated(error)) return
683+
call check(error, zfill(test_char, 26) == "00 left pad this string ", &
684+
& 'zfill: output_length > len(string), test_case 4')
685+
if (allocated(error)) return
686+
call check(error, zfill("", 10) == "0000000000", &
687+
& 'zfill: output_length > len(string), test_case 5')
688+
if (allocated(error)) return
689+
690+
! output_length <= len(string)
691+
call check(error, zfill(test_string, 18) == "left pad this string", &
692+
& 'zfill: output_length <= len(string), test_case 1')
693+
if (allocated(error)) return
694+
call check(error, zfill(test_string, -4) == "left pad this string", &
695+
& 'zfill: output_length <= len(string), test_case 2')
696+
if (allocated(error)) return
697+
call check(error, zfill(test_char, 20) == " left pad this string ", &
698+
& 'zfill: output_length <= len(string), test_case 3')
699+
if (allocated(error)) return
700+
call check(error, zfill(test_char, 17) == " left pad this string ", &
701+
& 'zfill: output_length <= len(string), test_case 4')
702+
if (allocated(error)) return
703+
call check(error, zfill("", 0) == "", &
704+
& 'zfill: output_length <= len(string), test_case 5')
705+
if (allocated(error)) return
706+
call check(error, zfill("", -12) == "", &
707+
& 'zfill: output_length <= len(string), test_case 6')
708+
709+
end subroutine test_zfill
710+
662711
end module test_string_functions
663712

664713

0 commit comments

Comments
 (0)