- Mark as New
- Bookmark
- Subscribe
- Mute
- Subscribe to RSS Feed
- Permalink
- Report Inappropriate Content
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.
Link Copied
- « Previous
-
- 1
- 2
- Next »
- Mark as New
- Bookmark
- Subscribe
- Mute
- Subscribe to RSS Feed
- Permalink
- Report Inappropriate Content
FortranFan, I get errors from the program posted in reply 4. The difference between that and the one you have here is that the reply 4 code is for a component in a derived type where the one in reply 21 does not. However, it is clear that we have a general problem with TRANSFER here and it's being looked at.
- Mark as New
- Bookmark
- Subscribe
- Mute
- Subscribe to RSS Feed
- Permalink
- Report Inappropriate Content
Reconsidering Hollerith as in the first half of Quote #8, it seems that the possibilities are either to document the behavior as bug-compatible with some version of ifort (requires a small book of new docs), redesign Hollerith to something sensible and rewrite docs accordingly and fix compiler deviations from new design, or to just leave it as is, only fixing bugs as defined by influential customers.
Given limited resources and the low utility of any work expended on Hollerith, the last option does indeed seem quite sensible. I append a program which is consistent with the documentation for Hollerith:
program P use ISO_FORTRAN_ENV, only: INT64 implicit none write(*,*) '4H{|}~ < 2123456789',' is ',trim(merge('.TRUE. ','.FALSE.',4H{|}~ < 2123456789)) write(*,*) '4H{|}~ > 2123456789123456789_INT64',' is ',trim(merge('.TRUE. ','.FALSE.',4H{|}~ > 2123456789123456789_INT64)) write(*,*) '4H{|}~ > 8.0e37',' is ',trim(merge('.TRUE. ','.FALSE.',4H{|}~ > 8.0e37)) write(*,*) '4H{|}~ < 7.0d-154',' is ',trim(merge('.TRUE. ','.FALSE.',4H{|}~ < 7.0d-154)) end program P
Output:
4H{|}~ < 2123456789 is .TRUE. 4H{|}~ > 2123456789123456789_INT64 is .TRUE. 4H{|}~ > 8.0e37 is .TRUE. 4H{|}~ < 7.0d-154 is .TRUE.
- Mark as New
- Bookmark
- Subscribe
- Mute
- Subscribe to RSS Feed
- Permalink
- Report Inappropriate Content
Lee B. wrote:
..
(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). ..
@Lee B.,
Are you doing your tests with a derived type component? See Message #21. I ask because I do not get error #6946 with Intel Fortran, only incorrect execution. You didn't indicate derived type in your original post nor in your Message #18, so I would have expected your response to be the same as what I see in Message #21, but doesn't seem to be case.
- Mark as New
- Bookmark
- Subscribe
- Mute
- Subscribe to RSS Feed
- Permalink
- Report Inappropriate Content
Fortran Fan asked whether I have been testing with a derived type component. Yes, all my own testing has been done with a derived type component. I apologize for not making that more clear. Aside from the original title of the thread, I have glossed over that detail, and it does seem to produce different outcomes. I also don't have access to version 16 of ifort. Versions 10-15 at least seemed very consistent in giving error 6946 for the syntax in example (B).
- Mark as New
- Bookmark
- Subscribe
- Mute
- Subscribe to RSS Feed
- Permalink
- Report Inappropriate Content
Lee B. wrote:
Fortran Fan asked whether I have been testing with a derived type component. Yes, all my own testing has been done with a derived type component. I apologize for not making that more clear. Aside from the original title of the thread, I have glossed over that detail, and it does seem to produce different outcomes. I also don't have access to version 16 of ifort. Versions 10-15 at least seemed very consistent in giving error 6946 for the syntax in example (B).
Thanks for the clarification. And oops, sorry for not reading carefully - it's really my bad! I missed out on the title altogether and you did make a mention in the original post.
- Mark as New
- Bookmark
- Subscribe
- Mute
- Subscribe to RSS Feed
- Permalink
- Report Inappropriate Content
Quote #18 called once again for the release of the kraken, but I've pretty much emptied my bag of tricks at this point. Well, there is the possibility that it would be acceptable to use the string twice in the expression because it's going to be inserted via a macro in any case. First we review what easy ways we have to construct the necessary blanks:
module M implicit none private integer i type, bind(C), public :: T character :: a(32) = spread(' ',1,32) character :: b(32) = [(' ',i=1,32)] character :: c(32) = transfer(repeat(' ',32),['A']) character :: d(32) = reshape([' '],[32],pad=[' ']) end type T end module M program P implicit none call sub end program P subroutine sub use M implicit none type(T) U write(*,'(*(g0))') '#',U%a,'#' write(*,'(*(g0))') '#',U%b,'#' write(*,'(*(g0))') '#',U%c,'#' write(*,'(*(g0))') '#',U%d,'#' end subroutine sub
ifort says:
blank.f90(6): error #6263: This intrinsic function is invalid in constant expres sions. [SPREAD] character :: a(32) = spread(' ',1,32) ---------------------------^ blank.f90(6): error #6973: This is not a valid initialization expression. [SPR EAD] character :: a(32) = spread(' ',1,32) ---------------------------^ blank.f90(8): error #6258: The CHARACTER string result is greater than 7198 char acters. [32] character :: c(32) = transfer(repeat(' ',32),['A']) -----------------------------------------------^ blank.f90(8): error #7948: In this initialization, there are more variables than values assigned to the variables.character :: c(32) = transfer(repeat(' ',32),['A']) -------------------^ compilation aborted for blank.f90 (code 1)
So SPREAD is out (because it's a transformational intrinsic not allowed in f95 initialization expressions: documented) and TRANSFER(REPEAT... is out (second half of Quote #8). We move on with what we have left:
module M implicit none private integer i type, bind(C), public :: T character :: a(32) = [transfer('Hello, world',['A']),(' ',i=1,32-len('Hello, world'))] character :: b(32) = eoshift([(' ',i=1,32)],-len('Hello, world'),boundary=transfer('Hello, world',['A'])) character :: c(32) = [transfer('Hello, world',['A']),reshape([' '],[32-len('Hello, world')],pad=[' '])] character :: d(32) = eoshift(reshape([' '],[32-len('Hello, world')],pad=[' ']),-len('Hello, world'),transfer('Hello, world',['A'])) end type T end module M program P implicit none call sub end program P subroutine sub use M implicit none type(T) U write(*,'(*(g0))') '#',U%a,'#' write(*,'(*(g0))') '#',U%b,'#' write(*,'(*(g0))') '#',U%c,'#' write(*,'(*(g0))') '#',U%d,'#' end subroutine sub
ifort says:
def4a.f90(7): error #6263: This intrinsic function is invalid in constant expres sions. [EOSHIFT] character :: b(32) = eoshift([(' ',i=1,32)],-len('Hello, world'),boundary= transfer('Hello, world',['A'])) ---------------------------^ def4a.f90(7): error #6973: This is not a valid initialization expression. [EOS HIFT] character :: b(32) = eoshift([(' ',i=1,32)],-len('Hello, world'),boundary= transfer('Hello, world',['A'])) ---------------------------^ def4a.f90(9): error #6263: This intrinsic function is invalid in constant expres sions. [EOSHIFT] character :: d(32) = eoshift(reshape([' '],[32-len('Hello, world')],pad=[' ']),- len('Hello, world'),transfer('Hello, world',['A'])) ---------------------^ def4a.f90(9): error #6973: This is not a valid initialization expression. [EOS HIFT] character :: d(32) = eoshift(reshape([' '],[32-len('Hello, world')],pad=[' ']),- len('Hello, world'),transfer('Hello, world',['A'])) ---------------------^ compilation aborted for def4a.f90 (code 1)
So EOSHIFT is out for the same reason as SPREAD. Fine.
module M implicit none private integer i type, bind(C), public :: T character :: a(32) = [transfer('Hello, world',['A']),(' ',i=1,32-len('Hello, world'))] character :: b(32) = [transfer('Hello, world ',['A'])] character :: c(32) = [transfer('Hello, world',['A']),reshape([' '],[32-len('Hello, world')],pad=[' '])] character :: d(32) = transfer('Hello, world ',['A']) end type T end module M program P implicit none call sub end program P subroutine sub use M implicit none type(T) U write(*,'(*(g0))') '#',U%a,'#' write(*,'(*(g0))') '#',U%b,'#' write(*,'(*(g0))') '#',U%c,'#' write(*,'(*(g0))') '#',U%d,'#' end subroutine sub
Now this compiles, but we get
#N # #N # #NN # #Hello, world #
So just putting that TRANSFER inside array constructor brackets was enough to trigger a bug. I seem to be running out of ideas. Perhaps the O.P. could submit a bug report to pgfortran or use the macro to detect whether or not ifort is the compiler and choose between the possible syntaxes accordingly.
- Mark as New
- Bookmark
- Subscribe
- Mute
- Subscribe to RSS Feed
- Permalink
- Report Inappropriate Content
Lee B. wrote:
.. 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).. So the search for an idiomatic, correct enough approach to default initialize a character array continues.
@Lee B.,
Re: your comment about "the search for an idiomatic, correct enough approach to default initialize a character array continues," I suggest you post this quest on comp.lang.fortran as well and seek feedback on possible approaches that, per the experts who contribute to that forum, conform to current Fortran standard. That is, seek a wider view on all the effort RO has taken for you in this thread. You can then develop an idiom from the list of possible, standard-conforming approaches. It's likely the compilers you use fail with some or all of the possible approaches that get revealed, but as you know, that will only mean the compilers need fixing (like how Steve has followed up here with bug incident submissions) and not that the approaches are incorrect.
By the way, I personally would prefer (A) over (B) above; to me, it comes across as simpler.
Separately, since you mention the character array is a derived type component and chances are your derived type as other components as well, have you considered initialization procedures (possibly as type-bound procedures) and/or defined constructors as an alternate way to approach this issue?
- Mark as New
- Bookmark
- Subscribe
- Mute
- Subscribe to RSS Feed
- Permalink
- Report Inappropriate Content
Repeat Offender suggested that I should notify Portland Group about what appears to be a regression in their compiler, and I agree, and I will do that. For now, the best syntax for me, in the sense of most widely applicable, seems to be what I earlier called variant (A):
character(len=1, kind=c_char) :: library(16) = transfer([character(16)::"a test"],['a'])
This is easy to wrap in a macro, and (I think, haven't actually done it yet) easy to conditionally switch out for (B) if pgfortran is in use.
I have also gone on to test against a couple of versions of IBM's xlf compiler. And a good thing. That compiler strictly adheres to the Standard with respect to the len=1 question for interoperable components. I.e., it's a fatal error to use anything other than len=1 for xlf. Recall that ifort 15.X only warns, but that was enough to prompt my original posting. Thankfully, xlf also seems happy with variant (A) as above. To summarize, variant (A) also works with a broad selection of gfortran, ifort, and pgfortran versions, although pgfortran seems to add trailing junk starting with their version 14.x.
Thanks to all once again for the many good ideas on how to "find the corners" of this particular problem.
- Mark as New
- Bookmark
- Subscribe
- Mute
- Subscribe to RSS Feed
- Permalink
- Report Inappropriate Content
FortranFan had some additional suggestions, and thank you. Comp.lang.fortran looks like it's in my future, yes. Regarding other approaches to initialization, I do of course have some other choices. There is a strong requirement for interoperability with C. The macro(s) I mentioned earlier will in fact generate a typedef for C, and a "type, bind(c) :: ..." declaration for Fortran. I think the interoperability requirement limits me to static declarations, and also cannot use type-bound procedures. I also want the variables to be accessible to a Fortran namelist statement, which generally means Fortran strings, no pointers, no allocatables, etc. It's a fairly tight box I have put myself in. Fortran default initialization of derived type components would be a very nice feature to include, if possible, because that lets me put all the relevant information about a given variable, accessible to both languages, on a single line.
- Mark as New
- Bookmark
- Subscribe
- Mute
- Subscribe to RSS Feed
- Permalink
- Report Inappropriate Content
Lee B. wrote:
FortranFan had some additional suggestions, and thank you. Comp.lang.fortran looks like it's in my future, yes. Regarding other approaches to initialization, I do of course have some other choices. There is a strong requirement for interoperability with C. The macro(s) I mentioned earlier will in fact generate a typedef for C, and a "type, bind(c) :: ..." declaration for Fortran. I think the interoperability requirement limits me to static declarations, and also cannot use type-bound procedures. I also want the variables to be accessible to a Fortran namelist statement, which generally means Fortran strings, no pointers, no allocatables, etc. It's a fairly tight box I have put myself in. Fortran default initialization of derived type components would be a very nice feature to include, if possible, because that lets me put all the relevant information about a given variable, accessible to both languages, on a single line.
I suggest you keep an eye on Fortran 2015 features for enhanced interoperability with C which allows more flexibility; you may know Intel Fortran has begun introducing some of Fortran 2015 features starting with their upcoming compiler 16 release and more may be coming. Of course, you have other constraints as well in terms of Fortran namelist and so forth, but the C aspect may get more relaxed over time.
Perhaps for the use case of interest to you now, the constructor option too may not be of interest but it may be useful to you in some other scenarios in the future:
module m use, intrinsic :: iso_c_binding, only : c_char implicit none private integer, parameter, public :: LEN_LIBRARY = 32 character(len=*, kind=c_char), parameter :: C_SPACE = c_char_" " type, public, bind(c) :: t character(len=1, kind=c_char) :: library(LEN_LIBRARY) = C_SPACE end type t interface t module procedure construct_t end interface contains pure function construct_t( str ) result(new_t) !.. Argument list character(len=*), intent(in) :: str !.. function result type(t) :: new_t !.. local variables integer :: I !.. Checks for string length elided forall (I = 1:LEN(str) ) new_t%library(I) = str(I:I) end forall !.. return end function construct_t end module m
program p
use m, only : t implicit none type(t) :: foo type(t) :: bar foo = t( "foo" ) print *, " size(foo%library) = ", size(foo%library) print *, " foo%library = ", foo%library bar = t( "bar" ) print *, " size(bar%library) = ", size(bar%library) print *, " bar%library = ", bar%library stop end program p
size(foo%library) = 32 foo%library = foo size(bar%library) = 32 bar%library = bar Press any key to continue . . .
- Mark as New
- Bookmark
- Subscribe
- Mute
- Subscribe to RSS Feed
- Permalink
- Report Inappropriate Content
Version 16 is available now, and it has all of the TS29113 C interoperability features to be in Fortran 2015. While one can now have non-1-length character variables be interoperable, they get passed by "C descriptor" which requires code changes on the C side.
- Mark as New
- Bookmark
- Subscribe
- Mute
- Subscribe to RSS Feed
- Permalink
- Report Inappropriate Content
Tried version 16. It seems to take all the transformational intrinsics in initialization expressions now. Doesn't help because PACK now gives an ICE, and although SPREAD works the code using it fails due to TRANSFER. I don't know what I was thinking with EOSHIFT. For a rank-1 ARRAY= argument, the BOUNDARY= argument, if present, must be scalar, so that doesn't help us to shift in 'Hello, world'.
- Mark as New
- Bookmark
- Subscribe
- Mute
- Subscribe to RSS Feed
- Permalink
- Report Inappropriate Content
A fix for REPEAT (issues DPD200375286 and DPD200375302 ) has been made and I expect it to appear in Update 1.
- Mark as New
- Bookmark
- Subscribe
- Mute
- Subscribe to RSS Feed
- Permalink
- Report Inappropriate Content
Good that your team is picking these off, Steve. I noticed that I didn't get a DPD for TRANSFER in an array constructor (Quote #27).
module M implicit none integer, private :: i type, bind(C) :: T1 character :: a(32) = [transfer('Hello, world',['A']),(' ',i=1,32-len('Hello, world'))] end type T1 !DEC$ IF DEFINED(ALLOW_T2) type :: T2 character(4) :: a(8) = [character(4) :: (repeat(achar(64+i),i),i=1,8)] end type T2 !DEC$ ENDIF end module M program P implicit none call sub end program P subroutine sub use M implicit none BLOCK type(T1) U1 write(*,'(*(g0))') 'U1%a = ',U1%a END BLOCK !DEC$ IF DEFINED(ALLOW_T2) BLOCK type(T2) U2 write(*,'(*(g0))') 'U2%a = ',U2%a END BLOCK !DEC$ ENDIF end subroutine sub
Gets(with ifort /nologo def.f90)
U1%a = N
Also does the fix for REPEAT get the rather more complicated syntax in the above code if compiled with
ifort /nologo /DALLOW_T2 def.f90
Currently it errors out with #6258:
def.f90(9): error #6258: The CHARACTER string result is greater than 7198 charac ters. character(4) :: a(8) = [character(4) :: (repeat(achar(64+i),i),i=1,8)] -----------------------------------------------^
- Mark as New
- Bookmark
- Subscribe
- Mute
- Subscribe to RSS Feed
- Permalink
- Report Inappropriate Content
The REPEAT fix should get that one too. I will check.
- Mark as New
- Bookmark
- Subscribe
- Mute
- Subscribe to RSS Feed
- Permalink
- Report Inappropriate Content
DPD200375296 has been fixed and I expect that to be in update 1.
- Mark as New
- Bookmark
- Subscribe
- Mute
- Subscribe to RSS Feed
- Permalink
- Report Inappropriate Content
DPD200375283 should get fixed in update 1. The REPEAT issue (compiling the #35 example with /DALLOW_T2 now works.)
The #27/#35 example I think is the same bug as in #5/#9, DPD200375290. I have attached this new variant to that issue.
- Mark as New
- Bookmark
- Subscribe
- Mute
- Subscribe to RSS Feed
- Permalink
- Report Inappropriate Content
DPD200375286 (#10) should get fixed in update 1.
- Mark as New
- Bookmark
- Subscribe
- Mute
- Subscribe to RSS Feed
- Permalink
- Report Inappropriate Content
DPD200375302 (second half of #8) fixed for Update 1.

- Subscribe to RSS Feed
- Mark Topic as New
- Mark Topic as Read
- Float this Topic for Current User
- Bookmark
- Subscribe
- Printer Friendly Page
- « Previous
-
- 1
- 2
- Next »