/[MITgcm]/MITgcm/pkg/gchem/gchem_calc_tendency.F
ViewVC logotype

Annotation of /MITgcm/pkg/gchem/gchem_calc_tendency.F

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


Revision 1.4 - (hide annotations) (download)
Thu Dec 22 19:05:27 2011 UTC (12 years, 5 months ago) by jmc
Branch: MAIN
CVS Tags: checkpoint64h, checkpoint64a, checkpoint64c, checkpoint64b, checkpoint64e, checkpoint64d, checkpoint64g, checkpoint64f, checkpoint63p, checkpoint63q, checkpoint63r, checkpoint63s, checkpoint63l, checkpoint63m, checkpoint63n, checkpoint63o, checkpoint63h, checkpoint63i, checkpoint63j, checkpoint63k, checkpoint64
Changes since 1.3: +22 -28 lines
remove/avoid un-used variables

1 jmc 1.4 C $Header: /u/gcmpack/MITgcm/pkg/gchem/gchem_calc_tendency.F,v 1.3 2007/11/05 19:05:01 jmc Exp $
2 mlosch 1.1 C $Name: $
3    
4     #include "GCHEM_OPTIONS.h"
5    
6     CBOP
7     C !ROUTINE: GCHEM_CALC_TENDENCY
8    
9     C !INTERFACE: ==========================================================
10     SUBROUTINE GCHEM_CALC_TENDENCY(
11     I myTime, myIter, myThid )
12    
13     C !DESCRIPTION:
14     C In the case of GCHEM_SEPARATE_FORCING not defined,
15     C this subroutine computes the tracer tendencies due to a
16     C bio-geogchemistry or ecosystem model and stores them on an array
17     C gchemTendency, that will be incorporated into regular timestepping in
18     C in ptracers_intergrate.F
19 jmc 1.3 C The current example uses the CFC package, but his is meant to
20 mlosch 1.1 C be replaced by anything that the user provides.
21    
22     C !USES: ===============================================================
23     IMPLICIT NONE
24     #include "SIZE.h"
25     #include "GRID.h"
26     #include "DYNVARS.h"
27     #include "EEPARAMS.h"
28     #include "PARAMS.h"
29     #include "PTRACERS_SIZE.h"
30 jmc 1.3 #include "PTRACERS_PARAMS.h"
31     #include "PTRACERS_FIELDS.h"
32 mlosch 1.1 #include "GCHEM.h"
33     #include "GCHEM_FIELDS.h"
34    
35     C !INPUT PARAMETERS: ===================================================
36 jmc 1.4 C myTime :: current time
37     C myIter :: current timestep
38 mlosch 1.1 C myThid :: thread number
39     _RL myTime
40 jmc 1.4 INTEGER myIter, myThid
41     CEOP
42 mlosch 1.1
43     #ifdef ALLOW_GCHEM
44     # ifndef GCHEM_SEPARATE_FORCING
45     C !LOCAL VARIABLES: ====================================================
46     C i,j :: loop indices
47     C iTracer :: ptracer number
48     C bi,bj :: tile indices
49     C k :: vertical level
50     INTEGER i,j
51     INTEGER iTracer
52 jmc 1.4 INTEGER bi,bj,iMin,iMax,jMin,jMax,k
53 mlosch 1.1
54     C gchemTendency is re-initialized here
55     DO iTracer = 1, PTRACERS_numInUse
56     DO bj=myByLo(myThid),myByHi(myThid)
57     DO bi=myBxLo(myThid),myBxHi(myThid)
58 jmc 1.4 DO k = 1, Nr
59     DO j = 1-OLy, sNy+OLy
60     DO i = 1-OLx, sNx+OLx
61     gchemTendency(i,j,k,bi,bj,iTracer) = 0. _d 0
62 mlosch 1.1 ENDDO
63     ENDDO
64 jmc 1.3 ENDDO
65 mlosch 1.1 ENDDO
66     ENDDO
67     ENDDO
68     C
69     C Here is the place for code to compute bio-geochemical
70     C tendency terms (sometimes referred to as source-minus-sink
71     C terms). The tendencies are stored on gchemTendency, as show
72     C in the CFC-example.
73     C
74     C loop over tiles
75     DO bj=myByLo(myThid),myByHi(myThid)
76     DO bi=myBxLo(myThid),myBxHi(myThid)
77     C define horizontal loop ranges
78     iMin = 1
79     iMax = sNx
80     jMin = 1
81     jMax = sNy
82 jmc 1.4 C DO iTracer = 1, PTRACER_numInUse
83     C DO k = 1, Nr
84     C DO j = 1-OLy, sNy+OLy
85     C DO i = 1-OLx, sNx+OLx
86     C gchemTendency(i,j,k,bi,bj,iTracer) = your specific model
87 mlosch 1.1 C ENDDO
88     C ENDDO
89 jmc 1.3 C ENDDO
90 mlosch 1.1 C ENDDO
91 jmc 1.3
92 mlosch 1.1 #ifdef ALLOW_CFC
93     ccccccccccccccccccccccccc
94     c chemical forcing c
95     ccccccccccccccccccccccccc
96     ccccccccccccccccccccccccccc CFC cccccccccccccccccccccccccccccccc
97     c
98 jmc 1.4 k = 1
99     CALL CFC11_FORCING( pTracer (1-OLx,1-OLy,1,bi,bj,1),
100     & gchemTendency(1-OLx,1-OLy,1,bi,bj,1),
101     & bi, bj, iMin, iMax, jMin, jMax,
102 mlosch 1.2 & myIter, myTime, myThid )
103 jmc 1.4 CALL CFC12_FORCING( pTracer (1-OLx,1-OLy,1,bi,bj,2),
104     & gchemTendency(1-OLx,1-OLy,1,bi,bj,2),
105     & bi, bj, iMin, iMax, jMin, jMax,
106 mlosch 1.2 & myIter, myTime, myThid )
107 mlosch 1.1
108     cccccccccccccccccccccccccc END CFC cccccccccccccccccccccccccccccccccc
109     #endif /* ALLOW_CFC */
110     C end of tile-loops
111     ENDDO
112     ENDDO
113     # endif /* GCHEM_SEPARATE_FORCING */
114     #endif /* ALLOW_GCHEM */
115    
116     RETURN
117     END

  ViewVC Help
Powered by ViewVC 1.1.22