4.8.2.9. NODAL_FORCE_EXT

This subroutine defines a user - defined nodal force. NODAL_FORCE returns the total nodal force for the defined node set or sheet bodies, whereas the NODAL_FORCE_EXT returns the nodal force for each node belonging to the defined node set. The outputted data is here.

Table 4.30 Function Name

Language type

Subroutine

FORTRAN

nodal_force_ext (ID,TI ME,UPAR,NPAR,IFBODY,NODARR,NONDE,JFLAG,IFLAG,RESULT)

C/C++

nodal_force_ext (int id, double time, double upar[], int npar, int ifbody, int nodarr[], int nonde, int jflag, int iflag, double result[])

Table 4.31 Parameter information

Variable Name

Size

Description

id

int

Nodal Force sequential identification

time

double

Current simulation time of RecurDyn/Solver.

upar

double *

Parameters defined by the user. There is no limit about the maximum size of array.

npar

int

Number of user parameters.

ifbody

int

FFlex body sequential ID.

nodarr

int[nonde]

Node sequential ID array of input node set.

nonde

int

Number of nodes of a node set

jflag

int

When RecurDyn/Solver evaluates the Jacobian, the flag is true. Otherwise, the flag is false.

iflag

int

When RecurDyn/Solver makes its initial call to this routine, the flag is true. Otherwise, the flag is false.

result

double[no nde*6]

Nodal forces. Acting point of the nodal force is each center of each node. Reference frame of each force vector must be the ground inertia marker.

Example

This subroutine returns an air resistance force to a sheet as nodal force.

../_images/image3241.png

Figure 4.113 Air resistance model

Note

If the user wants to run this model using a user subroutine, the user can refer it in the directory (<install dir>\Help\usub\**).

Listing 4.17 Fortran code for Nodal Force Extension
 C---- SUB. NODAL_FORCE_EXT
   SUBROUTINE NODAL_FORCE_EXT
  &          (ID,TIME,UPAR,NPAR,IFBODY,NODARR,NONDE,
  &           JFLAG,IFLAG,RESULT)

 C---- TO EXPORT * SUBROUTINE
       !DEC$ ATTRIBUTES DLLEXPORT,C::NODAL_FORCE_EXT

 C---- INCLUDE SYSTEM CALL
       INCLUDE 'SYSCAL.F'

 C---- DEFINE VARIABLES
 C     Parameter Information
 C     ID     : Nodal Force sequential identification. (Input)
 C     TIME   : Simulation time of RD/Solver. (Input)
 C     UPAR   : Parameters defined by user. (Input)
 C     NPAR   : Number of user parameters. (Input)
 C     IFBODY : FFLEX Body sequential ID. (Input)
 C     NODARR : Node sequential ID array of input node set. (Input)
 C     NONDE  : Number of node of node set. (Input)
 C     JFLAG  : When RD/Solver evaluates a Jacobian, the flag is true. (Input)
 C     IFLAG  : When RD/Solver initializes arrays, the flag is true. (Input)
 C     RESULT : Returned nodal force vector. Acting point of the nodal force is each center of each node.
 C              Reference frame of each force vector must be Ground.InertiaMarker. (Output, Size : nonde * 6)

       DOUBLE PRECISION TIME, UPAR(*)
       INTEGER ID, NPAR, IFBODY, NODARR(*), NONDE
       LOGICAL JFLAG, IFLAG
       DOUBLE PRECISION RESULT(*)

 C---- USER STATEMENT
 c     local variable
       integer i,j,nodeid,errflg
       double precision Area, Cd, rho
       double precision vn(3), vn_mag, ucf, scale
       integer MKID(2), nMK

       Cd = upar(1)
       rho = upar(2)
       scale = upar(3)
       call rd_ucf(ucf)
       MKID(1) = 0
       MKID(2) = 0
       nMK = 0

       do i=1, nonde
         call get_fflex_nodetvel(ifbody,nodarr(i),MKID,nMK,vn,errflg)
         vn_mag = dsqrt(vn(1)**2+vn(2)**2+vn(3)**2)
         call get_fflex_nodeid(ifbody,nodarr(i),nodeid,errflg)
         if( nodeid .eq. 10000 .or. nodeid .eq. 10001) then
             Area = 100
         else if (nodeid .ge. 20000 .and. nodeid .lt. 30000) then
             Area = 200
         else Area = 400
         endif
         do j=1, 3
             if(vn_mag .eq. 0.0d0) then
               result((i-1)*6+j) = 0.0d0
             else
               result((i-1)*6+j)=-1.0d0/2.0d0*Cd*rho*vn_mag*vn_mag*Area
     &                         *(vn(j)/vn_mag) ! direction
     &                         /ucf            ! making force unit
     &                         *scale          ! an amplifier
             endif
         enddo
       enddo

       RETURN
       END
Listing 4.18 C/C++ code for Nodal Force Extension
 #include "stdafx.h"
 #include "DllFunc.h"
 #include "stdlib.h"
 #include "math.h"

 NodalForceExt_API void __cdecl nodal_force_ext
   (int id, double time, double upar[], int npar, int ifbody, int nodarr[], int nonde, int jflag, int iflag, double result[])
 {
   using namespace rd_syscall;
   // Parameter Information
   //   id      :  Nodal Force sequential identification. (Input)
   //   time    :  Simulation time of RD/Solver. (Input)
   //   upar    :  Parameters defined by user. (Input)
   //   npar    :  Number of user parameters. (Input)
   //   ifbody  :  FFLEX Body sequential ID. (Input)
   //   nodarr  :  Node sequential ID array of input node set. (Input)
   //   nonde   :  Number of node of node set. (Input)
   //   jflag   :  When RD/Solver evaluates a Jacobian, the flag is true. (Input)
   //   iflag   :  When RD/Solver initializes arrays, the flag is true. (Input)
   //   result  :  Returned nodal force vector. Acting point of the nodal force is each center of each node.
   //            Reference frame of each force vector must be Ground.InertiaMarker . (Output, Size : nonde * 6)

   // User Statement
   int i, j, nodeid,errflg;
   double Area, Cd, rho;
   double vn[3], vn_mag, ucf, scale;
   WCHAR NodeName[256];
   char  strNodeName[256];

   if (iflag) {
     for(i=0;i<nonde;i++){
       get_fflex_nodestringname(ifbody,nodarr[i],(TCHAR*)NodeName,&errflg);
       wcstombs(strNodeName,NodeName,256);  // Wide-byte character --> Multibyte character
       printmsg("========================",(int)strlen("==================="));
       printmsg(strNodeName,(int)strlen(strNodeName));
       printmsg("========================",(int)strlen("==================="));
     }
   }

   Cd = upar[0];
   rho = upar[1];
   scale = upar[2];
   rd_ucf(&ucf);

   for(i=0;i<nonde;i++){
     // Set velocity vector of node
     get_fflex_nodetvel(ifbody,nodarr[i],NULL,0,vn,&errflg);
     vn_mag = sqrt(pow(vn[0],2)+pow(vn[1],2)+pow(vn[2],2));

       get_fflex_nodeid(ifbody,nodarr[i],&nodeid,&errflg);

       if (nodeid == 10000 || nodeid == 10001)
       {
         Area = 100;
       }
       else if (nodeid >= 20000 && nodeid < 30000)
       {
         Area = 200;
       }
       else
         Area = 400;

     for(j=0;j<3;j++){
       if (vn_mag == 0.0)
         result[i*6+j] = 0.0;
       else
         result[i*6+j] = -1.0/2.0*Cd*rho*vn_mag*vn_mag*Area
         *(vn[j]/vn_mag) // Set negative direction of the nodal velocity
         /ucf            // Making force unit
         *scale;         //

       result[i*6+j+3] = 0.0;
     }
   }
 }