Silverfrost Forums

Welcome to our forums

use of LOC function and /UNDEF

29 Apr 2015 12:31 #16253

hi,

we make use of the following unusual syntax (for reasons too complicated to explain here!):

LOC(VARIABLE) = IADDRESS

and it works well, but fails to compile under /undef with the following error:

ERROR 215: Invalid expression on left hand side of assignment

I realise it's an unusual use of the LOC function but we'd still like to be able to compile code with /undef during testing.

K

29 Apr 2015 1:03 #16254

This code looks strange to me. Can you post a small program that illustrates the context and describe what it should do.

29 Apr 2015 1:17 #16256

it works well

Looks to me that you have discovered an improbability overflow: when the improbability is infinite it behaves as infinitely probable - and works!

Putting a function, especially a standard one, on the LHS of an assignment statement can't ever be right - or can it?

29 Apr 2015 1:35 #16257

ok...

Essentially, we have a routine that stores addresses of variables used in our dialogues thus:

SUBROUTINE SETADDR( ISCREEN, IFIELD, A) INTEGER IADDRESS(MAXSCR,MAXFLD) COMMON/BLAH/ IADDRESS IADDRESS(ISCREEN, IFIELD) = LOC(A)

Then in the dialogue handling code we may want to do some 'sense checking' so we reverse the usage:

SUBROUTINE CHECKFIELD (ISCREEN, IFIELD, AMIN, AMAX, IRET) INTEGER IADDRESS(MAXSCR,MAXFLD) COMMON/BLAH/ IADDRESS LOC(A) = IADDRESS(ISCREEN, IFIELD) IRET = 0 IF( A.LT.AMIN .OR. A.GT.AMAX) THEN WRITE(,) 'Entered value outside limits' IRET = 1 ENDIF

is that enough info?

K

29 Apr 2015 6:47 #16260

Could you supply simpler and complete code. For example, the following is a working program in a similar context...

integer iaddress
real a
iaddress = loc(a)
fcore4(iaddress) = 42.0
print*,a
end
29 Apr 2015 8:58 #16261

Quoted from LitusSaxonicum

Putting a function, especially a standard one, on the LHS of an assignment statement can't ever be right - or can it?

Well its clearly nonsense in Fortran 95 though as you see in Paul's post above nonsense is sometimes acceptable. There is a meaning in Python but even there it looks a little weird. Also there is such a syntax in Fortran 2008 but there are not many compilers.

I believe what Kenny T is trying to do is dereference the address. In which case instead of

LOC(A) =  IADDRESS(ISCREEN, IFIELD)

he should use the following

A = FCORE4(IADDRESS(ISCREEN, IFIELD))

Since FCORE4 is the inverse of LOC.

Kenny T seems to have forgotten about this thread where he posted the same solution in 2013 (if its the same, the one and only Kenny T ๐Ÿ˜ƒ ) :

https://software.intel.com/en-us/forums/topic/394026

30 Apr 2015 8:59 #16265

Here's a complete example with a comment that FCORE4 doesn't do the business:

!ftn95$free
MODULE CMAPS
 TYPE SCA
   REAL	:: Y1, Y2
 END TYPE SCA
  
 TYPE CMAP
   INTEGER				:: I1, I2
   REAL					:: R1, R2
   REAL, POINTER		:: VALS(:)
   TYPE (SCA), POINTER	:: SC    
  END TYPE CMAP
END MODULE CMAPS

  
PROGRAM NMAP

  USE CMAPS
  
  TYPE (CMAP),POINTER	:: CM
  
  
	ALLOCATE (CM, stat=IST)
	CM%I1	=  1
	CM%I2	=  2
	CM%R1	=  10.
	CM%R2	=  20.
	ALLOCATE (CM%VALS(30), stat=IST)
	DO I = 1, 30
	 CM%VALS(I)	=  I/2.
	END DO
 	ALLOCATE (CM%SC)
 	CM%SC%Y1	=  0.
 	CM%SC%Y2	=  1.
	
	IAD	=  loc(CM)
	CALL FUDGEIT (IAD)
	
END PROGRAM


SUBROUTINE FUDGEIT (IAD)

  USE CMAPS
  
  TYPE (CMAP), POINTER	:: CM
  
  
  	NN	=  3
	loc(CM)	=  IAD
	N	=  size(CM%VALS)
	WRITE (*,*) CM%I1, CM%I2, CM%R1, CM%R2, N
	WRITE (*,*) (CM%VALS(J),J=1,N,5)
	WRITE (*,*) CM%SC%Y1, CM%SC%Y2
	
!	CM	=  fcore4(IAD)		! wont compile
	
END SUBROUTINE FUDGEIT

Some more detail as to the thinking behind what is going on:

We have a linked list structure which we want to use with different models. The basic model has some scalars and vectors, but in some circumstances we want to add stuff to it โ€“ in other words, change the model. The example is a (basic version) of a colour map which describes how to plot the data. But in a different context we might want a file name or a regression result, each another derived type pointer. If we can reference these through their address and access via loc() we donโ€™t have to have a different linked list structure (and all its associated code) for each variant.

K

30 Apr 2015 11:58 #16267

Uncompilable code snippets with the author's own assessment of what the code is doing (or what it is not doing) are problematic. Here is a slight modification of the subroutine above http://forums.silverfrost.com/posting.php?mode=quote&p=18057

SUBROUTINE CHECKFIELD (ISCREEN, IFIELD, AMIN, AMAX, IRET)
integer, parameter :: maxscr=25, maxfld=80
INTEGER IADDRESS(MAXSCR,MAXFLD)
COMMON/BLAH/ IADDRESS
LOC(A) = IADDRESS(ISCREEN, IFIELD)
IRET = 0
IF( A.LT.AMIN .OR. A.GT.AMAX) THEN
WRITE(*,*) 'Entered value outside limits'
IRET = 1
ENDIF
end subroutine

The only modification is the declaration of the parameters used in the array declaration, without which the code is not valid. For the modified code, FTN95 clearly says what it thinks:

[FTN95/Win32 Ver. 7.10.0 Copyright (c) Silverfrost Ltd 1993-2014]
0005) LOC(A) = IADDRESS(ISCREEN, IFIELD)
COMMENT - This statement function definition for LOC hides the intrinsic routine of the same name
    NO ERRORS, 1 COMMENT  [<CHECKFIELD> FTN95/Win32 v7.10.0]

Placed just after the variable declarations, the line containing LOC is taken as an ASF definition. The selection of the name of the ASF to be the same as the name of a standard function (or nonstandard but common extension, as with LOC) is the source of much confusion. What is in a name?

30 Apr 2015 11:58 #16268

Uncompilable code snippets with the author's own assessment of what the code is doing (or what it is not doing) are problematic. Here is a slight modification of the subroutine above http://forums.silverfrost.com/posting.php?mode=quote&p=18057

SUBROUTINE CHECKFIELD (ISCREEN, IFIELD, AMIN, AMAX, IRET)
integer, parameter :: maxscr=25, maxfld=80
INTEGER IADDRESS(MAXSCR,MAXFLD)
COMMON/BLAH/ IADDRESS
LOC(A) = IADDRESS(ISCREEN, IFIELD)
IRET = 0
IF( A.LT.AMIN .OR. A.GT.AMAX) THEN
WRITE(*,*) 'Entered value outside limits'
IRET = 1
ENDIF
end subroutine

The only modification is the declaration of the parameters used in the array declaration, without which the code is not valid. For the modified code, FTN95 clearly says what it thinks:

[FTN95/Win32 Ver. 7.10.0 Copyright (c) Silverfrost Ltd 1993-2014]
0005) LOC(A) = IADDRESS(ISCREEN, IFIELD)
COMMENT - This statement function definition for LOC hides the intrinsic routine of the same name
    NO ERRORS, 1 COMMENT  [<CHECKFIELD> FTN95/Win32 v7.10.0]

Placed just after the variable declarations, the line containing LOC is taken as an ASF definition. The selection of the name of the ASF to be the same as the name of a standard function (or nonstandard but common extension, as with LOC) is the source of much confusion. What is in a name?

30 Apr 2015 11:59 #16269

Uncompilable code snippets with the author's own assessment of what the code is doing (or what it is not doing) are problematic. Here is a slight modification of the subroutine above http://forums.silverfrost.com/posting.php?mode=quote&p=18057

SUBROUTINE CHECKFIELD (ISCREEN, IFIELD, AMIN, AMAX, IRET)
integer, parameter :: maxscr=25, maxfld=80
INTEGER IADDRESS(MAXSCR,MAXFLD)
COMMON/BLAH/ IADDRESS
LOC(A) = IADDRESS(ISCREEN, IFIELD)
IRET = 0
IF( A.LT.AMIN .OR. A.GT.AMAX) THEN
WRITE(*,*) 'Entered value outside limits'
IRET = 1
ENDIF
end subroutine

The only modification is the declaration of the parameters used in the array declaration, without which the code is not valid. For the modified code, FTN95 clearly says what it thinks:

[FTN95/Win32 Ver. 7.10.0 Copyright (c) Silverfrost Ltd 1993-2014]
0005) LOC(A) = IADDRESS(ISCREEN, IFIELD)
COMMENT - This statement function definition for LOC hides the intrinsic routine of the same name
    NO ERRORS, 1 COMMENT  [<CHECKFIELD> FTN95/Win32 v7.10.0]

Placed just after the variable declarations, the line containing LOC is taken as an ASF definition. The selection of the name of the ASF to be the same as the name of a standard function (or nonstandard but common extension, as with LOC) is the source of much confusion. What is in a name?

30 Apr 2015 12:01 (Edited: 30 Apr 2015 12:24) #16270

Sorry about the multiple 'replies'. The forum server replied 'Debug Mode, try submitting later', which I did.

Here is a screenshot:

https://www.dropbox.com/s/4cot0e0aih0si0z/dbgmode.png?dl=0

MODERATOR: Please keep the first copy and delete the rest, and delete this apology.

30 Apr 2015 12:06 #16271

Sorry about the multiple 'replies'. The forum server replied 'Debug Mode, try submitting later', which I did. Here is a screenshot:

https://www.dropbox.com/s/4cot0e0aih0si0z/dbgmode.png?dl=0

MODERATOR: Please keep the first copy and delete the rest, and delete this apology.

30 Apr 2015 12:07 #16272

Kenny,

I am struggling to understand your problem.

I think you could use an expression like 'cm%r1 = fcore4(IAD)' for a real4 component of type (CMAP), but not equating a real4 value to a type(CMAP) CM.

All the core intrinsic functions are effective virtual arrays of the memory for the intrinsic data types. They are effectively arrays, whose argument is the memory byte address and can be used as arrays on either the left or right of =.

Also, your use of loc (CM) also has problems, as you can not guarantee the order and placement of intrinsic data types within the CMAP structure. All that ' = fcore4(IAD)' provides is the 4 bytes, starting from memory address IAD, as a real*4 variable.

You would need to develop a type (CMAP) function CMAP CORE N, that transfers the n bytes of the CMAP structure, starting from memory byte address IAD, but again, I don't think you can make assumptions of the byte order of intrinsic variables within the TYPE (CMAP).

Is this what you are trying to do ?

John

30 Apr 2015 2:31 #16278

I'll reply with more detail later.

note to the mods:

i've checked the 'notify me' box but, after the initial notification of the first reply from Paul, i'm no longer getting the emails? (which is why i didn't reply earlier!)

K

30 Apr 2015 4:34 #16279

Quoted from JohnCampbell Kenny,

I am struggling to understand your problem.

I think you could use an expression like 'cm%r1 = fcore4(IAD)' for a real4 component of type (CMAP), but not equating a real4 value to a type(CMAP) CM.

All the core intrinsic functions are effective virtual arrays of the memory for the intrinsic data types. They are effectively arrays, whose argument is the memory byte address and can be used as arrays on either the left or right of =.

Also, your use of loc (CM) also has problems, as you can not guarantee the order and placement of intrinsic data types within the CMAP structure. All that ' = fcore4(IAD)' provides is the 4 bytes, starting from memory address IAD, as a real*4 variable.

You would need to develop a type (CMAP) function CMAP CORE N, that transfers the n bytes of the CMAP structure, starting from memory byte address IAD, but again, I don't think you can make assumptions of the byte order of intrinsic variables within the TYPE (CMAP).

Is this what you are trying to do ?

John

Hi John,

to overcome the 'random' storage of structure elements, we actually use the 'SEQUENCE' statement.

Our problem is that we find this 'method' very useful and make extensive use of it so want it to be available to us when compiling with /undef. it behaves perfectly under /debug...

with other compilers (e.g. gfortran) there is a 'cray pointer' method, which also seems to work (although we haven't tested it extensively):

SUBROUTINE DT_RSCAPoint (RSCALAR, IADD)

  TYPE (RSCA), POINTER	:: RSCALAR
  INTEGER :: IADD

	#IFDEF GFORT
	   POINTER (IADD2, RSCALAR)
	   IADD2  = IADD
	#ELSE
	   loc(RSCALAR)	=  IADD
	#ENDIF
	
END SUBROUTINE    

but i don't believe they are available in FTN95?

K[/i]

30 Apr 2015 11:37 #16282

Kenny,

If you know the byte length of the CMAP type structure (which could vary between compilers) and the start address of where you want it stored, can't you just use a loop to transfer n bytes to the address, using ICOREx, in a purpose built function ? I would expect that the layout of a type structure could vary significantly between compilers, depending on the alignment approach and allowance for small or large arrays within the type structure. ( Look at the way FTN95 stores modules, splitting out large arrays )

The use of LOC was not standard at Fortran 95, which is where FTN95 is at and I am not sure how standard 'cray pointers' have become. I have not seen 'LOC (RSCALAR) = ' used in this way before, so am not surprised you would need a work around with FTN95, using the xCOREx approach.

John

1 May 2015 6:20 #16285

For my application I took a different approach.

The address of the data (of differing types) is stored generically in INTEGER (KIND=3) array and has a type array associated with it as well. At run time, after data are entered, the program goes through the array and moves the data into the appropriate destination (based on a 'type' associated with each location). I did this to make the code more 'portable', but it also solved the /undef issue that would arise. Here are a few examples. I'm fortunate that the character data used is always < 1024 bytes in length.

	SUBROUTINE CHAR_MOVE(CDATA)
        CHARACTER*(*),target:: CDATA
        INTEGER*4 LEN_CHAR
        CHARACTER*1024,POINTER::LOC_POINTER
        COMMON/LOCSERVICES/LOC_POINTER,LEN_CHAR
        LOC_POINTER(1:LEN_CHAR) = CDATA
        RETURN
        END
        SUBROUTINE I2_MOVE(DATA_VAL)
        INTEGER*2,target:: DATA_VAL
        INTEGER*2,POINTER::LOC_POINTER
        INTEGER*4 LEN_CHAR
        COMMON/LOCSERVICES/LOC_POINTER,LEN_CHAR
        LOC_POINTER = DATA_VAL
        RETURN
        END
.
.
.

There are similar routines for all the basic data types allowed and KIND=xxx variations of those types. This works in DEBUG and RELEASE equally well.

In the calling routine, the following convention is used:

        INTEGER*4 TARGET_LOCATION,TARGET_LENGTH
        COMMON/LOCSERVICES/TARGET_LOCATION,TARGET_LENGTH
.
.
.
        TARGET_LOCATION = LOCDAT(I) ! LOCDAT has the LOC() values
        CALL I2_MOVE(I2_DATA)

This technique can also extend to any arbitrary data type.

Please login to reply.