- Mark as New
- Bookmark
- Subscribe
- Mute
- Subscribe to RSS Feed
- Permalink
- Report Inappropriate Content
Hi Dear,
- Mark as New
- Bookmark
- Subscribe
- Mute
- Subscribe to RSS Feed
- Permalink
- Report Inappropriate Content
Hi Milad,
Check the "Abaqus User Subroutines Reference Guide" in the Abaqus documentation to confirm the UMAT subroutine arguments for the version of Abaqus you are using. The arguments in the subroutine statement can occasionally change for different versions of Abaqus, and then a previously written user subroutine can have run time errors.
I recommend writing a "main" program to test your UMAT separately from Abaqus to confirm that the subroutine runs correctly. Write a main program that provides all the inputs to the user subroutine, and even vary the input values to test that the subroutine does not have run time errors.
Run the Abaqus job from the command line instead of from within Abaqus/CAE as that should show you information about the compiling and linking that Abaqus is doing. Perhaps there will be error messages indicating if the compiling or linking was unsuccessful. Try running the Abaqus analysis from the Intel Fortran initialized console (CMD) window, which you can open from the Start button. I have had good success using that Fortran CMD window to run Abaqus with user subroutines. Depending on your version of Fortran, the location in the Start menu would be something like:
Start -> Intel Parallel Studio XE 2015 -> Compiler and Performance Libraries -> Command Prompt with Intel Compiler -> Intel 64 Visual Studio 2013 mode
To determine if the Abaqus job is crashing immediately, or actually getting in to the user subroutine, you can write debugging information from the user subroutine to the Abaqus message file (*.msg) using file unit = 7 (for Abaqus/Standard) using write() statements. You could write the passed input values and intermediate values from the subroutine to the message file to determine if data or a calculation is causing a run time error. Then look in the *.msg file for your debugging information; assuming the .msg file is created by Abaqus. Refer to the "Abaqus Analysis User's Guide" in section 3.7.1 "Fortran unit numbers used by Abaqus" and there is a list of the file unit numbers you can use for output. You could take the input values from the Abaqus message file and use them in your main program to further test the user subroutine.
Regards,
Greg Thorwald
Link Copied
- Mark as New
- Bookmark
- Subscribe
- Mute
- Subscribe to RSS Feed
- Permalink
- Report Inappropriate Content
A Web search shows that the code-144 message is from the Abaqus EXE, and is probably an indication that your user routine experienced a floating-point error (e.g., floating division by zero, sqrt(neg. arg), etc.). Apparently, Abaqus hooks up its own FPU error handler to service FPU exceptions.
You may attempt to examine your code and narrow down the part of it that cause the FPU exception. Otherwise, try an Abaqus user forum.
- Mark as New
- Bookmark
- Subscribe
- Mute
- Subscribe to RSS Feed
- Permalink
- Report Inappropriate Content
Hi Milad,
Check the "Abaqus User Subroutines Reference Guide" in the Abaqus documentation to confirm the UMAT subroutine arguments for the version of Abaqus you are using. The arguments in the subroutine statement can occasionally change for different versions of Abaqus, and then a previously written user subroutine can have run time errors.
I recommend writing a "main" program to test your UMAT separately from Abaqus to confirm that the subroutine runs correctly. Write a main program that provides all the inputs to the user subroutine, and even vary the input values to test that the subroutine does not have run time errors.
Run the Abaqus job from the command line instead of from within Abaqus/CAE as that should show you information about the compiling and linking that Abaqus is doing. Perhaps there will be error messages indicating if the compiling or linking was unsuccessful. Try running the Abaqus analysis from the Intel Fortran initialized console (CMD) window, which you can open from the Start button. I have had good success using that Fortran CMD window to run Abaqus with user subroutines. Depending on your version of Fortran, the location in the Start menu would be something like:
Start -> Intel Parallel Studio XE 2015 -> Compiler and Performance Libraries -> Command Prompt with Intel Compiler -> Intel 64 Visual Studio 2013 mode
To determine if the Abaqus job is crashing immediately, or actually getting in to the user subroutine, you can write debugging information from the user subroutine to the Abaqus message file (*.msg) using file unit = 7 (for Abaqus/Standard) using write() statements. You could write the passed input values and intermediate values from the subroutine to the message file to determine if data or a calculation is causing a run time error. Then look in the *.msg file for your debugging information; assuming the .msg file is created by Abaqus. Refer to the "Abaqus Analysis User's Guide" in section 3.7.1 "Fortran unit numbers used by Abaqus" and there is a list of the file unit numbers you can use for output. You could take the input values from the Abaqus message file and use them in your main program to further test the user subroutine.
Regards,
Greg Thorwald
- Mark as New
- Bookmark
- Subscribe
- Mute
- Subscribe to RSS Feed
- Permalink
- Report Inappropriate Content
Hi guys,thanks for your helpful replies,
Mr.Greg Thorwald : i,m using abaqus 6.10 -VS2008-intel composer XE 11,i also attached the error running the job through cmd line,it appears in compiling stage,so do u think thts coming probably from a compiling error?! besides when i complie the code in fortran without linking to abaqus im getting these errors:
1.error LNK2019: unresolved external symbol _MAIN__ referenced in function _main libifcoremt.lib(for_main.obj)
2. fatal error LNK1120: 1 unresolved externals Debug\Console5.exe
i've checked the .msg and .dat from abaqus output but unfortunately couldnt get anything.
im gonna try CMD window to run Abaqus with user subroutines
Regards,
- Mark as New
- Bookmark
- Subscribe
- Mute
- Subscribe to RSS Feed
- Permalink
- Report Inappropriate Content
You probably overlooked the fact that you need to write a Fortran main program that calls the DLL routine, and compile it and link to the import library of the DLL.
It is far more useful to have console output and program output presented/attached as text rather than as an image.
The image file err1.png appears to be the same as the one in #1, and the text in it does not match the description in #4.
- Mark as New
- Bookmark
- Subscribe
- Mute
- Subscribe to RSS Feed
- Permalink
- Report Inappropriate Content
thanks for ur guidance,im very new to fortran coding,(havent written the code,just try to run it and apply it to more complex model),thts the code(.for) :(the attached file is the ouput of abaqus after linking-job aborted).
c ******************************************************************************************* C
C C
C ABAQUS UMAT--EYEVP.FOR C
C C
C C
C C
C C
C C C
C C
C C
C FINAL UPDATE: DECEMBER,2004 C
C C
C NOTES: C
C THIS CODE CAN ONLY BE USED FOR PLANE STRAN AND AXISYMETRIC PROBLEM! C
C C
c ******************************************************************************************* C
C ACDEMIC NOTES: C
C 1. NO YIELD CONDITION IS USED TO JUDGE INITIAL YIELD (1-NON) C
C 2. No HARDENING RULES ARE USED TO COMPUTE PK0, WHICK IS COMPUTED FROM P AND Q (2-NON) C
C ******************************************************************************************* C
C NOTES: C
C 1 STATE VARIBLES ARE DEFINED IN THIS UMAT C C
C 1.VOLUMETRIC STRAIN; C C
C ******************************************************************************************* C
C IMPORTANT ABAQUS CONVENTION: C
C 1. HYDROSTATIC STRESS P=(-1/3)(SUM(STRESS)); C
C 2. TRY TO ENSURE FEW TRICKS AS POSSIBLE IN CODES C
C ******************************************************************************************* C
SUBROUTINE UMAT(STRESS,STATEV,DDSDDE,SSE,SPD,SCD,
1 RPL,DDSDDT,DRPLDE,DRPLDT,STRAN,DSTRAN,TIME,DTIME,
2 TEMP,DTEMP,PREDEF,DPREF,DPRED,MATERL,NDI,NSHR,NTENS,
3 NSTATV,PROPS,NPROPS,COORDS,DROT,PNEWDT,CELENT,DFGRD0,
4 DFGRD1,NOEL,NPT,LAYER,KSPT,KSTEP,KINC)
C
IMPLICIT REAL*8 (A-H,O-Z)
C
CHARACTER*8 CMNAME
DIMENSION STRESS(NTENS),STATEV(NSTATV),DDSDDE(NTENS,NTENS),
1 DDSDDT(NTENS),DRPLDE(NTENS),STRAN(NTENS),DSTRAN(NTENS),
2 TIME(2),PREDEF(1),DPRED(1),PROPS(NPROPS),COORDS(3),DROT(3,3),
3 DFGRDO(3,3),DFGRD1(3,3)
C*******************************************************************************************************C
C DEFINITE THE CONSTANT PARAMETER IN EVP MODEL;ELASTIC AND VISCO-PLASTIC COMPONENTS C *
C ELASTIC PARAMETERS KAPAV THE RATIO BETWEEN REBOUND MODULUS AND SPECIFIC VOLUMN;ENU POSSION'S RATIO C
C P0--INITIAL MEAN STRESS FOR INITIAL VOLUMETRIC STRAIN C
C (CALCULATED BASED ON THE INITIAL STRESS CONDITIONS,INPUT VALUE) C
C CREEP COMPRESSION PESAV THE RATIO BETWEEN CREEP PARAMETER(PESA) AND SPECIFIC VOLUMN C
C T0 INITIAL TIME FOR CREEP STARTING C
C REFERENCE LINE DEFINITION NAMDV THE RATIO BETWEEN COMPRESSION MODULUS AND SPECIFIC VOLUMN C
C PK00 INTERCEPT HYPOSTATIC PRESSURE (MEAN STRESS) INPUT VALUE C
C EEPVMO INITIAL ELASTOPLASTIC STRAIN C
C CRITICAL STATE LINE M THE SLOPE OF THE CRITIAL STATE LINE (COMPUTED FROM ANGLE(AFA)) C
C PHI EFFECTIVE INTERNAL FRICTION ANGLE(DG) C
C PK0 A STATE VARIABLE,CAOMPUTED FROM FLOW SURFACE C
C (INITIAL VALUE WHICH CAN BE COMPUTED FROM FROM INITIAL STRESS STATES) C
C KK0 LATERAL PRESSURE COEFFICIENT C
C EVKL LIMIT VISCOPLASTIC STRAIN (INPUT) C
C BETA PARAMETER DETERMING TYPE OF ALORITHM C
C DIFFERENT BETA CORRESPONDS TO DIFFERENT INTEGRATION ALGORITHM: C
C (BETA=1 BACKWARD EULER INTEGRATION) (BETA=0 FORWARD EULER INTEGRATION) C
C TEST-TESTING CONDITION WHICH MEANS THE CHOICE OF M (INCLINATION OF CRITIAL STATE LINE) C
C ******************************************************************************************************C
C +++++++++ MAIN PROGRAM +++++++++++++ C
C THE WHOLE PROCESS IS DEVIDED INTO TWO STAGES: DIRECT ALGORITHM (NO ITERATION) C
C THE PREESS-DEPENDENT ELASTIC BEHAVIOR IS USED IN THE ALGORITHM FOR SIMPLICITY C
C ******************************************************************************************************C
C MAIN PROGRAM
C
C DEFINITED VARIABLES USED IN MAIN PROGRAM
C
DIMENSION STRANT(4),DET(4),DSTRESS(4),DD1(4,4),DSTRESSN(4)
DIMENSION SIGMT(4),DD(4,4),DSIGM(NTENS),SIGM(NTENS),ETOTAL(4)
DIMENSION DEDSN(4,4),DFDSN(4),DD2N(4,4),EELAS(4),EVPR(4)
C
DOUBLE PRECISION KAPAV,NAMDV,T0,ENU,PESAV,EEPVM0,SIGM,EVK0
DOUBLE PRECISION EVKL,PHI,PM0,BETA,AFA,M,SIGMT,KE,KG,DP
DOUBLE PRECISION DSIGM,DD,F,P,Q,PN,AG,KKK,PNON,D1,D2,D4
DOUBLE PRECISION PP,QQ,PPK,AA,BB,AA1,B,AA2,EVT,DEVT,EVTT
DOUBLE PRECISION DEVPR(4),EVPN(4),SIGMN(4),DESN(4,4),DEVP(4)
DOUBLE PRECISION DQDS(4),DPKDS(4),DQ,DPK,EVTN
DOUBLE PRECISION DFP,ESP,ESQ,ESEV,DEVPS,EVPSR,ESHER,DESHER
C
PARAMETER (PI=3.1415926)
C
C PARAMETERS DEFINITION FOR SUBROUTINES
C
DIMENSION DEE(4),STS(4),DFDS(4),STS1(4),EVPRN(4)
DIMENSION STS2(4),EV2(4),DFSS1(4),DFSS2(4),DFSS3(4),DSTS(4)
DIMENSION DC(4,4),GES(4,4),DEDS(4,4),DES(4,4)
DIMENSION A(4,4),HN(4,4),DD2(4,4),DD0(4,4),DE(4,4),DD20(4,4)
C
DOUBLE PRECISION P1,QI,PM1,PESAV2,P02,E0,EL,DTIME2
DOUBLE PRECISION PM2,A2,B2,E1,E11,E12,KK2,BETA2
C
INTEGER K,K1,K2,I,J,NMAX
C
C TOTALLY 11 CONSTANTS NPROPS=12
C
KAPAV=PROPS(1)
ENU=PROPS(2)
PK00=PROPS(3)
PESAV=PROPS(4)
NAMDV=PROPS(5)
T0=PROPS(6)
EEPVM0=PROPS(7)
PHI=PROPS(8)
KKK=PROPS(9)
EVKL=PROPS(10)
BETA=PROPS(11)
TEST=PROPS(12)
C
C DEFINITE THE TYPE OF PROBLEM
C
IF(NDI.NE.3) THEN
WRITE(6,1)
1 FORMAT(//,30X,'***ERROR-THIS UMAT MAY ONLY BE USED FOR ***',
1 'ELEMENTS WITH THREE DIRECT STRESS COMPONENTS')
ENDIF
C
C CALCULATE PARAMETER--AFA AND M FROM K0 AND PHI
C
AFA=3.0*(1.0-KKK)/(1.0+2.0*KKK)
C
AG=PI/180.0*PHI
C
C CHOSE THE CORRESPONDING M FOR CRITIAL STATE LINE(FAILURE LINE)
C
IF(TEST.EQ.1) M=6.0*(SIN(AG))/(3.0-SIN(AG))
IF(TEST.EQ.2) M=6.0*(SIN(AG))/(3.0+SIN(AG))
C
IF(ENU.GT.0.4999.AND.ENU.LT.0.5001) ENU=0.499
C
C DEFINITE THE VOLUMETRIC STRAIN AND TOTAL STRAIN:EVT AND STRANT
C EV-VOLUMETRIC STRAIN; DEV-INCREMENT OF VOLUMETRIC STRAIN
C
EVT=0.0
DO K1=1,NDI
EVT=EVT+STRAN(K1)
ENDDO
C
EVT=STATEV(1)
C
C COMPUTE P AND Q IN THE CURRENT N STEP
C
P=(-1.0)*(STRESS(1)+STRESS(2)+STRESS(3))/3.0
Q=(STRESS(1)-STRESS(2))*(STRESS(1)-STRESS(2))+
1 (STRESS(1)-STRESS(3))*(STRESS(1)-STRESS(3))+
2 (STRESS(3)-STRESS(2))*(STRESS(3)-STRESS(2))
C
DO K1=NDI+1,NTENS
Q=Q+6.0*STRESS(K1)*STRESS(K1)
ENDDO
Q=SQRT(Q/2.0)+1.0E-25
C
C REDUCE THE TIME INCREMENT FOR THE GEOSTATIC STEP TO ENSURE ZERO
C INITIAL STRAIN CAN BE OBTAINED. ALSO, THIS TIME INCREMENT CAN NOT BE
C CHANGED IN INPUT DATA FILE! THE RULE TO CHOSE IT IS STRAIN < 1.0E-6
C
IF(KSTEP.EQ.1) DTIME=0.01
C
C CALCULATE HARDENING PARAMETER PK AT LAST STEP
C
PK=P+(Q-AFA*P)*(Q-AFA*P)/P/(M*M-AFA*AFA)
C
C CALCULATE ELASTIC STIFFNESS MATRIX
C
KE=1.0/KAPAV*ABS(P)
KG=3.0*0.5*(1.0-2.0*ENU)/(1.0+ENU)*KE
C
C FORM THE STIFFNESS MATRIX IN THIS STEP
C
DO I=1,NTENS
DO J=1,NTENS
DD1(I,J)=0.0
ENDDO
ENDDO
C
C DEFINE BASIC ELEMENT IN NONLINEAR ELASTIC STIFFNESS MATRIX
C PRESSURE-DEPENDENT NONLINEAR ELASTIC
C
D1=KE+4.0*KG/3.0
C
D2=KE-2.0*KG/3.0
C
D4=KG
C
DO I=1,NDI
DO J=1,NDI
DD1(J,I)=D2
ENDDO
DD1(I,I)=D1
ENDDO
C
DO I=NDI+1,NTENS
DD1(I,I)=D4
ENDDO
C
C UPDATE STRESS-STRESS=STRESS+DSTRESS USING DIRECT EXPLICIT ALGORITHM
C
CALL FLOW1(STRESS,AFA,M,PK00,NAMDV,EEPVM0,T0,DFDSN,EVPRN,EVT,
1 EVKL,PESAV)
C
CALL FLOW2(STRESS,AFA,M,PESAV,EVT,PK00,EEPVM0,EVKL,NAMDV,T0,
1 DFDSN,DFSS1,DFSS2,DFSS3,DEDSN)
C
DO 100 I=1,NTENS
DO 100 J=1,NTENS
DC(I,J)=0.0
DO 100 K=1,NTENS
DC(I,J)=DC(I,J)+DD1(I,K)*DTIME*BETA*DEDSN(K,J)
100 CONTINUE
C
DO 105 I=1,NTENS
DO 105 J=1,NTENS
IF(I.EQ.J) DC(I,J)=1.0+DC(I,J)
105 CONTINUE
C
C SYSMETRY AND INVERSION OF MATRIX DC
C
CALL INVERT(DC,4)
C
DO 110 I=1,4
DO 110 J=1,4
DES(I,J)=0.0
DO 110 K=1,4
DES(I,J)=DES(I,J)+DC(I,K)*DD1(K,J)
110 CONTINUE
C
DO I=1,NTENS
DO J=1,NTENS
DD2(I,J)=DES(I,J)
ENDDO
ENDDO
C
C FORM JACOBIAN MATRIX
C
DO K1=1,NTENS
DO K2=1,NTENS
DDSDDE(K1,K2)=DD2(K1,K2)
ENDDO
ENDDO
C
C CALCULATE NEW STRESS INCREMENT DSTRESS
C
DO K=1,NTENS
DSTRESS(K)=0.0
ENDDO
C
DO K1=1,NTENS
DO K2=1,NTENS
DSTRESS(K2)=DSTRESS(K2)
1 +DDSDDE(K2,K1)*(DSTRAN(K1)-DTIME*EVPRN(K1))
ENDDO
ENDDO
C
C UPDATE THE NEW STRESS FOR N+1 STEP
C
DO K1=1,NTENS
STRESS(K1)=STRESS(K1)+DSTRESS(K1)
ENDDO
C ***** THE END OF STRESS UPDATE ALGORITHM ******
C
C COMPUTE THE INCREMENT OF P-DP
C
DP=(-1.0)*(DSTRESS(1)+DSTRESS(2)+DSTRESS(3))*1.0/3.0
C
C COMPUTE AND UPDATE THE VOLUMETRIC STRAIN EVM USING PK FOR N INCREMENT
C 1 COMPUTE THE VISCOPLASTIC STRAIN RATE B
C
PKK=ABS(PK/PK00)
AA=EEPVM0+NAMDV*LOG(PKK)-EVT
BB=(1.0+AA/EVKL)
AA1=AA/BB
IF(PESAV.GT.1.0E-7) THEN
AA2=AA1/PESAV
!! IF(AA2.GT.0.0) AA2=0.0
B=(BB**2)*(EXP(AA2))
B=PESAV/T0*B
ELSE
B=0.0
ENDIF
C
C 2 COMPUTE THE DERIVATIVE OF VISCOOLASTIC STRAIN RATE WITH RESPECT
C TO PK AND VOLUME STRAIN:JP AND JV
C
JP=2.0*NAMDV/BB/EVKL/P+NAMDV/PESAV/P/BB/BB
JV=(-1.0)*2.0/BB/EVKL+(-1.0)/PESAV/BB/BB
C
C FORM INCREMENT OF VOLUME STRAIN
C
DEVT=(KAPAV*DP/P+DTIME*B*(1.0+BETA*JP*DP))/(1.0-DTIME*B*BETA*JV)
C
C UPDATE VOLUMETRIC STRAIN EVT; HARDENING PARAMETER PK; P AND Q;
C
EVT=EVT+DEVT
! IF(EVT.LT.0.0) EVT=0.0
! IF(AA.GT.0.0) EVT=NAMDV*LOG(PKK)
C
STATEV(1)=EVT
C
C 1. TOTAL STRAIN ENERGY
C
DEE1=0.0
TDE=0.0
DO K1=1,NTENS
TDE=TDE+(STRESS(K1)*DSTRAN(K1))
ENDDO
C
C 2. SPECIFIC ELASTIC STRAIN ENERGY
C
DO K1=1,NTENS
DO K2=1,NTENS
DEE(K2)=DEE(K2)+DSTRAN(K1)*DD1(K1,K2)
ENDDO
ENDDO
C
DO K=1,NTENS
DEE1=DEE1+DEE(K)*DSTRAN(K)
ENDDO
C
SSE=SSE+DEE1
SPD=SPD+TDE-DEE1
RETURN
END
C ********************************** THE END OF MAIN PROGRAM *****************************
C
C ********************************************************************************** C
C NOTES: THE FOLLOWING SECTION IS SUBROUTINES INVOKED IN THE MAIN PROGRAM C C
C SUBROUTINES (TOTALLY 4) C C
C ********************************************************************************** C
C ================================================================================== C
C 1. FLOW DIRECTION--FLOW(I) C
C THE ONE-ORDER DERIVATION OF YIELD FUNCTION WITH REPECT TO STRESS TENSOR C
c SUBROUTINE FLOW1(I) C
C NOTES: 1. STS1-STRESS TENSOR C
C 2. DFDS-DERIVATIVE OF YIELD FUNCTION VERSUS STRESS TTENSOR C
C 3. AFA1-AFA; 4.M1-M; 5.P1,Q1--MEAN STRESS AND DEVIATOR STRESS C
C 4. EVPRN-ELASTRO-VISCOPLASTIC STRAIN RATE FOR N STEP C
C ================================================================================== C
SUBROUTINE FLOW1(STS1,AFA,M,PK00,NAMDV,EEPVM0,T0,DFDS,EVPR,
1 EVT,EVKL,PESAV)
C
IMPLICIT REAL*8 (A-H,O-Z)
C
DIMENSION DFDS(4),STS1(4),EVPR(4)
DOUBLE PRECISION PK00,STS1,DFDS,AFA,M,PK,PKPK0,NAMDV
DOUBLE PRECISION EEPVM0,T0,EVT,EVKL,PESAV,EVPR,BBB
DOUBLE PRECISION A,B,C,P1,Q1,GE1,GE3,AAA,AAA1
INTEGER K,I,J,KSTEP
C
C MISES STRESS(Q)
C
A=STS1(1)-STS1(2)
B=STS1(2)-STS1(3)
C=STS1(3)-STS1(1)
P1=(-1.0)*(STS1(1)+STS1(2)+STS1(3))/3.0
Q1=A*A+B*B+C*C
Q1=Q1+6.0*STS1(4)*STS1(4)
Q1=SQRT(Q1/2.0)+1.0E-25
C
PK=P1+(Q1-AFA*P1)*(Q1-AFA*P1)/(M*M-AFA*AFA)/P1
C
GE1=PESAV/T0
GE3=2.0*P1-PK-2.0*AFA*(Q1-AFA*P1)/(M*M)
1 +(AFA*AFA)*(PK-2.0*P1)/M/M
C
! IF(GE3.LT.0.01) GE3=0.01
C
C CALCULATE FIRST DERIVATIVE OF YIELD FUNCTION TO STRESS TENSOR DFDS
C
DO I=1,3
DFDS(I)=(2.0*P1-PK-(Q1-AFA*P1)*(2.0*AFA+9.0*P1/Q1)/(M*M)
1 +(AFA*AFA)*(PK-2.0*P1)/(M*M))*1.0/3.0*(-1.0)+3.0*STS1(I)
2 *(Q1-AFA*P1)/Q1/(M*M)
ENDDO
DFDS(4)=6.0*STS1(4)*(Q1-AFA*P1)/Q1/(M*M)
C
DO K1=1,4
PKPK0=ABS(PK/PK00)
AAA=EEPVM0+NAMDV*(LOG(PKPK0))-EVT
!! IF(AAA.GT.0.0) AAA=0.0
BBB=(1.0+AAA/EVKL)
IF(PESAV.GT.1.0E-7) THEN
AAA1=AAA/BBB/PESAV
C
C ENSURE EVT LARGER THAN REFERENCE STRAIN EVR
C
!! IF(AAA1.GT.0.0) AAA1=0.0
EVPR(K1)=GE1*(BBB**2)*(EXP(AAA1))/(ABS(GE3))*DFDS(K1)
ELSE
EVPR(K1)=0.0
ENDIF
ENDDO
C
RETURN
END
C **************************** FFFFFFFFFFFFFFFFFF ********************************
C ================================================================================== C
C 2. SUBROUTINE FLOW2 (STS2,....) C
C DIREVATION OF VISCOPLASTIC RATE WITH RESPECT TO STRESS TENSOR C
C NOTES: 1.DEDS-DIREVATION OF VISCOPLASTIC RATE WITH RESPECT TO STRESS TENSOR C
C 2.DFDS-FIRST DERIVATIVE OF YIELD FUNCTION TO STRESS TENSOR C
C 3.STS2-STRESS TENSOR; 4.EV-VOLUMN STRAIN C
C 5.EVKL-LIMIT VISCOPLASTIC STRAIN C
C ================================================================================== C
SUBROUTINE FLOW2(STS2,AFA,M,PESAV,EVT,PK00,EEPVM0,EVKL,NAMDV,T0,
1 DFDS,DFSS1,DFSS2,DFSS3,DEDS)
C
IMPLICIT REAL*8 (A-H,O-Z)
C
DIMENSION DFDS(4),DFSS1(4),DFSS2(4),DFSS3(4),STS2(4)
DIMENSION GES(4),DEDS(4,4),DC(4,4),DC1(4,4),DFDS2(4,4)
DOUBLE PRECISION AFA,M,NAMDV,PK,EVT,PK00,EPVM0,T0,PESAV
DOUBLE PRECISION PM22,B2,A2,P,Q,Q1,Q2,Q3,EVKR,E11
DOUBLE PRECISION E12,EVKL,E1,EVKR0
INTEGER K,I,J,KSTEP
C
C FIRSTLY, CALCULATE P AND Q AND PM
c CALCULATE P
C
P=(-1.0)*(STS2(1)+STS2(2)+STS2(3))/3.0
C
C CALCULATE Q
C
Q1=STS2(1)-STS2(2)
Q2=STS2(2)-STS2(3)
Q3=STS2(1)-STS2(3)
Q=Q1*Q1+Q2*Q2+Q3*Q3
Q=Q+6.0*STS2(4)*STS2(4)
Q=SQRT(Q/2.0)+1.0E-25
C
PK=P+(Q1-AFA*P)*(Q1-AFA*P)/(M*M-AFA*AFA)/P
C
C FORM UNIT MATRIX
C
DO 405 I=1,4
GES(I)=1.0
405 CONTINUE
GES(4)=0.0
C
C CALCULATE DEDS
C
DO 430 I=1,3
DFSS1(I)=-1.0/3.0
DFSS2(I)=1.0*P+STS2(I)
DFSS3(I)=-1.0/3.0
430 CONTINUE
C
DFSS1(4)=0.0
DFSS2(4)=2.0*STS2(4)
DFSS3(4)=0.0
C
DO 450 I=1,4
DO 450 J=1,4
450 DFDS2=0.0
C
DO I=1,4
DO J=1,4
DFDS2(I,J)=DFSS1(I)*(-2.0/3.0-AFA/(M*M)/3.0*(9.0*P/Q+2.0*AFA)
1 +2.0/3.0*AFA*AFA/M/M)*GES(J)
2 +AFA/(M*M)/Q*(2.0-GES(J))*STS2(J)
3 +DFSS2(I)*1.5*AFA/Q/Q/Q/(M*M)*(3.0*P*P*GES(J)
4 +(2.0*Q*Q*GES(J)+9.0*(2.0-GES(J))*P*STS2(J))/3.0)
5 +DFSS3(I)*3.0/(M*M)*(1.0-AFA*P/Q)*GES(J)
C
IF (I.EQ.J) THEN
DFDS2(I,J)=DFDS2(I,J)+3.0*(2.0-GES(J))/(M*M)
1 *(1.0-AFA*P/Q)
ENDIF
ENDDO
ENDDO
C
DO 410 I=1,4
DO 410 J=1,4
DC(I,J)=DFDS(I)*GES(J)
DC1(I,J)=DFDS(I)*((2.0-GES(J))*STS2(J)+P*GES(J))
410 CONTINUE
C
C FORM B2 AND A2 TO CALCULATE SCALAR VALUE IN YIELD RULE
C
B2=2.0*P-PK-2.0*AFA*(Q-AFA*P)/(M*M)+(AFA*AFA)*(PK-2.0*P)/(M*M)
C
! IF(B2.LT.0.01) B2=0.01
C
PM22=ABS(PK/PK00)
EVKR=EEPVM0+NAMDV*(LOG(PM22))-EVT
C
!! IF(EVKR.GT.0.0) EVKR=0.0
C
E1=1.0+EVKR/EVKL
E11=EVKR/E1
C
C EVKL--LIMIT OF THE VISCOPLASTIC STRAIN
C
IF(PESAV.GT.1.E-7) THEN
E12=E11/PESAV
IF (E12.GT.0.0) E12=0.0
A2=PESAV/T0*(E1**2)*(EXP(E12))
ELSE
A2=0.0
ENDIF
C
C FORM DEDS(I,J)-DIFFERENTIATION OF VISCOPLASTIC STRAIN RATE TO STRESS TENSOR
C
DO I=1,4
DO J=1,4
IF (PESAV.GT.1.0E-7) THEN
DEDS(I,J)=DFDS2(I,J)*A2/(ABS(B2))
1 +(DC(I,J)*2.0/3.0+3.0*AFA*DC1(I,J)/Q/(M*M))/(B2*B2)*A2
ELSE
DEDS(I,J)=0.0
ENDIF
ENDDO
ENDDO
C
RETURN
END
C **************************** FFFFFFFFFFFFFFFFFF ********************************
C ============================================================================ C
C 3. INVERT FORM INVERSION OF MATRIX C
C SUBROUTINE FOR CALCULATING THE INVERT MARTRIX OF THE STIFFNESS MATRIX C
C ============================================================================ C
SUBROUTINE INVERT(A,NMAX)
C
IMPLICIT REAL*8 (A-H,O-Z)
C
DIMENSION A(4,4)
INTEGER N,J,NMAX,I
C
DO 310 N=1,NMAX
D=A(N,N)
DO 320 J=1,NMAX
320 A(N,J)=-A(N,J)/D
DO 450 I=1,NMAX
IF(N-I) 410,450,410
410 DO 440 J=1,NMAX
IF(N-J) 420,440,420
420 A(I,J)=A(I,J)+A(I,N)*A(N,J)
440 CONTINUE
450 A(I,N)=A(I,N)/D
A(N,N)=1.0/D
310 CONTINUE
C
RETURN
END
C **************************** FFFFFFFFFFFFFFFFFF ********************************
C **************************** //// THE END \\\\ ********************************
- Mark as New
- Bookmark
- Subscribe
- Mute
- Subscribe to RSS Feed
- Permalink
- Report Inappropriate Content
please correct me if im wrong.(have no experience coding in fortran);
1-i need to write a Fortran main program(run the subroutine as a individual code), and compile it and link to the import library of the DLL.(dont have any idea now??)
the text in it does not match the description in #4.<<<<<<< what do u mean by that?sry i didnt understand that
THTS the abaqus input file:
**
**TRIAXIAL TEST SIMULATION:DRAINED TEST
**
** PARTS
**
*Part, name=Part-1
*End Part
**
** ASSEMBLY
**
*Assembly, name=Assembly
**
*Instance, name=Part-1-1, part=Part-1
*Node
1, 0., 0.
2, 0.019, 0.
3, 0., 0.038
4, 0.019, 0.038
*Element, type=CAX4
1, 1, 2, 4, 3
** Region: (CLAY:Picked)
*Elset, elset=_I1, internal
1,
** Section: CLAY
*Solid Section, elset=_I1, material=CLAY
1.,
*End Instance
*Nset, nset=_PickedSet4, internal, instance=Part-1-1
1, 3
*Elset, elset=_PickedSet4, internal, instance=Part-1-1
1,
*Nset, nset=_PickedSet5, internal, instance=Part-1-1
2, 4
*Elset, elset=_PickedSet5, internal, instance=Part-1-1
1,
*Nset, nset=_PickedSet6, internal, instance=Part-1-1
1, 2
*Elset, elset=_PickedSet6, internal, instance=Part-1-1
1,
*ELSET,ELSET=ECLAY, instance=Part-1-1
1
*NSET,NSET=NCLAY,instance=Part-1-1
1,2,3,4
*NSET,NSET=TOP,instance=Part-1-1
3,4
*NSET,NSET=BOTTOM,instance=Part-1-1
1,2
*NSET,NSET=LHS,instance=Part-1-1
1,3
*End Assembly
**
** MATERIALS
**
*MATERIAL,NAME=CLAY
*User Material, TYPE=MECHANICAL, constants=12,unsymm
0.0125, 0.3, 9.48, 0.0023, 0.0837, 1.0, 0.0, 25.37,
0.999, 0.355, 1.0, 2
*DEPVAR
1,
**
*INITIAL CONDITIONS, TYPE=RATIO
NCLAY,1.08, 0., 1.08, 0.038
*INITIAL CONDITIONS,TYPE=STRESS,GEOSTATIC
ECLAY,-1.0E2, 0., -1.0E2, 0.038, 0.999
**
**
*INITIAL CONDITIONS,TYPE=SOLUTION
ECLAY, 0.1972
**
**
*AMPLITUDE,NAME=RATE,DEFINITION=TABULAR,TIME=STEP TIME,VALUE=RELATIVE
0.1, 0.0435, 0.2, 0.0870, 0.3, 0.1304, 0.4, 0.1739,
0.5, 0.2174, 0.6, 0.2609, 0.7, 0.3043, 0.8, 0.3478,
0.9, 0.3913, 1.0, 0.4348, 1.1, 0.4783, 1.2, 0.5217,
1.3, 0.5652, 1.4, 0.6087, 1.5, 0.6522, 1.6, 0.6957,
1.7, 0.7391, 1.8, 0.7826, 1.9, 0.8261, 2.0, 0.8696,
2.1, 0.9130, 2.2, 0.9565, 2.3, 1.0
**
** ----------------------------------------------------------------
**
*STEP
GEOSTATIC INITIAL STRESS STATE
*GEOSTATIC
*DLOAD
ECLAY,P2,1.0E2
**
** BOUNDARY CONDITIONS
**
*Boundary
BOTTOM, 2
TOP,2
LHS,1
*Output, field, FREQUENCY=1
*ELEMENT OUTPUT,ELSET=ECLAY
S,E
**
** HISTORY OUTPUT: H-Output-1
*EL PRINT
S,
E
**
*END STEP
**
** ---------------------------------------------------------------
** STEP: STEP100
**
*Step,EXTRAPOLATION=NO,INC=10000,UNSYMM=YES
STEP100
*STATIC
0.0005,2.3,1.0E-20,0.0005
**
**KEEP CONSTANT VERTICAL STRAIN RATE 1.0E-6 PER SECOND
**
*BOUNDARY,AMPLITUDE=RATE
TOP,2,2,0.0076
*EL PRINT
S,
E,
SDV,
*NODE PRINT
U,RF
**
*Output, field, FREQUENCY=5
*ELEMENT OUTPUT,ELSET=ECLAY
S,
E,
SDV
**
** HISTORY OUTPUT: H-Output-1
**
*Output, history, frequency=5
*ELEMENT OUTPUT,ELSET=ECLAY
S,
E,
SDV
*End Step
- Mark as New
- Bookmark
- Subscribe
- Mute
- Subscribe to RSS Feed
- Permalink
- Report Inappropriate Content
From the command line messages it looks like Abaqus has compiled and linked to the user subroutine and started the analysis. To investigate further, I still recommend that you write a main program that can call the user subroutine to confirm that it is working correctly before running from Abaqus. Then add write statements to unit=7 (to the Abaqus *.msg message file) within the user subroutine to see if Abaqus has been able to call the user subroutine and pass input values. Adding more write statements will give an indication of progress through the user subroutine and where the crash occurs.
- Mark as New
- Bookmark
- Subscribe
- Mute
- Subscribe to RSS Feed
- Permalink
- Report Inappropriate Content
m b. wrote:
(have no experience coding in fortran)
1-i need to write a Fortran main program(run the subroutine as a individual code), and compile it and link to the import library of the DLL.(dont have any idea now??)
In that case, you cannot proceed with the task. Sorry.

- Subscribe to RSS Feed
- Mark Topic as New
- Mark Topic as Read
- Float this Topic for Current User
- Bookmark
- Subscribe
- Printer Friendly Page