Google Groups no longer supports new Usenet posts or subscriptions. Historical content remains viewable.
Dismiss

Unknown syntax error while compiling subroutines

144 views
Skip to first unread message

nik@cabana

unread,
May 1, 2017, 6:55:35 PM5/1/17
to
Dear all,

I have written following two fortran subroutines, which are called by external Abaqus program iteratively. My program is exiting with unknown error regarding compilation of these subroutines. Can anybody tell me what is the syntax error here? Thank you in advance, Nik

SUBROUTINE SIGINI(SIGMA,COORDS,NTENS,NCRDS,NOEL,NPT,LAYER,
1 KSPT,LREBAR,NAMES)
C
INCLUDE 'ABA_PARAM.INC'
C
DIMENSION SIGMA(NTENS),COORDS(NCRDS)
CHARACTER NAMES(2)*80

REAL, DIMENSION(3,3) :: T,X,STRESSXYZ,STRESSRTZ
REAL :: Stress,r,c,s,ylim,sine,cosine,radius,depth,dummy1,dummy2
INTEGER :: i,j
INTEGER, parameter :: NROWS=4442796, NCOLS=8
REAL :: output(NROWS,NCOLS)
REAL, DIMENSION(1,6) :: xy

ylim=-8.701882 !6309 Size Bearing
r=SQRT(COORDS(1)**2 + COORDS(3)**2)

if (COORDS(2)>ylim) then
sine=COORDS(1)/r
cosine=COORDS(3)/r
dummy1=(36.5948*sine-COORDS(1))**2 + (COORDS(2))**2 !6309 Size Bearing
dummy2=(36.5948*cosine-COORDS(3))**2 !6309 Size Bearing
radius=SQRT(dummy1+dummy2)
depth=radius-9.0805 !6309 Size Bearing
elseif(COORDS(2)<=ylim) then
depth=34-r !6309 Size Bearing
endif

if (depth<-0.0001) then
Stress=0 !This insures residual stress in ball = 0
elseif (depth>=-0.0001 .AND. depth<=0.026) then
!Stress=(300*depth/0.026)-700
Stress=-400
elseif(depth>0.026 .AND. depth<=0.5) then
Stress=-400
elseif(depth>0.5 .AND. depth<=1) then
!Stress=(400*depth/0.265)-1154.72
Stress=800*(depth-1)
else
Stress=0
endif

STRESSXYZ(:,:)=0.0
STRESSRTZ(:,:)=0.0
STRESSRTZ(2,2)=Stress !Residual stress is applied in circumferential direction
STRESSRTZ(3,3)=Stress !Residual stress is applied in axial direction
c=COORDS(1)/r
s=COORDS(3)/r
T(:,:)=0.0
T(1,1)=c
T(1,2)=-s
T(2,1)=s
T(2,2)=c
T(3,3)=1
X(:,:)=0.0
X(1,1)=c
X(1,2)=s
X(2,1)=-s
X(2,2)=c
X(3,3)=1
STRESSXYZ=T*STRESSRTZ*X

if (depth>=1) then
CALL Read_xcsv(output)
i=27*(NOEL-1)+NPT
xy(1,:)=output(i,3:8)
STRESSXYZ(1,1)=xy(1,1)
STRESSXYZ(2,2)=xy(1,2)
STRESSXYZ(3,3)=xy(1,3)
STRESSXYZ(1,2)=xy(1,4)
STRESSXYZ(1,3)=xy(1,5)
STRESSXYZ(2,3)=xy(1,6)
endif

SIGMA(1)=STRESSXYZ(1,1)
SIGMA(2)=STRESSXYZ(2,2)
SIGMA(3)=STRESSXYZ(3,3)
SIGMA(4)=STRESSXYZ(1,2)
SIGMA(5)=STRESSXYZ(1,3)
SIGMA(6)=STRESSXYZ(2,3)

RETURN
END


Subroutine Read_xcsv (xcsv)
IMPLICIT NONE
! read real numbers from CSV file

integer, parameter :: iu=20, nrows = 4442796, ncols = 8

real :: xcsv(nrows,ncols)
integer :: i

open (unit=iu,file="D:\E\3D\Run_2.csv",action="read",status="old")

do i=1,nrows
read (iu,*) xcsv(i,:)
end do
close (unit=iu)
END Subroutine Read_xcsv

steve kargl

unread,
May 1, 2017, 7:03:49 PM5/1/17
to
nik@cabana wrote:

> I have written following two fortran subroutines, which are called by external
> Abaqus program iteratively. My program is exiting with unknown error regarding
> compilation of these subroutines. Can anybody tell me what is the syntax error
> here? Thank you in advance, Nik

You forgot a few important details. What is the exact error message?
What Fortran compiler? What options were used with Fortran program?

--
steve

nik@cabana

unread,
May 1, 2017, 7:10:43 PM5/1/17
to
Hello, the error is unknown. The program exit automatically without showing any output. Abaqus just gives compilation error without any specific details. FYI, the code runs fine without adding following lines:

CALL Read_xcsv(output)

Subroutine Read_xcsv (xcsv)
IMPLICIT NONE
! read real numbers from CSV file

integer, parameter :: iu=20, nrows = 4442796, ncols = 8

real :: xcsv(nrows,ncols)
integer :: i

open (unit=iu,file="D:\E\3D\Run_2.csv",action="read",status="old")

do i=1,nrows
read (iu,*) xcsv(i,:)
end do
close (unit=iu)
END Subroutine Read_xcsv

When, I add these lines the simulation is aborted. Its Intel compiler 17.0 Update 2 Intel (R) 64 Visual Studio 2013.

steve kargl

unread,
May 1, 2017, 7:20:27 PM5/1/17
to
nik@cabana wrote:

> On Monday, May 1, 2017 at 7:03:49 PM UTC-4, steve kargl wrote:
>> nik@cabana wrote:
>>
>> > I have written following two fortran subroutines, which are called by external
>> > Abaqus program iteratively. My program is exiting with unknown error regarding
>> > compilation of these subroutines. Can anybody tell me what is the syntax error
>> > here? Thank you in advance, Nik
>>
>> You forgot a few important details. What is the exact error message?
>> What Fortran compiler? What options were used with Fortran program?
>>
>> --
>> steve
>
> Hello, the error is unknown. The program exit automatically without showing any output. Abaqus just gives compilation error without any specific details. FYI, the code runs fine without adding following lines:
>
> CALL Read_xcsv(output)
>
> Subroutine Read_xcsv (xcsv)
> IMPLICIT NONE
> ! read real numbers from CSV file
>
> integer, parameter :: iu=20, nrows = 4442796, ncols = 8
>
> real :: xcsv(nrows,ncols)

340 MB array. Can your system and system settings accomodate the array?

> integer :: i

Add
integer ios
character(len=80) msg

>
> open (unit=iu,file="D:\E\3D\Run_2.csv",action="read",status="old")

Change to

open (unit=iu,file="D:\E\3D\Run_2.csv",status="old",iostat=ios,iomsg=msg)
if (ios /= 0) then
print *, trim(msg)
stop
end if

>
> do i=1,nrows
> read (iu,*) xcsv(i,:)
> end do
> close (unit=iu)
> END Subroutine Read_xcsv
>
> When, I add these lines the simulation is aborted. Its Intel compiler 17.0 Update 2 Intel (R) 64 Visual Studio 2013.

--
steve

nik@cabana

unread,
May 1, 2017, 7:36:05 PM5/1/17
to
Hey,
for this line:
open (unit=iu,file="D:\E\3D\Run_2.csv",status="old",iostat=ios,iomsg=msg)

the last iostat=ios,iomsg=msg) part becomes green. Does it mean compiler is treating it as comment? How can continue it in next line?

steve kargl

unread,
May 1, 2017, 7:43:23 PM5/1/17
to
nik@cabana wrote:

> On Monday, May 1, 2017 at 7:20:27 PM UTC-4, steve kargl wrote:
>> nik@cabana wrote:
>>
>> > On Monday, May 1, 2017 at 7:03:49 PM UTC-4, steve kargl wrote:
>> >> nik@cabana wrote:
>> >>
>> >> > I have written following two fortran subroutines, which are called by external
>> >> > Abaqus program iteratively. My program is exiting with unknown error regarding
>> >> > compilation of these subroutines. Can anybody tell me what is the syntax error
>> >> > here? Thank you in advance, Nik
>> >>
>> >> You forgot a few important details. What is the exact error message?
>> >> What Fortran compiler? What options were used with Fortran program?
>> >>
> Hey,
> for this line:
> open (unit=iu,file="D:\E\3D\Run_2.csv",status="old",iostat=ios,iomsg=msg)
>
> the last iostat=ios,iomsg=msg) part becomes green. Does it mean compiler is treating it as comment? How can continue it in next line?

I don't use Intel or Visual Studio (or Windows for that matter). To split a line
and assuming free-form source code, do

open (unit=iu,file="D:\E\3D\Run_2.csv",status="old", &
& iostat=ios, iomsg=msg)

--
steve


dpb

unread,
May 1, 2017, 7:52:24 PM5/1/17
to
On 05/01/2017 6:10 PM, nik@cabana wrote:
> On Monday, May 1, 2017 at 7:03:49 PM UTC-4, steve kargl wrote:
>> nik@cabana wrote:
>>
>>> I have written following two fortran subroutines, which are called by external
>>> Abaqus program ...


Compile the subroutines independently of trying to run them in Abaqus
first; then you'll at least be able to see what errors are.

You also need to find the information about what switches are used by
the batch file that is dispatched to do the compilation; the separation
of your code from the compiler by the intermediary program makes
debugging much more difficult; at least get them to compile successfully
first.

--

nik@cabana

unread,
May 1, 2017, 8:04:35 PM5/1/17
to
Both the subroutines run successfully when compiled independently without Abaqus. For example, following code run without any error:
PROGRAM Area
!---------------------------------------------------------------------
!
! This program gets data from stored .csv file
!
!---------------------------------------------------------------------
IMPLICIT NONE


! Declare local variables
INTEGER :: a,b
INTEGER, parameter :: NROWS=4442796, NCOLS=8
REAL :: radius, output(NROWS,NCOLS), x(1,6), y(3,3)
integer:: NELM, NPT, i
NELM=164548
NPT=27
CALL Read_xcsv(output)
i=27*(NELM-1)+NPT
x(1,:)=output(i,3:8)
!x(2,:)=output(i,6:8)
!x(3,:)=output(i,9:11)
!y=transpose(x)
write(*, '(A)', ADVANCE = "NO") "The stored data is: "
write(*,*) x(1,:)
write (*,*) 'Enter the values for a & b:'
read (*,*) a,b

END PROGRAM Area

Subroutine Read_xcsv (xcsv)
IMPLICIT NONE
! read real numbers from CSV file

integer, parameter :: iu=20, nrows = 4442796, ncols = 8

real :: xcsv(nrows,ncols)
integer :: i
integer :: ios
character(len=80) :: msg

open (unit=iu,file="D:\E\3D\Run_2.csv",action="read", &
status="old", iostat=ios,iomsg=msg)
if (ios/=0) then
print *,trim(msg)
stop
endif


do i=1,nrows
read (iu,*) xcsv(i,:)
end do
close (unit=iu)
END Subroutine Read_xcsv


Also the SIGINI subroutine also run on its own. The problem arises when I use SIGINI and Read_xcsv subroutines together.

nik@cabana

unread,
May 1, 2017, 9:14:10 PM5/1/17
to
Hey, no success with that. But I did figure out what is the problem. Issue is with the size of this arrary: output(NROWS,NCOLS). If I decrease its size from 4442796X8 to 81000X8 then code is running fine. Is there any way to make sure Fortran compiler is able to handle such a large amount of data?? Subroutine is coded in fortran 77 language. Also, instead of inputting entire csv file into fortran can I extract data from specific rows/columns to avoid working with such a large amount of data?

Richard Maine

unread,
May 1, 2017, 10:20:22 PM5/1/17
to
nik@cabana <nikhil...@gmail.com> wrote:

> Is there any way to make sure Fortran compiler is able to handle such a
> large amount of data??

That has more to do with the operating system and environment than much
particular to the Fortran language. A better solution is usually not to
use such large arrays if they aren't actually needed, as suggested
below.

> Subroutine is coded in fortran 77 language.

No, it is not. Not even particularly close. It is full of features not
introduced until Fortran 90.

> Also, instead of inputting entire csv file into fortran can I extract data
> from specific rows/columns to avoid working with such a large amount of
> data?

Of course. And that's normally far preferable. If it isn't obvious how
to write code to do that, I'm afraid that's more a question of how to
program almost anything than I'm well suited to tutor on.

--
Richard Maine
email: last name at domain . net
domain: summer-triangle

herrman...@gmail.com

unread,
May 2, 2017, 2:31:50 AM5/2/17
to
On Monday, May 1, 2017 at 6:14:10 PM UTC-7, nik@cabana wrote:

(snip)

> Hey, no success with that.
> But I did figure out what is the problem.
> Issue is with the size of this arrary: output(NROWS,NCOLS).
> If I decrease its size from 4442796X8 to 81000X8 then code is
> running fine.
> Is there any way to make sure Fortran compiler is able to
> handle such a large amount of data??

As noted in another recent thread, Fortran compilers often allocate
such arrays on the stack, and many linkers, often without knowing
what the compiler did, allocate a small stack.

One fix is to use a larger stack.

Another fix, which often works, is to make it ALLOCATABLE,
then ALLOCATE it, which usually doesn't put it on the stack.

But you should also know how much you actually need, and adjust
accordingly.
Message has been deleted

mecej4

unread,
May 2, 2017, 5:45:31 AM5/2/17
to
On 5/1/2017 8:14 PM, nik@cabana wrote:
> Hey, no success with that. But I did figure out what is the problem.
> Issue is with the size of this arrary: output(NROWS,NCOLS).
> If I decrease its size from 4442796X8 to 81000X8 then code is
> running fine. Is there any way to make sure Fortran compiler is
> able to handle such a large amount of data?? Subroutine is coded
> in fortran 77 language. Also, instead of inputting entire csv
> file into fortran can I extract data from specific rows/columns to
> avoid working with such a large amount of data?
>

As far as the Abaqus subroutine is concerned, all you need is one row
out of 4.4 million. When you go to your office mailbox stand to pick up
your mail, you skip all the boxes except yours. You don't make Xerox
copies of the contents of all the mail boxes, and then retrieve yours.

So, declare a 1-D array output(NCOLS), and do

my_row = 27*(NOEL-1)+NPT
call Read_xcsv(output,my_row)

in the caller, and in the subroutine that reads the file, do

DO i=1,my_row-1
READ(iu,*)
END DO
READ(iu,I)output
CLOSE(iu)
RETURN

The stack consumption is reduced from 142 MB to 64 B.

You should also think of more sensible arrangements. If the Abaqus
program will always consume a small subset of the rows in the CSV file,
extract just those rows into a (much smaller) file, and have the Abaqus
program read that file, instead. Likewise, if the subroutine will be
called a large number of times, store the row in memory after reading
the file just once.

-- mecej4

mec...@clothes.com
Disrobe and don Gmail to reply.

mecej4

unread,
May 2, 2017, 5:47:57 AM5/2/17
to
On 5/2/2017 4:45 AM, mecej4 wrote:
> READ(iu,I)output
^
READ(iu,*)output

That was a typographical error.

-- mecej4
mec...@noclothes.com
Message has been deleted

robin....@gmail.com

unread,
May 2, 2017, 7:00:36 AM5/2/17
to
You need an explicit interface for READ_XCSV.

robin....@gmail.com

unread,
May 2, 2017, 7:07:54 AM5/2/17
to
> Hey, no success with that. But I did figure out what is the problem. Issue is with the size of this arrary: output(NROWS,NCOLS). If I decrease its size from 4442796X8 to 81000X8 then code is running fine. Is there any way to make sure Fortran compiler is able to handle such a large amount of data?? Subroutine is coded in fortran 77 language.

No, both subroutines are in Fortran 90 and later language.
The first subroutine is in fixed source form, and incorrectly uses "C" for
comment instead of '!'.

The second subroutine uses Fortran 90 and later construct(s) also.
0 new messages