Skip to content

Commit b098e78

Browse files
committed
Deploying to stdlib-fpm from @ 8f7ac8d 🚀
1 parent 3c212ab commit b098e78

File tree

3 files changed

+100
-3
lines changed

3 files changed

+100
-3
lines changed

example/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.f90

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

1818
!> Version: experimental
1919
!>
@@ -208,6 +208,15 @@ end function to_string_2_l_c_bool
208208
module procedure :: count_char_char
209209
end interface count
210210

211+
!> Version: experimental
212+
!>
213+
!> Left pad the input string with zeros.
214+
!> [Specifications](../page/specs/stdlib_strings.html#zfill)
215+
interface zfill
216+
module procedure :: zfill_string
217+
module procedure :: zfill_char
218+
end interface zfill
219+
211220
contains
212221

213222

@@ -962,6 +971,30 @@ elemental function count_char_char(string, pattern, consider_overlapping) result
962971
end if
963972

964973
end function count_char_char
974+
975+
!> Left pad the input string with zeros
976+
!>
977+
!> Returns a new string
978+
pure function zfill_string(string, output_length) result(res)
979+
type(string_type), intent(in) :: string
980+
integer, intent(in) :: output_length
981+
type(string_type) :: res
982+
983+
res = string_type(padl(char(string), output_length, "0"))
984+
985+
end function zfill_string
986+
987+
!> Left pad the input string with zeros
988+
!>
989+
!> Returns a new string
990+
pure function zfill_char(string, output_length) result(res)
991+
character(len=*), intent(in) :: string
992+
integer, intent(in) :: output_length
993+
character(len=max(len(string), output_length)) :: res
994+
995+
res = padl(string, output_length, "0")
996+
997+
end function zfill_char
965998

966999

9671000
end module stdlib_strings

test/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)