A symbol must be a defined parameter in this context

Dear friends,

I’m started deviding my crane runway program in seperate functions. My goal is to make a dll callable from Excel VBA.
the following code gives me an error: "A symbol must be a defined parameter in this context [MAXMOM] on line 79: MaxMin=(maxmom,minmom).
Did some research but still have no clue what’s going on.
Some help would be greatly appreciated.

program mom
! Moments in a 2 span continuous beam with equal spans under up to 4 moving point loads.
! 20/05/2024 R.M. Versie A
implicit none
real :: x               ! Position where moment is calculated
real :: a               ! Position point load
real :: b               ! L -a
real :: Mx              ! Moment at x
real :: Va              ! Shear end support
real :: Vb              ! Shear mid support
real :: Rb              ! Reaction in B
real :: a1, a2, a3      ! Distance between point loads
real :: P1, P2, P3, P4  ! Point loads 
real :: L               ! Length span
integer :: ix, ia       ! Counter
real, parameter :: t = 0.05                    ! Distance between studied points
real :: maximum
real :: minimum
real :: maxVa
real :: maxVb
real :: maxRb
real :: posx, minposx
real :: posa, minposa
integer, allocatable :: maxpos(:)
integer, allocatable :: minpos(:)
real, dimension(:,:), allocatable :: moments ! Array moments
real, dimension(:), allocatable :: DkEnd ! Shear End
real, dimension(:), allocatable :: DkMid ! Shear Mid
real, dimension(:), allocatable :: ReacB ! Reaction B
real, dimension(2) :: MaxMin
integer :: n 


L = 6.
a1 = 3.6
a2 = 1.
a3 = 1.
P1 = 112.3
P2 = 112.3
P3 = 0.
P4 = 0.

n= int(2*L/t +1)
write(*,*) 'Max Min', MaxMin
end program mom

! Function to calculate moments maxmin

real function MaxMin(n,L,P1,P2,P3,P4,a1,a2,a3,t) 
implicit none

integer :: ia, ix
integer, intent(in) :: n
real, intent(in) :: L
real, intent(in) :: P1
real, intent(in) :: P2
real, intent(in) :: P3
real, intent(in) :: P4
real, intent(in) :: a1
real, intent(in) :: a2
real, intent(in) :: a3
real, intent(in) :: t
real, dimension(:,:), allocatable :: moments
real :: Mx
real :: maxmom
real :: minmom

allocate (moments(n,n))
do ix = 1, n
    do ia = 1, n
        moments(ia, ix) = Mx((ix-1)*t, (ia-1)*t, L, P1) +                    & 
                          Mx((ix-1)*t, (ia-1)*t - a1, L, P2) +               &
                          Mx((ix-1)*t, (ia-1)*t - (a1+a2), L, P3) +          &
                          Mx((ix-1)*t, (ia-1)*t - (a1+a2+a3), L, P4) 
    end do
end do
maxmom=maxval(moments)
minmom=minval(moments)
 MaxMin=(maxmom,minmom)
end function MaxMin

real function Mx(x,a,L,P)   
! Function to calcute moment under one moving point load    
implicit none
!Calling parameters
real, intent(inout) :: x   ! Position where moment is calculated
real, intent(inout) :: a   ! Position point load
real, intent(in) :: L   ! Span
real, intent(in) :: P   ! Value load
real :: b
! Evaluate Mx
if (a < L) then
   b = L-a
else
    a = 2*L-a
    b = L-a
    x = 2*L-x
endif
if (a < 0 .or. a > 2*L) then
    Mx = 0.0
else if (x <= a) then
    Mx = ((P * b) / (4 * (L ** 3))) * ((4 * (L ** 2)) - (a * (L + a))) * x
else if ((x > a) .and. (x <= L)) then
    Mx = ((P * b) / (4 * (L ** 3))) * ((4 * (L ** 2)) - (a * (L + a))) * x - P * (x - a)
else if (x > L) then
    Mx = -(((P * b * a) / (4 * L ** 3)) * (L + a)) * (2 * L - x)
end if 
end function Mx

@rmoortgat ,

Please see the silly example below first:

   integer :: a = 1, b = 2 !<-- for illustration only; don't do this in actual code, it can lead to implied SAVE with nasty consequences
   integer :: x(2)
   x = [ a, b ] !<-- note it's not x = ( a, b )
   print *, x
end 
C:\temp>gfortran -ffree-form p.f -o p.exe

C:\temp>p.exe
           1           2

Now, note the use of square brackets [ .. ]. This is what you want with array definitions in Fortran.

Note the use of parenthesis ( .. ) preceded the syntax for arrays and it was applied for COMPLEX intrinsic type.

This is the issue you have encountered with your MaxMin assignment statement in your code.

1 Like

Thank you!
I used square brackets (my mistake) but now I get: The shapes of the array expressions do not conform.

Look into RESULT keyword with FUNCTION declarations in Fortran, that helps in many a context including what you have now:

..
function MaxMin(n,L,P1,P2,P3,P4,a1,a2,a3,t) result(r)
implicit none

integer :: ia, ix
integer, intent(in) :: n
real, intent(in) :: L
real, intent(in) :: P1
real, intent(in) :: P2
real, intent(in) :: P3
real, intent(in) :: P4
real, intent(in) :: a1
real, intent(in) :: a2
real, intent(in) :: a3
real, intent(in) :: t
! Function result
real :: r(2)
..
r = [ maxmom, minmom ]
..

P.S.> Obviously the function result can be any valid Fortran name. as per the author’s fancy/style. r is just an illustration

1 Like

For @rmoortgat and any other reader who may encounter a similar error with Intel Fortran processor, especially in the context of working with COMPLEX instrinsic type:

Note the following example:

   complex :: c
   real, parameter :: x = 1.0
   real, parameter :: y = 0.5
   real :: a , b
   c = ( x, y )     !<-- Supported: x and y are named constants
   c = ( 2.0, 0.1 ) !<-- Supported: the use of literal constants
   a = 1.0 ; b = 0.
   c = ( a, b )     !<-- Not supported by the standard; references to object a, b in a literal constant definition on the RHS
end
C:\temp>ifx /c /free p.f
Intel(R) Fortran Compiler for applications running on Intel(R) 64, Version 2024.1.0 Build 20240308
Copyright (C) 1985-2024 Intel Corporation. All rights reserved.

p.f(7): error #6211: A symbol must be a defined parameter in this context.   [A]
   c = ( a, b )     !<-- Not supported by the standard
---------^
compilation aborted for p.f (code 1)

C:\temp>

That’s, references to mutable objects in a literal constant definition e.g., here with ( .., .. ) for a COMPLEX type, is not supported by the standard.

This is what the processor meant by its message, “A symbol must be a defined parameter in this context”.

Attention: @greenrongreen , Intel Fortran team may want to get feedback from the user community re: the text of the message here:

  • chances are the users of Intel Fortran compiler will struggle to understand the message, particularly because “defined parameter” is not that a common term in Fortran literature. The influence of the standard means “named constant” is a better reflection of what is meant.
  • Technically, a sentence like so might be better: “A symbol must be a named or a literal constant in this context (A, B)” Just my “2 cents” here.
1 Like

Thanks!

Verzonden vanaf Outlook voor Android

Still getting: The shapes of the array expressions do not conform in this context [R]

Compiled with: ifx Mx_new.f90 /exe:maxmom.exe

program mom
! Moments in a 2 span continuous beam with equal spans under up to 4 moving point loads.
! 20/05/2024 R.M. Versie A
implicit none
real :: x               ! Position where moment is calculated
real :: a               ! Position point load
real :: b               ! L -a
real :: Mx              ! Moment at x
real :: Va              ! Shear end support
real :: Vb              ! Shear mid support
real :: Rb              ! Reaction in B
real :: a1, a2, a3      ! Distance between point loads
real :: P1, P2, P3, P4  ! Point loads 
real :: L               ! Length span
integer :: ix, ia       ! Counter
real, parameter :: t = 0.05                    ! Distance between studied points
real :: maximum
real :: minimum
real :: maxVa
real :: maxVb
real :: maxRb
real :: posx, minposx
real :: posa, minposa
integer, allocatable :: maxpos(:)
integer, allocatable :: minpos(:)
real, dimension(:,:), allocatable :: moments ! Array moments
real, dimension(:), allocatable :: DkEnd ! Shear End
real, dimension(:), allocatable :: DkMid ! Shear Mid
real, dimension(:), allocatable :: ReacB ! Reaction B
real, dimension(2) :: MaxMin
integer :: n 


L = 6.
a1 = 3.6
a2 = 1.
a3 = 1.
P1 = 112.3
P2 = 112.3
P3 = 0.
P4 = 0.

n= int(2*L/t +1)
write(*,*) 'Max Min', MaxMin
end program mom

! Function to calculate moments maxmin

real function MaxMin(n,L,P1,P2,P3,P4,a1,a2,a3,t) result(r)
implicit none

integer :: ia, ix
integer, intent(in) :: n
real, intent(in) :: L
real, intent(in) :: P1
real, intent(in) :: P2
real, intent(in) :: P3
real, intent(in) :: P4
real, intent(in) :: a1
real, intent(in) :: a2
real, intent(in) :: a3
real, intent(in) :: t
real, dimension(:,:), allocatable :: moments
real :: Mx
real, dimension(2) :: r
real :: maxmom
real :: minmom

allocate (moments(n,n))
do ix = 1, n
    do ia = 1, n
        moments(ia, ix) = Mx((ix-1)*t, (ia-1)*t, L, P1) +                    & 
                          Mx((ix-1)*t, (ia-1)*t - a1, L, P2) +               &
                          Mx((ix-1)*t, (ia-1)*t - (a1+a2), L, P3) +          &
                          Mx((ix-1)*t, (ia-1)*t - (a1+a2+a3), L, P4) 
    end do
end do
maxmom=maxval(moments)
minmom=minval(moments)
r=[maxmom, minmom]
end function MaxMin

real function Mx(x,a,L,P)   
! Function to calcute moment under one moving point load    
implicit none
!Calling parameters
real, intent(inout) :: x   ! Position where moment is calculated
real, intent(inout) :: a   ! Position point load
real, intent(in) :: L   ! Span
real, intent(in) :: P   ! Value load
real :: b
! Evaluate Mx
if (a < L) then
   b = L-a
else
    a = 2*L-a
    b = L-a
    x = 2*L-x
endif
if (a < 0 .or. a > 2*L) then
    Mx = 0.0
else if (x <= a) then
    Mx = ((P * b) / (4 * (L ** 3))) * ((4 * (L ** 2)) - (a * (L + a))) * x
else if ((x > a) .and. (x <= L)) then
    Mx = ((P * b) / (4 * (L ** 3))) * ((4 * (L ** 2)) - (a * (L + a))) * x - P * (x - a)
else if (x > L) then
    Mx = -(((P * b * a) / (4 * L ** 3)) * (L + a)) * (2 * L - x)
end if 
end function Mx

Please review my post upthread.

You can notice in my illustration the type declaration of the function result in the definition of the FUNCTION characteristics is eschewed when the RESULT clause is included. This is as per the standard.

Whereas you retained REAL in the funciton declaration statement, hence the error from the compiler due to invalid syntax.

By the way, are you familiar with books such as "Fortran for Scientists and Engineers, Stephen Chapman, McGraw-Hill, 4th Edition? A few days with books such as this can save you a lot of time.

You may soon realize online forums aren’t always the best when it comes to learning basic syntax, you can pick up some good ideas and tips but books are really hard to beat to develop a good foundation to help discern various different suggestions (some good, some bad) you will get on a forum such as this one. Say my own posts for example: discerning readers know to be most careful as to what to follow (little) and what to ignore (much) - good studies of books and papers help fine-tune such discernment and proper discrimination.

1 Like

You’re absolutely right. These are beginners questions and RTFM and so on.
I’m reading Chapman and Chivers but that takes months.
Learning a new language at 78 is a bit harder than at 28 and most of all you haven’t that much time left.

Roger

1 Like

I’m sorry but I still need some help.
Now the program compiles and runs.
However function Mx gives the correct result when called but MinMax always gives [0.,0.]
I even think that MinMax never gets executed.
I wonder if the problem hasn’t to do with calling another function within a function. Does the program return to the calling function or to the main function.
I attempted to debug step by step in VS but that doesn’t seem to work.
I did an attempt with a module but I can’t get this to work.
Roger

program mom
! Moments in a 2 span continuous beam with equal spans under up to 4 moving point loads.
! 20/05/2024 R.M. Versie A

implicit none
real :: x               ! Position where moment is calculated
real :: a               ! Position point load
real :: b               ! L -a
real :: Mx              ! Moment at x
real :: Va              ! Shear end support
real :: Vb              ! Shear mid support
real :: Rb              ! Reaction in B
real :: a1, a2, a3      ! Distance between point loads
real :: P1, P2, P3, P4  ! Point loads 
real :: L               ! Length span
integer :: ix, ia       ! Counter
real, parameter :: t = 0.05                    ! Distance between studied points
real :: maximum
real :: minimum
real :: maxVa
real :: maxVb
real :: maxRb
real :: posx, minposx
real :: posa, minposa
integer, allocatable :: maxpos(:)
integer, allocatable :: minpos(:)
real, dimension(:), allocatable :: DkEnd ! Shear End
real, dimension(:), allocatable :: DkMid ! Shear Mid
real, dimension(:), allocatable :: ReacB ! Reaction B
real, dimension(2) :: MaxMin
integer :: n 


L = 6.
a1 = 3.6
a2 = 1.
a3 = 1.
P1 = 112.3
P2 = 112.3
P3 = 0.
P4 = 0.

n= int(2*L/t +1)
write(*,*) 'Max Min', MaxMin
write(*,*) 'Mx =', Mx(3.,3.,6.,100.)
end program mom

! Function to calculate moments maxmin

function MaxMin(n,L,P1,P2,P3,P4,a1,a2,a3,t) 
implicit none
real, dimension(2) :: MaxMin
integer :: ia, ix
integer :: n
real :: L
real :: P1
real :: P2
real :: P3
real :: P4
real :: a1
real :: a2
real :: a3
real :: t
real, dimension(:,:), allocatable :: moments
real :: Mx
real :: maxmom
real :: minmom
allocate (moments(n,n))
do ix = 1, n
    do ia = 1, n
        moments(ia, ix) = Mx((ix-1)*t, (ia-1)*t, L, P1) +                    & 
                          Mx((ix-1)*t, (ia-1)*t - a1, L, P2) +               &
                          Mx((ix-1)*t, (ia-1)*t - (a1+a2), L, P3) +          &
                          Mx((ix-1)*t, (ia-1)*t - (a1+a2+a3), L, P4) 
    end do
end do
write(*,*) 'test2'
maxmom=maxval(moments)
minmom=minval(moments)
MaxMin= [maxmom, minmom]
end function MaxMin


real function Mx(x,a,L,P)   
! Function to calcute moment under one moving point load    
implicit none
!Calling parameters
real :: x   ! Position where moment is calculated
real :: a   ! Position point load
real :: L   ! Span
real :: P   ! Value load
real :: b
! Evaluate Mx
if (a < L) then
   b = L-a
else
    a = 2*L-a
    b = L-a
    x = 2*L-x
endif
if (a < 0 .or. a > 2*L) then
    Mx = 0.0
else if (x <= a) then
    Mx = ((P * b) / (4 * (L ** 3))) * ((4 * (L ** 2)) - (a * (L + a))) * x
else if ((x > a) .and. (x <= L)) then
    Mx = ((P * b) / (4 * (L ** 3))) * ((4 * (L ** 2)) - (a * (L + a))) * x - P * (x - a)
else if (x > L) then
    Mx = -(((P * b * a) / (4 * L ** 3)) * (L + a)) * (2 * L - x)
end if 
end function Mx
    

I have not studied the code in detail, but the following looks odd:

real, dimension(2) :: MaxMin
[...]
write(*,*) 'Max Min', MaxMin

You have both a local array and a function named MaxMin. I think the above just prints out the array, and the function is never referenced.

No succes. I give up.

Roger

@rmoortgat ,

Not so fast, try not to give up!

Please give this a try and check if this is what you would like your program to compute:

Click to see edited code
module moments_m
   ! Module for calculations of moments

   implicit none

contains

   ! Function to calculate moments maxmin
   function MaxMin(n,L,P1,P2,P3,P4,a1,a2,a3,t)
      real, dimension(2) :: MaxMin
      integer :: ia, ix
      integer :: n
      real :: L
      real :: P1
      real :: P2
      real :: P3
      real :: P4
      real :: a1
      real :: a2
      real :: a3
      real :: t
      real, dimension(:,:), allocatable :: moments
      real :: maxmom
      real :: minmom
      allocate (moments(n,n))
      do ix = 1, n
         do ia = 1, n
            moments(ia, ix) = Mx((ix-1)*t, (ia-1)*t, L, P1) +                    &
            Mx((ix-1)*t, (ia-1)*t - a1, L, P2) +               &
               Mx((ix-1)*t, (ia-1)*t - (a1+a2), L, P3) +          &
               Mx((ix-1)*t, (ia-1)*t - (a1+a2+a3), L, P4)
         end do
      end do
      write(*,*) 'test2'
      maxmom=maxval(moments)
      minmom=minval(moments)
      MaxMin= [maxmom, minmom]

      return

   end function MaxMin

   real function Mx(x,a,L,P)
      ! Function to calcute moment under one moving point load

      !Calling parameters
      real :: x   ! Position where moment is calculated
      real :: a   ! Position point load
      real :: L   ! Span
      real :: P   ! Value load
      real :: b
      ! Evaluate Mx
      if (a < L) then
         b = L-a
      else
         a = 2*L-a
         b = L-a
         x = 2*L-x
      endif
      if (a < 0 .or. a > 2*L) then
         Mx = 0.0
      else if (x <= a) then
         Mx = ((P * b) / (4 * (L ** 3))) * ((4 * (L ** 2)) - (a * (L + a))) * x
      else if ((x > a) .and. (x <= L)) then
         Mx = ((P * b) / (4 * (L ** 3))) * ((4 * (L ** 2)) - (a * (L + a))) * x - P * (x - a)
      else if (x > L) then
         Mx = -(((P * b * a) / (4 * L ** 3)) * (L + a)) * (2 * L - x)
      end if
      
      return

   end function Mx

end module

! A program to compute moments using the module
program mom

   use moments_m, only : MaxMin, Mx

   ! Moments in a 2 span continuous beam with equal spans under up to 4 moving point loads.
   ! 20/05/2024 R.M. Versie A

   implicit none

   real :: x               ! Position where moment is calculated
   real :: a               ! Position point load
   real :: b               ! L -a
   real :: Va              ! Shear end support
   real :: Vb              ! Shear mid support
   real :: Rb              ! Reaction in B
   real :: a1, a2, a3      ! Distance between point loads
   real :: P1, P2, P3, P4  ! Point loads
   real :: L               ! Length span
   integer :: ix, ia       ! Counter
   real, parameter :: t = 0.05                    ! Distance between studied points
   real :: maximum
   real :: minimum
   real :: maxVa
   real :: maxVb
   real :: maxRb
   real :: posx, minposx
   real :: posa, minposa
   integer, allocatable :: maxpos(:)
   integer, allocatable :: minpos(:)
   real, dimension(:), allocatable :: DkEnd ! Shear End
   real, dimension(:), allocatable :: DkMid ! Shear Mid
   real, dimension(:), allocatable :: ReacB ! Reaction B
   integer :: n

   L = 6.
   a1 = 3.6
   a2 = 1.
   a3 = 1.
   P1 = 112.3
   P2 = 112.3
   P3 = 0.
   P4 = 0.

   n= int(2*L/t +1)
   write(*,*) 'Max Min', MaxMin(n,L,P1,P2,P3,P4,a1,a2,a3,t)
   write(*,*) 'Mx =', Mx(3.,3.,6.,100.)

   stop

end program mom
  • Intel Fortran processor does the following with the above edited code:
C:\temp>ifx /free /standard-semantics p.f
Intel(R) Fortran Compiler for applications running on Intel(R) 64, Version 2024.1.0 Build 20240308
Copyright (C) 1985-2024 Intel Corporation. All rights reserved.

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

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

C:\temp>p.exe
 test2
 141.5127 -120.2733
 Mx = 121.8750

C:\temp>

You may notice some suggested changes to your code:

  1. Your functions MaxMin and Mx are moved to a Fortran MODULE named moments_m
  2. Your program mom then USEs this module,
  3. You may refer to your books on Fortran re: details around MODULEs and USE of them and the benefits they provide, especially with explicit interfaces,
  4. Given the USE and the explicit interfaces, the declarations of MaxMin and Mx in the calling program become extraneous and are removed,
  5. However the reference to MaxMin then in the print statement in the main program becomes a function invocation and thus it requires actual arguments (parameters) which are provided.

Hope this helps and you can take the learnings and adapt your program and extend it further.

Happy Coding!

2 Likes

Thank you for your support.
The output of MaxMin still gives [0.,0.] which it shouldn’t.
This function was tested in a more straight-forward program and I’m sure it works.
In my opinion there are two posibilities:

  • the function MaxMin for some reason doesn’t work as expected in this context.
  • the function never gets executed. A ‘test’ write in the function never get’s written.

Roger

Hallelujah, it works!
I did some cleaning up and removed variable definitions who are not needed anymore and now I get the expected values.
This is very bizar.
Thank you very much for your help, I learned a lot.

Roger

1 Like