fortran-lang / stdlib

Fortran Standard Library
https://stdlib.fortran-lang.org
MIT License
1.04k stars 165 forks source link

Function to construct array of character variables #410

Open Beliavsky opened 3 years ago

Beliavsky commented 3 years ago

A defect of Fortran is that you cannot write x = ["one","three","four"] but must instead either pad with x = ["one ","three","four "] or write x = [character(len=5) :: "one","three","four"], which is wordy. A convenience function that I use in many of my programs lets you write x = c("one","three","four"). It works for up to 10 arguments. I suggest something like it for stdlib. Here is the code:

function c(x1,x2,x3,x4,x5,x6,x7,x8,x9,x10) result(vec)
! return character array containing present arguments
character (len=*)  , intent(in), optional    :: x1,x2,x3,x4,x5,x6,x7,x8,x9,x10
character (len=100)            , allocatable :: vec(:)
character (len=100)            , allocatable :: vec_(:)
integer                                      :: n
allocate (vec_(10))
if (present(x1))  vec_(1)  = x1
if (present(x2))  vec_(2)  = x2
if (present(x3))  vec_(3)  = x3
if (present(x4))  vec_(4)  = x4
if (present(x5))  vec_(5)  = x5
if (present(x6))  vec_(6)  = x6
if (present(x7))  vec_(7)  = x7
if (present(x8))  vec_(8)  = x8
if (present(x9))  vec_(9)  = x9
if (present(x10)) vec_(10) = x10
n = count([present(x1),present(x2),present(x3),present(x4),present(x5), &
           present(x6),present(x7),present(x8),present(x9),present(x10)])
allocate (vec(n))
if (n > 0) vec = vec_(:n)
end function c

The user is not supposed to write things like x= c(x1="a",x3="b")

urbanjost commented 3 years ago

Allowing the desired syntax is already a common extension. If it has not already been proposed to support that you should.

The interesting use of COUNT() got me thinking about whether PRESENT() was elemental (pretty sure now it is not) and whether you could make an elemental function with an optional argument (which seemed unlikely but I could not find anything in the standard so far that prohibits it but still looking) so I just tried it with gfortran and such a function compiles and runs but did not give me the answer I expected. Still playing with that, but did make a version that allows for the string length to be equal to the longest string input, and to allow non-sequential arguments to be specified by name. It got really convoluted though because I was really playing with whether you could pass an array of optional arguments or not. I don't think the second one (x=c(x1="a",x3="b") ) is very important but I really would like the function to allow input strings of any length and to return an array with the LEN of the longest input string. You could do that with yours by just adding a preceding if(present(xNN)) maxlen=max(maxlen,len(xNN) and then your COUNT to get the length and size for VEC and then put the arguments straight into VEC.

Does anyone see anything definitive in the standard that says whether calling GETL should work or if GETL as written is not allowed? The following does work otherwise like the above C but with any length input and with output length equal to the longest input string but I was playing so I would not use the way I did it; but it does show you can sure right Fortran that does not look like FORTRAN :>

module m_c
private
public :: c
contains
function c(x1,x2,x3,x4,x5,x6,x7,x8,x9,x10,x11,x12,x13,x14,x15) result(vec)
! return character array containing present arguments
character (len=*),intent(in),optional :: &
   & x1,x2,x3,x4,x5,x6,x7,x8,x9,x10,x11,x12,x13,x14,x15
character (len=:),allocatable         :: vec(:)
integer                               :: maxlen, valcount, place

   !! what the heck should this do if anything?
   write(*,'(*(i0,1x))')getl([x1,x2,x3,x4,x5,x6,x7,x8,x9,x10,x11,x12,x13,x14,x15])
   write(*,*)maxval(getl([x1,x2,x3,x4,x5,x6,x7,x8,x9,x10,x11,x12,x13,x14,x15]))

   if(allocated(vec))deallocate(vec)
   maxlen=0
   valcount= count([sz( x1),sz( x2),sz( x3),sz( x4),sz( x5) &
                 & ,sz( x6),sz( x7),sz( x8),sz( x9),sz(x10) &
                 & ,sz(x11),sz(x12),sz(x13),sz(x14),sz(x15) ])
   allocate (character(len=maxlen) :: vec(valcount))
   place=0
   call put( x1); call put( x2); call put( x3); call put( x4); call put( x5)
   call put( x6); call put( x7); call put( x8); call put( x9); call put(x10)
   call put(x11); call put(x12); call put(x13); call put(x14); call put(x15)
contains

elemental integer function getl(arg)
character(len=*),intent(in),optional :: arg
   if(present(arg))then;getl=len(arg);else;getl=0;endif
end function getl

logical function sz(arg)
character(len=*),intent(in),optional :: arg
   sz=present(arg)
   maxlen=merge(max(maxlen,len(arg)),maxlen,present(arg))
end function sz

subroutine put(arg)
character(len=*),intent(in),optional :: arg
   if(present(arg))then
      place=place+1
      vec(place)=arg
   endif
end subroutine put

end function c
end module m_c

program testit
use M_c, only : c
implicit none
character(len=:),allocatable :: output(:)
   output=c("one","two","three","four","five","six","seven")

   write(*,'(*(g0))')'SIZE=',size(output),' LEN=',len(output)
   write(*,'(*("[",a,"]":,","))')output

   output=c(x1="one",x5="two")

   write(*,'(*(g0))')'SIZE=',size(output),' LEN=',len(output)
   write(*,'(*("[",a,"]":,","))')output
end program testit

So even though GETL compiled it gave an answer of all 3s but the rest did work, showing it is relatively easy to output an array of the width of the longest input value a little more generically. Anyone have any thoughts on GETL()?

3 3 3 3 3 3 3 3 3 3 3 3 3 3 3
           3
SIZE=7 LEN=5
[one  ],[two  ],[three],[four ],[five ],[six  ],[seven]
3 3 3 3 3 3 3 3 3 3 3 3 3 3 3
           3
SIZE=2 LEN=3
[one],[two]
tsbg commented 3 years ago

The problem is the array construtor [x1, x2, x3, ..., x10]. What is the result if one of the arguments is missing? My own solution to this problem looks like this:

module m
  !
  implicit none
  private
  !
  public :: c
  !
contains
  !
  ! Return character array containing present arguments.
  !
  function c(x0, x1, x2, x3, x4, x5, x6, x7, x8, x9) result(vec)
    character(len=*), optional, intent(in) :: x0, x1, x2, x3, x4
    character(len=*), optional, intent(in) :: x5, x6, x7, x8, x9
    character(len=:), allocatable          :: vec(:)
    !
    integer :: alen(0:9), mlen, narg, i, j
    !
    alen = -1
    if (present(x0)) alen(0) = len(x0); if (present(x1)) alen(1) = len(x1)
    if (present(x2)) alen(2) = len(x2); if (present(x3)) alen(3) = len(x3)
    if (present(x4)) alen(4) = len(x4); if (present(x5)) alen(5) = len(x5)
    if (present(x6)) alen(6) = len(x6); if (present(x7)) alen(7) = len(x7)
    if (present(x8)) alen(8) = len(x8); if (present(x9)) alen(9) = len(x9)
    !
    narg = count(alen >= 0)
    mlen = max(0, maxval(alen))
    allocate (character(len=mlen) :: vec(narg))
    !
    j = 0
    do i = 0, size(alen) - 1
      if (alen(i) < 0) cycle
      j = j + 1
      select case (i)
      case (0); vec(j) = x0; case (1); vec(j) = x1
      case (2); vec(j) = x2; case (3); vec(j) = x3
      case (4); vec(j) = x4; case (5); vec(j) = x5
      case (6); vec(j) = x6; case (7); vec(j) = x7
      case (8); vec(j) = x8; case (9); vec(j) = x9
      end select
    end do
    !
    return
  end function c
  !
end module m

program test
  !
  use :: m
  !
  implicit none
  !
  character(len=:), allocatable :: arr(:)
  !
  arr = c('one', 'two', 'three', '', x7='s e v e n')
  write (*, '("size: ",i0,", length: ",i0)') size(arr), len(arr)
  write(*,'(*("[",a,"]":,","))') arr
  !
  arr = c()
  write (*, '("size: ",i0,", length: ",i0)') size(arr), len(arr)
  !
end program test

Output:

size: 5, length: 9
[one      ],[two      ],[three    ],[         ],[s e v e n]
size: 0, length: 0

It would be cool, if the the dummy arguments could be accessed like an array.