UT-SIM
  • Home
  • Architecture
    • Communication
    • Integration Modules
    • Substructure Modules
  • Users
    • Get Started with UT-SIM >
      • OpenSees
      • Abaqus
      • S-Frame
      • VecTor Suite
      • NICON-NIO
      • NICON-AIO
    • Download
  • Developers
    • Source Code
    • Communication Examples >
      • C/C++
      • Fortran
      • Matlab
      • Python
    • Download
  • Hybrid Simulation
  • Numerical Simulation
  • Application Examples
  • Workshop
  • News
  • Collaborators
  • Contact
  • References

Fortran module development

fortran

To develop an integration model or an substructure model in Fortran code for communication, the developer needs to provide the explicit linkage to the DataExchange DLL in the code. This document assumes that the develoepr is familiar with the Fortran language.

Link with DataExchange library (Fortran)¶

To explicitly link with the DLL in Fortran, the first thing is to define function pointers which can be considered as aliases for the functions implemented in DataExchange.dll. The name of the function pointers use the same name as the functions in the DataExchange.dll except that the word "Func" is attached to the end of each function name. The function variables should be declared properly.

INTERFACE
    INTEGER*4 FUNCTION setupconnectionFunc(port, socket, flag, addr, protocol) BIND(C, NAME='setupconnection')

        INTEGER*4,value :: port
        INTEGER*4 socket
        INTEGER*4,value :: flag
        CHARACTER addr
        INTEGER*4,value :: protocol

    END FUNCTION setupconnectionFunc
    END INTERFACE

    INTERFACE    
    INTEGER*4 FUNCTION InitializationFunc(socket, flag, protocol) BIND(C, NAME='initialization')

        INTEGER*4,value :: socket
        INTEGER*4,value :: flag
        INTEGER*4,value :: protocol

    END FUNCTION InitializationFunc
    END INTERFACE

    INTERFACE    
    INTEGER*1 FUNCTION CommandFunc(socket, flag, protocol) BIND(C, NAME='command')

        INTEGER*4,value :: socket
        INTEGER*4,value :: flag
        INTEGER*4,value :: protocol

    END FUNCTION CommandFunc
    END INTERFACE

    INTERFACE
    INTEGER*4 FUNCTION RecvDataFunc(socket, response, lens, protocol) BIND(C, NAME='recvdata')

        INTEGER*4,value :: socket
        REAL*8 response(lens)
        INTEGER*4,value :: lens
        INTEGER*4,value :: protocol

    END FUNCTION RecvDataFunc
    END INTERFACE

    INTERFACE
    INTEGER*4 FUNCTION SendDataFunc(socket, sdata, lens, protocol) BIND(C, NAME='senddata') 

        INTEGER*4,value :: socket
        REAL*8 sdata(lens)
        INTEGER*4,value :: lens
        INTEGER*4,value :: protocol

    END FUNCTION SendDataFunc
    END INTERFACE

    INTERFACE
    INTEGER*4 FUNCTION terminateFunc(socket) BIND(C, NAME='close')

        INTEGER*4 socket

    END FUNCTION terminateFunc
    END INTERFACE

    INTERFACE
    SUBROUTINE UpdataMessageHeaderFunc(version,command,testtype,subt,pre,ndof) BIND(C, NAME='updatemessageHeader')

        INTEGER*1,value :: version
        INTEGER*1,value :: command
        INTEGER*1,value :: testtype
        INTEGER*1,value :: subt
        INTEGER*1,value :: pre
        INTEGER*2,value :: ndof      

    END SUBROUTINE UpdataMessageHeaderFunc
    END INTERFACE

    INTERFACE
    SUBROUTINE UpdateCommandFunc(command) BIND(C, NAME='updatecommand')

        INTEGER*1,value :: command

    END SUBROUTINE UpdateCommandFunc
    END INTERFACE   

    INTERFACE
    SUBROUTINE UpdateSubtypeFunc(disp, vel, accel, force, stiff, mass, temp) BIND(C, NAME='updatedatatype')

        INTEGER*4,value :: disp
        INTEGER*4,value :: vel
        INTEGER*4,value :: accel
        INTEGER*4,value :: force
        INTEGER*4,value :: stiff
        INTEGER*4,value :: mass
        INTEGER*4,value :: temp

    END SUBROUTINE UpdateSubtypeFunc
    END INTERFACE

    INTERFACE
    INTEGER*4 FUNCTION indicatorFunc() BIND(C, NAME='indicator')
    END FUNCTION indicatorFunc
    END INTERFACE

Now the function pointers hold the functions of the DLL and you can use them using the function pointers other than the actual function names in the DataExchange.dll. For example, the way to use the setupconnection() function to establish the connection is shown below

iResult = setupconnectionFunc(PortNumber, sockfd, flag, machineInetAddr, TCP_IP)

Integration Model (Fortran)¶

In addition to the above code to link with the DataExchange.dll, the code starts with declaring variables required for communication.

PortNumber = 8090                                            ! port number
    machineInetAddr = '127.0.0.1'                                ! IP address; 

    sockfd = 0                                                   ! initialize socket number
    flag = 1                                                     ! 1 - integration module; 2 - substructure module
    numdofs = 3                                                  ! total interface DOFs

where

  • PortNumber: port number. This number should be consistent with the port number specified in the substructure model below.
  • machineInetAddr: IP address of machine with the substructure model. For the case that the integration and substructure models are modelled in the same Windows machine, the standard IP address of "127.0.0.1" can be used.
  • sockfd: a SOCKET type variable for a newly generated socket
  • flag: a variable to be used in the DataExchange.dll functions to indicate the model is a integration model or a substructure model.
  • numdofs: a variable defines the total number of degrees of freedom

Communication Initialization¶

Then, three DLL functions are called to initialize the data exchange format, set up the connection with the substructure model, and send the initialized data exchange format to the substructure model.

! initialize data exchange format    
    CALL UpdataMessageHeaderFunc(2, 0, Software_only, VecTor2, Double_precision, numdofs)

    ! setup connection
    iResult = setupconnectionFunc(PortNumber, sockfd, flag, machineInetAddr, TCP_IP)
    IF (iResult .NE. 0) THEN
        write(*,*) 'Connection failed'
    ELSE
        write(*,*) 'Connection done'
    END IF

    ! send data exchange format to server for initialization
    iResult = InitializationFunc(sockfd, flag, TCP_IP)
    IF (iResult .NE. 0) THEN
        write(*,*) 'Initialization failed'
    ELSE
        write(*,*) 'Initialization done'
    END IF

where UpdateMessageHeaderFunc(version, command, testtype, subtype, precision, numdofs) function is used to initialize the following information defined in the header block of the data exchanged through UTNP (see here for more details).

  • version: this parameter corresponds to the Version parameter in the data exchange format. It is 2 for the current release version.
  • command: this parameter corresponds to the Command parameter in the data exchange format. It can be defined as zero at this initialization stage.
  • testtype: this parameter corresponds to thie Test type parameter in the data exchange format. Depending on the simulation methods, one of the following values can be used to initialize the parameter.
    • 1 - Pseudo-dynamic (ramp-hold) simulation
    • 2 - Pseudo-dynamic (continuous) simulation
    • 4 - Numerical multi-platform simulation
  • subtype: this parameter corresponds to the Substructure type parameter in the data exchange format. Depending on the substructure modules, one of the following values can be used to initialize the parameter
    • 1 - OpenSees
    • 2 - Zeus-NL
    • 3 - ABAQUS
    • 4 - VecTor2
    • 5 - NICON-AIO or NICON-NIO
    • 6 - VecTor4
    • 7 - LS-Dyna
  • precision: this parameter corresponds to the Precision parameter in the data exchange format. It can be defined as 1 for single precision and 2 for double precision
  • numdofs: this parameter corresponds to the Number of DOFs parameter in the data exchange format. It is equal to the total number of effective DOFs at the interface nodes for communication.

Sending Data¶

Once communication is established and the data format parameters are initialized, the integration module starts with sending displacement command to the substructure.

!-------------------------------------------------------------------------------------------------
        ! send trial displacement to the substructure module 
        !-------------------------------------------------------------------------------------------------
        ! define the command in the message header block for imposing target displacement   
        CALL UpdateCommandFunc (Impose_TargetValues)

        ! define the type of data to be appended to the message header 
        ! Updatetype (disp, vel, accel, force, stiff, mass,temperature)
        ! use 1 and 0 to enable and disable the data in the function. 
        CALL UpdateSubtypeFunc (1, 0, 0, 0, 0, 0, 0)

        ! send the updated data header to the substructure module
        action = CommandFunc(sockfd, flag, TCP_IP)

        ! calculate the data size to be appended to the message header
        lens = indicatorFunc()

        ALLOCATE(sdata(lens))

        DO J= 1, lens
            sdata(J) = unn(J)    
        END DO

        ! send the data to the substructure module
        iResult = SendDataFunc(sockfd, sdata, lens, TCP_IP)

        IF (iResult .NE. 0) THEN 
            WRITE(*,*) 'Failed to send disp.'
            EXIT
        ELSE 
            WRITE(*,*) 'Disp sent.'
        END IF

        ! deallocation of variable
        DEALLOCATE(sdata)

Receiving Data¶

Once the restoring force is computed in the substructure module, the integration module sends another command for receiving the computed force from the substructure module.

! update the command in the message header for receiving data from the substructure module  
        CALL UpdateCommandFunc (Report_Values)

        ! define the type of data to be appended to the message header 
        ! Updatetype (disp, vel, accel, force, stiff, mass,temperature)
        ! use 1 and 0 to enable and disable the data in the function. 
        CALL UpdateSubtypeFunc (0, 0, 0, 1, 0, 0, 0)

        ! send the updated message header to the substructure module
        action = CommandFunc(sockfd, flag, TCP_IP)

        ! calculate the size to be appended to the message header
        lens = indicatorFunc()

        ALLOCATE(rdata(lens))

        ! receive the computed restoring force from substructure module
        iResult = RecvDataFunc(sockfd, rdata, lens, TCP_IP)         
        IF (iResult .NE. 0) THEN
            WRITE(*,*) 'Failed to receive force.'
            EXIT
        ELSE
            WRITE(*,*) 'Force received.'
        END IF

        ! Formulate the equivalent force to solve the system's motion equation 
        DO J=1, lens
            force(j) = rdata(j)
            Pe(j) = P(j) - force(j)
        END DO

        ! deallocation of variable
        DEALLOCATE(rdata)

The above sending and receving data steps are repeated until the end of the simulation.

Disconnection¶

Once the simulation is done, the following is included in the code to disconnect the integration module from the substructure module.

!-------------------------------------------------------------------------------------------------
        ! terminate communication
        !-------------------------------------------------------------------------------------------------

        ! define command in the data format for disconnection
        CALL UpdateCommandFunc (Terminate)

        ! send data format to server
        action = CommandFunc(sockfd, flag, TCP_IP)

        ! disconnect and close socket
        iResult = terminateFunc(sockfd)

        write(*,*) 'Simulation done.'

Substructure Model (C/C++)¶

Similar to the above integration module, the variables for the port number, IP address, socket number, and indicator of module type should be defined after the program is linked with the DataExchange.dll.

! define socket variables
        PortNumber = 8090;                                ! port number
        machineInetAddr = '0.0.0.0';                      ! ipAddress of server; 

        sockfd = 0;                                       ! initialize socket number
        flag = 2;                                         ! 1 - integration module; 2 - substructure module

Communication Initialization¶

The same UpdateMessageHeaderFunc, setupconnectionFunc, InitializationFunc are used in the substructure module to initialize the message header and the connection with the integration module. The only difference is the value of flag which indicates that the dll functions are being called by a substructure module.

! Initialize data exchange format    
        CALL UpdataMessageHeaderFunc(2, 0, 0, 0, Double_precision, 0)

        ! setup connection
        iResult = setupconnectionFunc(PortNumber, sockfd, flag, machineInetAddr, TCP_IP)
        IF (iResult .NE. 0) THEN
            write(*,*) 'Connection failed'
        END IF

        ! send data exchange format to server for initialization
        iResult = InitializationFunc(sockfd, flag, TCP_IP)

After the connection is built, a switch statement is included, which defines different actions based on the received command values in the message header.

! receive data format from integration module
        action = CommandFunc(sockfd, flag, TCP_IP)

        SELECT CASE (action)

        CASE (Impose_TargetValues)

            ! code to receive data from the integration module (see below)

        CASE (Report_Values)

            ! code to send computed data to the integration module (see below)

        CASE (Terminate) 

            ! exit the switch statement

        CASE DEFAULT

            write(*,*) 'Invalid action received'

        END SELECT

Receiving Data¶

In the above case of Impose_TargetValues, the substructure module receives the displacement from the integration module. Detailed code is shown below:

! calculate the size to be appended to the message header
        lens = indicatorFunc()    

        ALLOCATE (rdata(lens)) 

        do I = 1, lens
            rdata(I) = I
        end do

        ! receive displacement from the integration module
        iResult = RecvDataFunc(sockfd, rdata, lens, TCP_IP)
        IF (iResult .NE. 0) THEN
            write(*,*) 'Failed to receive trial displacement.'
            EXIT
        ELSE 
            write(*,*) 'Trial displacement received';
        END IF 

        ! save the displacement for analysis
        DO I = 1, lens
            Tdisp(I) = rdata(I)
        END DO

        ! deallocation of variable
        DEALLOCATE (rdata)

Sending Data¶

In the case of Report_Values, the substructure module sends the computed restoring force back to the integration module. Detailed code is shown below:

! calculate the size to be appended to the message header
        lens = indicatorFunc()    
        ALLOCATE (sdata(lens)) 

        ! calculate the restoring force with respect to the received displacement
        do I = 1, lens
            RF(I) = 0
            do J = 1, lens 
                RF(I) = RF(I) + K(I,J) * Tdisp(J)
            end do
        end do

        ! initialize force vector
        do I = 1, lens
            sdata(I) = RF(I)    
        end do

        ! send the computed force to integration module
        iResult = SendDataFunc(sockfd, sdata, lens, TCP_IP)
        IF (iResult .NE. 0) THEN
            write(*,*) 'Failed to send computed force.'
            EXIT
        ELSE 
            write(*,*) 'Computed force sent';
        END IF 

        ! deallocation of variable 
        DEALLOCATE (sdata)

Disconnection¶

At the end of the simulation, the communication is disconnected.

!------------------------------------------------------------------------------------
        !   Disconnect communication and close socket
        !------------------------------------------------------------------------------------
        iResult = terminateFunc(sockfd)

        write(*,*) 'Simulation done.'

Source Code Downloading¶

The source code of above communication example in Fortran can be downloaded from here.

Proudly powered by Weebly
  • Home
  • Architecture
    • Communication
    • Integration Modules
    • Substructure Modules
  • Users
    • Get Started with UT-SIM >
      • OpenSees
      • Abaqus
      • S-Frame
      • VecTor Suite
      • NICON-NIO
      • NICON-AIO
    • Download
  • Developers
    • Source Code
    • Communication Examples >
      • C/C++
      • Fortran
      • Matlab
      • Python
    • Download
  • Hybrid Simulation
  • Numerical Simulation
  • Application Examples
  • Workshop
  • News
  • Collaborators
  • Contact
  • References