| Type | Intent | Optional | Attributes | Name | ||
|---|---|---|---|---|---|---|
| integer, | intent(in) | :: | IL | |||
| integer, | intent(in) | :: | Pprof | |||
| real(kind=r64), | intent(in) | :: | G | |||
| real(kind=r64), | intent(in) | :: | DpF(2) | |||
| real(kind=r64), | intent(in) | :: | DpT(2) | |||
| real(kind=r64), | intent(in) | :: | BetaF(2) | |||
| real(kind=r64), | intent(in) | :: | BetaT(2) | |||
| real(kind=r64), | intent(in) | :: | RhoStF(2) | |||
| real(kind=r64), | intent(in) | :: | RhoStT(2) | |||
| integer, | intent(in) | :: | From | |||
| integer, | intent(in) | :: | To | |||
| real(kind=r64), | intent(in) | :: | ActLh | |||
| real(kind=r64), | intent(in) | :: | OwnHeightFactor | 
Nodes of different colours represent the following:
Solid arrows point from a procedure to one which it calls. Dashed arrows point from an interface to procedures which implement that interface. This could include the module procedures in a generic interface or the implementation in a submodule of an interface in a parent module. Where possible, edges connecting nodes are given different colours to make them easier to distinguish in large graphs.
Nodes of different colours represent the following:
Solid arrows point from a procedure to one which it calls. Dashed arrows point from an interface to procedures which implement that interface. This could include the module procedures in a generic interface or the implementation in a submodule of an interface in a parent module. Where possible, edges connecting nodes are given different colours to make them easier to distinguish in large graphs.
    SUBROUTINE PresProfile(il,Pprof,G,DpF,DpT,BetaF,BetaT,RhoStF, &
            RhoStT,From,To,ActLh,OwnHeightFactor)
          ! SUBROUTINE INFORMATION:
          !       AUTHOR         Lixing Gu
          !       DATE WRITTEN   Oct. 2005
          !       MODIFIED       na
          !       RE-ENGINEERED  This subroutine is revised based on PresProfile subroutine from COMIS
          ! PURPOSE OF THIS SUBROUTINE:
          ! This subroutine calculates for a large opening profiles of stack pressure difference and
          ! densities in the zones linked by the a detailed opening cmponent.
          ! METHODOLOGY EMPLOYED:
          ! The profiles are obtained in the following
          ! way:    - the opening is divided into NrInt vertical intervals
          !         - the stack pressure difference and densities in From-
          !           and To-zone are calculated at the centre of each
          !           interval aswell as at the top and bottom of the LO
          !          - these values are stored in the (NrInt+2)-dimensional
          !             arrays DpProf, RhoProfF, RhoProfT.
          ! The calculation of stack pressure and density in the two zones
          ! is based on the arrays DpF/T, RhoStF/T, BetaF/T. These arrays
          ! are calculated in the COMIS routine Lclimb. They contain the
          ! values of stack pressure and density at the startheight of the
          ! opening and at startheights of all layers lying inside the
          ! opening, and the density gradients across the layers.
          ! The effective startheight zl(1/2) in the From/To zone and the
          ! effective length actLh of the LO take into account the
          ! startheightfactor, heightfactor and ownheightfactor. Thus for
          ! slanted windows the range of the profiles is the vertical
          ! projection of the actual opening.
          ! REFERENCES:
          ! Helmut E. Feustel and Alison Rayner-Hooson, "COMIS Fundamentals," LBL-28560,
          ! Lawrence Berkeley National Laboratory, Berkeley, CA, May 1990
          ! USE STATEMENTS:
          ! na
          IMPLICIT NONE    ! Enforce explicit typing of all variables in this routine
          ! SUBROUTINE ARGUMENT DEFINITIONS:
          INTEGER, INTENT(IN)  :: IL       ! Linkage number
          INTEGER, INTENT(IN)  :: Pprof    ! Opening number
          REAL(r64), INTENT(IN)     :: G        ! gravitation field strength [N/kg]
          REAL(r64), INTENT(IN) :: DpF(2) ! Stack pressures at start heights of Layers
                                                 ! in the FROM zone (starting at linkheight) [Pa]
          REAL(r64), INTENT(IN) :: DpT(2) ! Stack pressures at start heights of Layers
          REAL(r64), INTENT(IN)     :: BetaF(2) ! Density gradients in the FROM zone (starting at linkheight) [Kg/m3/m]
          REAL(r64), INTENT(IN)     :: BetaT(2) ! Density gradients in the TO zone (starting at linkheight) [Kg/m3/m]
          REAL(r64), INTENT(IN)     :: RhoStF(2) ! Density at the start heights of Layers in the FROM zone
                                            ! (starting at linkheight) [Kg/m3]
          REAL(r64), INTENT(IN)     :: RhoStT(2) ! Density at the start heights of Layers in the TO zone
                                            ! (starting at linkheight) [Kg/m3]
          REAL(r64), INTENT(IN)     :: ActLh    ! Actual height of opening [m]
          REAL(r64), INTENT(IN)     :: OwnHeightFactor ! Cosine of deviation angle of the opening plane from the vertical direction
          INTEGER, INTENT(IN)  :: From     ! Number of FROM zone
          INTEGER, INTENT(IN)  :: To       ! Number of To zone
          ! SUBROUTINE PARAMETER DEFINITIONS:
          ! na
          ! INTERFACE BLOCK SPECIFICATIONS
          ! na
          ! DERIVED TYPE DEFINITIONS
          ! na
          ! SUBROUTINE LOCAL VARIABLE DECLARATIONS:
      REAL(r64) zF(2),zT(2) ! Startheights of layers in FROM-, TO-zone
      REAL(r64) zStF(2),zStT(2) ! Startheights of layers within the LO, starting with the actual startheight of the LO.
                           ! The values in the arrays DpF, DpT, BetaF, BetaT, RhoStF, RhoStT are calculated at these heights.
      REAL(r64) hghtsFR, hghtsTR
      REAL(r64) hghtsF(NrInt+2),hghtsT(NrInt+2) ! Heights of evaluation points for pressure and density profiles
      REAL(r64) Interval ! Distance between two evaluation points
      REAL(r64) delzF,delzT ! Interval between actual evaluation point and startheight of actual layer in FROM-, TO-zone
      INTEGER AnzLayF,AnzLayT ! Number of layers in FROM-, TO-zone
      INTEGER lF,lT ! Actual index for DpF/T, BetaF/T, RhoStF/T, zStF/T
      INTEGER n,i,k
      ! FLOW:
      ! Initialization
      delzF=0.0d0
      delzT=0.0d0
      Interval=ActLh*OwnHeightFactor/NrInt
      DO n=1,NrInt
        hghtsF(n+1)=AirflowNetworkLinkageData(il)%NodeHeights(1)+Interval*(n-0.5d0)
        hghtsT(n+1)=AirflowNetworkLinkageData(il)%NodeHeights(2)+Interval*(n-0.5d0)
      END DO
      hghtsF(1)=AirflowNetworkLinkageData(il)%NodeHeights(1)
      hghtsT(1)=AirflowNetworkLinkageData(il)%NodeHeights(2)
      hghtsF(NrInt+2)=AirflowNetworkLinkageData(il)%NodeHeights(1)+ActLh*OwnHeightFactor
      hghtsT(NrInt+2)=AirflowNetworkLinkageData(il)%NodeHeights(2)+ActLh*OwnHeightFactor
      lF=1
      lT=1
      If (From .eq. 0) then
        AnzLayF=1
      Else
        AnzLayF=0
      End if
      If (To .eq. 0) then
        AnzLayT=1
      Else
        AnzLayT=0
      End if
      IF (AnzLayF.GT.0) THEN
        DO n=1,AnzLayF
          zF(n)=0.0d0
          If (hghtsF(1) .LT. 0.0d0) zF(n)=hghtsF(1)
        ENDDO
      ENDIF
      IF (AnzLayT.GT.0) THEN
        DO n=1,AnzLayT
          zT(n)=0.0d0
          If (hghtsT(1) .LT. 0.0d0) zT(n)=hghtsT(1)
        ENDDO
      ENDIF
      zStF(1)=AirflowNetworkLinkageData(il)%NodeHeights(1)
      i=2
      k=1
      DO WHILE (k.LE.AnzLayF)
        IF (zF(k).GT.zStF(1)) Exit
        k=k+1
      END DO
      DO WHILE (k.LE.AnzLayF)
        IF (zF(k).GT.hghtsF(NrInt)) EXIT
        zStF(i)=zF(k) !Objexx:BoundsViolation zStF(i) @ i>2 and zF(k) @ k>2
        i=i+1
        k=k+1
      END DO
      zStF(i)=AirflowNetworkLinkageData(il)%NodeHeights(1)+ActLh*OwnHeightFactor !Objexx:BoundsViolation zStF(i) @ i>2
      zStT(1)=AirflowNetworkLinkageData(il)%NodeHeights(2)
      i=2
      k=1
      DO WHILE (k.LE.AnzLayT)
        IF (zT(k).GT.zStT(1)) EXIT
        k=k+1
      END DO
      DO WHILE (k.LE.AnzLayT)
        IF (zT(k).GT.hghtsT(NrInt)) EXIT !Objexx:BoundsViolation zT(k) @ k>2
        zStT(i)=zT(k) !Objexx:BoundsViolation zStF(i) @ i>2 and zT(k) @ k>2
        i=i+1
        k=k+1
      END DO
      zStT(i)=AirflowNetworkLinkageData(il)%NodeHeights(2)+ActLh*OwnHeightFactor !Objexx:BoundsViolation zStT(i) @ i>2
      ! Calculation of DpProf, RhoProfF, RhoProfT
      DO i=1,NrInt+2
        hghtsFR=hghtsF(i)
        hghtsTR=hghtsT(i)
        DO
          IF (hghtsFR.GT.zStF(lF+1)) THEN
            IF (lF .gt. 2) EXIT
            lF=lF+1
          END IF
          IF (hghtsFR.LE.zStF(lF+1)) Exit
        END DO
        DO
          IF (hghtsTR.GT.zStT(lT+1)) THEN
            lT=lT+1
          END IF
          IF (hghtsTR.LE.zStT(lT+1)) Exit
        END DO
        delzF=hghtsF(i)-zStF(lF)
        delzT=hghtsT(i)-zStT(lT)
        RhoProfF(i+Pprof)=RhoStF(lF)+BetaF(lF)*delzF
        RhoProfT(i+Pprof)=RhoStT(lT)+BetaT(lT)*delzT
        DpProf(i+Pprof)=DpF(lF)-DpT(lT) &
            -G*(RhoStF(lF)*delzF+BetaF(lF)*delzF**2/2.0d0) &
            +G*(RhoStT(lT)*delzT+BetaT(lT)*delzT**2/2.0d0)
      END DO
      RETURN
    END SUBROUTINE PresProfile