Google Groups no longer supports new Usenet posts or subscriptions. Historical content remains viewable.
Dismiss

Gfortran 4.9 supports deferred-length character components

896 views
Skip to first unread message

Damian Rouson

unread,
Mar 8, 2014, 7:48:58 PM3/8/14
to
I've seen several people mention in this newsgroup that they would like to have access to support for deferred-length character components. The gfortran developers would like to have users test this code soon as the next compiler release is imminent. It should now be possible to do things like the following:

program main
type container
character(:), allocatable :: string
end type
type(container) :: something
something%string = "Hello, world!"
print *,something%string
end program

AFAIK, the only way to test the capability right now is to grab the gfortran source (see http://gcc.gnu.org/svn.html) and build the compiler from source.

Anyone who is on OS X might also consider installing the gcc49 port from macports, which updates roughly weekly. The latest gcc49 port available there is from a a 2 March 2014 snapshot of the gcc repository, which I don't think is quite recent enough, but I've submitted a ticket to macports to request an update so I imagine one will be available soon.

For those on Linux, there are regularly updated gcc 4.9 binaries at http://gfortran.com/download/x86_64/snapshots/, but the snapshot there is from the same date as the macports port.

Enjoy!

Damian


Vipul Parekh

unread,
Mar 9, 2014, 3:00:29 AM3/9/14
to
Great news!

Anyone know about the binary availability for Windows platform? For Windows too, Equation.com (http://www.equation.com/servlet/equation.cmd?fa=fortran) provides a build dated March 2nd, 2014 which doesn't include this feature.

The deferred length character component feature as well as the finalization capabilities are two things I'm keen to try out with gfortran 4.9.

Now, if only I can get submodules soon! :-))

Vipul

Wolfgang Kilian

unread,
Mar 10, 2014, 3:57:45 AM3/10/14
to
On 03/09/2014 01:48 AM, Damian Rouson wrote:
> I've seen several people mention in this newsgroup that they would like to have access to support for deferred-length character components. The gfortran developers would like to have users test this code soon as the next compiler release is imminent. It should now be possible to do things like the following:
>
> program main
> type container
> character(:), allocatable :: string
> end type
> type(container) :: something
> something%string = "Hello, world!"
> print *,something%string
> end program

If you want tons of nontrivial tests: re-implement the
ISO_VARYING_STRING module with deferred-length character as internal
representation.

Although deferred-length character is very welcome by itself, the string
type from ISO_VARYING_STRING is still more useful. With that type, you
can store variable-length strings in arrays. Of course, the
VARYING_STRING type is just the container of your example with lots of
functions built around it.

-- Wolfgang

> AFAIK, the only way to test the capability right now is to grab the gfortran source (see http://gcc.gnu.org/svn.html) and build the compiler from source.
>
> Anyone who is on OS X might also consider installing the gcc49 port from macports, which updates roughly weekly. The latest gcc49 port available there is from a a 2 March 2014 snapshot of the gcc repository, which I don't think is quite recent enough, but I've submitted a ticket to macports to request an update so I imagine one will be available soon.
>
> For those on Linux, there are regularly updated gcc 4.9 binaries at http://gfortran.com/download/x86_64/snapshots/, but the snapshot there is from the same date as the macports port.
>
> Enjoy!
>
> Damian
>
>


--
E-mail: firstnameini...@domain.de
Domain: yahoo

\"VladimĂ­r Fuka <"name.surnameat

unread,
Mar 10, 2014, 4:56:59 AM3/10/14
to

> AFAIK, the only way to test the capability right now is to grab the
> gfortran source (see http://gcc.gnu.org/svn.html) and build the compiler
> from source.

You don't have to use SVN. It was always extremely slow for me, maybe
there is some trick in it, and you can somehow download just the current
trunk, but downloading all the history in all branches was a neverending
story for me.

Fortunately, today a new source snapshot is available
ftp://gd.tuwien.ac.at/gnu/gcc/snapshots/LATEST-4.9 . That is what I have
been waiting for to be able to test the patch. The compilation phase was
never a problem to me, it is just 2 or 3 commands.

Janus

unread,
Mar 10, 2014, 8:00:27 AM3/10/14
to

> > AFAIK, the only way to test the capability right now is to grab the
> > gfortran source (see http://gcc.gnu.org/svn.html) and build the compiler
> > from source.
>
> You don't have to use SVN.

... but you should. It's easier to update and also working with patches is much more comfortable.


> It was always extremely slow for me, maybe
> there is some trick in it, and you can somehow download just the current
> trunk, but downloading all the history in all branches was a neverending
> story for me.

Well, obviously you should not check out the *whole* GCC repo at once (there's *lots* of branches). Only pulling trunk should be rather quick:

svn co svn://gcc.gnu.org/svn/gcc/trunk

Cheers,
Janus

Richard Maine

unread,
Mar 10, 2014, 11:05:17 AM3/10/14
to
Wolfgang Kilian <kil...@invalid.com> wrote:

> Although deferred-length character is very welcome by itself, the string
> type from ISO_VARYING_STRING is still more useful. With that type, you
> can store variable-length strings in arrays.

I grant your point about arrays of varying length strings (where each
array element has a different length). But I generally find
allocatable-length character to be more useful in most situations. The
biggest reason is that allocatable-length character is still the same
type as character, whereas ISO_VARYING_STRING introduces a distinct
type. This causes pain when mixing ISO_VARYING_STRING stuff with
"regular" character strings. For example, if you have some procedure
aith a character argument, you can't pass an ISO_VARYING_STRING one. You
can, however, pass an allocatable-length one (as long as the length is
allocated). All kinds of simillar issues. For example, try using an
ISO_VARYING_STRING for a filename in an OPEN.

--
Richard Maine
email: last name at domain . net
domain: summer-triangle

Stansfield Temmelmeier

unread,
Mar 10, 2014, 11:10:50 AM3/10/14
to
On 2014-03-10, Richard Maine <nos...@see.signature> wrote:
> Wolfgang Kilian <kil...@invalid.com> wrote:
>
>> Although deferred-length character is very welcome by itself, the string
>> type from ISO_VARYING_STRING is still more useful. With that type, you
>> can store variable-length strings in arrays.
>
> I grant your point about arrays of varying length strings (where each
> array element has a different length). But I generally find
> allocatable-length character to be more useful in most situations.

I am waiting for Solaris Studio to support this. Until then Intel and
gfortran have big advantage. It takes much too long to get this support.

Stan

Wolfgang Kilian

unread,
Mar 10, 2014, 11:46:42 AM3/10/14
to
Yes, I'm doing that all the time. That's what the CHAR and VAR_STR
transformational functions are for. It would be simpler if those
transformations could be omitted, but the compiler will tell me if I did
it wrong. (Exception: formatted WRITE if the format string is not a
constant - but in that case an error will occur at runtime.)

The more annoying issue with ISO_VARYING_STRING is the inability to
default-initialize a derived-type component of type varying string, not
even with the empty string. Unfortunately, if I read the F2008 standard
correctly, this is also true with allocatable deferred-length character
components. Special-casing the 'deallocated' case is always an
unnecessary complication. Fixed-length character components can be
default-initialized as empty (actually, blank). But they are fixed length.

After all, Fortran is one of the few languages that can effortlessly
handle multi-dimensional arrays. It's a bit odd that this is still not
true if the array elements are strings.

-- Wolfgang

tlc...@gmail.com

unread,
Mar 10, 2014, 2:10:31 PM3/10/14
to
On Saturday, March 8, 2014 7:48:58 PM UTC-5, Damian Rouson wrote:
Damian,

I should be able to do some strong tests with both pFUnit and with my template package sometime this week. I won't wait for the Mac port, but will have someone in my group install the latest Linux release.

Thanks,

- Tom

tlc...@gmail.com

unread,
Mar 11, 2014, 5:07:12 PM3/11/14
to
Worked well in my limited suite of use cases.

Is there a tentative date for the actual release of 4.9?

- Tom

Brian Rollo

unread,
Mar 19, 2014, 7:01:07 AM3/19/14
to
Around the beginning of April.

Izaak B Beekman

unread,
Mar 19, 2014, 9:00:13 AM3/19/14
to
On 2014-03-09 00:48:58 +0000, Damian Rouson said:
( snip )
> For those on Linux, there are regularly updated gcc 4.9 binaries at
> http://gfortran.com/download/x86_64/snapshots/, but the snapshot there
> is from the same date as the macports port.
> Enjoy!
>
> Damian

Hi Damian & gfortran volunteers,
I've tried building gcc from the svn trunk on my mac, but ran into some
problems linking against libgmp. Macports is still not up to date (no
support for deferred length character components) however,
http://hpc.sourceforge.net/ has gcc4.9 binaries for Mac, which appear
to at least nominally support deferred length character components. The
version of gfortran they provide is:

GNU Fortran (GCC) 4.9.0 20140309 (experimental)

However, when I compile my test code, I run into numerous ICEs with
gfortran-4.9. Depending on which lines I comment out I get
'segmentation fault 11' or 'gimplification failed' errors. My test code
does stress out a recent intel fortran compiler (ifort) release as well
(it seems to create a memory leak) but it will successfully compile
with ifort, and issues no warnings when compile time warnings are
enabled. I would like to successfully install the most recent version
of gfortran from the development trunk before submitting a bug report,
but as I noted above, I'm having some issues at link time. If anyone is
interested in seeing if the errors go away when a more recent version
of gfortran is used, I will include the code below. You can also
browse the code and comment on it on a gist I created:
https://gist.github.com/zbeekman/e84691492039ebd0c646

module stringhelper_m
! use kinds_m ,only: WP ,WI
implicit none
integer ,parameter :: WP = kind(1.0D0) ,WI = kind(1)
# ifndef TESTING
private
# endif
public :: string_t ,len ,Int2Char ,C2FChar ,ConcatInt!visible for //
work around...
type :: string_t
private
character(:) ,allocatable :: string
contains
procedure :: Get
procedure :: Concat
procedure :: ConcatChars
procedure :: ConcatInt
procedure :: Assign
procedure :: AssignChars
procedure :: Int2String
procedure :: C2FString
generic :: operator(//) => Concat ,ConcatChars ,ConcatInt
generic :: assignment(=) => Assign ,AssignChars ,C2FString ,Int2String
end type
interface string_t
procedure :: StringConstructor
end interface
interface len
pure function strlen(s) bind(c,name='strlen') !Steal std C library
function
use :: iso_c_binding ,only: c_ptr ,c_size_t
implicit none
type(c_ptr) ,intent(in) ,value :: s
integer(c_size_t) :: strlen
end function
end interface
contains
function StringConstructor(string) result(res)
character(*) ,intent(in) :: string
type(string_t) :: res
res%string = string
end function
elemental subroutine Assign(lhs,rhs)
class(string_t) ,intent(inout) :: lhs
class(string_t) ,intent(in) :: rhs
lhs%string = rhs%string !realloc lhs
end subroutine
elemental subroutine AssignChars(lhs,rhs)
class(string_t) ,intent(inout) :: lhs
character(*) ,intent(in) :: rhs
lhs%string = rhs
end subroutine
function C2FChar(c_charptr) result(res)
use iso_c_binding ,only: c_char ,c_ptr ,c_f_pointer
type(c_ptr) ,intent(in) :: c_charptr
character(:) ,allocatable :: res
character(kind=c_char,len=1) ,pointer :: string_p(:)
integer(WI) :: i ,c_str_len
c_str_len = len(c_charptr)
call c_f_pointer(c_charptr,string_p,[c_str_len])
allocate(character(c_str_len) :: res)
forall (i = 1:c_str_len) res(i:i) = string_p(i)
end function
subroutine C2FString(lhs,rhs)
use iso_c_binding ,only: c_char ,c_ptr ,c_f_pointer
class(string_t) ,intent(inout) :: lhs
type(c_ptr) ,intent(in) :: rhs
character(kind=c_char,len=1) ,pointer :: string_p(:)
integer(WI) :: i ,c_str_len
c_str_len = len(rhs)
call c_f_pointer(rhs,string_p,[c_str_len])
if ( allocated(lhs%string) ) then
if (len(lhs%string) /= c_str_len) deallocate(lhs%string)
end if
if ( .not. allocated(lhs%string) ) &
allocate(character(c_str_len) :: lhs%string)
forall (i = 1:c_str_len) lhs%string(i:i) = string_p(i)
end subroutine
elemental function Concat(lhs,rhs) result(res)
class(string_t) ,intent(in) :: lhs ,rhs
class(string_t) ,allocatable :: res
allocate(res,mold=lhs)
res%string = lhs%string // rhs%string
end function
elemental function ConcatChars(lhs,rhs) result(res)
class(string_t) ,intent(in) :: lhs
character(*) ,intent(in) :: rhs
class(string_t) ,allocatable :: res
allocate(res,mold=lhs)
res%string = lhs%string // rhs ! Valgrind seems to think that this
line leaks memory.
end function
elemental function Get(this) result(res)
class(string_t) ,intent(in) :: this
character(:) ,allocatable :: res
res = this%string
end function
elemental function NoDigits(i) result(res)
integer(WI) ,intent(in) :: i
integer(WI) :: res
res = ceiling(log10(real(i,WP)),WI)
end function
elemental function Int2Char(i) result(res)
integer(WI) ,intent(in) :: i
character(:) ,allocatable :: res
allocate(character(NoDigits(i)) :: res)
write(res,'(I0)') i
end function
elemental subroutine Int2String(lhs,rhs)
class(string_t) ,intent(inout) :: lhs
integer(WI) ,intent(in) :: rhs
integer(WI) :: length
length = NoDigits(rhs)
if ( allocated(lhs%string) ) deallocate(lhs%string)
allocate(character(length) :: lhs%string)
write(lhs%string,'(I0)') rhs
end subroutine
elemental function ConcatInt(lhs,rhs) result(res)
class(string_t) ,intent(in) :: lhs
integer(WI) ,intent(in) :: rhs
class(string_t) ,allocatable :: res
integer(WI) :: length
character(:) ,allocatable :: work
allocate(res,mold=lhs)
length = NoDigits(rhs)
allocate(character(length) :: work)
write(work,'(I0)') rhs
res%string = lhs%string // work !realloc lhs
deallocate(work)
end function
end module


--
-Zaak

0 new messages