ProductsAbaqus/Standard User subroutine interface      SUBROUTINE URDFIL(LSTOP,LOVRWRT,KSTEP,KINC,DTIME,TIME)
C
      INCLUDE 'ABA_PARAM.INC'
C
      DIMENSION ARRAY(513),JRRAY(NPRECD,513),TIME(2)
      EQUIVALENCE (ARRAY(1),JRRAY(1,1))
      user coding to read the results file
      RETURN
      END 
 Variables to be defined
 
 
 Variables passed in for information
 
 Example: Terminating an analysis upon exceeding a Mises stress limitThe example below reads the values of Mises stress for the current increment from record 12 in the results file and terminates the analysis if any of the values of Mises stress written to the results file exceed 2.09 × 108. Here, POSFIL is used to position you to read from the current increment.       SUBROUTINE URDFIL(LSTOP,LOVRWRT,KSTEP,KINC,DTIME,TIME)
C
      INCLUDE 'ABA_PARAM.INC'
C
      DIMENSION ARRAY(513),JRRAY(NPRECD,513),TIME(2)
      EQUIVALENCE (ARRAY(1),JRRAY(1,1))
      PARAMETER(TOL=2.09D8)
C
C FIND CURRENT INCREMENT.
C
      CALL POSFIL(KSTEP,KINC,ARRAY,JRCD)
      DO K1=1,999999
         CALL DBFILE(0,ARRAY,JRCD)
         IF (JRCD .NE. 0) GO TO 110
         KEY=JRRAY(1,2)
C
C RECORD 12 CONTAINS VALUES FOR SINV
C
         IF (KEY.EQ.12) THEN
            IF (ARRAY(3).GT.TOL) THEN
               LSTOP=1
               GO TO 110
            END IF
         END IF
      END DO
 110  CONTINUE
C
      RETURN
      END
 Example: Terminating an analysis when the maximum Mises stress value stops increasingThis example demonstrates the use of URDFIL and POSFIL to stop an analysis when the maximum value of Mises stress in the model does not increase from one increment in the results file to the next. A data statement is used to save the maximum Mises stress value from the last increment. LOVRWRT is also used in this case to overwrite an increment in the results file once it has been read in URDFIL. The subroutine shown below must be modified to define the maximum Mises stress in the data statement each time a job is restarted. This can be avoided by removing the LOVRWRT=1 statement and recoding the routine to read both the previous and the current increment to check that the Mises stress increases from one increment to the next (in this case you must correctly handle the first increment written to the results file as there will be no previous increment). The results file must also be properly appended on restart if you wish to compare the values of Mises stress between the first increment of a restart and the final increment of the job being restarted. This approach has the disadvantage that the results file may become quite large, as no information in the file will be overwritten.       SUBROUTINE URDFIL(LSTOP,LOVRWRT,KSTEP,KINC,DTIME,TIME)
C
      INCLUDE 'ABA_PARAM.INC'
C
      DIMENSION ARRAY(513),JRRAY(NPRECD,513),TIME(2)
      EQUIVALENCE (ARRAY(1),JRRAY(1,1))
C
C INITIALIZE THE OLD MAXIMUM. FOR A JOB THAT IS BEING RESTARTED
C THIS VALUE SHOULD BE SET TO THE MAXIMUM MISES STRESS IN THE
C ORIGINAL ANALYSIS.
C
      DATA OLDMAX/-1.D0/
C
      CURRMAX = 0.D0
C
C FIND CURRENT INCREMENT.
C
      CALL POSFIL(KSTEP,KINC,ARRAY,JRCD)
C
C SEARCH FOR THE HIGHEST VALUE OF MISES STRESS
C AND STORE THIS IN CURRMAX
C
      DO K1=1,999999
         CALL DBFILE(0,ARRAY,JRCD)
         IF (JRCD.NE.0) GO TO 110
         KEY=JRRAY(1,2)
         IF (KEY.EQ.12) THEN
            IF (ARRAY(3).GT.CURRMAX) CURRMAX=ARRAY(3)
         END IF
      END DO
 110  CONTINUE
C
C COMPLETED READING OF CURRENT INCREMENT. NOW CHECK TO
C SEE IF VALUE OF MISES STRESS HAS INCREASED SINCE 
C LAST INCREMENT
C
      IF (CURRMAX.LE.OLDMAX) LSTOP=1
      OLDMAX=CURRMAX
      LOVRWRT=1
C
      RETURN
      END | |||||||||||||