Subroutine Format

<< Click to Display Table of Contents >>

Navigation:  Flexcom > Theory > Applied Loading > User Subroutines >

Subroutine Format

Previous pageNext page

Blank or template FORTRAN listings of the user_defined_element and user_solver_variables subroutines are shown below. The structure of these subroutines will be familiar to experienced FORTRAN programmers, but is quite straightforward even for beginners.

The subroutine statement at the top opens the routine. This contains a list of arguments which are used to share information between the custom subroutine and the main program source code.

The implicit none statement ensures that all variables are explicitly defined.

The variable declaration section lists the program arguments and their data types. Array variables are also sized appropriately.

Comments, starting with an exclamation (!) symbol, are used to improve code clarity.

The end subroutine statement closes the routine.

You should insert your own custom code towards the end of the template, just after the "Insert user code here" statement.

 

User Defined Element Template

subroutine user_defined_element(iter,time,ramp,depth,rhow,nnode,nncon,ncord,nndof,nelmn,necon,nedof,ndamp,npipcurv,npippts,   &
 mxpipnod,n0kpipnod,maxre,num_int,elmcon,nodcon,intoun,ietoue,etype,edamp,cord,displacement,velocity,acceleration,trgb,tglu,disp_prev,pos_prev, &
 vel_prev,acc_prev,cdnn,cdtt,cann,catt,cmnn,reno,nore,pip_reaction,axial_force,y_shear,z_shear,torque,y_bending,z_bending,eff_tension,y_curvature,      &
 z_curvature,length,eiyy,eizz,gj,ea,mass,polar,dint,ddrag,dbuoy,dout,dcont,fluid,damper,pip_curve_defn,pip_curve_npts,pip_stiffness_data)

 
!dec$ attributes dllexport, stdcall, reference :: user_defined_element
 implicit none
 
 ! Input variables - cannot be modified within this subroutine
 
 
 integer(4), intent(in) :: iter       !< Current iteration
 !dec$ attributes value :: iter
 real(8), intent(in)    :: time       !< Current timestep
 !dec$ attributes value :: time
 real(8), intent(in)    :: ramp       !< Ramp
 !dec$ attributes value :: ramp
 real(8), intent(in)    :: depth      !< Water depth
 !dec$ attributes value :: depth
 real(8), intent(in)    :: rhow       !< Water density
 !dec$ attributes value :: rhow
 integer(4), intent(in) :: nnode      !< Number of nodes in the model.
 !dec$ attributes value :: nnode
 integer(4), intent(in) :: nncon      !< Number of nodes with connected elements
 !dec$ attributes value :: nncon
 integer(4), intent(in) :: ncord      !< Number of coordinates
 !dec$ attributes value :: ncord
 integer(4), intent(in) :: nndof      !< Number of degrees of freedom per node (6)
 !dec$ attributes value :: nndof
 integer(4), intent(in) :: nelmn      !< Number of elements in the model.
 !dec$ attributes value :: nelmn
 integer(4), intent(in) :: necon      !< Number of elements connected
 !dec$ attributes value :: necon
 intege        r(4), intent(in) :: nedof      !< Number of degrees of freedom per element (14)
 !dec$ attributes value :: nedof
 integer(4), intent(in) :: ndamp      !< Number of damper elements
 !dec$ attributes value :: ndamp
 integer(4), intent(in) :: npipcurv   !< No. of pipe-in-pipe curves.
 !dec$ attributes value :: npipcurv
 integer(4), intent(in) :: npippts    !< No. of pipe-in-pipe curve points.
 !dec$ attributes value :: npippts
 integer(4), intent(in) :: mxpipnod   !< Max. no. of pipe-in-pipe connecting node pairs.
 !dec$ attributes value :: mxpipnod
 integer(4), intent(in) :: n0kpipnod  !< No. of zero-stiffness sliding pipe-in-pipe connections for the application of hydrodynamic loads only.
 !dec$ attributes value :: n0kpipnod
 integer(4), intent(in) :: maxre      !< Maximum Reynolds' number array size.
 !dec$ attributes value :: maxre
 integer(4), intent(in) :: num_int    !< Number of integration points per element.
 !dec$ attributes value :: num_int
 
 integer(4), intent(in), dimension(nncon, nelmn) :: elmcon        !< Element connectivity array
 !dec$ attributes reference :: elmcon           
 integer(4), intent(in), dimension(necon,nnode)  :: nodcon        !< Node connectivity array
 !dec$ attributes reference :: nodcon           
 integer(4), intent(in), dimension(nnode)        :: intoun        !< Internal node to user node numbering array
 !dec$ attributes reference :: intoun           
 integer(4), intent(in), dimension(nelmn)        :: ietoue        !< Internal element to user element numbering array
 !dec$ attributes reference :: ietoue
 integer(4),  intent(in), dimension(nelmn)       :: etype         !< Element type - (1) Beam, (2) Spring, (3) Hinge, (4) Damper
 !dec$ attributes reference :: etype
 integer(4),  intent(in), dimension(nelmn)       :: edamp         !< Damper element number array
 !dec$ attributes reference :: edamp
 real(8),  intent(in), dimension(ncord,nnode)    :: cord          !< Initial nodal co-ordinates.
 !dec$ attributes reference :: cord             
 real(8),  intent(in), dimension(nndof,nnode)    :: displacement  !< Nodal displacements at previous iteration.
 !dec$ attributes reference :: displacement     
 real(8),  intent(in), dimension(nndof,nnode)    :: velocity      !< Nodal velocities at previous iteration.
 !dec$ attributes reference :: velocity         
 real(8),  intent(in), dimension(nndof,nnode)    :: acceleration  !< Nodal accelerations at previous iteration.
 !dec$ attributes reference :: acceleration     
 real(8),  intent(in), dimension(3,3,nelmn)      :: trgb          !< Rigid body rotation (local undeformed -> convected) transformation matrix.
 !dec$ attributes reference :: trgb             
 real(8),  intent(in), dimension(3,3,nelmn)      :: tglu          !< Global to local undeformed transformation matrix.
 !dec$ attributes reference :: tglu             
 real(8),  intent(in), dimension(nndof,nnode)    :: disp_prev     !< Nodal displacements at previous timestep
 !dec$ attributes reference :: disp_prev        
 real(8),  intent(in), dimension(nndof,nnode)    :: pos_prev      !< Nodal positions at previous timestep
 !dec$ attributes reference :: pos_prev         
 real(8),  intent(in), dimension(nndof,nnode)    :: vel_prev      !< Nodal velocities at previous timestep
 !dec$ attributes reference :: vel_prev         
 real(8),  intent(in), dimension(nndof,nnode)    :: acc_prev      !< Nodal accelerations at previous timestep
 !dec$ attributes reference :: acc_prev 
 real(8),  intent(in), dimension(nelmn,3)        :: axial_force   !< Axial force in elements at previous timestep
 !dec$ attributes reference :: axial_force      
 real(8),  intent(in), dimension(nelmn,3)        :: y_shear       !< Y Shear forces in elements at previous timestep
 !dec$ attributes reference :: y_shear          
 real(8),  intent(in), dimension(nelmn,3)        :: z_shear       !< Z Shear forces in elements at previous timestep
 !dec$ attributes reference :: z_shear          
 real(8),  intent(in), dimension(nelmn,3)        :: torque        !< Torque in elements at previous timestep
 !dec$ attributes reference :: torque           
 real(8),  intent(in), dimension(nelmn,3)        :: y_bending     !< Y bending moments in elements at previous timestep
 !dec$ attributes reference :: y_bending        
 real(8),  intent(in), dimension(nelmn,3)        :: z_bending     !< Z bending moments in elements at previous timestep
 !dec$ attributes reference :: z_bending        
 real(8),  intent(in), dimension(nelmn,3)        :: eff_tension   !< Effective Tension in elements at previous timestep
 !dec$ attributes reference :: eff_tension      
 real(8),  intent(in), dimension(nelmn,3)        :: y_curvature   !< Y curvatures in elements at previous timestep
 !dec$ attributes reference :: y_curvature      
 real(8),  intent(in), dimension(nelmn,3)        :: z_curvature   !< Z curvatures in elements at previous timestep
 !dec$ attributes reference :: z_curvature
 
 ! Output variables - can be modified within this subroutine if required
       
 real(8),  intent(inout), dimension(nelmn)       :: length        !< Element natural length
 !dec$ attributes reference :: length
 real(8),  intent(inout), dimension(nelmn)       :: eiyy          !< Element linear EIyy
 !dec$ attributes reference :: eiyy
 real(8),  intent(inout), dimension(nelmn)       :: eizz          !< Element linear EIzz
 !dec$ attributes reference :: eizz
 real(8),  intent(inout), dimension(nelmn)       :: gj            !< Element linear GJ
 !dec$ attributes reference :: gj
 real(8),  intent(inout), dimension(nelmn)       :: ea            !< Element linear EA
 !dec$ attributes reference :: ea
 real(8),  intent(inout), dimension(nelmn)       :: mass          !< Element mass per unit length
 !dec$ attributes reference :: mass
 real(8),  intent(inout), dimension(nelmn)       :: polar         !< Element polar inertia per unit length
 !dec$ attributes reference :: polar
 real(8),  intent(inout), dimension(nelmn)       :: dint          !< Element internal diameters
 !dec$ attributes reference :: dint
 real(8),  intent(inout), dimension(nelmn)       :: ddrag         !< Element drag diameters
 !dec$ attributes reference :: ddrag
 real(8),  intent(inout), dimension(nelmn)       :: dbuoy         !< Element buoyancy diameters
 !dec$ attributes reference :: dbuoy
 real(8),  intent(inout), dimension(nelmn)       :: dout          !< Element outer diameters
 !dec$ attributes reference :: dout
real(8),  intent(inout), dimension(nelmn)       :: dcont         !< Element contact diameters
!dec$ attributes reference :: dcont
real(8),  intent(inout), dimension(nelmn,4)     :: fluid         !< Element fluid contents - (1) Top elevation (fluid head), (2) Density, (3) Internal pressure, (4) Velocity
!dec$ attributes reference :: fluid
real(8),  intent(inout), dimension(ndamp,4)     :: damper        !< Damper element properties - (1) C0, (2) C1, (3) C2, (4) C0_Threshold
!dec$ attributes reference :: damper
 
real(8),  intent(inout), dimension(maxre,num_int,nelmn)  :: cdnn !< Drag coefficients in the direction normal to the element.
!dec$ attributes reference :: cdnn
real(8),  intent(inout), dimension(maxre,nelmn)          :: cdtt !< Drag coefficients in the direction tangential to the element.
!dec$ attributes reference :: cdtt                               
real(8),  intent(inout), dimension(maxre,nelmn)          :: cann !< Added mass coefficients in the direction normal to the element.
!dec$ attributes reference :: cann                               
real(8),  intent(inout), dimension(maxre,nelmn)          :: catt !< Added mass coefficients in the direction tangential to the element.
!dec$ attributes reference :: catt                               
real(8),  intent(inout), dimension(maxre,nelmn)          :: cmnn !< Inertia coefficients in the direction normal to the element.
!dec$ attributes reference :: cmnn                               
real(8),  intent(inout), dimension(maxre,nelmn)          :: reno !< Reynolds' number data.
!dec$ attributes reference :: reno                               
integer(4),  intent(inout), dimension(maxre,nelmn)       :: nore !< Number of Reynolds' numbers for each element.
!dec$ attributes reference :: nore
 
real(8),  intent(in), dimension(mxpipnod-n0kpipnod,3)    :: pip_reaction       !< The reaction at each contact pair.
!dec$ attributes reference :: pip_reaction                                 
 
real(8),  intent(inout), dimension(mxpipnod-n0kpipnod,3) :: pip_stiffness_data !< Properties of each connection pair.
!dec$ attributes reference :: pip_stiffness_data                          
 
real(8),  intent(inout), dimension(npipcurv,npippts,2)   :: pip_curve_defn     !< Array holding the nonlinear curve data.
!dec$ attributes reference :: pip_curve_defn                                  
                                                                               
integer(4),  intent(inout), dimension(npipcurv)          :: pip_curve_npts     !< Number of points on each nonlinear curve.
!dec$ attributes reference :: pip_curve_npts
 
! Variable names
!     iter               : Current iteration
!     time               : Current timestep
!     ramp               : Ramp                
!     depth              : Water depth
!     rhow               : Water density
!     nnode              : Number of nodes in the model
!     nncon              : Number of nodes with connected elements
!     ncord              : Number of coordinates
!     nndof              : Number of degrees of freedom per node (6)
!     nelmn              : Number of elements in the model
!     necon              : Number of elements connected
!     nedof              : Number of degrees of freedom per element (14)
!     ndamp              : Number of damper elements
!     npipcurv           : Number of pipe-in-pipe curves
!     npippts            : Number of points in each pipe-in-pipe curve
!     mxpipnod           : Number of pipe-in-pipe nodes
!     n0kpipnod          : Number of pipe-in-pipe zero stiffness nodes
!     elmcon             : Element connectivity array
!     nodcon             : Node connectivity array
!     intoun             : Internal node to user node numbering array
!     ietoue             : Internal element to user element numbering array
!     etype              : Element type - (1) Beam, (2) Spring, (3) Hinge, (4) Damper
!     edamp              : Damper element number array
!     cord               : Initial nodal co-ordinates
!     displacement       : Nodal displacements at previous iteration
!     velocity           : Nodal velocities at previous iteration
!     acceleration       : Nodal accelerations at previous iteration
!     trgb               : Rigid body rotation (local undeformed -> convected) transformation matrix
!     tglu               : Global to local undeformed transformation matrix
!     disp_prev          : Nodal displacements at previous timestep
!     pos_prev           : Nodal positions at previous timestep
!     vel_prev           : Nodal velocities at previous timestep
!     acc_prev           : Nodal accelerations at previous timestep
!     axial_force        : Axial force in elements at previous timestep
!     y_shear            : Y Shear forces in elements at previous timestep
!     z_shear            : Z Shear forces in elements at previous timestep
!     torque             : Torque in elements at previous timestep
!     y_bending          : Y bending moments in elements at previous timestep
!     z_bending          : Z bending moments in elements at previous timestep
!     eff_tension        : Effective Tension in elements at previous timestep
!     y_curvature        : Y curvatures in elements at previous timestep
!     z_curvature        : Z curvatures in elements at previous timestep
!     length             : Element natural length
!     eiyy               : Element linear EIyy
!     eizz               : Element linear EIzz
!     gj                 : Element linear GJ
!     ea                 : Element linear EA
!     mass               : Element mass per unit length
!     polar              : Element polar inertia per unit length
!     dint               : Element internal diameters
!     ddrag              : Element drag diameters
!     dbuoy              : Element buoyancy diameters
!     dout               : Element outer diameters
!     dcont              : Element contact diameters
!     fluid              : Element fluid contents -
!                            (1) Top elevation (fluid head)
!                            (2) Density
!                            (3) Internal pressure
!                            (4) Velocity
!     damper             : Element contact diameters
!                            (1) C0
!                            (2) C1
!                            (3) C2
!                            (4) C0_Threshold
!     pip_reaction           (1) - Axial reaction.
!                            (2) - Normal Reaction.
!                            (3) - Transverse Reaction.
!     pip_stiffness_data     (1) - Axial Stiffness.
!                            (2) - Normal Stiffness.
!                            (3) - Transverse Stiffness.
!     pip_curve_defn         Each point on the a data pairs curve is described by:
!                            (1) - Displacement.
!                            (2) - Force.
!                            In the case of a Power Law curve, there is only one entry:
!                            (1) - Exponent.
!                            (2) - Contact force.
 
 
! Declare local variables...
 
 
! Insert user code below this line...
  
  end subroutine user_defined_element

User Solver Variables Template

 subroutine user_solver_variables(iter,time,ramp,depth,rhow,nnode,nncon,ncord,nndof,nelmn,necon,nedof,     &
      size_force,size_mass,size_stiff,mxpipnod,n0kpipnod,elmcon,nodcon,intoun,ietoue,cord,displacement,               &
      velocity,acceleration,trgb,tglu,disp_prev,pos_prev,vel_prev,acc_prev,pip_reaction,axial_force,y_shear,    &
      z_shear,torque,y_bending,z_bending,eff_tension,y_curvature,z_curvature,force,mass,stiff)
    !dec$ attributes dllexport, stdcall, reference :: user_solver_variables
      implicit none
 
      integer, intent(in)    :: iter        !< Current iteration
      !dec$ attributes value :: iter
      real(8), intent(in)    :: time        !< Current timestep
      !dec$ attributes value :: time
      real(8), intent(in)    :: ramp        !< Ramp
      !dec$ attributes value :: ramp
      real(8), intent(inout) :: depth       !< Water depth
      !dec$ attributes reference :: depth
      real(8), intent(inout) :: rhow        !< Water density
      !dec$ attributes reference :: rhow
      integer(4), intent(in) :: nnode       !< Number of nodes in the model.
      !dec$ attributes value :: nnode
      integer(4), intent(in) :: nncon       !< Number of nodes with connected elements
      !dec$ attributes value :: nncon
      integer(4), intent(in) :: ncord       !< Number of coordinates
      !dec$ attributes value :: ncord
      integer(4), intent(in) :: nndof       !< Number of degrees of freedom per node (6)
      !dec$ attributes value :: nndof
      integer(4), intent(in) :: nelmn       !< Number of elements in the model.
      !dec$ attributes value :: nelmn
      integer(4), intent(in) :: necon       !< Number of elements connected
      !dec$ attributes value :: necon
      integer(4), intent(in) :: nedof       !< Number of degrees of freedom per element (14)
      !dec$ attributes value :: nedof
      integer(4), intent(in) :: size_force  !< Dimension of the global force vector
      !dec$ attributes value :: size_force
      integer(4), intent(in) :: size_mass   !< Dimension of the global mass matrix
      !dec$ attributes value :: size_mass
      integer(4), intent(in) :: size_stiff  !< Dimension of the global stiffness matrix
      !dec$ attributes value :: size_stiff
      integer(4), intent(in) :: mxpipnod    !< Max. no. of pipe-in-pipe connecting node pairs.
      !dec$ attributes value :: mxpipnod
      integer(4), intent(in) :: n0kpipnod   !< No. of zero-stiffness sliding pipe-in-pipe connections 
      !dec$ attributes value :: n0kpipnod
 
      integer(4), intent(in), dimension(nncon, nelmn)              :: elmcon        !< Element connectivity array
      !dec$ attributes reference :: elmcon                     
      integer(4), intent(in), dimension(necon,nnode)               :: nodcon        !< Node connectivity array
      !dec$ attributes reference :: nodcon                     
      integer(4), intent(in), dimension(nnode)                     :: intoun        !< Internal node to user node numbering array
      !dec$ attributes reference :: intoun                     
      integer(4), intent(in), dimension(nelmn)                     :: ietoue        !< Internal element to user element numbering array
      !dec$ attributes reference :: ietoue                     
      real(8),  intent(in), dimension(ncord,nnode)                 :: cord          !< Initial nodal co-ordinates.
      !dec$ attributes reference :: cord                       
      real(8),  intent(in), dimension(nndof,nnode)                 :: displacement  !< Nodal displacements at previous iteration.
      !dec$ attributes reference :: displacement               
      real(8),  intent(in), dimension(nndof,nnode)                 :: velocity      !< Nodal velocities at previous iteration.
      !dec$ attributes reference :: velocity                   
      real(8),  intent(in), dimension(nndof,nnode)                 :: acceleration  !< Nodal accelerations at previous iteration.
      !dec$ attributes reference :: acceleration               
      real(8),  intent(in), dimension(3,3,nelmn)                   :: trgb          !< Rigid body rotation (local undeformed -> convected) transformation matrix.
      !dec$ attributes reference :: trgb                       
      real(8),  intent(in), dimension(3,3,nelmn)                   :: tglu          !< Global to local undeformed transformation matrix.
      !dec$ attributes reference :: tglu                       
      real(8),  intent(in), dimension(nndof,nnode)                 :: disp_prev     !< Nodal displacements at previous timestep
      !dec$ attributes reference :: disp_prev                  
      real(8),  intent(in), dimension(nndof,nnode)                 :: pos_prev      !< Nodal positions at previous timestep
      !dec$ attributes reference :: pos_prev                   
      real(8),  intent(in), dimension(nndof,nnode)                 :: vel_prev      !< Nodal velocities at previous timestep
      !dec$ attributes reference :: vel_prev                   
      real(8),  intent(in), dimension(nndof,nnode)                 :: acc_prev      !< Nodal accelerations at previous timestep
      !dec$ attributes reference :: acc_prev                   
      real(8),  intent(in), dimension(nelmn,3)                     :: axial_force   !< Axial force in elements at previous timestep
      !dec$ attributes reference :: axial_force                
      real(8),  intent(in), dimension(nelmn,3)                     :: y_shear       !< Y Shear forces in elements at previous timestep
      !dec$ attributes reference :: y_shear                    
      real(8),  intent(in), dimension(nelmn,3)                     :: z_shear       !< Z Shear forces in elements at previous timestep
      !dec$ attributes reference :: z_shear                    
      real(8),  intent(in), dimension(nelmn,3)                     :: torque        !< Torque in elements at previous timestep
      !dec$ attributes reference :: torque                     
      real(8),  intent(in), dimension(nelmn,3)                     :: y_bending     !< Y bending moments in elements at previous timestep
      !dec$ attributes reference :: y_bending                  
      real(8),  intent(in), dimension(nelmn,3)                     :: z_bending     !< Z bending moments in elements at previous timestep
      !dec$ attributes reference :: z_bending                  
      real(8),  intent(in), dimension(nelmn,3)                     :: eff_tension   !< Effective Tension in elements at previous timestep
      !dec$ attributes reference :: eff_tension                
      real(8),  intent(in), dimension(nelmn,3)                     :: y_curvature   !< Y curvatures in elements at previous timestep
      !dec$ attributes reference :: y_curvature                
      real(8),  intent(in), dimension(nelmn,3)                     :: z_curvature   !< Z curvatures in elements at previous timestep
      !dec$ attributes reference :: z_curvature
 
      real(8),  intent(inout), dimension(size_force,nedof)         :: force         !< Global force vector at previous iteration
      !dec$ attributes reference :: force
      real(8),  intent(inout), dimension(nedof,nedof,size_mass)    :: mass          !< Global mass matrix.
      !dec$ attributes reference :: mass
      real(8),  intent(inout), dimension(nedof,nedof,size_stiff)   :: stiff         !< Global stiffness matrix.
      !dec$ attributes reference :: stiff
      
      real(8),  intent(in), dimension(mxpipnod-n0kpipnod,3)        :: pip_reaction  !< The reaction at each contact pair.
      !dec$ attributes reference :: pip_reaction                                    !!
                                                                                    !< 1 - Axial reaction.
                                                                                    !< 2 - Normal Reaction.
                                                                                    !< 3 - Transverse Reaction.
 
     ! Variable names
   !     iter               : Current iteration
   !     time               : Current timestep
   !     ramp               : Ramp
   !     nnode              : Number of nodes in the model
   !     nncon              : Number of nodes with connected elements
   !     ncord              : Number of coordinates
   !     nndof              : Number of degrees of freedom per node (6)
   !     nelmn              : Number of elements in the model
   !     necon              : Number of elements connected
   !     nedof              : Number of degrees of freedom per element (14)
   !     size_force         : Dimension of the global force vector
   !     size_mass          : Dimension of the global mass matrix
   !     size_stiff         : Dimension of the global stiffness matrix
   !     elmcon             : Element connectivity array
   !     nodcon             : Node connectivity array
   !     intoun             : Internal node to user node numbering array
   !     ietoue             : Internal element to user element numbering array
   !     cord               : Initial nodal co-ordinates
   !     displacement       : Nodal displacements at previous iteration
   !     velocity           : Nodal velocities at previous iteration
   !     acceleration       : Nodal accelerations at previous iteration
   !     trgb               : Rigid body rotation (local undeformed -> convected) transformation matrix
   !     tglu               : Global to local undeformed transformation matrix
   !     disp_prev          : Nodal displacements at previous timestep
   !     pos_prev           : Nodal positions at previous timestep
   !     vel_prev           : Nodal velocities at previous timestep
   !     acc_prev           : Nodal accelerations at previous timestep
   !     axial_force        : Axial force in elements at previous timestep
   !     y_shear            : Y Shear forces in elements at previous timestep
   !     z_shear            : Z Shear forces in elements at previous timestep
   !     torque             : Torque in elements at previous timestep
   !     y_bending          : Y bending moments in elements at previous timestep
   !     z_bending          : Z bending moments in elements at previous timestep
   !     eff_tension        : Effective Tension in elements at previous timestep
   !     y_curvature        : Y curvatures in elements at previous timestep
   !     z_curvature        : Z curvatures in elements at previous timestep
   !     force              : Global force vector at previous iteration
   !     mass               : Global mass matrix.
   !     stiff              : Global stiffness matrix.
 
 
   ! Declare local variables...
 
   ! Insert user code below this line...
      
    end subroutine user_solver_variables