-2

I am trying to write a FORTRAN subroutine for ABAQUS that would modify the seepage coefficient and thus the flow depending on whether there is contact on the surface. In order to do so I need 2 subroutines URDFIL to retrieve the node data and FLOW to modify the seepage coefficient.

However, when I compile my subroutine I get the following errors:

flow_us.for(81): error #6837: The leftmost part-ref in a data-ref can not be a function reference. [K_ELE_DETAILS]
       IF(K_ELE_DETAILS(E_INDX)%IS_CONT(N_INDX).EQ.0)THEN
----------^
flow_us.for(81): error #6158: The structure-name is invalid or is missing. [K_ELE_DETAILS]
       IF(K_ELE_DETAILS(E_INDX)%IS_CONT(N_INDX).EQ.0)THEN

Obviously it is repeated for the 3 lines (if's) that contain such structure (81,8, and 89).

Please find the code below and hopefully someone will be able to help

****************************************************************************************
***SUBROUTINE FOR ADAPTIVE FLUID FLOW
****************************************************************************************
****************************************************************************************
**
**
**
*USER SUBROUTINE
    SUBROUTINE URDFIL(LSTOP,LOVRWRT, KSTEP, KINC, DTIME, TIME)
    INCLUDE 'ABA_PARAM.INC'
C
    DIMENSION ARRAY(513),JRRAY(NPRECD,513),TIME(2)
    EQUIVALENCE (ARRAY(1),JRRAY(1,1))
C DECLARATIONS
    TYPE ELE_DATA
        SEQUENCE
        DOUBLE PRECISION :: NODE_COORD(9)
        DOUBLE PRECISION :: OPP_NODE_COORD(9)
        DOUBLE PRECISION :: IPT_COORD(9)
        DOUBLE PRECISION :: POR(3)
        DOUBLE PRECISION :: OPP_POR(3)
        INTEGER :: ELE_NUM
        INTEGER :: OPP_ELE_NUM
        INTEGER :: NODE_NUM(3)
        INTEGER :: OPP_NODE_NUM(3)
        INTEGER :: IPT_NUM(3)
        INTEGER :: OPP_IS_CONT(3)           
    END TYPE ELE_DATA

    TYPE(ELE_DATA)::K_ELE_DETAILS(500)
    COMMON K_ELE_DETAILS
    PARAMETER (THRESHOLD_CSTRESS=1.0E-6)
*******************************************************
    INTEGER :: NO_OF_NODES
    INTEGER :: NO_OF_ELEMENTS
    INTEGER :: NO_OF_DIM
    COMMON NO_OF_DIM, NO_OF_NODES, NO_OF_ELEMENTS
********************************************************
C INITIALIZE   
    LSTOP=0
    LOVRWRT=1
    LOP=0
    NO_OF_NODES=10000
    NO_OF_ELEMENTS=10000
    NO_OF_DIM=2

        DO K1=1,999999
            CALL DBFILE(0, ARRAY,JRCD)
            IF (JCRD.NE.0) GO TO 110
            KEY=JRRAY(1,2)
*******************************************************
C THE KEYS USED IN THE FOLLOWING LINES REFER
C TO INFORMATION ON THE SURFACE, NODES, CONTACT ETC
            IF (KEY.EQ.1501) THEN
            ELSE IF (KEY.EQ.1502)THEN
            ELSE IF(KEY.EQ.1911) THEN
            ELSE IF(KEY.EQ.108.AND.SURFACE_N_SET.EQ.'N_TOP') THEN
            ELSE IF(KEY.EQ.107.AND.SURFACE_N_SET.EQ.'N_TOP') THEN
            ELSE IF(KEY.EQ.1503)THEN
            ELSE IF(KEY.EQ.1504.AND.K_NODE_SET.EQ.'N_TOP')THEN
            ELSE IF(KEY.EQ.1511.AND.K_NODE_SET.EQ.'N_TOP')THEN
C IS THE NODE IN CONTACT?
120  CONTINUE
        END IF
        END DO 
110  CONTINUE
            RETURN
            END

**********************************************************
**********************************************************
*USER SUBROUTINE
    SUBROUTINE FLOW(H, SINK, KSTEP, KINC, TIME, NOEL, NPT, COORDS,
    1 JLTYP,SNAME)
    INCLUDE 'ABA_PARAM.INC'
C
    DIMENSION TIME(2), COORDS(3)
    CHARACTER*80 SNAME

    MIN_DIST=10E-20
    DO K25=1,NO_OF_ELEMENTS
        DO K26=1,NO_OF_NODES
C FINDS THE CLOSEST NODE TO THE INTEGRATION POINT NPT
        END DO
    END DO
C NOT IN CONTACT
    IF(K_ELE_DETAILS(E_INDX)%IS_CONT(N_INDX).EQ.0)THEN
        IF(K_ELE_DETAILS(E_INDX)%POR(N_INDX).GE.0) THEN
            SINK=0
            H=0.001
        ELSE
            SINK=0
            H=1
        END IF
    ELSE IF(K_ELE_DETAILS(E_INDX)%IS_CONT(N_INDX).EQ.1)THEN
C IF THERE IS CONTACT
        SINK=0
        H=0
    END IF
    RETURN
    END
General Grievance
  • 4,555
  • 31
  • 31
  • 45
  • Why is your code in all caps? Words spelled with all lowercase letters tend to be more legible than those spelled using only uppercase ones. Furthermore, there is little chance of confusing the letter `i` with the numeral `1`, the letter `B` with the numeral `8`, etc., which can be a problem with some fonts. Lastly, please write your code in free-form. In modern code, using structured control statements (such as `select case` or `if-then-else`) statement labels are uncommon. In fixed-source format the first five columns are therefore wasted because they are rarely used. – jlokimlin Aug 25 '16 at 18:05
  • 1
    Add `implicit none` at the appropriate point in each subroutine. – francescalus Aug 25 '16 at 18:19
  • Thanks. I am by no means an expert in Fortran and these subroutines were started by someone else in my research group and I had to have a look at them over the last couple of days which has made it harder for me to completely understand how they work. Could any of you explain me where that implicit none bits need to be added and what would it do?? Thanks – Tania Sánchez Aug 25 '16 at 21:50
  • 1
    The abaqus include file already contains an implicit statement (which is not `implicit none`) - adding implicit none will unfortunately conflict with that. – IanH Aug 25 '16 at 22:02
  • 1
    To be explicit after IanH's comment invalidated my earlier: in `flow` there is no declaration of `k_ele_details`, so it's taken implicitly as a function. The type definition and declarations from `urdfil` are not accessible in the other subroutines. And there are no global variables (except anything from the included file). In short, the compiler error message is merely that you haven't declared a variable as an array of a declared type. How to fix the entire program is quite involved, though. – francescalus Aug 25 '16 at 22:54
  • it looks like someone intended to pass `K_ELE_DETAILS` by common from one sub to the other, but there is no common in subroutine `flow`. I'm not sure what to make of two unnamed common blocks in `urdfil`. – agentp Sep 01 '16 at 00:19

1 Answers1

0

I think you meant to write

IF(K_ELE_DETAILS(E_INDX)%OPP_IS_CONT(N_INDX).EQ.0) THEN

instead of

IF(K_ELE_DETAILS(E_INDX)%IS_CONT(N_INDX).EQ.0)THEN

Also, if you intent to extend this code with type-bound procedures, you cannot reference a component of a function result of derived data type without an appropriate interface. Such issues are rarely encountered if the type declaration is confined to a module. The module will automatically generate the correct interface for type-bound procedures.

jlokimlin
  • 593
  • 4
  • 9
  • 4
    It looks to me (the code isn't complete) in the subroutine `flow` that `K_ELE_DETAILS` is function with integer result. This is through implicit typing. – francescalus Aug 25 '16 at 18:26