/[MITgcm]/MITgcm/verification/carbon/code_ad_ptracers/ptracers_init.F
ViewVC logotype

Annotation of /MITgcm/verification/carbon/code_ad_ptracers/ptracers_init.F

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


Revision 1.1 - (hide annotations) (download)
Sun Oct 26 01:45:05 2003 UTC (20 years, 7 months ago) by heimbach
Branch: MAIN
CVS Tags: checkpoint54f_post, checkpoint52i_pre, checkpoint53f_post, checkpoint54a_pre, checkpoint53b_pre, checkpoint51q_post, checkpoint52e_post, checkpoint52c_post, checkpoint52j_pre, checkpoint54a_post, checkpoint52l_post, checkpoint52k_post, checkpoint52l_pre, checkpoint52a_pre, checkpoint52b_post, branch-netcdf, checkpoint52e_pre, checkpoint54, checkpoint53b_post, checkpoint51r_post, checkpoint53, checkpoint52, checkpoint52b_pre, checkpoint52n_post, checkpoint54b_post, checkpoint52f_pre, checkpoint51t_post, checkpoint53d_pre, checkpoint52a_post, checkpoint54c_post, checkpoint54d_post, checkpoint52i_post, checkpoint53g_post, checkpoint52f_post, checkpoint52d_post, checkpoint54e_post, checkpoint51p_post, checkpoint52j_post, checkpoint53c_post, checkpoint53d_post, checkpoint51o_post, checkpoint52m_post, checkpoint51u_post, checkpoint52h_pre, checkpoint53a_post, ecco_c52_e35, checkpoint51s_post
Branch point for: netcdf-sm0, branch-nonh
moving and updating code... to code_ad...

1 heimbach 1.1 C $Header: /u/gcmpack/MITgcm/verification/carbon/code_ptracers/ptracers_init.F,v 1.1 2003/06/27 02:11:12 heimbach Exp $
2     C $Name: $
3    
4     #include "PTRACERS_OPTIONS.h"
5     #ifdef ALLOW_GCHEM
6     # include "GCHEM_OPTIONS.h"
7     #endif
8    
9     CBOP
10     C !ROUTINE: PTRACERS_INIT
11    
12     C !INTERFACE: ==========================================================
13     SUBROUTINE PTRACERS_INIT( myThid )
14    
15     C !DESCRIPTION:
16     C Initialize PTRACERS data structures
17    
18     C !USES: ===============================================================
19     IMPLICIT NONE
20     #include "SIZE.h"
21     #include "EEPARAMS.h"
22     #include "PARAMS.h"
23     #include "GRID.h"
24     #include "PTRACERS.h"
25     cswdptr -- add ---
26     #ifdef ALLOW_GCHEM
27     # include "GCHEM.h"
28     #endif
29     cswdptr --- end add --
30    
31    
32     C !INPUT PARAMETERS: ===================================================
33     C myThid :: thread number
34     INTEGER myThid
35    
36     C !OUTPUT PARAMETERS: ==================================================
37     C none
38    
39     #ifdef ALLOW_PTRACERS
40    
41     C !LOCAL VARIABLES: ====================================================
42     C i,j,k,bi,bj,iTracer :: loop indices
43     INTEGER i,j,k,bi,bj,iTracer
44     CHARACTER*(10) suff
45     #ifndef ALLOW_GCHEM
46     INTEGER tIter0
47     PARAMETER ( tIter0 = 0 )
48     #endif
49     CEOP
50    
51     C Loop over tracers
52     DO iTracer = 1, PTRACERS_num
53    
54     C Loop over tiles
55     DO bj = myByLo(myThid), myByHi(myThid)
56     DO bi = myBxLo(myThid), myBxHi(myThid)
57    
58     C Initialize arrays in common blocks :
59     DO k=1,Nr
60     DO j=1-Oly,sNy+OLy
61     DO i=1-Olx,sNx+Olx
62     IF ( K .EQ. 1 .AND. hFacC(I,J,K,bi,bj) .NE. 0 ) THEN
63     pTracer(i,j,k,bi,bj,iTracer) = 1. _d 0
64     ELSE
65     pTracer(i,j,k,bi,bj,iTracer) = 0. _d 0
66     ENDIF
67     gPtr(i,j,k,bi,bj,iTracer) = 0. _d 0
68     gPtrNM1(i,j,k,bi,bj,iTracer) = 0. _d 0
69     ENDDO
70     ENDDO
71     ENDDO
72    
73     #ifdef ALLOW_TIMEAVE
74     C Initialize averages to zero
75     c CALL TIMEAVE_RESET(GM_Kwx_T,Nr, bi,bj,myThid)
76     c CALL TIMEAVE_RESET(GM_Kwy_T,Nr, bi,bj,myThid)
77     c CALL TIMEAVE_RESET(GM_Kwz_T,Nr, bi,bj,myThid)
78     c DO k=1,Nr
79     c GM_TimeAve(k,bi,bj)=0.
80     c ENDDO
81     #endif /* ALLOW_TIMEAVE */
82    
83     C end bi,bj loops
84     ENDDO
85     ENDDO
86    
87     C end of Tracer loop
88     ENDDO
89    
90     C Now read initial conditions and always exchange
91     cswdptr IF (nIter0.EQ.0) THEN
92     cswdptr -- change ---
93     IF (nIter0.EQ.tIter0) THEN
94     cswdptr -- end change ---
95     DO iTracer = 1, PTRACERS_numInUse
96     IF ( PTRACERS_initialFile(iTracer) .NE. ' ' ) THEN
97     _BEGIN_MASTER( myThid )
98     CALL READ_FLD_XYZ_RL(PTRACERS_initialFile(iTracer),' ',
99     & pTracer(1-Olx,1-Oly,1,1,1,iTracer) ,0,myThid)
100     _END_MASTER(myThid)
101     cswdptr -- add ---
102     ELSE
103     #ifdef ALLOW_GCHEM
104     DO bj=myByLo(myThid),myByHi(myThid)
105     DO bi=myBxLo(myThid),myBxHi(myThid)
106     DO j=1-Oly,sNy+Oly
107     DO i=1-Olx,sNx+Olx
108     DO k=1,nR
109     pTracer(i,j,k,bi,bj,iTracer)=0.d0
110     cswddic QQQ
111     if (iTracer.eq.1)
112     & pTracer(i,j,k,bi,bj,iTracer)=2.23d0 !dic mol/m3
113     if (iTracer.eq.2)
114     & pTracer(i,j,k,bi,bj,iTracer)=2.37d0 !alk moleq/m3
115     if (iTracer.eq.3)
116     & pTracer(i,j,k,bi,bj,iTracer)=2.17d-3 !po4 mol/m3
117     if (iTracer.eq.4)
118     & pTracer(i,j,k,bi,bj,iTracer)=1.d-5 !dop mol/m3
119     if (iTracer.eq.5)
120     & pTracer(i,j,k,bi,bj,iTracer)=0.17d0 !o2 mol/m3
121     if (iTracer.eq.6)
122     & pTracer(i,j,k,bi,bj,iTracer)=4.d-7 !fe mol/m3
123     enddo
124     ENDDO
125     ENDDO
126     ENDDO
127     ENDDO
128     #endif
129     cswdptr -- end add ---
130     ENDIF
131     _EXCH_XYZ_R8(pTracer(1-Olx,1-Oly,1,1,1,iTracer),myThid)
132     ENDDO
133     ENDIF
134    
135     C Read from a pickup file if nIter0
136     cswdptr IF (nIter0.NE.0) THEN
137     cswdptr -- change --
138     IF (nIter0.GT.tIter0) THEN
139     C-- Suffix for pickup files
140     IF (pickupSuff.EQ.' ') THEN
141     WRITE(suff,'(I10.10)') nIter0
142     ELSE
143     WRITE(suff,'(A10)') pickupSuff
144     ENDIF
145     CALL PTRACERS_READ_CHECKPOINT( nIter0,suff,myThid )
146     ENDIF
147    
148     #endif /* ALLOW_PTRACERS */
149    
150     RETURN
151     END

  ViewVC Help
Powered by ViewVC 1.1.22