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