Abaqus DFLUX subroutine in Fortran

六月ゝ 毕业季﹏ 提交于 2021-01-28 08:40:49

问题


this is my first post here and I hope I will be clear describing the issues I'm having with Abaqus subroutine. I'm quite a newbie using Fortran. Basically, my goal is to define a non-uniform surface heat flux over an open cross-section tube and I'm using the DFLUX subroutine. Being open cross-section, the flux is influenced by the self-shadowing of the structure and has to be defined accordingly. Apparently the subroutine is called at each integration point, so that the coordinates of these points are not stored and I have each time just X,Y,Z values for a single point. What I'd like to do is to store all the coordinates in one array so that I can compare the different points to apply the conditions for the heat flux. I've read around about COMMON blocks or SAVE command, but I can't find how to use such options in my subroutine. I hope I've been clear enough. This is the subroutine I'm using:

     SUBROUTINE DFLUX(FLUX,SOL,JSTEP,JINC,TIME,NOEL,NPT,COORDS,JLTYP,
 1 TEMP,PRESS,SNAME)

  INCLUDE 'ABA_PARAM.INC'

   REAL X,Y,Z,t,pi,theta
   parameter(pi=3.1415)
   DIMENSION COORDS(3),FLUX(2),TIME(2)

   CHARACTER*80 SNAME

  X=COORDS(1)-0.1 ! X coordinate of the center in global ref
  Y=COORDS(2)+0.1732 ! Y coord of the center in global ref
  Z=COORDS(3)
  t=TIME(2)
  theta=atan2(X,Y)
  if (JSTEP.eq.1) then !Step with heat flux impinging on structure
  !flux dependant on the angle of incidence
      if (theta.ge.0 .and.theta.le.pi/2 .or. theta.le.-pi/2) then
       flux(1)=1400*abs(cos(theta))
       flux(2)=0
    else !shadowed portion of the structure
       flux(1)=0
       flux(2)=0
    endif
  else
     STOP
  endif
  RETURN

  END

回答1:


background: Abaqus provides a number of Fortran subroutine "templates" (in fixed-format/F77 style) that allow users to get specific info or influence certain aspects of the solution during an analysis, aka user-subroutines. Abaqus controls when the user-subroutines are called, what info is passed in/out, etc. Users cannot change any of that, and have no access to the main program or its proprietary source code. However, within a user-subroutine, the user is free to write any valid code they feel is necessary.

In this question, the OP wants to store information from each call to the dflux user-subroutine so that it is available to other subroutines or to other calls to the dflux subroutine. Note: this capability is not provided by dflux, so the OP needs a work-around.

possible work-arounds: Luckily, the dflux user-subroutine provides the element number, the integration point number, and the spatial coords for the current call. This info can probably be used to store (and access) any data you need. The data storage/transfer method might be accomplished through a COMMON block, a Fortran module, or even a text file or some other external "database".

> I recommend the module-based approach. However, see this answer for a good explanation of how to use both COMMON blocks and modules.

(EDIT) For completeness, a very simple example with a module and an abaqus subroutine could be structured something like:

module data_mod
  ! Any routine may access this module with the statement: "USE data_mod".
  ! Any variable within the module is then shared by those routines.

  implicit none

  ! You can use an allocatable array, but for this example I will assume
  ! there are 1000 or fewer points, and up to 10 values for each.
  real, dimension(1000,10) :: point_data

end module data_mod


subroutine dflux(....all the args...)
  ! Note: you must "USE" modules before any other statements in the routine.

  use data_mod

  ! Now you may carry on with the rest of your code. 
  ! Be sure to have the required "INCLUDE 'ABA_PARAM.INC" statement,
  ! which defines how abaqus implements "IMPLICIT REAL" for your machine,
  ! and all of the boilerplate variable declarations included with the 
  ! DFLUX subroutine template.

  include 'aba_param.inc'
  (...etc...)

  ! For simplicity, I am assuming you have a unique ID for each point, and
  ! each ID is numerically equal to one of the row indices in 'point_data'.
  ! When ready to read/write data in the 'point_data' array:

  ! Read data:
  neighbor_vals(:) = point_data(NEIGHBOR_ID, 2:)
  old_data_at_current_point(:) = point_data(ID, 2:)

  (...etc...)

  ! Write data:
  point_data(ID,2:4) = coords(:)
  point_data(ID,5) = result1
  point_data(ID,6) = result2

end subroutine dflux

> You will need to choose a type of data container and some clever organizational concept - perhaps using the element number, integration point number, or the (x,y,z) coordinates to uniquely identify the data you want to store. For instance, a simple 2-dimensional (MxN) array might be sufficient: each row represents the Mth integration point, the first column contains the unique point identifier(s), and the remaining columns contain any values you want to store from each point. Note: Determining which points are "neighbors" is another topic you will need a clever solution for. Once you've done this, perhaps neighboring points can be stored in the array as well, for faster access.

> You are safe reading data from other integration points stored in the data container, but do not write/change the values stored in the data container (whether it is within a COMMON block or a module) unless it is for the current integration point where dflux is currently being called.


side notes:

  1. New users often think they are stuck writing FORTRAN 77 in their Abaqus user-subroutines. They aren't.
  2. The easiest way to use modules along with abaqus user-subroutines is to place them at the top of your file. Abaqus will then compile and link them automatically when you run the analysis.


来源:https://stackoverflow.com/questions/55022283/abaqus-dflux-subroutine-in-fortran

易学教程内所有资源均来自网络或用户发布的内容,如有违反法律规定的内容欢迎反馈
该文章没有解决你所遇到的问题?点击提问,说说你的问题,让更多的人一起探讨吧!