30.2. Example of Fortran Subroutine user_force

SUBROUTINE USER_FORCE(MODE,I_CONTROL,R_CONTROL,NSTRUC,TIME,TIMESTEP,STAGE, &
                       POSITION,VELOCITY,COG, &
                       FORCE,ADDMASS,ERRORFLAG)

!DECLARATION TO MAKE USER_FORCE PUBLIC WITH UN-MANGLED NAME 

!DEC$ attributes dllexport , STDCALL , ALIAS : "USER_FORCE" :: user_force

!DEC$ ATTRIBUTES REFERENCE :: I_CONTROL, R_CONTROL
!DEC$ ATTRIBUTES REFERENCE :: POSITION, VELOCITY, COG, FORCE, ADDMASS
!DEC$ ATTRIBUTES REFERENCE :: MODE, NSTRUC, TIME, TIMESTEP, STAGE
!DEC$ ATTRIBUTES REFERENCE :: ERRORFLAG

IMPLICIT NONE

INTEGER MODE, NSTRUC, STAGE, ERRORFLAG
REAL TIME, TIMESTEP
INTEGER, DIMENSION (100) :: I_CONTROL
REAL, DIMENSION (100) :: R_CONTROL
REAL, DIMENSION (3,NSTRUC) :: COG
REAL, DIMENSION (6,NSTRUC) :: POSITION, VELOCITY, FORCE
REAL, DIMENSION (6,6,NSTRUC) :: ADDMASS

! Input Parameter Description:
!
! MODE(Int)     - 0 = Initialisation. This routine is called once with mode 0
!                     before the simulation. All parameters are as described
!                     below except for STAGE, which is undefined. FORCES and
!                     ADDMASS are assumed undefined on exit.
!                     IERR if set to > 0 on exit will cause
!                     the simulation to stop.
!
!                 1 = Called during the simulation. FORCE/ADDMASS output expected.
! 
!                99 = Termination. This routine is called once with mode 99
!                     at the end of the simulation.
!
! I_CONTROL(100)- User-defined integer control parameters input in .DAT file.
! R_CONTROL(100)- User-defined real control parameters input in .DAT file.
!
! NSTRUC(Int)   - Number of structures in the simulation
!
! TIME          - The current time (see STAGE below)
!
! TIMESTEP      - The timestep size (DT, see STAGE below)
!
! STAGE(Int)    - The stage of the integration scheme. AQWA time integration is
!                 based on a 2-stage predictor corrector method. This routine is
!                 therefore called twice at each timestep, once with STAGE=1 and
!                 once with STAGE=2. On stage 2 the position and velocity are
!                 predictions of the position and velocity at TIME+DT. 
!                 e.g. if the initial time is 0.0 and the step 1.0 seconds then 
!                 calls are as follows for the first 3 integration steps:
!
!                 CALL USER_FORCE(.....,TIME=0.0,TIMESTEP=1.0,STAGE=1 ...)
!                 CALL USER_FORCE(.....,TIME=0.0,TIMESTEP=1.0,STAGE=2 ...)
!                 CALL USER_FORCE(.....,TIME=1.0,TIMESTEP=1.0,STAGE=1 ...)
!                 CALL USER_FORCE(.....,TIME=1.0,TIMESTEP=1.0,STAGE=2 ...)
!                 CALL USER_FORCE(.....,TIME=2.0,TIMESTEP=1.0,STAGE=1 ...)
!                 CALL USER_FORCE(.....,TIME=2.0,TIMESTEP=1.0,STAGE=2 ...)
!
! COG(3,NSTRUC) - Position of the Center of Gravity in the Definition axes. 
!
! POSITION(6,NSTRUC) - Position of the structure in the FRA; angles in radians
!
! VELOCITY(6,NSTRUC) - Velocity of the structure in the FRA
!                      angular velocities in radians/s
!
!
! Output Parameter Description:
!
! FORCE(6,NSTRUC) - Force on the Center of gravity of the structure. NB: these
!                   forces are applied in the Fixed Reference axis e.g.
!                   the surge(X) force is ALWAYS IN THE SAME DIRECTION i.e. in
!                   the direction of the X fixed reference axis.
!
! ADDMASS(6,6,NSTRUC)
!                 - Added mass matrix for each structure. As the value of the
!                   acceleration is dependent on FORCES, this matrix may be used
!                   to apply inertia type forces to the structure. This mass
!                   will be added to the total added mass of the structure at
!                   each timestep at each stage.
!
! ERRORFLAG       - Error flag. The program will abort at any time if this
!                   error flag is non-zero. The values of the error flag will
!                   be output in the abort message.

!------------------------------------------------------------------------
! MODE=0 - Initialize any summing variables/open/create files.
!          This mode is executed once before the simulation begins.
!------------------------------------------------------------------------

      IF (MODE.EQ.0) THEN
         
		 CONTINUE


!------------------------------------------------------------------------
! MODE=1 - On-going - calculation of forces/mass
!------------------------------------------------------------------------

      ELSEIF (MODE.EQ.1) THEN
         FORCE = (-1.0E6 * POSITION) - (2.0E5 * VELOCITY)
         ADDMASS = 0
         ERRORFLAG = 0


!------------------------------------------------------------------------
! MODE=99 - Termination - Output/print any summaries required/Close Files
!           This mode is executed once at the end of the simulation
!------------------------------------------------------------------------

!      ELSEIF (MODE.EQ.99) THEN



!------------------------------------------------------------------------
! MODE# ERROR - OUTPUT ERROR MESSAGE
!------------------------------------------------------------------------

       ELSE	

       ENDIF
       RETURN

END SUBROUTINE USER_FORCE