The closest I was able to come up with is
! SPDX-Identifier: CC0-1.0
module strings_chomp
implicit none
private
public :: chomp
!> Remove trailing characters in set or substring from string.
!> If no character set is provided trailing whitespace is removed.
interface chomp
module procedure :: chomp_set
module procedure :: chomp_substring
end interface chomp
type :: force_kwargs_hack
end type force_kwargs_hack
contains
!> Remove trailing characters in set from string.
pure function chomp_set(string, force_kwargs, set) result(chomped_string)
character(len=*), intent(in) :: string
type(force_kwargs_hack), optional, intent(in) :: force_kwargs
character(len=*), intent(in) :: set
character(len=:), allocatable :: chomped_string
integer :: last
last = verify(string, set, back=.true.)
chomped_string = string(1:last)
end function chomp_set
!> Remove trailing substrings from string.
pure function chomp_substring(string, force, kwargs, substring) result(chomped_string)
character(len=*), intent(in) :: string
type(force_kwargs_hack), optional, intent(in) :: force, kwargs
character(len=*), intent(in) :: substring
character(len=:), allocatable :: chomped_string
integer :: last, nsub
last = len(string)
nsub = len(substring)
if (nsub > 0) then
do while(string(last-nsub+1:last) == substring)
last = last - nsub
end do
end if
chomped_string = string(1:last)
end function chomp_substring
end module strings_chomp
program test_chomp
use strings_chomp, only : chomp
implicit none
! valid usage:
print '(a)', chomp("hello", set="lo") ! "he"
print '(a)', chomp("hello", substring="lo") ! "hel"
! invalid usage:
print '(a)', chomp("hello", "lo") ! invalid with one positional argument
print '(a)', chomp("hello", "lo", "lo") ! invalid with two positional arguments
print '(a)', chomp("hello", set="lo", substring="lo") ! invalid with two keyword arguments
end program test_chomp
It exploits some optional private derived types which probably can never be provided. Having a different number of such derived types as dummy arguments changes the function signature sufficiently to allow putting them in the same generic interface.
⯠gfortran invalid.f90
invalid.f90:61:15:
61 | print '(a)', chomp("hello", "lo") ! invalid with one positional argument
| 1
Error: There is no specific function for the generic āchompā at (1)
invalid.f90:62:15:
62 | print '(a)', chomp("hello", "lo", "lo") ! invalid with two positional arguments
| 1
Error: There is no specific function for the generic āchompā at (1)
invalid.f90:63:15:
63 | print '(a)', chomp("hello", set="lo", substring="lo") ! invalid with two keyword arguments
| 1
Error: There is no specific function for the generic āchompā at (1)
⯠gfortran test.f90 && ./a.out
he
hel
⯠ifort invalid.f90
invalid.f90(61): error #6284: There is no matching specific function for this generic function reference. [CHOMP]
print '(a)', chomp("hello", "lo") ! invalid with one positional argument
-----------------^
invalid.f90(62): error #6284: There is no matching specific function for this generic function reference. [CHOMP]
print '(a)', chomp("hello", "lo", "lo") ! invalid with two positional arguments
-----------------^
invalid.f90(63): error #6284: There is no matching specific function for this generic function reference. [CHOMP]
print '(a)', chomp("hello", set="lo", substring="lo") ! invalid with two keyword arguments
-----------------^
compilation aborted for invalid.f90 (code 1)
⯠ifort test.f90 && ./a.out
he
hel
⯠nvfortran invalid.f90
NVFORTRAN-S-0155-Could not resolve generic procedure chomp (invalid.f90: 61)
NVFORTRAN-S-0155-Could not resolve generic procedure chomp (invalid.f90: 62)
NVFORTRAN-S-0155-Could not resolve generic procedure chomp (invalid.f90: 63)
0 inform, 0 warnings, 3 severes, 0 fatal for test_chomp
⯠nvfortran test.f90 && ./a.out
/usr/bin/ld: warning: /opt/nvidia/Linux_x86_64/21.1/compilers/lib/nvhpc.ld contains output sections; did you forget -T?
he
hel
⯠nagfor invalid.f90
NAG Fortran Compiler Release 7.0(Yurakucho) Build 7038
Warning: invalid.f90, line 31: Unused dummy variable FORCE_KWARGS
Warning: invalid.f90, line 50: Unused dummy variable FORCE
Warning: invalid.f90, line 50: Unused dummy variable KWARGS
Error: invalid.f90, line 61: No specific match for reference to generic CHOMP
Error: invalid.f90, line 62: No specific match for reference to generic CHOMP
Error: invalid.f90, line 63: No specific match for reference to generic CHOMP
[NAG Fortran Compiler error termination, 3 errors, 3 warnings]
⯠nagfor test.f90 && ./a.out
NAG Fortran Compiler Release 7.0(Yurakucho) Build 7038
Warning: test.f90, line 31: Unused dummy variable FORCE_KWARGS
Warning: test.f90, line 50: Unused dummy variable FORCE
Warning: test.f90, line 50: Unused dummy variable KWARGS
[NAG Fortran Compiler normal termination, 3 warnings]
he
hel