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

Annotation 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.5 - (hide annotations) (download)
Mon Nov 5 19:27:02 2007 UTC (16 years, 6 months ago) by jmc
Branch: MAIN
CVS Tags: checkpoint60, checkpoint61, checkpoint62, checkpoint59q, checkpoint59p, checkpoint59r, checkpoint59m, checkpoint59l, checkpoint59o, checkpoint59n, checkpoint59k, checkpoint59j, checkpoint62c, checkpoint62b, checkpoint62a, checkpoint62g, checkpoint62f, checkpoint62e, checkpoint62d, checkpoint62j, checkpoint62i, checkpoint62h, checkpoint61f, checkpoint61g, checkpoint61d, checkpoint61e, checkpoint61b, checkpoint61c, checkpoint61a, checkpoint61n, checkpoint61o, checkpoint61l, checkpoint61m, checkpoint61j, checkpoint61k, checkpoint61h, checkpoint61i, checkpoint61v, checkpoint61w, checkpoint61t, checkpoint61u, checkpoint61r, checkpoint61s, checkpoint61p, checkpoint61q, checkpoint61z, checkpoint61x, checkpoint61y
Changes since 1.4: +17 -16 lines
keep up-to-date with pkg/ptracers source code
( PTRACERS.h splitted in 2 header files)

1 jmc 1.5 C $Header: /u/gcmpack/MITgcm/verification/tutorial_global_oce_latlon/code/ptracers_forcing_surf.F,v 1.4 2007/10/25 20:00:22 dfer Exp $
2 jmc 1.1 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 jmc 1.5 #include "PTRACERS_PARAMS.h"
30     #include "PTRACERS_FIELDS.h"
31 jmc 1.1
32     C !INPUT PARAMETERS: ===================================================
33     C bi,bj :: tile indices
34     C myTime :: model time
35     C myIter :: time-step number
36     C myThid :: thread number
37     INTEGER bi, bj, iMin, iMax, jMin, jMax
38     _RL myTime
39     INTEGER myIter
40     INTEGER myThid
41    
42     #ifdef ALLOW_PTRACERS
43    
44     C !LOCAL VARIABLES: ====================================================
45     C i,j :: loop indices
46     C iTrc :: tracer index
47     C ks :: surface level index
48     INTEGER i, j
49     INTEGER iTrc, ks
50     CEOP
51    
52     IF ( usingPCoords ) THEN
53     ks = Nr
54     ELSE
55     ks = 1
56     ENDIF
57    
58     C Example of how to add forcing at the surface
59     DO iTrc=1,PTRACERS_numInUse
60     DO j = jMin, jMax
61     DO i = iMin, iMax
62 jmc 1.5 surfaceForcingPTr(i,j,bi,bj,iTrc) =
63 jmc 1.3 & + 1. _d 0 / (10. _d 0 * 86400. _d 0)
64     & * ( 0. _d 0 - pTracer(i,j,ks,bi,bj,iTrc) )
65 dfer 1.2 & * drF(ks) * _hFacC(i,j,ks,bi,bj)
66 jmc 1.1 ENDDO
67     ENDDO
68     ENDDO
69    
70     #ifdef EXACT_CONSERV
71     IF ( (nonlinFreeSurf.GT.0 .OR. usingPCoords)
72     & .AND. useRealFreshWaterFlux ) THEN
73    
74     DO iTrc=1,PTRACERS_numInUse
75    
76     c- NonLin_FrSurf and RealFreshWaterFlux : PmEpR effectively changes
77     c the water column height ; temp., salt, (tracer) flux associated
78     c with this input/output of water is added here to the surface tendency.
79     c
80 jmc 1.5 IF (PTRACERS_EvPrRn(iTrc).NE.UNSET_RL) THEN
81 jmc 1.1 DO j = jMin, jMax
82     DO i = iMin, iMax
83 jmc 1.5 surfaceForcingPTr(i,j,bi,bj,iTrc) =
84     & surfaceForcingPTr(i,j,bi,bj,iTrc)
85 jmc 1.1 & + PmEpR(i,j,bi,bj)
86     & *( PTRACERS_EvPrRn(iTrc) - pTracer(i,j,ks,bi,bj,iTrc) )
87 jmc 1.3 & *mass2rUnit
88 jmc 1.1 ENDDO
89     ENDDO
90     ENDIF
91    
92     ENDDO
93 dfer 1.4
94     C---+----1----+----2----+----3----+----4----+----5----+----6----+----7-|--+----|
95     ELSE
96     #else /* EXACT_CONSERV */
97     IF (.TRUE.) THEN
98     #endif /* EXACT_CONSERV */
99    
100     C-- EmPmR does not really affect the water column height (for tracer budget)
101     C and is converted to a salt tendency.
102    
103     IF (convertFW2Salt .EQ. -1.) THEN
104     C- use local surface tracer field to calculate forcing term:
105    
106     DO iTrc=1,PTRACERS_numInUse
107    
108 jmc 1.5 IF (PTRACERS_EvPrRn(iTrc).NE.UNSET_RL) THEN
109     C account for Rain/Evap tracer content (PTRACERS_EvPrRn) using
110 dfer 1.4 C local surface tracer
111     DO j = jMin, jMax
112     DO i = iMin, iMax
113 jmc 1.5 surfaceForcingPTr(i,j,bi,bj,iTrc) =
114     & surfaceForcingPTr(i,j,bi,bj,iTrc)
115 dfer 1.4 & + EmPmR(i,j,bi,bj)
116 jmc 1.5 & *( pTracer(i,j,ks,bi,bj,iTrc) - PTRACERS_EvPrRn(iTrc) )
117 dfer 1.4 & *mass2rUnit
118     ENDDO
119     ENDDO
120     ENDIF
121    
122     ENDDO
123    
124     ELSE
125     C- use uniform tracer value to calculate forcing term:
126    
127     DO iTrc=1,PTRACERS_numInUse
128    
129 jmc 1.5 IF (PTRACERS_EvPrRn(iTrc).NE.UNSET_RL) THEN
130     C account for Rain/Evap tracer content (PTRACERS_EvPrRn) assuming uniform
131 dfer 1.4 C surface tracer (=PTRACERS_ref)
132     DO j = jMin, jMax
133     DO i = iMin, iMax
134 jmc 1.5 surfaceForcingPTr(i,j,bi,bj,iTrc) =
135     & surfaceForcingPTr(i,j,bi,bj,iTrc)
136 dfer 1.4 & + EmPmR(i,j,bi,bj)
137 jmc 1.5 & *( PTRACERS_ref(ks,iTrc) - PTRACERS_EvPrRn(iTrc) )
138 dfer 1.4 & *mass2rUnit
139     ENDDO
140     ENDDO
141     ENDIF
142    
143     ENDDO
144    
145     C- end local-surface-tracer / uniform-value distinction
146     ENDIF
147    
148 jmc 1.1 ENDIF
149 dfer 1.4
150     C---+----1----+----2----+----3----+----4----+----5----+----6----+----7-|--+----|
151 jmc 1.1
152     #endif /* ALLOW_PTRACERS */
153    
154     RETURN
155     END

  ViewVC Help
Powered by ViewVC 1.1.22