Consider one possible model for a new intrinsic string type as shown below:
Click to see some "library" code
module string_m
private
type :: string_t
private
character(len=:), allocatable :: m_s
contains
private
procedure :: write_s
procedure :: assign_s
generic, public :: assignment(=) => assign_s
generic, public :: write(formatted) => write_s
end type
generic :: string_t => construct_s
public :: string_t
contains
function construct_s( s ) result(new_string)
character(len=*), intent(in) :: s
type(string_t) :: new_string
new_string%m_s = s
end function
subroutine assign_s( this, s )
class(string_t), intent(inout) :: this
character(len=*), intent(in) :: s
this%m_s = s
end subroutine
subroutine write_s(this, lun, iotype, vlist, istat, imsg)
! argument definitions
class(string_t), intent(in) :: this
integer, intent(in) :: lun
character(len=*), intent(in) :: iotype
integer, intent(in) :: vlist(:)
integer, intent(out) :: istat
character(len=*), intent(inout) :: imsg
! local variable
character(len=9) :: sfmt
sfmt = "(A)"
if ( (iotype == "DT").and.(size(vlist) >= 1) ) then
! vlist(1) to be used as the field width of the character component.
write(sfmt,"(A,I2,A)", iostat=istat, iomsg=imsg ) "(A", vlist(1), ")"
if (istat /= 0) return
end if
write(lun, fmt=sfmt, iostat=istat, iomsg=imsg) this%m_s
return
end subroutine write_s
end module
use string_m, only : string_t
type(string_t), allocatable :: parts(:)
parts = [ string_t("valve"), string_t("compressor"), string_t("transducer") ]
call show_second(parts)
parts(2) = "thermocouple"
call show_second(parts)
contains
subroutine show_second(strings)
type(string_t), intent(in) :: strings(*)
! "where does the second element start, and how big is it?"
! the answer: what the coder expects, this is not rocket science
print *, strings(2)
end subroutine
end
C:\temp>ifort /standard-semantics /free p.f
Intel(R) Fortran Intel(R) 64 Compiler Classic for applications running on Intel(R) 64, Version 2021.9.0 Build 20230302_000000
Copyright (C) 1985-2023 Intel Corporation. All rights reserved.
Microsoft (R) Incremental Linker Version 14.34.31937.0
Copyright (C) Microsoft Corporation. All rights reserved.
-out:p.exe
-subsystem:console
p.obj
C:\temp>p.exe
compressor
thermocouple
But for the array constructor verbosity and unpleasantness with
..
parts = [ string_t("valve"), string_t("compressor"), string_t("transducer") ]
..
and the needlessly verbose need for a type(string_t) the pieces are all nearly there.
What is missing are the aspects I highlighted above, especially with the inability of a library author to implement the use case of practitioners to have substring data reference of the form parts(3)(1:4) which is quite important.
The issue with the array constructor syntax is nowhere as difficult as made it out be in the context of an intrinsic type STRING. Meaning, the standard can easily work out the rules with something new - say assumed-length, so that
parts = [ string_t : "valve", "compressor", "transducer" ]
can be the equivalent of the far more verbose
parts = [ string_t("valve"), string_t("compressor"), string_t("transducer") ]
This is nowhere as difficult as is made it out to be by @everythingfunctional . The key here is likely to be for the standard to be silent about the underlying model and not presume a length-type parameter exists for the type and therefore the implementations can do what is best for them, say possibly with an underlying ALLOCATABLE component. And without the length-type parameter, the compact syntax gets parsed as done for other features that are similarly syntactic sugar.