/[MITgcm]/MITgcm/pkg/ptracers/ptracers_forcing_surf.F
ViewVC logotype

Annotation of /MITgcm/pkg/ptracers/ptracers_forcing_surf.F

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


Revision 1.9 - (hide annotations) (download)
Mon Nov 5 18:48:04 2007 UTC (16 years, 7 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.8: +17 -16 lines
split PTRACERS.h in 2 header files: PTRACERS_FIELDS.h & PTRACERS_PARAMS.h

1 jmc 1.9 C $Header: /u/gcmpack/MITgcm/pkg/ptracers/ptracers_forcing_surf.F,v 1.8 2007/10/25 13:11:59 mlosch Exp $
2 dimitri 1.1 C $Name: $
3    
4     #include "PTRACERS_OPTIONS.h"
5    
6     CBOP
7 jmc 1.2 C !ROUTINE: PTRACERS_FORCING_SURF
8 dimitri 1.1
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 jmc 1.5 #include "GRID.h"
25     #include "SURFACE.h"
26 dimitri 1.1 #include "FFIELDS.h"
27 jmc 1.3 c #include "DYNVARS.h"
28 jmc 1.5 #include "PTRACERS_SIZE.h"
29 jmc 1.9 #include "PTRACERS_PARAMS.h"
30     #include "PTRACERS_FIELDS.h"
31 dimitri 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 jmc 1.5 C iTrc :: tracer index
47     C ks :: surface level index
48     INTEGER i, j
49     INTEGER iTrc, ks
50 dimitri 1.1 CEOP
51    
52 jmc 1.5 IF ( usingPCoords ) THEN
53     ks = Nr
54     ELSE
55     ks = 1
56     ENDIF
57    
58 dimitri 1.1 C Example of how to add forcing at the surface
59 jmc 1.5 DO iTrc=1,PTRACERS_numInUse
60 dimitri 1.1 DO j = jMin, jMax
61 jmc 1.4 DO i = iMin, iMax
62 jmc 1.9 surfaceForcingPTr(i,j,bi,bj,iTrc) =
63 jmc 1.4 & 0. _d 0
64     c & surfaceForcingS(i,j,bi,bj)
65     ENDDO
66 dimitri 1.1 ENDDO
67 jmc 1.5 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 jmc 1.9 IF (PTRACERS_EvPrRn(iTrc).NE.UNSET_RL) THEN
80 jmc 1.5 DO j = jMin, jMax
81     DO i = iMin, iMax
82 jmc 1.9 surfaceForcingPTr(i,j,bi,bj,iTrc) =
83     & surfaceForcingPTr(i,j,bi,bj,iTrc)
84 jmc 1.5 & + PmEpR(i,j,bi,bj)
85     & *( PTRACERS_EvPrRn(iTrc) - pTracer(i,j,ks,bi,bj,iTrc) )
86 jmc 1.6 & *mass2rUnit
87 jmc 1.5 ENDDO
88     ENDDO
89     ENDIF
90    
91 dimitri 1.1 ENDDO
92 dfer 1.7
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 jmc 1.9 IF (PTRACERS_EvPrRn(iTrc).NE.UNSET_RL) THEN
108     C account for Rain/Evap tracer content (PTRACERS_EvPrRn) using
109 dfer 1.7 C local surface tracer
110     DO j = jMin, jMax
111     DO i = iMin, iMax
112 jmc 1.9 surfaceForcingPTr(i,j,bi,bj,iTrc) =
113     & surfaceForcingPTr(i,j,bi,bj,iTrc)
114 dfer 1.7 & + EmPmR(i,j,bi,bj)
115 jmc 1.9 & *( pTracer(i,j,ks,bi,bj,iTrc) - PTRACERS_EvPrRn(iTrc) )
116 mlosch 1.8 & *mass2rUnit
117 dfer 1.7 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 jmc 1.9 IF (PTRACERS_EvPrRn(iTrc).NE.UNSET_RL) THEN
129     C account for Rain/Evap tracer content (PTRACERS_EvPrRn) assuming uniform
130 dfer 1.7 C surface tracer (=PTRACERS_ref)
131     DO j = jMin, jMax
132     DO i = iMin, iMax
133 jmc 1.9 surfaceForcingPTr(i,j,bi,bj,iTrc) =
134     & surfaceForcingPTr(i,j,bi,bj,iTrc)
135 dfer 1.7 & + EmPmR(i,j,bi,bj)
136 jmc 1.9 & *( PTRACERS_ref(ks,iTrc) - PTRACERS_EvPrRn(iTrc) )
137 dfer 1.7 & *mass2rUnit
138     ENDDO
139     ENDDO
140     ENDIF
141    
142     ENDDO
143    
144     C- end local-surface-tracer / uniform-value distinction
145     ENDIF
146    
147 jmc 1.5 ENDIF
148 dfer 1.7
149     C---+----1----+----2----+----3----+----4----+----5----+----6----+----7-|--+----|
150 dimitri 1.1
151     #endif /* ALLOW_PTRACERS */
152    
153     RETURN
154     END

  ViewVC Help
Powered by ViewVC 1.1.22