Incorporating a Module into the FRAMEwork System (FRAMES)


Title Page
Legal Notice
Table of Contents
Introduction
Example
STEP 1
STEP 2
STEP 3
STEP 4
STEP 5
APPENDIX A
APPENDIX B
APPENDIX C
APPENDIX D
 

Appendix C
Post-Processor for the Constantly Stirred Tank Reduction Model

The following FORTRAN code could serve as a post-processor for integrating the Constantly Stirred Tank Reduction Model into FRAMES. An application programming interface built into FRAMES makes this type of a program unnecessary in most cases. The instructions on how to integrate a model into FRAMES provide additional details.


!     Last change:  KJC  21 Jun 2003   10:07 pm
program main

USE DataSet
implicit none
! This version is not using any standard dictionaries.  It is a standalone program in FRAMES 2.0.


! This is essentially a copy of the data produced by the CSTR model itself.
! The following lines represent data associated with each chemical.
  INTEGER*4 NumChem,ChemIdx,NumTime,TimeIdx
  CHARACTER*20 TUnits,CUnits,FUnits
  CHARACTER*4096 CNAME,CASID
  REAL*8 Time,Conc,Flux

! The data below are for connecting to FRAMES.
CHARACTER(256) CommandLine
CHARACTER*4096 Path,Simulation,ModuleId,OutputDictionary,OutputDataSet,OModId
INTEGER*4 pid,NOMod,i,j,NOSet
LOGICAL OutputSetFound

  OutputSetFound=.FALSE.
  call getCL(commandline)   ! Get the command line handed the program.
  READ(commandline,*) path,simulation,moduleId
  pid=OpenIO(path,simulation,moduleId)
  if (pid.gt.0) then ! a pid less than 0 means something is wrong
    write (*,*)"pid",pid
    if (NumOMod(pid,moduleId,NOMod).ge.0) then     ! Read the number of inputs.
      WRITE(*,*) NOMod ! Loop across all inputs.
      do i=1,NOMod
        IF (getOModId(pid,moduleId,i,OModId).ge.0) then
          WRITE(*,*)TRIM(OModId)
          if (NumOModSet(pid,moduleId,OModId,NOSet).ge.0) then
            WRITE(*,*) NOSet
            do j=1,NoSet
              if (getODictionary(pid,moduleId,oModId,j,OutputDictionary).ge.0) then ! Get the dictionary.
                WRITE(*,*) TRIM(OutputDictionary)
                if (OutputDictionary.eq."CSTROutput") then                       ! Is it the UI dictionary we expect?
                  if (getODataSet(pid,moduleId,oModId,j,OutputDataSet).ge.0) then  ! Get the dataset name.
                    WRITE(*,*) TRIM(OutputDataSet)
                    OutputSetFound=.TRUE.                                    ! Set the flag that says it is OK.
                  end if
                end if
              END if
            END do
          END if
        END if
      end do
    end if
  END if
  if (OutputSetFound) then
    WRITE(*,*) "Output Data set found"
    OPEN (UNIT=20,  FILE="CSTROutput.txt", STATUS='OLD')
    READ(20,FMT='(i4)') NumChem
    do ChemIdx=1,NumChem
      READ(20,FMT='(A80)') CName
      READ(20,FMT='(A80)') CASID
      call WriteString1(pid,OutputDataSet,"Name","",ChemIdx,CName)
      call WriteString1(pid,OutputDataSet,"CASID","",ChemIdx,CASID)
      READ(20,FMT='(I4)') NumTime
      READ(20,*)TUnits,CUnits,FUnits
      do TimeIdx=1,NumTime
        READ(20,FMT='(3G8.3)')Time,Conc,Flux
        call WriteReal2(pid,OutputDataSet,"Time","yr",ChemIdx,TimeIdx,Time)
        call WriteReal2(pid,OutputDataSet,"Conc","mg/L",ChemIdx,TimeIdx,Conc)
        CALL WriteReal2(pid,OutputDataSet,"Flux","g/yr",ChemIdx,TimeIdx,Flux)
      end do
    end do
    CLOSE(UNIT=20)
    ! Close the input/output system and save the results.
  END if
  call CloseIO(pid,0)
end program

Battelle Logo
Home | Security and Privacy | Contact Us