Intel® Fortran Compiler
Build applications that can scale for the future with optimized code designed for Intel® Xeon® and compatible processors.
29277 Discussions

default initialization of interoperable character components of derived types

Lee_B_1
Beginner
6,322 Views

I noticed recently that intel fortran, about version 15.0.X, has started warning about the length of interoperable character components:

warning #8753: A CHARACTER component of an interoperable derived type must have length 1.   [LIBRARY]
  character(kind=c_char,len=32) :: library = "some name"

The Standard does require that interoperable character variables have len=1, or in other words, a declaration like this: (I wish this worked.)

  (1)  character(kind=c_char, len=1) :: library(32) = "some name" ! Cannot actually initialize a character array like this.

Up to now, I've been skirting the question, because scalar character variables with len>1 "just work", at least for the compilers I'm mostly interested in using.  So the perennial question that I haven't been able to answer is:

How do I assign a sensible default to a character array declared as in (1) above?

To be clear, the statement at (1) will compile, and will dutifully set library to 32 repetitions of the character 's'.  Not sensible.  Or I *could* do it like this:

  (2)  character(kind=c_char, len=1) :: library(32) = [ 's','o','m','e',' ','n','a','m','e' ] ! (In reality, trailing blanks are necessary.)

Also not sensible.  I have tried defining a pure function that converts a scalar string to an array, but the compiler seems to disagree about the legality of such a specification expression.  Am I forgetting something obvious here?  Default values are really kind of important.  Thank you for any comments or guidance on this matter.

0 Kudos
39 Replies
JVanB
Valued Contributor II
4,330 Views

Yeah, I  don't see why a scalar component with any length can't interoperate with a C array of char component like they can as actual and dummy arguments. Seems desirable but maybe it's too hard to fit it into the standard.

A default initializer, just like a plain old initializer, must be an initialization expression; specification expressions aren't good enough.

integer, parameter :: my_component_len = 32
character(len=my_component_len,kind=C_CHAR), parameter :: my_initial_value = 'some name'
...
character(len=1,kind=c_char) :: library(my_component_len) = transfer(my_initial_value,[C_CHAR_'A'])
...

 

0 Kudos
Lee_B_1
Beginner
4,330 Views

Thanks very much for your comments and a *working* demonstration of transfer in this context.  I didn't have the guts to post my own various attempts with transfer (none worked.)  We're getting closer to a usable idiom.  It's still hard to see how to cram everything onto one line, which is the great benefit of default initialization.  Anyway, I am always glad to learn something new about transfer.

0 Kudos
JVanB
Valued Contributor II
4,330 Views

I couldn't see why you put 'working' in quotes. Maybe you wanted it fleshed out with a compilable example. Here is one such with also a one-line version. The one-line version has the problem that I don't think you get to do specification inquiries on the component being initialized because there just isn't any syntax for it. Thus in type T2 the magic number 32 must be there in two places.

module M
   use ISO_C_BINDING
   implicit none
   private
   integer, parameter :: my_component_len = 32
   character(my_component_len,C_CHAR), parameter :: my_initial_value = 'some name'
   type, bind(C), public :: T1
      character(kind=C_CHAR) :: library(my_component_len) = transfer(my_initial_value,['A'])
   end type T1
   type, bind(C), public :: T2
      character(kind=C_CHAR), dimension(32) :: x = reshape(transfer('another name',['A']),[32],pad = [' '])
   end type T2
end module M

program P
   implicit none
   call sub
end program P

subroutine sub
   use M
   implicit none
   type(T1) U1
   type(T2) U2
   write(*,'(*(g0))') U1%library
   write(*,'(*(g0))') U2%x
end subroutine sub

Now, when compiled with gfortran default.f90 -odefault, the resulting default.exe produces the expected:

some name
another name

But ifort /nologo default.f90 yields errors:

default.f90(11): error #6946: In this DATA statement, there are more values assi
gned to variables then there are variables.  There must be the same number of va
lues and variables.   [' ']
      character(kind=C_CHAR), dimension(32) :: x = reshape(transfer('another nam
e',['A']),[32],pad = [' '])
--------------------------------------------------------------------------------
----------------------^
default.f90(21): error #7013: This module file was not generated by any release
of this compiler.   
   use M
-------^
default.f90(23): error #6457: This derived type name has not been declared.   [T
1]
   type(T1) U1
--------^
default.f90(24): error #6457: This derived type name has not been declared.   [T
2]
   type(T2) U2
--------^
default.f90(25): error #6404: This name does not have a type, and must have an e
xplicit type.   [U1]
   write(*,'(*(g0))') U1%library
----------------------^
default.f90(25): error #6460: This is not a field name that is defined in the en
compassing structure.   [LIBRARY]
   write(*,'(*(g0))') U1%library
-------------------------^
default.f90(26): error #6404: This name does not have a type, and must have an e
xplicit type.   [U2]
   write(*,'(*(g0))') U2%x
----------------------^
default.f90(26): error #6460: This is not a field name that is defined in the en
compassing structure.   
   write(*,'(*(g0))') U2%x
-------------------------^
compilation aborted for default.f90 (code 1)

I don't know whether the Intel Fortran developers are working to ameliorate this situation.

 

0 Kudos
JVanB
Valued Contributor II
4,330 Views

Ooh... I though I had it with a helper parameterized derived type:

module M
   use ISO_C_BINDING
   implicit none
!   private
   type Lemma1(K)
      integer, KIND :: K
      character(len = K, kind = C_CHAR) C
   end type Lemma1
   type, bind(C), public :: T3
      character(kind=C_CHAR), dimension(32) :: library = transfer(Lemma1(K=32)(C='some name'),['A'])
   end type T3
end module M

program P
   use M
   implicit none
   write(*,'(*(g0))') Lemma1(K=32)(C='some name')
   write(*,'(*(g0))') len(transfer(Lemma1(K=32)(C='some name'),['A']))
   write(*,'(*(g0))') size(transfer(Lemma1(K=32)(C='some name'),['A']))
   write(*,'(*(g0))') transfer(Lemma1(K=32)(C='some name'),['A'])
   call sub
end program P

subroutine sub
   use M
   implicit none
   type(T3) U3
   write(*,'(*(g0))') U3%library
end subroutine sub

But the output with ifort is:

some name
1
32
some name
ssssssssssssssssssssssssssssssss

Do I just not understand PDTs, or is this another compiler bug?

 

0 Kudos
JVanB
Valued Contributor II
4,330 Views

Hey, I finally found one that ifort likes!

module M
   use ISO_C_BINDING
   implicit none
   private
   type, bind(C), public :: T4
      character(kind=C_CHAR), dimension(32) :: library = transfer([character(32)::'some name'],['A'])
   end type T4
end module M

program P
   implicit none
   call sub
end program P

subroutine sub
   use M
   implicit none
   type(T4) U4
   write(*,'(*(g0))') U4%library
end subroutine sub

Third time's the charm, I suppose.

 

0 Kudos
JVanB
Valued Contributor II
4,330 Views

It turns out that a PDT isn't necessary to demonstrate the fault in Quote #5.

module M
   use ISO_C_BINDING
   implicit none
   type Lemma2
      character(len = 32, kind = C_CHAR) C
   end type Lemma2
   type, bind(C), public :: T3
      character(kind=C_CHAR), dimension(32) :: library = transfer(Lemma2(C='some name'),['A'])
   end type T3
end module M

program P
   use M
   implicit none
   type(Lemma2), parameter :: y1 = Lemma2(C='some name')
   character, parameter :: y2(32) = transfer(y1,['A'])
   character y3(32)
   write(*,'(*(g0))') 'y1 = ',y1
   write(*,'(*(g0))') 'y2 = ',y2
   y3 = transfer(y1,['A'])
   write(*,'(*(g0))') 'y3 = ',y3
   call sub
end program P

subroutine sub
   use M
   implicit none
   type(T3) U3
   write(*,'(*(g0))') 'U3%library = ',U3%library
end subroutine sub

Output with ifort:

y1 = some name
y2 = ssssssssssssssssssssssssssssssss
y3 = some name
U3%library = ssssssssssssssssssssssssssssssss

Output with gfortran:

y1 = some name
y2 = some name
y3 = some name
U3%library = some name

So it was the TRANSFER from a derived type to a character array in an initialization expression that caused the fault. Same thing in an ordinary expression was no problem. TRANSFER from other things to a character array, even in an initialization expression may still be OK, see Quote #6.

 

0 Kudos
JVanB
Valued Contributor II
4,330 Views

Sorry, it's too smoky out to be my avatar.jpg, so I had another couple of attempts, even though I found success in Quote #6. I thought maybe Hollerith constants would be OK because you could just append lots of spaces without counting provided that you had at least as many as required. Unfortunately if any characters after the fourth of a Hollerith constant are non-blank, it is unusable as the SOURCE= argument to TRANSFER.

program P
   implicit none
   write(*,*) 5H12345
   write(*,*) transfer('12345',['A'])
   write(*,*) transfer(4H1234,['A'])
   write(*,*) transfer(5H1234 ,['A'])
!   write(*,*) transfer(5H    5,['A'])
end program P

Works with output,

 12345
 12345
 1234
 1234

But if that fateful line is uncommented, the output with ifort /nologo def3a.f90 is:

def3a.f90(7): error #6043: This Hollerith or character constant is too long and
cannot be used in the current numeric context.   [5H    5]
   write(*,*) transfer(5H    5,['A'])
-----------------------^
compilation aborted for def3a.f90 (code 1)

Another possibility was to go back to TRANSFER and RESHAPE, but to append enough spaces to the SOURCE= argument to RESHAPE that the PAD= argument, which seemed to cause difficulties before, would be unnecessary. This also led to errors:

program P
   implicit none
   character(44), parameter :: x = 'Hello, world'//repeat(' ',32)
   character, parameter :: z(44) = transfer(x,['A'])
   character y(32)
!   character, parameter :: w(44) = transfer('Hello, world'//repeat(' ',32),['A'])
   write(*,*) x
   y = reshape(transfer('Hello, world'//repeat(' ',32),['A']),[32])
   write(*,*) y
   write(*,*) z
!   write(*,*) w
end program P

With output:

 Hello, world
 Hello, world
 Hello, world

But if the 'w' lines are uncommented, we get, with ifort /nologo def1a.f90:

def1a.f90(6): error #6258: The CHARACTER string result is greater than 7198 char
acters.   [32]
   character, parameter :: w(44) = transfer('Hello, world'//repeat(' ',32),['A']
)
-----------------------------------------------------------------------^
def1a.f90(6): error #6366: The shapes of the array expressions do not conform.
 
   character, parameter :: w(44) = transfer('Hello, world'//repeat(' ',32),['A']
)
---------------------------^
compilation aborted for def1a.f90 (code 1)

So it seems that the two-step initialization expression is OK, the one-step ordinary expression is OK, but the one-step initialization expression causes a failure. So fa, one success, three failures requiring initialization expressions, and one failure for an ordinary expression.

 

0 Kudos
JVanB
Valued Contributor II
4,330 Views

I had another thought (about this bordering on compulsive behavior? :) ) about using the SIZE= argument to TRANSFER so as to do away with the RESHAPE part entirely.

program P
   implicit none
   character(44), parameter :: x = 'Hello, world'//repeat(' ',32)
   character, parameter :: z(32) = transfer(x,'A',32)
   character y(32)
   character, parameter :: w(12) = transfer('Hello, world','A',12)
   write(*,*) x
   y = transfer('Hello, world'//repeat(' ',32),'A',32)
   write(*,*) y
   write(*,*) z
   write(*,*) w
end program P

Output with gfortran:

 Hello, world
 Hello, world
 Hello, world
 Hello, world

Output with ifort:

 Hello, world
 Hello, world
 HHHHHHHHHHHHHHHHHHHHHHHHHHHHHHHH
 HHHHHHHHHHHH

So even in relatively simple contexts, the SIZE= argument to TRANSFER in initialization expressions is resulting in incorrect values being generated.

 

0 Kudos
JVanB
Valued Contributor II
4,330 Views

A seventh syntax. Works with gfortran, fails with ifort:

module M
   use ISO_C_BINDING
   implicit none
   private
   type, bind(C), public :: T7
      character(kind=C_CHAR), dimension(32) :: x = pack(transfer('Hello, world',['A']),.TRUE.,transfer(repeat(' ',32),['A']))
   end type T7
end module M

program P
   implicit none
   call sub
end program P

subroutine sub
   use M
   implicit none
   type(T7) U7
   write(*,'(*(g0))') U7%x
end subroutine sub

But to be fair, transformational intrinsics that were not allowed in initialization expressions in f95 are documented as being only partially implemented in current ifort initialization expressions.

 

0 Kudos
Steven_L_Intel1
Employee
4,330 Views

I'll be working through RO's various test cases today and submitting bug reports where needed.

#4 - DPD200375283
#5 - DPD200375290 (As RO notes, the PDT is not needed)
#8 - This is documented behavior:

  • When the length of the constant is greater than the length implied by the data type, the constant is truncated on the right. If any characters other than blank characters are truncated, a warning occurs.

I do find it interesting that it's an error and not a warning, but I can't get too excited about this.
#9 - I decided this was the same general issue as #5 and attached it to that report.
#10 - DPD200375286
#12 - 
DPD200375296

others tbs

0 Kudos
FortranFan
Honored Contributor III
4,330 Views

Steve Lionel (Intel) wrote:

I'll be working through RO's various test cases today and submitting bug reports where needed.

Steve,

My apologies for trying to pile on the bug reports you plan to work through today for RO, but his usual brilliant self had me trying one thing out this morning which resulted in an ICE and I feel compelled to report it, hope you won't mind adding this too to your list :-) 

program p

   use, intrinsic :: iso_c_binding, only : c_char, c_null_char

   implicit none

   integer :: I
   integer, parameter :: LEN_LIBRARY = 32
   character(len=LEN_LIBRARY, kind=c_char), parameter :: STR = c_char_"some name"
   character(len=1, kind=c_char), parameter :: library(LEN_LIBRARY) = transfer( STR,                &
                                                mold=[ ( c_null_char, I = 1, LEN_LIBRARY) ] )

   print *, " size(library) = ", size(library)
   print *, " library = ", library

   stop

end program p
Compiling with Intel(R) Visual Fortran Compiler 16.0.0.063 [Intel(R) 64]...
p.f90
fortcom: Fatal: There has been an internal compiler error (C0000094).
compilation aborted for p.f90 (code 1)

FWIW, the above code compiles and runs ok with gfortran (GCC 6.0 development trunk).

 

0 Kudos
FortranFan
Honored Contributor III
4,330 Views

Steve Lionel (Intel) wrote:

I'll be working through RO's various test cases today and submitting bug reports where needed.

Steve,

Separately, RO's posts inspired me to try several variations, all of which work in gfortran, but none in Intel Fortran, compiler 16, update 2.  My attempts all appear to be standard-conforming (at least per my read of transformational intrinsics in 2008 standard) and they seem to me to be sufficiently different enough from RO's cases that makes me think Intel compiler might benefit if these additional cases were also looked at by you/Intel and worked upon where needed.  But I'm not 100% confident.  And you already have your hands full with so many cases from RO that I'm hesitant to report my variations.  If you and your colleagues feel differently and think "more cases the better" for the Intel compiler product, let me know and I can work toward reporting all I found.  To get a better feel for my attempts, here's one quick one:

program p

   use, intrinsic :: iso_c_binding, only : c_char, c_null_char

   implicit none

   integer, parameter :: LEN_LIBRARY = 32
   character(len=1,kind=c_char), parameter :: library(LEN_LIBRARY) = transfer( "some name",           &
                                                                                mold=[ c_null_char ], &
                                                                                size=LEN_LIBRARY )

   print *, " size(library) = ", size(library)
   print *, " library = ", library

   stop

end program p

Upon execution with gfortran,

  size(library) =           32
  library = some name

Upon execution with Intel Fortran, compiler 16 (update 2),

  size(library) =  32
  library = ################################
Press any key to continue . . .

By the way, Intel compiler did warn, "warning #7748: Since the physical representation of the result is shorter than that of SOURCE, the physical representation of the result is the leading part of SOURCE." and I do appreciate the fact some processor dependence aspect may be coming into the above case since the standard does say for the TRANSFER instrinsic: 

27 representation of the result is that of SOURCE. If the physical representation of the result is longer than that
28 of SOURCE, the physical representation of the leading part is that of SOURCE and the remainder is processor
29 dependent. If the physical representation of the result is shorter than that of SOURCE, the physical representation
30 of the result is the leading part of SOURCE. If D and E are scalar variables such that the physical representation

but I am not sure Intel compiler has got it all correct.   It can be a lot of effort though to review such variations.

Thanks much,

0 Kudos
Steven_L_Intel1
Employee
4,330 Views

The more the merrier. I suspect some of these are the same problem underneath, but one never knows.

0 Kudos
JVanB
Valued Contributor II
4,330 Views

The ICE in Quote #12 is new. C0000094 is integer division by zero, which is what you get for violating F08/0137. However, the code in Quote #12 doesn't violate F08/0137, but is strange in that the shape of the array doesn't matter for the MOLD= argument to TRANSFER, but putting that ac-implied-do in that initialization expression looks like it may be responsible for the ICE even so.

Quote #13 is the same as Quote #9: SIZE= argument to TRANSFER present in an initialization expression.

For any of these tests to work in gfortran doesn't necessarily imply that they work in gfortran :)

My perception is that gfortran is a little loose about the way it implements initialization expressions and differentiates them from ordinary expressions. If you want to be sure that gfortran is using its initialization expression mechanism, make a KIND number depend at least syntactically on the result of the expression. Similarly, if you want to make certain that it's applying its ordinary expression mechanism, make the expression depend on something that the compiler doesn't know in advance, such as a procedure argument. I would say that the gfortran developers aren't always careful about this distinction, and in particular there are some tests which straddle the borderline between specification expressions and initialization expressions that gfortran doesn't do anything useful with.

ifort seems to evaluate expressions with a little prejudice in that initialization expressions in the executable-part get handled differently from initialization expressions in the specification-part. Thus you may encounter a bug which shows itself in one context but not another. These compiler variations make it trickier to get good test coverage for initialization expressions.

Thanks, Steve, for looking into these issues.

 

0 Kudos
FortranFan
Honored Contributor III
4,330 Views

Repeat Offender wrote:

..

Quote #13 is the same as Quote #9: SIZE= argument to TRANSFER present in an initialization expression.

For any of these tests to work in gfortran doesn't necessarily imply that they work in gfortran :)

My perception is that gfortran is a little loose about the way it implements initialization expressions ..

I read the code in Quote #9 to have a scalar MOLD, so I tried an array MOLD in combination with SIZE.  Since the standard mentions 3 different cases for TRANSFER intrinsic, I was wondering if the compiler development team had interpreted it any different from other views on that function.

Yes, something in gfortran doesn't mean it is correct; it is simply another data point, to be used or discarded.

 

0 Kudos
Steven_L_Intel1
Employee
4,330 Views

I've updated post 11 with all the issue numbers. RO is correct that the #12 case has relevance to F08/0137 and also that this example doesn't violate the rule in that interp. We did change the compiler (for a future release) to follow F08/0137 but with that change, the test in #12 gives an inappropriate error.

RO also correctly observes that ifort handles constant expressions in contexts where they are required (such as in KIND numbers) differently than in other contexts.

I think I had better quit for the day before the developers form a lynch party for me....

0 Kudos
Lee_B_1
Beginner
4,330 Views

To follow up on my original post from last Friday, I'm grateful for the extended discussion of this topic.  Apologies to Repeat Offender for not being more clear in my use of the word working.  I quoted it using the old-style star '*' character to emphasize that I had in fact tried out your suggestion, and compiled and ran it successfully, unlike my own feeble efforts with transfer.  A couple of your later suggestions are even nicer in that they didn't use a separate parameter:

  (A) character(len=1, kind=c_char) :: library(16) = transfer([character(16)::"a test"],['a'])

  (B) character(len=1, kind=c_char) :: library(16) = reshape(transfer('a test2',['a']),[16],pad = [' '])

I especially like (B).  It's a little strange looking, but uses familiar intrinsics in the expected fashion.  It just has good intentions.  Sadly, ifort has that little  #6946 problem with (B).  Either (A) or (B) would be quite usable, if you're willing to wrap them in a macro, which I am.  I did test (A) and (B) against a variety of versions of gfortran, ifort, and pgfortran (Portland Group.)  Gfortran appeared to succeed on both (A) and (B), for 9 versions ranging from 4.4.6 through 4.9.3.  Nineteen versions of ifort, from 11.1.046 through 15.0.187 worked on (A), but uniformly failed for (B) (#6946).  Portland Group seems to work with (B) for 12 versions beginning with 11.1, ending with 15.5, and it works for (A) for versions 11.1 through 13.6.  However, pgfortran starts putting in random trailing characters in the string initialized with (A), beginning at 14.10 through 15.5.

So the search for an idiomatic, correct enough approach to default initialize a character array continues.

0 Kudos
JVanB
Valued Contributor II
4,330 Views

Referring back to Quote #8, there were actually two errors there. The first one dealt with Hollerith constants where the murky piece of documentation https://software.intel.com/en-us/node/510956 details the extension. For actual arguments, "For Hollerith constants, a numeric data type of sufficient size to hold the length of the constant is assumed." And an example where the argument is converted to REAL(16) is shown. From that example, I don't see why 5H12345 isn't converted to INTEGER(8) or even CHARACTER(5), which would be the case in a WRITE statement. By that documentation one might think that the Hollerith constant as an actual argument might get converted to something that could be used for generic resolution, but...

module M
   use ISO_FORTRAN_ENV
   implicit none
!   private
   public sub
   interface sub
      module procedure subc,subi4,subi8,subr8,subr16
   end interface sub
   contains
      subroutine subc(x)
         character(*) x
         write(*,'(*(g0))') 'subroutine subc was called'
         write(*,'(*(g0))') 'len(x) = ',len(x)
         write(*,'(*(g0))') 'x = ',x
      end subroutine subc
      subroutine subi4(x)
         integer(INT32) x
         write(*,'(*(g0))') 'subroutine subi4 was called'
         write(*,'(*(g0))') 'kind(x) = ',kind(x)
         write(*,'(a,A4)') 'x = ',x
      end subroutine subi4
      subroutine subi8(x)
         integer(INT64) x
         write(*,'(*(g0))') 'subroutine subi8 was called'
         write(*,'(*(g0))') 'kind(x) = ',kind(x)
         write(*,'(a,A8)') 'x = ',x
      end subroutine subi8
      subroutine subr8(x)
         real(REAL64) x
         write(*,'(*(g0))') 'subroutine subr8 was called'
         write(*,'(*(g0))') 'kind(x) = ',kind(x)
         write(*,'(a,A8)') 'x = ',x
      end subroutine subr8
      subroutine subr16(x)
         real(REAL128) x
         write(*,'(*(g0))') 'subroutine subr16 was called'
         write(*,'(*(g0))') 'kind(x) = ',kind(x)
         write(*,'(a,A16)') 'x = ',x
      end subroutine subr16
end module M

program P
   use M
   implicit none
!   call sub(5H12345)
   call subc(5H12345)
   call subi4(5H12345)
   call subi8(5H12345)
   call subr8(5H12345)
   call subr16(5H12345)
end program P

When this program is executed as is, we get an error at run-time:

subroutine subc was called
len(x) = 5
x = 12345
subroutine subi4 was called
kind(x) = 4
x = 1234
subroutine subi8 was called
kind(x) = 8
x = 12345
subroutine subr8 was called
kind(x) = 8
x = 12345
subroutine subr16 was called
kind(x) = 16
forrtl: severe (157): Program Exception - access violation
Image              PC                Routine            Line        Source

hollerith.exe      00007FF628DC1756  Unknown               Unknown  Unknown
hollerith.exe      00007FF628E1726E  Unknown               Unknown  Unknown
hollerith.exe      00007FF628E013BB  Unknown               Unknown  Unknown
KERNEL32.DLL       00007FF8145C13D2  Unknown               Unknown  Unknown
ntdll.dll          00007FF814915454  Unknown               Unknown  Unknown

And when the generic invocation is uncommented, ifort /nologo Hollerith.f90 yields:

hollerith.f90(45): error #6285: There is no matching specific subroutine for thi
s generic subroutine call.   [SUB]
   call sub(5H12345)
--------^
compilation aborted for hollerith.f90 (code 1)

When one might expect perhaps subi8 to get invoked. Can conversion of Hollerith constants go all the way up to COMPLEX(16)? The documentation doesn't say.

As for the second half of Quote #8, I would say that getting error #6258 is very suspicious:

def1a.f90(6): error #6258: The CHARACTER string result is greater than 7198 char
acters.   [32]
   character, parameter :: w(44) = transfer('Hello, world'//repeat(' ',32),['A']
)
-----------------------------------------------------------------------^

So it seems to me that this may be a different class of error than the ones already reported in Quote #11.

 

0 Kudos
Steven_L_Intel1
Employee
4,330 Views

Second half of #8 escalated as DPD200375302.

As for Hollerith constants, look at the documentation topic "Determining the Data Type of Nondecimal Constants".

For Hollerith constants, a numeric data type of sufficient size to hold the length of the constant is assumed.

I'll take a closer look at your example.

0 Kudos
FortranFan
Honored Contributor III
4,201 Views

Steve,

What's it about the 6946 error in message #4 and message #18?  Is it something to do with compiler options and/or version?  I ask because I don't get that error with standard-semantics and compiler 16, update 2: this was one of the variations I mentioned earlier today.

program p

   use, intrinsic :: iso_c_binding, only : c_char, c_null_char

   implicit none

   integer, parameter :: LEN_LIBRARY = 32
   character(len=*, kind=c_char), parameter :: C_SPACE = c_char_" "
   character(len=1,kind=c_char), parameter :: library(LEN_LIBRARY) =                                &
      reshape(transfer( "some name", mold=[ c_null_char ] ), shape=[ LEN_LIBRARY  ],                &
              pad = [ C_SPACE ] )

   print *, " size(library) = ", size(library)
   print *, " library = ", library

   stop

end program p

With standard-semantics, the code compiles fine but the execution result is an arry constant all filled with blanks.  FWIW, gfortran gives an array filled with "s", "o", "m", .. and padded with blanks.

0 Kudos
Reply