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 B
Pre-Processor for the Constantly Stirred Tank Reduction Model

The following FORTRAN code could serve as a pre-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:50 pm
program main

USE DataSet
USE SystemDev

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 used by the CSTR model itself.
! The following lines represent data associated with each chemical.
  INTEGER*4 NumChem
  CHARACTER(4096) CNAME,CASID
  REAL*8 Qco,kd,S,lambda,TFinal,Ct,Ctp
! QCo (g/yr)   Mass flux into CSTR
! kd (cm^3/g)  Soil partition coefficient
! S (mg/L)     Solubility limit
! lambda (1/yr) Decay rate of the chemical
! TFinal (yr)  Last year to report
! Ct  (g/cm^3) Initial concentration on total volume
! Ctp (mg/kg)  Initial concentration on total weight
  INTEGER*4 EnterCt
! EnterCt is a flag to signify whether Ct or Ctp is entered.
  INTEGER*4 NTimes
! The number of times to report

! The following line represents data associated with the site.
  REAL*8 L,W,Th,b,Ks,i,thetaFc,rhoS,Bd
! L (cm)         Length of site
! W (cm)         Width of site
! Th (cm)        Thickness of site
! b           Soil type exponent
! Ks (cm/s converted to cm/yr) Saturated K
! i (cm/yr)      Infiltration rate
! thetaFc ()     Field capacity
! rhoS (g/cm^3)  Particle density
! Bd (g/cm^3)    Bulk density

! The data below are for connecting to FRAMES.
CHARACTER(256) CommandLine
CHARACTER*4096 Path,Simulation,ModuleId,IModuleId
CHARACTER*4096 InputDictionary,InputDataSet
INTEGER*4 pid,NIMod,j,NIModSet
LOGICAL InputSetFound
INTEGER ierr

INTEGER*4 chem

InputSetFound=.FALSE.
  call getCL(commandline)   ! Get the command line handed the program.
  READ(commandline,*) path,simulation,moduleId
  WRITE(*,*)TRIM(Path)," ",TRIM(Simulation)," ",TRIM(moduleid)
  READ(*,*)ierr
  pid=OpenIO(path,simulation,moduleId)
  if (pid.gt.0) then ! a pid less than 0 means something is wrong
    if (GetIconUIset(pid,moduleId,InputDataSet).ge.0) then     ! Get the user interface dataset.
      InputSetFound=.TRUE.   ! Set the flag that says it is OK.
      InputDataSet=TRIM(InputDataSet)
      WRITE(*,*) "{",TRIM(InputDataSet),"}"
    END if
    open (UNIT=20, FILE="CSTRInput.txt",IOSTAT=ierr) ! Our goal is to create this input file.
    if (InputSetFound) then
      L=readReal(pid,InputDataSet,"l","cm")            ! Units are now checked.
      W=readReal(pid,InputDataSet,"W","cm")            ! Values are found by name and not
      Th=readReal(pid,InputDataSet,"Th","cm")          ! location in the file.
      TFinal=readReal(pid,InputDataSet,"TFinal","yr")
      b=readReal(pid,InputDataSet,"b","")
      Ks=readReal(pid,InputDataSet,"Ks","cm/s")
      i=readReal(pid,InputDataSet,"i","cm/yr")
      thetaFC=readReal(pid,InputDataSet,"thetaFc","")
      rhoS=readReal(pid,InputDataSet,"rhoS","g/cm3")
      bd=readReal(pid,InputDataSet,"Bd","g/cm3")
      write(*,*)L,W,Th,b,Ks,i,thetaFc,rhoS,Bd ! Take the read and make it a write.
      write(20,*)L,W,Th,b,Ks,i,thetaFc,rhoS,Bd ! Take the read and make it a write.
      NumChem=1
      write(*,*)NumChem
      write(20,*)NumChem
      do chem=1,NumChem
        call readString1 (pid ,InputDataSet ,"CName" ,"" ,chem , CName)
        WRITE(*,*) TRIM(CNAME)
        WRITE(20,*) TRIM(CNAME)
        call readString1(pid,InputDataSet,"CASID","",chem,CASID)
        WRITE(*,*) TRIM(CASID)
        WRITE(20,*) TRIM(CASID)
        READ(*,*) IERR
        Qco=readReal1(pid,InputDataSet,"Qco","g/yr",chem)
        kd=readReal1(pid,InputDataSet,"kd","cm^3/g",chem)
        S=readReal1(pid,InputDataSet,"S","mg/l",chem)
        lambda=readReal1(pid,InputDataSet,"lambda","1/y",chem)
        NTimes=readInt1(pid,InputDataSet,"NTimes","",chem)
        write(20,*)Qco,kd,S,lambda,Tfinal
        WRITE(20,*)NTimes
        write(*,*)Qco,kd,S,lambda,Tfinal
        WRITE(*,*)NTimes
        EnterCT=readLog1(pid,InputDataSet,"CtFlag","",chem)
        if (EnterCt.ne.0) then
          write(20,*)1
          ct=readReal1(pid,InputDataSet,"Ct","g/cm^3",chem)
          write(20,*)Ct
        else
          WRITE(20,*)0
          ctp=readReal1(pid,InputDataSet,"Ctp","mg/kg",chem)
          write(20,*)Ctp
        end if
      end do
    end if
    CLOSE(UNIT=20)
    ! Close the input/output system and do not save any changes.  We did not make any.
   call CloseIO(pid,1)
end program

Battelle Logo
Home | Security and Privacy | Contact Us