On Wednesday, September 23, 2015 at 11:39:07 AM UTC+10, nik@cabana wrote:
>
> dis what I got:
> Error in job Job-4: Problem during compilation - C:\Users\nikhildlondhe\Documents\Visual Studio 2013\Projects\UMAT_Trials\UMAT_Trials\UMAT.for
> Job Job-4 aborted due to errors.
>
This error message provides little information.
To me your code should compile but likely give incorrect results.
I expect you have
* not initialised key variables correctly or
* defined the correct variable kind, 4 byte integers and 8 byte reals
Below are some suggestions, which you should review and then correct.
I would expect that DDSDDT and STRESS are not provided with initial values, although I could be wrong on this ?
SUBROUTINE UMAT (STRESS,STATEV,DDSDDE,SSE,SPD,SCD,
1 RPL,DDSDDT,DRPLDE,DRPLDT,
2 STRAN,DSTRAN,TIME,DTIME,TEMP,DTEMP,PREDEF,DPRED,CMNAME,
3 NDI,NSHR,NTENS,NSTATV,PROPS,NPROPS,COORDS,DROT,PNEWDT,
4 CELENT,DFGRD0,DFGRD1,NOEL,NPT,LAYER,KSPT,KSTEP,KINC)
C
! INCLUDE 'ABA_PARAM.INC' ! this was not provided; and not required ??
C
C declare argument types explicitly ; is this correct ?
C I would expect 8 byte reals and 4 byte integers ??
INTEGER*4 NDI,NSHR,NTENS,NSTATV,NPROPS,
1 NOEL,NPT,LAYER,KSPT,KSTEP,KINC
real*8 SSE,SPD,SCD,RPL,DRPLDT,DTIME,TEMP,DTEMP,PNEWDT,CELENT
real*8 STRESS(NTENS),STATEV(NSTATV),
1 DDSDDE(NTENS,NTENS),DDSDDT(NTENS),DRPLDE(NTENS),
2 STRAN(NTENS),DSTRAN(NTENS),TIME(2),PREDEF(1),DPRED(1),
3 PROPS(NPROPS),
4 COORDS(3),DROT(3,3),DFGRD0(3,3),DFGRD1(3,3)
C
real*8 :: EMOD,ENU,EBULK3,EG2,EG,EG3,ELAM
integer*4 :: k, K1,K2
CHARACTER :: CMNAME*80
C !This code is written to simulate Isotropic Isothermal Elasticity, which is nothing but uniform elastic model from Abaqus
C !PROPS(1) = E; Young's modulus of the material
C !PROPS(2) = nu; Poission's ratio of the material
C !Please note this code is not applicable for plane stress conditions as the stiffness matrix is different for them
C !if (NDI/=3) then
C ! write(7,*) 'This UMAT only be used for elements with 3D'
C ! call XIT
C !endif
C
C !Elastic Properties definition
EMOD = PROPS(1)
ENU = PROPS(2)
EBULK3 = EMOD/(1-2*ENU)
EG2 = EMOD/(1+ENU)
EG = EG2/2
EG3 = 3*EG
ELAM = (EBULK3-EG2)/3
DDSDDE = 0 ! ##### zero values must first be initialised
do k = 1, NDI
DDSDDE(1:NDI,K) = ELAM
DDSDDE(K,K) = EG2+ELAM
end do
do K = NDI+1, NTENS
DDSDDE(K,K) = EG
end do
C !This part calculates stress based on element stiffness matrix and engineering strain only ??
do K = 1, NTENS
STRESS(K) = 0 ! #### is this stress component added to input STRESS(:) provided ??
! do K1=1, NTENS
! STRESS(K2)=STRESS(K2)+DDSDDE(K2,K1)*DSTRAN(K1)
! end do
STRESS(K) = STRESS(K) + DOT_PRODUCT (DDSDDE(:,K),DSTRAN(:)) ! DDSDDE is symmetric
end do
C
RETURN
END