/[MITgcm]/MITgcm/pkg/exf/exf_bulk_largeyeager04.F
ViewVC logotype

Diff of /MITgcm/pkg/exf/exf_bulk_largeyeager04.F

Parent Directory Parent Directory | Revision Log Revision Log | View Revision Graph Revision Graph | View Patch Patch

revision 1.1 by heimbach, Wed May 2 22:31:35 2007 UTC revision 1.2 by jmc, Mon May 7 19:35:20 2007 UTC
# Line 6  C $Name$ Line 6  C $Name$
6  CBOP  CBOP
7  C     !ROUTINE: EXF_BULK_LARGEYEAGER04  C     !ROUTINE: EXF_BULK_LARGEYEAGER04
8  C     !INTERFACE:  C     !INTERFACE:
9        SUBROUTINE EXF_BULK_LARGEYEAGER04( mytime, myiter, mythid )        SUBROUTINE EXF_BULK_LARGEYEAGER04( myTime, myIter, myThid )
10    
11  C     !DESCRIPTION: \bv  C     !DESCRIPTION: \bv
12  C     *==========================================================*  C     *==========================================================*
# Line 52  C     === Global variables === Line 52  C     === Global variables ===
52    
53  C     !INPUT/OUTPUT PARAMETERS:  C     !INPUT/OUTPUT PARAMETERS:
54  C     input:  C     input:
55         _RL myTime  C     myTime  :: Current time in simulation
56         INTEGER myIter  C     myIter  :: Current iteration number in simulation
57         INTEGER myThid           ! my Thread Id number  C     myThid  :: My Thread Id number
58          _RL     myTime
59          INTEGER myIter
60          INTEGER myThid
61  C     output:  C     output:
62  CEOP  CEOP
63    
64  #ifdef ALLOW_BULK_LARGEYEAGER04  #ifdef ALLOW_BULK_LARGEYEAGER04
65    
66  C     == Local variables ==  C     == Local variables ==
67        INTEGER i,j,k,bi,bj    !current grid point indices  C     i,j      :: grid point indices
68    C     bi,bj    :: tile indices
69    C     ssq      :: saturation specific humidity [kg/kg] in eq. with Sea-Surface water
70          INTEGER i,j,bi,bj
71    
72        _RL czol        _RL czol
73        _RL Tsf                ! surface temperature [K]        _RL Tsf                ! surface temperature [K]
# Line 72  C     == Local variables == Line 78  C     == Local variables ==
78        _RL delq               ! specific humidity difference [kg/kg]        _RL delq               ! specific humidity difference [kg/kg]
79        _RL deltap        _RL deltap
80        _RL ustar              ! friction velocity [m/s]        _RL ustar              ! friction velocity [m/s]
81        _RL tstar              ! temperature scale [K]        _RL tstar              ! turbulent temperature scale [K]
82        _RL qstar              ! humidity scale  [kg/kg]        _RL qstar              ! turbulent humidity scale  [kg/kg]
83        _RL ssttmp        _RL ssttmp
84        _RL ssq        _RL ssq
85        _RL rd                 ! = sqrt(Cd)          [-]        _RL rd                 ! = sqrt(Cd)          [-]
# Line 91  C     == Local variables == Line 97  C     == Local variables ==
97        _RL psixh              ! latent & sensib. stability function        _RL psixh              ! latent & sensib. stability function
98        _RL zwln               ! = log(zwd/zref)        _RL zwln               ! = log(zwd/zref)
99        _RL ztln               ! = log(zth/zref)        _RL ztln               ! = log(zth/zref)
100        _RL tau                ! surface stress  coef = rhoA * Ws * Cd        _RL tau                ! surface stress coef = rhoA * Ws * sqrt(Cd)
101          _RL windStress         ! surface wind-stress (@ grid cell center)
102        _RL tmpbulk        _RL tmpbulk
103        INTEGER iter        INTEGER iter
104    
# Line 112  c     Loop over tiles. Line 119  c     Loop over tiles.
119  C--   HPF directive to help TAMC  C--   HPF directive to help TAMC
120  CHPF$ INDEPENDENT  CHPF$ INDEPENDENT
121  #endif  #endif
122        do bj = mybylo(mythid),mybyhi(mythid)        DO bj = myByLo(myThid),myByHi(myThid)
123  #ifdef ALLOW_AUTODIFF_TAMC  #ifdef ALLOW_AUTODIFF_TAMC
124  C--    HPF directive to help TAMC  C--    HPF directive to help TAMC
125  CHPF$  INDEPENDENT  CHPF$  INDEPENDENT
126  #endif  #endif
127         do bi = mybxlo(mythid),mybxhi(mythid)         DO bi = myBxLo(myThid),myBxHi(myThid)
128          k = 1          DO j = 1,sNy
129          do j = 1,sny           DO i = 1,sNx
          do i = 1,snx  
130    
131  #ifdef ALLOW_AUTODIFF_TAMC  #ifdef ALLOW_AUTODIFF_TAMC
132            act1 = bi - myBxLo(myThid)            act1 = bi - myBxLo(myThid)
# Line 171  C    take U_N = del.U ; stability from d Line 177  C    take U_N = del.U ; stability from d
177  #else /* ifndef ALLOW_ATM_WIND */  #else /* ifndef ALLOW_ATM_WIND */
178  C     in this case ustress and vstress are defined a u and v points  C     in this case ustress and vstress are defined a u and v points
179  C     respectively, and we need to average to mass points to avoid  C     respectively, and we need to average to mass points to avoid
180  C     tau = 0 near coasts or other boundaries  C     windStress = 0 near coasts or other boundaries
181               tau   = sqrt(0.5*               windStress = sqrt(0.5 _d 0*
182       &                   (ustress(i,  j,bi,bj)*ustress(i  ,j,bi,bj)       &                   (ustress(i,  j,bi,bj)*ustress(i  ,j,bi,bj)
183       &                   +ustress(i+1,j,bi,bj)*ustress(i+1,j,bi,bj)       &                   +ustress(i+1,j,bi,bj)*ustress(i+1,j,bi,bj)
184       &                   +vstress(i,j,  bi,bj)*vstress(i,j  ,bi,bj)       &                   +vstress(i,j,  bi,bj)*vstress(i,j  ,bi,bj)
185       &                   +vstress(i,j+1,bi,bj)*vstress(i,j+1,bi,bj))       &                   +vstress(i,j+1,bi,bj)*vstress(i,j+1,bi,bj)
186       &                   )       &                   )    )
187               ustar = sqrt(tau/atmrho)               ustar = sqrt(windStess/atmrho)
188  #endif /* ALLOW_ATM_WIND */  #endif /* ALLOW_ATM_WIND */
189    
190  C--  initial guess for exchange other coefficients:  C--  initial guess for exchange other coefficients:
# Line 312  c IF ( ATEMP(i,j,bi,bj) .NE. 0. ) Line 318  c IF ( ATEMP(i,j,bi,bj) .NE. 0. )
318       &                         vwind(i,j,bi,bj)       &                         vwind(i,j,bi,bj)
319  #endif  #endif
320  #endif /* ifndef ALLOW_ATM_TEMP */  #endif /* ifndef ALLOW_ATM_TEMP */
321              enddo              ENDDO
322            enddo            ENDDO
323          enddo          ENDDO
324        enddo        ENDDO
325    
326  #endif /* ALLOW_BULKFORMULAE */  #endif /* ALLOW_BULK_LARGEYEAGER04 */
327    
328          RETURN
329        END        END

Legend:
Removed from v.1.1  
changed lines
  Added in v.1.2

  ViewVC Help
Powered by ViewVC 1.1.22