/[MITgcm]/MITgcm/model/src/external_forcing_surf.F
ViewVC logotype

Annotation of /MITgcm/model/src/external_forcing_surf.F

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


Revision 1.7 - (hide annotations) (download)
Wed Sep 25 19:36:50 2002 UTC (21 years, 9 months ago) by mlosch
Branch: MAIN
Changes since 1.6: +41 -21 lines
o cleaned up the use of rhoNil and rhoConst.
  - rhoNil should only appear in the LINEAR equation of state, everywhere
    else rhoNil is replaced by rhoConst, e.g. find_rho computes rho-rhoConst
    and the dynamical equations are all divided by rhoConst
o introduced new parameter rhoConstFresh, a reference density of fresh
  water, to remove the fresh water flux's dependence on rhoNil. The default
  value is 999.8 kg/m^3
o cleanup up external_forcing.F and external_forcing_surf.F
  - can now be used by both OCEANIC and OCEANICP

1 mlosch 1.7 C $Header: /u/gcmpack/models/MITgcmUV/model/src/external_forcing_surf.F,v 1.6 2002/02/10 00:39:22 jmc Exp $
2 cnh 1.5 C $Name: $
3 heimbach 1.1
4     #include "CPP_OPTIONS.h"
5    
6 cnh 1.5 CBOP
7     C !ROUTINE: EXTERNAL_FORCING_SURF
8     C !INTERFACE:
9 heimbach 1.2 SUBROUTINE EXTERNAL_FORCING_SURF(
10     I bi, bj, iMin, iMax, jMin, jMax,
11     I myThid )
12 cnh 1.5 C !DESCRIPTION: \bv
13     C *==========================================================*
14     C | SUBROUTINE EXTERNAL_FORCING_SURF
15     C | o Determines forcing terms based on external fields
16     C | relaxation terms etc.
17     C *==========================================================*
18     C \ev
19    
20     C !USES:
21 heimbach 1.1 IMPLICIT NONE
22     C === Global variables ===
23     #include "SIZE.h"
24     #include "EEPARAMS.h"
25     #include "PARAMS.h"
26     #include "FFIELDS.h"
27     #include "DYNVARS.h"
28     #include "GRID.h"
29 jmc 1.6 #ifdef NONLIN_FRSURF
30     #include "SURFACE.h"
31     #endif
32 heimbach 1.1
33 cnh 1.5 C !INPUT/OUTPUT PARAMETERS:
34 heimbach 1.1 C === Routine arguments ===
35 cnh 1.5 C myThid :: Thread no. that called this routine.
36 heimbach 1.1 INTEGER myThid
37 cnh 1.5 INTEGER bi,bj
38     INTEGER iMin, iMax
39     INTEGER jMin, jMax
40 heimbach 1.1
41 cnh 1.5 C !LOCAL VARIABLES:
42 heimbach 1.1 C === Local variables ===
43 cnh 1.5 INTEGER i,j
44 mlosch 1.7 C number of surface interface layer
45     INTEGER kSurface
46     _RL convertVol2Mass
47 cnh 1.5 CEOP
48 heimbach 1.2
49 mlosch 1.7 if ( buoyancyRelation .eq. 'OCEANICP' ) then
50     kSurface = Nr
51     convertVol2Mass = horiVertRatio
52     else
53     kSurface = 1
54     convertVol2Mass = 1. _d 0
55     endif
56    
57 heimbach 1.2 DO j = jMin, jMax
58     DO i = iMin, iMax
59 heimbach 1.1
60     c Zonal wind stress fu:
61 jmc 1.6 surfaceTendencyU(i,j,bi,bj) =
62 mlosch 1.7 & fu(i,j,bi,bj)*horiVertRatio*recip_rhoConst
63     & *recip_drF(kSurface)*recip_hFacW(i,j,kSurface,bi,bj)
64 heimbach 1.2 c Meridional wind stress fv:
65 jmc 1.6 surfaceTendencyV(i,j,bi,bj) =
66 mlosch 1.7 & fv(i,j,bi,bj)*horiVertRatio*recip_rhoConst
67     & *recip_drF(kSurface)*recip_hFacS(i,j,kSurface,bi,bj)
68 heimbach 1.1 c Net heat flux Qnet:
69 jmc 1.6 surfaceTendencyT(i,j,bi,bj) =
70 mlosch 1.7 & -Qnet(i,j,bi,bj)*recip_Cp*horiVertRatio*recip_rhoConst
71     & *recip_drF(kSurface)*recip_hFacC(i,j,kSurface,bi,bj)
72     & -lambdaThetaClimRelax
73     & *(theta(i,j,kSurface,bi,bj)-SST(i,j,bi,bj))
74 jmc 1.6 C Salt Flux (restoring term) :
75     C surfaceTendencyS(i,j,bi,bj) =
76 mlosch 1.7 C & -lambdaSaltClimRelax*(salt(i,j,kSurface,bi,bj)-SSS(i,j,bi,bj))
77 jmc 1.6 C notes : because truncation is different when this tendency is splitted
78     C in 2 parts, keep this salt flux with freshwater flux (see below)
79    
80     #ifdef ALLOW_PASSIVE_TRACER
81     c *** define the tracer surface tendency here ***
82     #endif /* ALLOW_PASSIVE_TRACER */
83 heimbach 1.2
84     ENDDO
85     ENDDO
86 jmc 1.6
87     c---+----1----+----2----+----3----+----4----+----5----+----6----+----7-|--+----|
88     C Surface salinity tendency and freshwater flux EmPmR:
89    
90     IF (.NOT.useRealFreshWaterFlux .OR. nonlinFreeSurf .LE. 0 ) THEN
91    
92     c- EmPmR does not really affect the water column height (for tracer budget)
93     c and is converted to a salt tendency.
94    
95     IF (convertFW2Salt .EQ. -1.) THEN
96     c- converts EmPmR to salinity tendency using surface local salinity
97     DO j = jMin, jMax
98     DO i = iMin, iMax
99     surfaceTendencyS(i,j,bi,bj) =
100 mlosch 1.7 & + EmPmR(i,j,bi,bj)*salt(i,j,kSurface,bi,bj)
101     & *recip_drF(kSurface)*recip_hFacC(i,j,kSurface,bi,bj)
102     & *convertVol2Mass
103     & -lambdaSaltClimRelax
104     & *(salt(i,j,kSurface,bi,bj)-SSS(i,j,bi,bj))
105 jmc 1.6 ENDDO
106     ENDDO
107     ELSE
108     c- converts EmPmR to virtual salt flux using uniform salinity (default=35)
109     DO j = jMin, jMax
110     DO i = iMin, iMax
111     surfaceTendencyS(i,j,bi,bj) =
112     & + EmPmR(i,j,bi,bj)*convertFW2Salt
113 mlosch 1.7 & *recip_drF(kSurface)*recip_hFacC(i,j,kSurface,bi,bj)
114     & *convertVol2Mass
115     & -lambdaSaltClimRelax*(salt(i,j,kSurface,bi,bj)-SSS(i,j,bi,bj))
116 jmc 1.6 ENDDO
117     ENDDO
118     ENDIF
119    
120     #ifdef NONLIN_FRSURF
121     c---+----1----+----2----+----3----+----4----+----5----+----6----+----7-|--+----|
122     ELSE
123    
124     c Salt Flux (restoring term) :
125     DO j = jMin, jMax
126     DO i = iMin, iMax
127     surfaceTendencyS(i,j,bi,bj) =
128 mlosch 1.7 & -lambdaSaltClimRelax
129     & *(salt(i,j,kSurface,bi,bj)-SSS(i,j,bi,bj))
130 jmc 1.6 ENDDO
131     ENDDO
132    
133     c- NonLin_FrSurf and RealFreshWaterFlux : PmEpR effectively changes
134     c the water column height ; temp., salt, (tracer) flux associated
135     c with this input/output of water is added here to the surface tendency.
136     c
137     c NB: PmEpR lag 1 time step behind EmPmR ( PmEpR_n = - EmPmR_n-1 ) to stay
138     c consitent with volume change (=d/dt etaN).
139    
140     IF (temp_EvPrRn.NE.UNSET_RL) THEN
141     DO j = jMin, jMax
142     DO i = iMin, iMax
143     surfaceTendencyT(i,j,bi,bj) = surfaceTendencyT(i,j,bi,bj)
144 mlosch 1.7 & + PmEpR(i,j,bi,bj)
145     & *( temp_EvPrRn - theta(i,j,kSurface,bi,bj) )
146     & *recip_drF(kSurface)*recip_hFacC(i,j,kSurface,bi,bj)
147     & *convertVol2Mass
148 jmc 1.6 ENDDO
149     ENDDO
150     ENDIF
151    
152     IF (salt_EvPrRn.NE.UNSET_RL) THEN
153     DO j = jMin, jMax
154     DO i = iMin, iMax
155     surfaceTendencyS(i,j,bi,bj) = surfaceTendencyS(i,j,bi,bj)
156 mlosch 1.7 & + PmEpR(i,j,bi,bj)
157     & *( salt_EvPrRn - salt(i,j,kSurface,bi,bj) )
158     & *recip_drF(kSurface)*recip_hFacC(i,j,kSurface,bi,bj)
159     & *convertVol2Mass
160 jmc 1.6 ENDDO
161     ENDDO
162     ENDIF
163    
164     #ifdef ALLOW_PASSIVE_TRACER
165     c *** add the tracer flux associated with P-E+R here ***
166     c IF (trac_EvPrRn.NE.UNSET_RL) THEN
167 mlosch 1.7 c & + PmEpR(i,j,bi,bj)*( trac_EvPrRn - tr1(i,j,kSurface,bi,bj) )
168     c & *recip_drF(kSurface)*recip_hFacC(i,j,kSurface,bi,bj)
169 jmc 1.6 c ENDIF
170     #endif /* ALLOW_PASSIVE_TRACER */
171    
172     #endif /* NONLIN_FRSURF */
173     ENDIF
174 heimbach 1.1
175     RETURN
176     END

  ViewVC Help
Powered by ViewVC 1.1.22