/[MITgcm]/MITgcm/verification/tutorial_global_oce_latlon/code/ptracers_forcing_surf.F
ViewVC logotype

Contents of /MITgcm/verification/tutorial_global_oce_latlon/code/ptracers_forcing_surf.F

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


Revision 1.4 - (show annotations) (download)
Thu Oct 25 20:00:22 2007 UTC (16 years, 7 months ago) by dfer
Branch: MAIN
Changes since 1.3: +58 -3 lines
Keep up to date with new versions checked in yesterday.

1 C $Header: /u/gcmpack/MITgcm/pkg/ptracers/ptracers_forcing_surf.F,v 1.8 2007/10/25 13:11:59 mlosch Exp $
2 C $Name: $
3
4 #include "PTRACERS_OPTIONS.h"
5
6 CBOP
7 C !ROUTINE: PTRACERS_FORCING_SURF
8
9 C !INTERFACE: ==========================================================
10 SUBROUTINE PTRACERS_FORCING_SURF(
11 I bi, bj, iMin, iMax, jMin, jMax,
12 I myTime,myIter,myThid )
13
14 C !DESCRIPTION:
15 C Precomputes surface forcing term for pkg/ptracers.
16 C Precomputation is needed because of non-local KPP transport term,
17 C routine KPP_TRANSPORT_PTR.
18
19 C !USES: ===============================================================
20 IMPLICIT NONE
21 #include "SIZE.h"
22 #include "EEPARAMS.h"
23 #include "PARAMS.h"
24 #include "GRID.h"
25 #include "SURFACE.h"
26 #include "FFIELDS.h"
27 c #include "DYNVARS.h"
28 #include "PTRACERS_SIZE.h"
29 #include "PTRACERS.h"
30
31 C !INPUT PARAMETERS: ===================================================
32 C bi,bj :: tile indices
33 C myTime :: model time
34 C myIter :: time-step number
35 C myThid :: thread number
36 INTEGER bi, bj, iMin, iMax, jMin, jMax
37 _RL myTime
38 INTEGER myIter
39 INTEGER myThid
40
41 #ifdef ALLOW_PTRACERS
42
43 C !LOCAL VARIABLES: ====================================================
44 C i,j :: loop indices
45 C iTrc :: tracer index
46 C ks :: surface level index
47 INTEGER i, j
48 INTEGER iTrc, ks
49 CEOP
50
51 IF ( usingPCoords ) THEN
52 ks = Nr
53 ELSE
54 ks = 1
55 ENDIF
56
57 C Example of how to add forcing at the surface
58 DO iTrc=1,PTRACERS_numInUse
59 DO j = jMin, jMax
60 DO i = iMin, iMax
61 surfaceForcingPtr(i,j,bi,bj,iTrc) =
62 & + 1. _d 0 / (10. _d 0 * 86400. _d 0)
63 & * ( 0. _d 0 - pTracer(i,j,ks,bi,bj,iTrc) )
64 & * drF(ks) * _hFacC(i,j,ks,bi,bj)
65 ENDDO
66 ENDDO
67 ENDDO
68
69 #ifdef EXACT_CONSERV
70 IF ( (nonlinFreeSurf.GT.0 .OR. usingPCoords)
71 & .AND. useRealFreshWaterFlux ) THEN
72
73 DO iTrc=1,PTRACERS_numInUse
74
75 c- NonLin_FrSurf and RealFreshWaterFlux : PmEpR effectively changes
76 c the water column height ; temp., salt, (tracer) flux associated
77 c with this input/output of water is added here to the surface tendency.
78 c
79 IF (PtRACERS_EvPrRn(iTrc).NE.UNSET_RL) THEN
80 DO j = jMin, jMax
81 DO i = iMin, iMax
82 surfaceForcingPtr(i,j,bi,bj,iTrc) =
83 & surfaceForcingPtr(i,j,bi,bj,iTrc)
84 & + PmEpR(i,j,bi,bj)
85 & *( PTRACERS_EvPrRn(iTrc) - pTracer(i,j,ks,bi,bj,iTrc) )
86 & *mass2rUnit
87 ENDDO
88 ENDDO
89 ENDIF
90
91 ENDDO
92
93 C---+----1----+----2----+----3----+----4----+----5----+----6----+----7-|--+----|
94 ELSE
95 #else /* EXACT_CONSERV */
96 IF (.TRUE.) THEN
97 #endif /* EXACT_CONSERV */
98
99 C-- EmPmR does not really affect the water column height (for tracer budget)
100 C and is converted to a salt tendency.
101
102 IF (convertFW2Salt .EQ. -1.) THEN
103 C- use local surface tracer field to calculate forcing term:
104
105 DO iTrc=1,PTRACERS_numInUse
106
107 IF (PtRACERS_EvPrRn(iTrc).NE.UNSET_RL) THEN
108 C account for Rain/Evap tracer content (PtRACERS_EvPrRn) using
109 C local surface tracer
110 DO j = jMin, jMax
111 DO i = iMin, iMax
112 surfaceForcingPtr(i,j,bi,bj,iTrc) =
113 & surfaceForcingPtr(i,j,bi,bj,iTrc)
114 & + EmPmR(i,j,bi,bj)
115 & *( pTracer(i,j,ks,bi,bj,iTrc) - PtRACERS_EvPrRn(iTrc) )
116 & *mass2rUnit
117 ENDDO
118 ENDDO
119 ENDIF
120
121 ENDDO
122
123 ELSE
124 C- use uniform tracer value to calculate forcing term:
125
126 DO iTrc=1,PTRACERS_numInUse
127
128 IF (PtRACERS_EvPrRn(iTrc).NE.UNSET_RL) THEN
129 C account for Rain/Evap tracer content (PtRACERS_EvPrRn) assuming uniform
130 C surface tracer (=PTRACERS_ref)
131 DO j = jMin, jMax
132 DO i = iMin, iMax
133 surfaceForcingPtr(i,j,bi,bj,iTrc) =
134 & surfaceForcingPtr(i,j,bi,bj,iTrc)
135 & + EmPmR(i,j,bi,bj)
136 & *( PTRACERS_ref(ks,iTrc) - PtRACERS_EvPrRn(iTrc) )
137 & *mass2rUnit
138 ENDDO
139 ENDDO
140 ENDIF
141
142 ENDDO
143
144 C- end local-surface-tracer / uniform-value distinction
145 ENDIF
146
147 ENDIF
148
149 C---+----1----+----2----+----3----+----4----+----5----+----6----+----7-|--+----|
150
151 #endif /* ALLOW_PTRACERS */
152
153 RETURN
154 END

  ViewVC Help
Powered by ViewVC 1.1.22