/[MITgcm]/MITgcm_contrib/ocean_inversion_project/code/ptracers_init.F
ViewVC logotype

Diff of /MITgcm_contrib/ocean_inversion_project/code/ptracers_init.F

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

revision 1.1 by dimitri, Thu Sep 18 02:33:38 2003 UTC revision 1.5 by dimitri, Tue Oct 21 06:21:52 2003 UTC
# Line 2  C $Header$ Line 2  C $Header$
2  C $Name$  C $Name$
3    
4  #include "PTRACERS_OPTIONS.h"  #include "PTRACERS_OPTIONS.h"
 #ifdef ALLOW_GCHEM  
 # include "GCHEM_OPTIONS.h"  
 #endif  
5    
6  CBOP  CBOP
7  C !ROUTINE: PTRACERS_INIT  C !ROUTINE: PTRACERS_INIT
# Line 14  C !INTERFACE: ========================== Line 11  C !INTERFACE: ==========================
11    
12  C !DESCRIPTION:  C !DESCRIPTION:
13  C     Initialize PTRACERS data structures  C     Initialize PTRACERS data structures
14  cdm   This file is customized to compute CO2 perturbations from 30 ocean  C     This file is customized to compute CO2 perturbations from
15  cdm   regions for Gruber's ocean inversion project.  C     30 ocean regions for Gruber's ocean inversion project.
16    
17  C !USES: ===============================================================  C !USES: ===============================================================
18        IMPLICIT NONE        IMPLICIT NONE
# Line 24  C !USES: =============================== Line 21  C !USES: ===============================
21  #include "PARAMS.h"  #include "PARAMS.h"
22  #include "GRID.h"  #include "GRID.h"
23  #include "PTRACERS.h"  #include "PTRACERS.h"
 cswdptr -- add ---  
 #ifdef ALLOW_GCHEM  
 # include "GCHEM.h"  
 #endif  
 cswdptr --- end add --  
24    
25    
26  C !INPUT PARAMETERS: ===================================================  C !INPUT PARAMETERS: ===================================================
# Line 42  C  none Line 34  C  none
34    
35  C !LOCAL VARIABLES: ====================================================  C !LOCAL VARIABLES: ====================================================
36  C  i,j,k,bi,bj,iTracer  :: loop indices  C  i,j,k,bi,bj,iTracer  :: loop indices
37        INTEGER i,j,k,bi,bj,iTracer        INTEGER i,j,k,bi,bj,iTracer,iMonth,iUnit,iRec
38        CHARACTER*(10) suff        CHARACTER*(10) suff
39  #ifndef ALLOW_GCHEM        _RL SumPtracer
40        INTEGER tIter0  
41        PARAMETER ( tIter0 = 0 )  #ifdef OCEAN_INVERSION_NETCDF
42  #endif        Real lon(Nx,Ny),bounds_lon(Nx,Ny,2,2)
43          Real lat(Nx,Ny),bounds_lat(Nx,Ny,2,2)
44          Real depth(Nr),bounds_depth(Nr,2)
45          Real MASK(Nx,Ny,Nr)
46          Real AREA(Nx,Ny)
47          Real BATHY(Nx,Ny)
48          Real REGION_MASK(Nx,Ny,PTRACERS_num)
49          Real REGION_AREA(PTRACERS_num)
50    #endif /* OCEAN_INVERSION_NETCDF */
51    
52  CEOP  CEOP
53                    
54  C Loop over tracers  C Loop over tracers
55        DO iTracer = 1, PTRACERS_num        DO iTracer = 1, PTRACERS_num
56    
57  C Loop over tiles  C Loop over tiles
58        DO bj = myByLo(myThid), myByHi(myThid)         DO bj = myByLo(myThid), myByHi(myThid)
59         DO bi = myBxLo(myThid), myBxHi(myThid)          DO bi = myBxLo(myThid), myBxHi(myThid)
60    
61  C Initialize arrays in common blocks :  C Initialize arrays in common blocks :
62          DO k=1,Nr           DO k=1,Nr
63              DO j=1-Oly,sNy+OLy
64               DO i=1-Olx,sNx+Olx
65                pTracer(i,j,k,bi,bj,iTracer) = 0. _d 0
66                gPtr(i,j,k,bi,bj,iTracer)    = 0. _d 0
67                gPtrNM1(i,j,k,bi,bj,iTracer) = 0. _d 0
68               ENDDO
69              ENDDO
70             ENDDO
71           DO j=1-Oly,sNy+OLy           DO j=1-Oly,sNy+OLy
72            DO i=1-Olx,sNx+Olx            DO i=1-Olx,sNx+Olx
73             pTracer(i,j,k,bi,bj,iTracer) = 0. _d 0             surfaceTendencyPtr(i,j,bi,bj,iTracer) = 0. _d 0
            gPtr(i,j,k,bi,bj,iTracer)    = 0. _d 0  
            gPtrNM1(i,j,k,bi,bj,iTracer) = 0. _d 0  
74            ENDDO            ENDDO
75           ENDDO           ENDDO
         ENDDO  
76    
77  C end bi,bj loops  C end bi,bj loops
78            ENDDO
79         ENDDO         ENDDO
       ENDDO  
80    
81  C end of Tracer loop  C end of Tracer loop
82        ENDDO        ENDDO
83    
84  C Read from a pickup file if nIter0  C Read from a pickup file if nIter0 is not zero
85  cswdptr IF (nIter0.NE.0) THEN        IF (nIter0.NE.0) THEN
 cswdptr -- change --  
       IF (nIter0.GT.tIter0) THEN  
86  C--     Suffix for pickup files  C--     Suffix for pickup files
87         IF (pickupSuff.EQ.' ') THEN         IF (pickupSuff.EQ.' ') THEN
88           WRITE(suff,'(I10.10)') nIter0           WRITE(suff,'(I10.10)') nIter0
# Line 88  C--     Suffix for pickup files Line 92  C--     Suffix for pickup files
92         CALL PTRACERS_READ_CHECKPOINT( nIter0,myThid )         CALL PTRACERS_READ_CHECKPOINT( nIter0,myThid )
93        ENDIF        ENDIF
94    
95  cdm   Initialize pTracerMasks  C     Initialize pTracerMasks
96        CALL PTRACERS_READ_MASK ( mythid )        CALL PTRACERS_READ_MASK ( mythid )
97    
98    C     Initialize pTracerTakahashi
99          CALL PTRACERS_READ_Takahashi ( mythid )
100    
101    C     Normalize pTracerTakahashi so that 1e18 mol/yr is released
102    C     from each model region defined in pTracerMasks.
103    C     It is assumed that each year is 365.25 days (31557600 s)
104    C     long and that each month is 2629800 s.
105    
106          DO iTracer = 1, PTRACERS_num
107           SumPtracer = 0.
108           DO bj = myByLo(myThid), myByHi(myThid)
109            DO bi = myBxLo(myThid), myBxHi(myThid)
110             DO j=1,sNy
111              DO i=1,sNx
112               DO iMonth=1,12
113                SumPtracer = SumPtracer + 2629800. * rA(I,J,bi,bj) *
114         &             pTracerMasks    (I,J,iTracer,bi,bj) *
115         &             pTracerTakahashi(I,J,iMonth ,bi,bj)
116               ENDDO
117              ENDDO
118             ENDDO
119            ENDDO
120           ENDDO
121           _GLOBAL_SUM_R8( SumPtracer, myThid )
122           DO bj = myByLo(myThid), myByHi(myThid)
123            DO bi = myBxLo(myThid), myBxHi(myThid)
124             DO j=1,sNy
125              DO i=1,sNx
126               DO iMonth=1,12
127                IF ( pTracerMasks(I,J,iTracer,bi,bj) .eq. 1. )
128         &             pTracerTakahashi(I,J,iMonth ,bi,bj) = 1.e18 *
129         &             pTracerTakahashi(I,J,iMonth ,bi,bj) / SumPtracer
130               ENDDO
131              ENDDO
132             ENDDO
133            ENDDO
134           ENDDO
135          ENDDO
136    
137    #ifdef OCEAN_INVERSION_PROJECT_TIME_DEPENDENT
138    C     Initialize atmospheric CO2 array
139          call mdsfindunit( iUnit, mythid)
140          open(iUnit,file='splco2_cis92a.dat',status='old',form="FORMATTED")
141          do iRec=1,pTracerAtm_Nrec
142             read(iUnit,*) pTracerAtmYear(iRec), pTracerAtmCO2(iRec)
143    cdb      print*, '###', iRec, pTracerAtmYear(iRec), pTracerAtmCO2(iRec)
144          enddo
145          close(iUnit)
146    #endif /* OCEAN_INVERSION_PROJECT_TIME_DEPENDENT */
147    
148    #ifdef OCEAN_INVERSION_NETCDF
149          DO j=1,Ny
150             DO i=1,Nx
151                lon           (i,j        ) = 0.
152                bounds_lon    (i,j,1,1    ) = 0.
153                bounds_lon    (i,j,1,2    ) = 0.
154                bounds_lon    (i,j,2,1    ) = 0.
155                bounds_lon    (i,j,2,2    ) = 0.
156                lat           (i,j        ) = 0.
157                bounds_lat    (i,j,1,1    ) = 0.
158                bounds_lat    (i,j,1,2    ) = 0.
159                bounds_lat    (i,j,2,1    ) = 0.
160                bounds_lat    (i,j,2,2    ) = 0.
161                AREA          (i,j        ) = 0.
162                BATHY         (i,j        ) = 0.
163                DO k=1,Nr
164                   MASK       (i,j,k      ) = 0.
165                ENDDO
166                DO iTracer = 1, PTRACERS_num
167                   REGION_MASK(i,j,iTracer) = 0.
168                ENDDO
169             ENDDO
170          ENDDO
171          DO k=1,Nr
172             depth            (    k      ) = 0.
173             bounds_depth     (    k,1    ) = 0.
174             bounds_depth     (    k,2    ) = 0.
175          ENDDO
176          DO iTracer = 1, PTRACERS_num
177             REGION_AREA      (      iTracer) = 0.
178          ENDDO
179          call WRITE_NC_MaskAreaBathy(
180         &     'ECCO','MIT GCM Release 1',
181         &     Nx,Ny,Nr,PTRACERS_num,
182         &     lon,bounds_lon,lat,bounds_lat,depth,bounds_depth,
183         &     MASK,AREA,BATHY,REGION_MASK,REGION_AREA)
184    #endif /* OCEAN_INVERSION_NETCDF */
185          stop
186  #endif /* ALLOW_PTRACERS */  #endif /* ALLOW_PTRACERS */
187    
188        RETURN        RETURN

Legend:
Removed from v.1.1  
changed lines
  Added in v.1.5

  ViewVC Help
Powered by ViewVC 1.1.22