Allocation: some explanation needed

Hello all,

this is an amateuristic attempt to write a program that calculates the moment in a 2 span continuous beam under moving point loads.
I did it first with VBA but calculating each element of a 241 x 241 array (5cm. mesh) takes forever. In the example I work with a very coarse mesh for testing purposes.
I would like to dynamically allocate an array of 2L/t + 1 x 2L/t +1 elements where L = span and t = distance between nodes.
But this does seem to be not possible.
Finally I wish to interface this little program with excel. Some tips how to do this would be appreciated.

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 :: 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.6                    ! Distance between studied points
!real, dimension( 21,21 ):: moments            ! Array moments
real :: maximum
real :: minimum
real :: posx
real :: posa
integer, allocatable :: maxpos(:)
real, dimension(:), allocatable :: moments
integer :: n 


write (*,*) 'Enter distance between point loads: a1 a2 a3'
read (*,*) a1, a2, a3

write (*,*) 'Enter point loads: P1 P2 P3 P4'
read (*,*) P1, P2, P3, P4

write (*,*) 'Enter length span: L'
read (*,*) L

n= int(2*L/t +1)
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

maximum = maxval(moments)
minimum = minval(moments)
maxpos = maxloc(moments)
posx = (maxpos(1)-1) * t
posa = (maxpos(2)-1) * t

write (*,*) 
do ix = 1, 21
        write(*,"(*(f8.2))") moments(ix,:)
end do

write (*,*) 'Maximum =', maximum
write (*,*) 'Minimum =', minimum
write (*,*) 'Maxloc =', maxpos
write (*,*) 'Posx =', posx
write (*,*) 'Posa =', posa
      
         
            
            
pause
end program mom
    
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


You have declared moments as a rank-1 array, but you are trying to allocate it as a rank-2 array. You have modify the declaration:

real, dimension(:,:), allocatable :: moments
!               ^^^

There are maybe some other problems in your code. If there are, please copy-paste the error messages from the compiler.

Thanks a lot. Mea Culpa, stupid mistake.
No more errors.
Next hurdle to overcome!
I suppose I have to compile a DLL in order to communicate with Excel VBA?

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 :: 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.6                    ! Distance between studied points

real :: maximum
real :: minimum
real :: posx
real :: posa
integer, allocatable :: maxpos(:)
real, dimension(:,:), allocatable :: moments ! Array moments
integer :: n 


write (*,*) 'Enter distance between point loads: a1 a2 a3'
read (*,*) a1, a2, a3

write (*,*) 'Enter point loads: P1 P2 P3 P4'
read (*,*) P1, P2, P3, P4

write (*,*) 'Enter length span: L'
read (*,*) L

n= int(2*L/t +1)
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

maximum = maxval(moments)
minimum = minval(moments)
maxpos = maxloc(moments)
posx = (maxpos(1)-1) * t
posa = (maxpos(2)-1) * t

write (*,*) 
do ix = 1, 21
        write(*,"(*(f8.2))") moments(ix,:)
end do

write (*,*) 'Maximum =', maximum
write (*,*) 'Minimum =', minimum
write (*,*) 'Maxloc =', maxpos
write (*,*) 'Posx =', posx
write (*,*) 'Posa =', posa
      
         
            
            
pause
end program mom
    
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 thought that the pause statement was obsolete? The “normal” way to have an interactive program pause is to execute a read statement with no input list. The i/o library then waits to see the carriage return (i.e. the end of record) before continuing.

You’re right. I’ll change it.
Roger