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

Pointer on Array - pointer and target same size but different shape.

BRAHIM__ADJEROUD
Beginner
4,301 Views

Hello

I have a little problem with array.

I would like to be able to access it according to coordinates relating to a table of rank 3 AND also according to coordinates of table of rank 1.

Here is an example below:

integer, dimension(2,2,2) , target:: Int_array_xyz
integer, dimension(8), pointer:: Int_array_xxx

Int_array_xyz = RESHAPE((I,I=1,8),(/2,2,2/))

Int_array_xxx(1) => Int_array_xyz(1,1,1)

________________________________________

This approach is not accepted.

It is also not possible to do the following:

integer, dimension(2,2,2) :: Int_array_xyz
integer, dimension(2) :: Int_array_xxx
EQUIVALENCE (Int_array_xxx(1) , Int_array_xyz(1,1,1) )

________________________________________

I’m trying to improve a computational tool, and for some reason, the previous developer chose to reference some values in a 3-dimensional space, and other values in a 1-dimensional space.

When someone wishes to perform matrix operations by combining certain values, we are obliged to carry out an expensive and dangerous calculation of index matches.
If I could access to some of my table values alternately according to the two index systems (1 dimension and 3 dimensions) I would save a lot of development time.

I thought about using the RESHAPE function to be able to switch from a 3D system to a 1D system, but it is not possible to make a RESHAPE on itself!


 

XXX(:,:,:) = RESHAPE(XXX(:),(/2,2,2/))

So I have to create two tables. So that I double the memory space used, and also I need to synchronize the tables when one or the other is modified.
 

XYZ(:,:,:) = RESHAPE(XXX(:),(/2,2,2/))

________________________________________

Does anyone have any ideas?
Is that possible? Do I have to look further, on the side of "type" or "class"?

Thank you

0 Kudos
51 Replies
FortranFan
Honored Contributor II
1,027 Views

jimdempseyatthecover (Blackbelt) wrote:

I can show you parts of an example, but it would be difficult to provide metrics. Description follows:

..

With the UNION, all this hoop jumping, is simple table driven. Without UNION I would not have this flexability.

Jim,

You don't mentioned any memory constraints which is the primary use case for a UNION type. .Unless you can immediately confirm your motivation for the non-standard UNION facility in Intel Fortran is entirely driven by the large amount of data you process in memory and the consequent space-saving needs, I'll request you make further effort to extract a fully working example out of your use case in your simulation.  That will really clear up the picture greatly, because as shown with your description, the value of UNION in your code is not at all obvious to me. 

With a working example which covers the important aspects of  your data processing needs, one can present an alternative based on the current standard and compare and contrast the two - chances are highly likely the alternative will appear 'inefficient' to you but it will still be useful to quantify how all you think it to be so .  Such an exercise then might help make some suggestions for improvement in a future revision of the Fortran standard 

0 Kudos
jimdempseyatthecove
Honored Contributor III
1,027 Views

The memory constraints were not my concern. What was my primary concerns were: data file size, flexibility of filtering of what data got stored, mild "compression" of data via type conversion, and speed of logging data. Files were produces for two purposes: data analysis and check pointing. When a simulation can take months to run, speed of simulation was a tradeoff amongst: filtering, compressing, logging frequency, checkpoint frequency. The structure of the data logging was such that data analysis could take place during a simulation run. Thus permitting me to determine if the model was running amok and be terminated, or continue to run. Check pointing was available to provide resume points should either I terminate the run (in order to re-tune parameters of change what/how results are logged), or should the simulation ab-end to be able to re-start or analyze what happened.

What I didn't show (would have complicated posting), where the higher level routines that logged 1D, 2D, 3D arrays, array sections, etc... the stream data "record" size is 1, 2, 4, or 8 bytes without record markers held in the data file. The byte size and conversion was held in a separate table (included in a header within the database).

Jim Dempsey

 

0 Kudos
FortranFan
Honored Contributor II
1,027 Views

jimdempseyatthecove (Blackbelt) wrote:

..  What was my primary concerns were: data file size, flexibility of filtering of what data got stored, mild "compression" of data via type conversion, and speed of logging data ..

Well, the issue here really is the UNION..MAP facility from the non-standard DEC extension and how that helps you more than any of the features in the Fortran standard.  And that's very difficult to understand from such an example.  Given the current Fortran standard, you can do any number of things to mimic what the DEC UNION..MAP does, including roll your own UNION type (see an option below).  The question becomes whether any of the options in the standard come close to satisfying your use case and if not, where all do they fall short.  To determine such gaps, you would need to try out options in the standard with some test case and evaluate the shortcomings of the standard features, hence my request for a full but stand-alone and working example of your needs with UNION..MAP i.e., outside of your physics simulation.

module kinds_m

   use, intrinsic :: iso_c_binding, only : I1 => c_int8_t, I2 => c_int16_t, I4 => c_int32_t, I8 => c_int64_t, &
      R4 => c_float, R8 => c_double, CK => c_char

   implicit none

end module

module union_m

   use kinds_m, only : I1, I2, I4, I8, R4, R8, CK
   use, intrinsic :: iso_c_binding, only : c_loc, c_f_pointer

   implicit none

   private

   type, public :: union_t
   ! Field of 8-bit integers
      private
      integer(I1) :: m_vals(8) = 0_i1
   contains
      private
      procedure, pass(this), public :: valReal8 => get_real8
      procedure, pass(this), public :: valReal4 => get_real4
      procedure, pass(this), public :: valINT8 => get_int64
      procedure, pass(this), public :: valINT4 => get_int32
      procedure, pass(this), public :: valINT2 => get_int16
      procedure, pass(this), public :: valINT1 => get_int8
      procedure, pass(this), public :: ArrayINT1 => get_vals
      procedure, pass(this), public :: Name => get_chars
   end type union_t

contains

   function get_real8( this ) result(pval)
      ! Argument list
      class(union_t), intent(in), target :: this
      ! Function result
      real(R8), pointer :: pval
      call c_f_pointer( cptr=c_loc(this%m_vals), fptr=pval )
      return
   end function get_real8

   function get_real4( this ) result(pval)
      ! Argument list
      class(union_t), intent(in), target :: this
      ! Function result
      real(R4), pointer :: pval
      call c_f_pointer( cptr=c_loc(this%m_vals), fptr=pval )
      return
   end function get_real4

   function get_int64( this ) result(pval)
      ! Argument list
      class(union_t), intent(in), target :: this
      ! Function result
      integer(I8), pointer :: pval
      call c_f_pointer( cptr=c_loc(this%m_vals), fptr=pval )
      return
   end function get_int64

   function get_int32( this ) result(pvals)
      ! Argument list
      class(union_t), intent(in), target :: this
      ! Function result
      integer(I4), pointer :: pvals
      call c_f_pointer( cptr=c_loc(this%m_vals), fptr=pvals )
      return
   end function get_int32

   function get_int16( this ) result(pvals)
      ! Argument list
      class(union_t), intent(in), target :: this
      ! Function result
      integer(I2), pointer :: pvals
      call c_f_pointer( cptr=c_loc(this%m_vals), fptr=pvals )
      return
   end function get_int16

   function get_int8( this ) result(pvals)
      ! Argument list
      class(union_t), intent(in), target :: this
      ! Function result
      integer(I1), pointer :: pvals
      call c_f_pointer( cptr=c_loc(this%m_vals), fptr=pvals )
      return
   end function get_int8

   function get_vals( this ) result(pvals)
      ! Argument list
      class(union_t), intent(in), target :: this
      ! Function result
      integer(I1), pointer :: pvals(:)
      call c_f_pointer( cptr=c_loc(this%m_vals), fptr=pvals, shape=[ size(this%m_vals) ] )
      return
   end function get_vals

   function get_chars( this ) result(name)
      ! Argument list
      class(union_t), intent(in), target :: this
      ! Function result
      character(kind=CK,len=size(this%m_vals)), pointer :: name
      call c_f_pointer( cptr=c_loc(this%m_vals), fptr=name )
      return
   end function get_chars

end module

program p

   use kinds_m, only : I1, I2, I4, I8, R4, R8, CK
   use union_m, only : union_t

   type(union_t), target :: u !<-- must have TARGET attribute
   real(R8) :: foo
   character(kind=CK,len=8) :: s

   u%name() = ck_"Hello World!"
   print *, "u%ArrayINT1 = ", u%ArrayINT1()
   print *, "achar(u%ArrayINT1) = ", achar(u%ArrayINT1())
   s = transfer( source=u%ArrayINT1(), mold=s )
   print *, "s = ", s, "; expected is ", u%name()

   u%valINT8() = int( Z'C0000000', kind=I8 )
   print *, "u%ArrayINT1 = ", u%ArrayINT1()
   print "(g0,z0)", "u%valINT8() = ", u%valINT8()

   u%valREAL8() = 99.0_r8
   print *, "u%ArrayINT1 = ", u%ArrayINT1()
   foo = transfer( source=u%ArrayINT1(), mold=foo )
   print *, "foo = ", foo, "; expected is ", u%valREAL8()

   stop

end program

Upon execution, you should get with Intel Fortran 19.0 Update 5:

 u%ArrayINT1 =  72 101 108 108 111 32 87 111
 achar(u%ArrayINT1) = Hello Wo
 s = Hello Wo; expected is Hello Wo
 u%ArrayINT1 =  0 0 0 -64 0 0 0 0
u%valINT8() = C0000000
 u%ArrayINT1 =  0 0 0 0 0 -64 88 64
 foo =  99.0000000000000 ; expected is  99.0000000000000

 

0 Kudos
LRaim
New Contributor I
1,027 Views

Using EQUIVALENCE things would be like this.

REAL(KIND=8) RVAR8 ; REAL(KIND=4) RVAR4(2) ; INTEGER(KIND=8) IVAR8 ; INTEGER(KIND=4) IVAR4(2) ; ....; CHARACTER (LEN=16) CVAR16 ;

CHARACTER (LEN=1) :: LVAR(16) 

EQUIVALENCE (RVAR8,RVAR4,IVAR8,IVAR4,CVAR16,LVAR)

Regards

 

0 Kudos
FortranFan
Honored Contributor II
1,027 Views

Luigi R. wrote:

Using EQUIVALENCE things would be like this.

REAL(KIND=8) RVAR8 ; REAL(KIND=4) RVAR4(2) ; INTEGER(KIND=8) IVAR8 ; INTEGER(KIND=4) IVAR4(2) ; ....; CHARACTER (LEN=16) CVAR16 ;

CHARACTER (LEN=1) :: LVAR(16) 

EQUIVALENCE (RVAR8,RVAR4,IVAR8,IVAR4,CVAR16,LVAR)

Regards

 

With EQUIVALENCE, which is based on the storage sequence and association, the Fortran standard does not permit a character sequence type to be equivalenced with a numeric sequence type nor does it permit equivalence of types of non-default real with non-default integer.

0 Kudos
jimdempseyatthecove
Honored Contributor III
1,027 Views

FF, thank you for taking your time to re-write a standards conformant work around. The work around you provided is incomplete seeing that it did not advance the buffer pointer. Do not spend any time to fix this omission as it is relatively easy to correct by making m_vals on line 22 a pointer (and adding to the type the remainder of my former Blob type, in particular the byte offset into the "unknown" POD). When I find time to work on this, I will consider making this change. An alternative would be to use an inter-op C reader/writer function.

Jim Dempsey

0 Kudos
FortranFan
Honored Contributor II
1,027 Views

jimdempseyatthecove (Blackbelt) wrote:

FF, thank you for taking your time to re-write a standards conformant work around. The work around you provided is incomplete seeing that it did not advance the buffer pointer. Do not spend any time to fix this omission as it is relatively easy to correct by making m_vals on line 22 a pointer (and adding to the type the remainder of my former Blob type, in particular the byte offset into the "unknown" POD). When I find time to work on this, I will consider making this change. An alternative would be to use an inter-op C reader/writer function.

Jim Dempsey

Jim, re: "The work around you provided is incomplete seeing that it did not advance the buffer pointer," yes I did that have in mind but my focus was only the UNION..MAP component of your blob type.  As you write, you can take such as a "home brew" union type and make it a component of your "blob type" and do the needful in terms of managing byte offsets, etc.

But I hope you can find some time to evaluate the option I show in Quote #25 (or other standard-conforming ones that may be better) because your evaluation and analysis will likely bring out the gaps and limitations in the existing standard facilities, particularly in terms of efficiency and performance.  Your findings can then prove highly valuable toward a proposal (e.g., at the GitHub site: https://github.com/j3-fortran/fortran_proposals) to improve what the Fortran standard can offer for yours and other coders' use cases with UNION type, etc. in a future revision.  Or better yet, if you have suggestions/ideas/proposals, please post them directly at https://github.com/j3-fortran/fortran_proposals

0 Kudos
jimdempseyatthecove
Honored Contributor III
1,027 Views

IMHO The standards conforming method to work around UNION...MAP introduces unnecessary complications in how to address the type conversions and obfuscates what is being done. The standards conforming method does mean portability, should that be a concern. As far as efficiency, I think that any good optimizing compiler can make both methods reasonably close when considering execution time + I/O time.

This said, I am in favor of a future Fortran Standard for having UNION. As to if this follows Intel's method or not, I have no preference on this.

Also, the Fortran Standard of TRANSFER to accomplish a cast is an abomination. Whey didn't they choose a more meaningful name such as REINTERPRET_CAST. Reason being is there has been great efforts by the Fortran Standards committee to include interoperable procedures with C. Why then wasn't the same name directive used in this case? I doubt if any Fortran application (1950's through present) would be harmed by using this keyword.

Using C_F_POINTER, C_PTR is equally unsatisfactory.

My 3 cents (inflationary adjusted)

Jim Dempsey

0 Kudos
jimdempseyatthecove
Honored Contributor III
1,027 Views

Just noticed something on TRANSFER that gives me pause. If you have an integer(1) :: array(8) and use

  aReal4 = TRANSFER(array, 0.0)

The four bytes inserted into aReal4 will be array(5:8) which is counter that of UNION.

(I know I can specify array(1:4), that is not the point)

Jim Dempsey

0 Kudos
Steve_Lionel
Honored Contributor III
1,027 Views

Jim, you are mistaken.

integer(1) array(8)
real(4) areal4

array = [1,2,3,4,5,6,7,8]
areal4 = TRANSFER(array,0.0)
print '(Z8.8)', areal4
end
D:\Projects>ifort t.f90
Intel(R) Visual Fortran Intel(R) 64 Compiler for applications running on Intel(R) 64, Version 19.0.5.281 Build 20190815
Copyright (C) 1985-2019 Intel Corporation.  All rights reserved.

Microsoft (R) Incremental Linker Version 14.23.28106.4
Copyright (C) Microsoft Corporation.  All rights reserved.

-out:t.exe
-subsystem:console
t.obj

D:\Projects>t.exe
04030201

 

0 Kudos
jimdempseyatthecove
Honored Contributor III
1,027 Views

I misread the IVF documentation for TRANSFER, it may need addressing

TRANSFER ((/2.2, 3.3, 4.4/), (/(0.0, 0.0)/), 1) results in a complex rank-one array having one element with the value (2.2, 3.3).
This is the correct way, but in the another example just below that the show:

CX = TRANSFER((/1.1, 2.2, 3.3/) , (/(0.0, 0.0)/), &
              SIZE= 1)

Dumb me (or brain fart), for carrying the 2.2, 3.3 into the result for CX as the result was not shown.
(I should have read the comment in the code example)

Thanks, for the correction.

The IVF documentation should address array elements to scalar:

If the physical representation of the result is larger than source, the result contains source's bit pattern in its right-most bits; the left-most bits of the result are undefined.

It is unclear as to what constitutes the right most bits.

Jim Dempsey

0 Kudos
FortranFan
Honored Contributor II
1,027 Views

jimdempseyatthecove (Blackbelt) wrote:

.. The standards conforming method to work around UNION...MAP introduces unnecessary complications in how to address the type conversions and obfuscates what is being done. ..

This said, I am in favor of a future Fortran Standard for having UNION ..

Also, the Fortran Standard of TRANSFER to accomplish a cast is an abomination. ..

Using C_F_POINTER, C_PTR is equally unsatisfactory. ..

Jim, as I've been informing you here, more effort will be needed on your part to better illustrate the need for UNION type in the standard: saying a conforming option "introduces unnecessary complications" or that it makes use of something which is "unsatisfactory" just does not pass muster.  You mention about "complications in how to address the type conversions and obfuscates what is being done," but then the DEC UNION..MAP option itself is a classic illustration of obfuscated type conversions and inadequate description and documentation of how it works for Intel Fortran customers; I can bet few understand it and know how to use it in their code.

I agree TRANSFER is an abomination and it's not really equivalent to EQUIVALENCE.  Note I only used TRANSFER in Quote #25 as an assertion check in couple of the cases, it shouldn't be needed in typical consumption scenarios of the shown 'union_t' class.

0 Kudos
Steve_Lionel
Honored Contributor III
1,027 Views

The standard uses the term "leading part":

Result Value. If the physical representation of the result has the same length as that of SOURCE, the physical
12 representation of the result is that of SOURCE. If the physical representation of the result is longer than that
13 of SOURCE, the physical representation of the leading part is that of SOURCE and the remainder is processor
14 dependent. If the physical representation of the result is shorter than that of SOURCE, the physical representation
15 of the result is the leading part of SOURCE. If D and E are scalar variables such that the physical representation
16 of D is as long as or longer than that of E, the value of TRANSFER (TRANSFER (E, D), E) shall be the value
17 of E. IF D is an array and E is an array of rank one, the value of TRANSFER (TRANSFER (E, D), E, SIZE (E))
18 shall be the value of E.

In your case, the result is shorter than SOURCE, so the result is the "leading part of SOURCE", meaning the lowest-addressed bytes. This text changed considerably in F2018 as a result of interpretation requests, as the previous text was unclear or in some odd combinations, impossible.

I agree that TRANSFER can be clunky. What you really want is a "variant type", something the language doesn't have. EQUIVALENCE has many restrictions that make it unusable for variant types, unless you want to use it for static or local, non-pointer, non-allocatable variables.  

Unions have been considered before, but were rejected (this was before my time on the committee.) I do think they are error-prone and that a true variant type is a better approach.

0 Kudos
BRAHIM__ADJEROUD
Beginner
1,027 Views

Ok, ok, ok
well, well, well,  
you have killed my willing to ask another question … all your messages just show me that I’m at the beginning of long long road before obtaining something really valuable …
Ok. It’s ok . Actually I will just close my eyes and jump in the mist of this forest which is the Fortran knowledge. Please wish me some luck.
So, here’s my jump :
- The first step :
My scientific code actually use NAMELIST statement for the user to performing the data input.
My code is modelazing some material comportment in some 3D cartesian space.
 
Actually our 3D cartesian space is sliced in 3D little mesh.  
So, for the description of our study case, we use simple files where thanks to the NAMELIST statement, we’re performing the cases description.
 
Don’t ask me why, but actually, for some input, we are using 1 dimension vector to input our 3D case description. And it’s really a pin in the ass for everyone to perform the conversion between the 3D space cartesian description of our case in the “not friendly” 1D vector case description.
 
But tables have turned and tomorrow I will came before my friends and I will say :
“Hello my friends ! Say goodbye to the old 1D vector case description. By my own, I have created a new revolutionary method … Well, let me think about it ! Mhhh, I will call this method  “pointer bounds remapping”. I know this method is a new revolution, but I will not put copyright on it. I’m just doing this for the science. “
 
So, thanks to all of you, my idea is to use (EQUIVALENCE or POINTER/TARGET) to perform the re-mapping between the new 3D Cartesian input and the old 1D vector input.
 
To be complete, I would like to be able to use my actual code to perform a conversion from the old data-set with 1D vector case description to new data-set with 3D cartesian and friendly case description….  
And I think to myself, what a wonderful idea. Now that I have my “pointer bound remapping” It will be so easy to perform this task !
Let me show you part of my code :

 

     PROGRAM ESSAI_NAMELIST
 
!     INPUT ARRAY
      INTEGER, DIMENSION(13728)           :: BOUNDARY_SET_AAA
      INTEGER, DIMENSION(0:21,0:11,0:51)  :: BOUNDARY_SET_XYZ
 
      INTEGER, DIMENSION(20,10,50)        :: WALL_SET_XYZ
 
!     INPUT OUTPUT FILES UNIT
      INTEGER :: INPUT_FILE_UNIT  = 10
      INTEGER :: OUTPUT_FILE_UNIT = 11  
 
      NAMELIST/BOUNDARY/ BOUNDARY_SET_AAA ,   ! 1D VECTOR INPUT
     &                    BOUNDARY_SET_XYZ ,  ! 3D CARTESIAN INPUT
     &                    WALL_SET_XYZ    
 
      EQUIVALENCE(BOUNDARY_SET_AAA, BOUNDARY_SET_XYZ)
 
!       INITIALISATION
      BOUNDARY_SET_AAA = 0;
      WALL_SET_XYZ     = 0;
 
!     NAMELIST READING PROCESS             
      OPEN(UNIT=INPUT_FILE_UNIT,FILE = "INPUT_FILE.DAT", STATUS ="OLD")
        READ(UNIT=INPUT_FILE_UNIT,NML=BOUNDARY)
      CLOSE(UNIT=INPUT_FILE_UNIT)
        
!     NAMELIST WRITING PROCESS             
      OPEN(UNIT=OUTPUT_FILE_UNIT, FILE="OUTPUT_FILE.DAT",  
     &                            STATUS = "REPLACE")  
        WRITE(UNIT=OUTPUT_FILE_UNIT, NML=BOUNDARY)  
      CLOSE(UNIT=OUTPUT_FILE_UNIT)
      END
 


 
So, my idea is really simple. I will just read an old style data set in 1D vector, and write a new one with friendly 3D cartesian space description.  
 
Here below my INPUT_FILE.DAT

 

# MESH NUMBER : 22*12*52 = 13728
# CELL NUMBER : 20 ; 10 ; 50  
 &BOUNDARY  
 
  BOUNDARY_SET_AAA( 1)   = 13728*0,
   
  BOUNDARY_SET_AAA(9350) = 1,
  BOUNDARY_SET_AAA(9372) = 1,
   
  BOUNDARY_SET_AAA(186) = 2,
  BOUNDARY_SET_AAA(187) = 2,
   
  WALL_SET_XYZ(10,1,10) = 000011,
  WALL_SET_XYZ(11,1,10) = 000011,
  WALL_SET_XYZ(12,1,10) = 000011,
  WALL_SET_XYZ(13,1,10) = 000011,
  WALL_SET_XYZ(14,1,10) = 000011,
  WALL_SET_XYZ(15,1,10) = 000011,
   
  WALL_SET_XYZ(10,2,10) = 000011,
  WALL_SET_XYZ(11,2,10) = 000011,
  WALL_SET_XYZ(12,2,10) = 000011,
  WALL_SET_XYZ(13,2,10) = 000011,
  WALL_SET_XYZ(14,2,10) = 000011,
  WALL_SET_XYZ(15,2,10) = 000011,
   
  WALL_SET_XYZ(1,1,34) = 000001,
  WALL_SET_XYZ(1,2,34) = 000001,
  WALL_SET_XYZ(1,3,34) = 000001,
  WALL_SET_XYZ(1,4,34) = 000001,
  WALL_SET_XYZ(1,5,34) = 000001,
 /


 
 And here bellow the OUTPUT_FILE.DAT :


 

&BOUNDARY
 BOUNDARY_SET_AAA = 185*0          , 2*2          , 9162*0          ,1          , 21*0          ,
 1          , 4356*0          ,
 BOUNDARY_SET_XYZ = 185*0          , 2*2          , 9162*0          ,1          , 21*0          ,
 1          , 4356*0          ,
 WALL_SET_XYZ= 1809*0          , 6*11         , 14*0          , 6*11         , 4765*0          ,
 1          , 19*0          ,1          , 19*0          ,1          , 19*0          ,
 1          , 19*0          ,1          , 3319*0          ,
 /


And so … my surprise is that the NAMELIST output are not the beginning of something easy to read. It’s just a short succession of value with no regard to the shape of the data printed.
So here is my first question : By any chance, is there a way to make my NAMELIST output more friendly ?(Any kind of compliance with the shape of the values for example ?)
… Mhhh, here a second little question …
Actually, in my scientific code, we’re performing initiation of our input shape and default value before the NAMELIST reading.
So, if my NAMELIST input don’t have the good size/shape, the execution just fail.
As the 1D vector / 3D vector is an issue, I’m wondering if there is a way to obtain so kind of polymorphism in the reading process ???
Maybe I need to have a look at the “assumed-size or assumed-shape arrays” in Fortran? … maybe it will not be a really big mess to reach 1D/3D polymorphism for some value…
 
And time now for the second step … !!
Here my second step in the thick forest of the Fortran knowledge...
As I wandered through your lines of code maturing my "NAMELIST" issue little question …
... all i can see is “UNION” “MAP” … Mhhh so I say to myself ... maybe our “NAMELIST” INPUT PROCESS is not the state of the art for the input ??!!??
Maybe there exist some more friendly way to perform the data input ?  
 
So my summary:
1.    Is there a way to make NAMELIST output just a little “user friendly”, (with some kind some compliance with shape of the values for examples)?
2.    Your opinion about the work I have to done before reaching 1D vector / 3D Cartesian coordinates polymorphism? Am I following the right road by searching on the “assumed-size or assumed-shape arrays” properties and the “pointer bounds remapping”.
3.    Your opinion on the NAMELIST statement. Isn't this method obsolete? What is actually the stat of the art ?
Thank Youuuuu
 

0 Kudos
Steve_Lionel
Honored Contributor III
1,027 Views

1. No - all you get is the variable name and values. The Fortran standard doesn't allow for anything else.

2. I'm skipping this question for now - others may want to chime in

3. NAMELIST is not considered obsolete in the language. But you may be asking more of it than it was designed for. 

0 Kudos
jimdempseyatthecove
Honored Contributor III
1,027 Views

RE: 1

You may be able to locate a utility program that converts a "compacted" namelist output into a more readable format that you prefer. If not, then you might be able to write one yourself. The problem you will encounter is attempting to duplicate something that looks like the original input you listed above when the original input has overstriking of variables data.

Jim Dempsey

0 Kudos
BRAHIM__ADJEROUD
Beginner
1,027 Views

Ok. For my question n°2, apparently, the use of assumed size array is not allowed with the NAMELIST reading process... And furthermore, I'm not really sûre to have the good understanding on how the assumed size arry work ... 

 

0 Kudos
Steve_Lionel
Honored Contributor III
1,027 Views

Assumed-size arrays have no known upper last bound - it is the responsibility of the programmer to make sure that the bounds are not exceeded. You can't use one of these in a NAMELIST because it has no idea how big the array is.

Assumed-size is mainly an artifact from the F77 days. In modern Fortran it would be better to use assumed-shape dummy arguments, where the extents are passed in from the caller. This does require an explicit interface.

0 Kudos
FortranFan
Honored Contributor II
1,027 Views

BRAHIM,ADJEROUD wrote:

.. 3.    Your opinion on the NAMELIST statement. Isn't this method obsolete? What is actually the stat of the art ? ..

Namelist is a nice facility, however it has limitations.

However what is "stat of the art" particularly with Fortran is a matter of opinion.  You can pursue formatted I/O and write your own read and write subroutines to work with data in a format that you and your colleagues can understand.

Or you consider a markup language such as XML or some data interchange format such as JSON.

Should you find JSON a good option, note there is a nice Fortran library available on GitHub: https://github.com/jacobwilliams/json-fortran and you can contact the author for more details.

0 Kudos
FortranFan
Honored Contributor II
1,004 Views

Steve Lionel (Ret.) (Blackbelt) wrote:

.. Unions have been considered before, but were rejected (this was before my time on the committee.) I do think they are error-prone and that a true variant type is a better approach.

Jim, would a variant type be better compared to what you have pursued with UNION..MAP feature in your code?  If a variant type is better, would you have a good example for it from another language?  C++ std::variant?

Thanks,

0 Kudos
andrew_4619
Honored Contributor II
1,004 Views

A variant type in Fortran would indeed be useful. I can think of several examples where that is what I  needed and instead had to adopt a more long winded/clumsy approaches.

0 Kudos
Reply