/[MITgcm]/MITgcm_contrib/ocean_inversion_project/code_bombC14/ini_tr1.F
ViewVC logotype

Annotation of /MITgcm_contrib/ocean_inversion_project/code_bombC14/ini_tr1.F

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


Revision 1.1 - (hide annotations) (download)
Thu May 25 06:43:08 2006 UTC (19 years, 2 months ago) by dimitri
Branch: MAIN
Configuring bomb C14 experiment with iter69 output based
on branch release1_50yr and verification/global_with_CFC11

1 dimitri 1.1 C $Header: /u/gcmpack/MITgcm/verification/global_with_CFC11/code1x1/Attic/ini_tr1.F,v 1.1.2.2 2005/08/25 18:21:17 dimitri Exp $
2     C $Name: release1_50yr $
3    
4     #include "CPP_OPTIONS.h"
5    
6     CBOP
7     C !ROUTINE: INI_TR1
8     C !INTERFACE:
9     SUBROUTINE INI_TR1( myThid )
10     C !DESCRIPTION: \bv
11     C *==========================================================*
12     C | SUBROUTINE INI_TR1
13     C | o Set initial tracer 1 distribution.
14     C *==========================================================*
15     C | Passive tracers 1-N can be initialised so as to dye fluid.
16     C | This routine is hardcoded for Nir's bomb C14 experiment.
17     C *==========================================================*
18     C \ev
19    
20     C !USES:
21     IMPLICIT NONE
22     C === Global variables ===
23     #include "SIZE.h"
24     #include "EEPARAMS.h"
25     #include "PARAMS.h"
26     #include "GRID.h"
27     #include "DYNVARS.h"
28     #ifdef ALLOW_PASSIVE_TRACER
29     #include "TR1.h"
30     #endif
31    
32     C !INPUT/OUTPUT PARAMETERS:
33     C == Routine arguments ==
34     C myThid - Number of this instance of INI_TR1
35     INTEGER myThid
36    
37     #ifdef ALLOW_PASSIVE_TRACER
38    
39     C !LOCAL VARIABLES:
40     C == Local variables ==
41     C iC, jC - Center of domain
42     C iD, jD - Disitance from domain center.
43     C rad - Radius of initial patch
44     C rD - Radial displacement of point I,J
45     C iG, jG - Global coordinate index
46     C bi,bj - Loop counters
47     C I,J,K
48     INTEGER iC, jC, iD, jD
49     INTEGER iG, jG
50     INTEGER bi, bj
51     INTEGER I, J, K, localWarnings
52     _RL rad, rD
53     CHARACTER*(MAX_LEN_MBUF) msgBuf
54     CEOP
55    
56     _BARRIER
57    
58     C-- Initialise tracer to inline.
59     DO bj = myByLo(myThid), myByHi(myThid)
60     DO bi = myBxLo(myThid), myBxHi(myThid)
61     DO K=1,Nr
62     DO J=1,sNy
63     DO I=1,sNx
64     tr1(I,J,K,bi,bj) = 0. _d 0
65     ENDDO
66     ENDDO
67     ENDDO
68     ENDDO
69     ENDDO
70     C Set initial tendency terms
71     localWarnings=0
72     DO bj = myByLo(myThid), myByHi(myThid)
73     DO bi = myBxLo(myThid), myBxHi(myThid)
74     DO K=1,Nr
75     DO J=1,sNy
76     DO I=1,sNx
77     gtr1 (I,J,K,bi,bj) = 0. _d 0
78     gtr1NM1(I,J,K,bi,bj) = 0. _d 0
79     ENDDO
80     ENDDO
81     ENDDO
82     ENDDO
83     ENDDO
84     C
85     _EXCH_XYZ_R8(tr1 , myThid )
86     _EXCH_XYZ_R8(gtr1 , myThid )
87     _EXCH_XYZ_R8(gtr1NM1 , myThid )
88    
89     C-- Input file names
90     FiceFile = 'FICE'
91     XkwFile = 'XKW'
92     PatmFile = 'PATM'
93     SssFile = 'WOA01_S'
94     SstFile = 'WOA01_T'
95     SurfDicPreindFile = 'surf_dic_preind'
96     SurfDicAnthroFile = 'surf_dic_anthro'
97     SurfNatD14CFile = 'surface_naturalD14C'
98    
99     C-- Compute numbers needed to determine DC14
100     CALL read_dc14
101    
102     #define OCMIP_USE_INTERP
103     C-- OCMIP_USE_INTERP option is useful for high-resolution integrations.
104     C For low-resolution, less that 1-deg, it's best to generate files
105     C separately because of sea-ice fraction.
106     C Caution: OCMIP_USE_INTERP as used is not thread-safe.
107     #ifdef OCMIP_USE_INTERP
108     CALL EXF_INTERP( SurfDicPreindFile,readBinaryPrec,
109     & SurfDicPreind,1,
110     & xC,yC,lon0,lon_inc,lat0,lat_inc,nlon,nlat,1,mythid )
111     CALL EXF_INTERP( SurfDicAnthroFile,readBinaryPrec,
112     & SurfDicAnthro,1,
113     & xC,yC,lon0,lon_inc,lat0,lat_inc,nlon,nlat,1,mythid )
114     CALL EXF_INTERP( SurfNatD14CFile,readBinaryPrec,
115     & SurfNatD14C,1,
116     & xC,yC,lon0,lon_inc,lat0,lat_inc,nlon,nlat,1,mythid )
117     #else
118     CALL MDSREADFIELD ( SurfDicPreindFile, readBinaryPrec,
119     & 'RS', 1, SurfDicPreind, 1,, myThid )
120     CALL MDSREADFIELD ( SurfDicAnthroFile, readBinaryPrec,
121     & 'RS', 1, SurfDicAnthro, 1,, myThid )
122     CALL MDSREADFIELD ( SurfNatD14CFile, readBinaryPrec,
123     & 'RS', 1, SurfNatD14C, 1,, myThid )
124     #endif
125    
126     #endif /* ALLOW_PASSIVE_TRACER */
127    
128     RETURN
129     END
130    
131     C====================================================================
132    
133     SUBROUTINE read_dc14
134    
135     C --------------------------------------------------------------------
136     C Reads temporal history of atmospheric DC14 in permil
137     C
138     C DC14_atm_year = year of measurement (mid-year)
139     C DC14_atm_n = DC14 in northern hemisphere
140     C DC14_atm_eq = DC14 at equator
141     C DC14_atm_s = DC14 in southern hemisphere
142     C --------------------------------------------------------------------
143    
144     IMPLICIT NONE
145     #include "TR1.h"
146    
147     INTEGER n, iu
148     PARAMETER (iu=10)
149    
150     CHARACTER*80 filen
151     C
152     C OPEN FILE
153     C ---------
154     filen='DC14_atm'
155     OPEN(UNIT=iu,FILE=filen,STATUS='old')
156     C
157     C READ FILE
158     C ---------
159     DO n = 1, 240
160     READ(iu,*)
161     + DC14_atm_year(n), DC14_atm_n(n),
162     + DC14_atm_eq (n), DC14_atm_s(n)
163     C WRITE(6,100)
164     C + DC14_atm_year(n), DC14_atm_n(n),
165     C + DC14_atm_eq (n), DC14_atm_s(n)
166     END DO
167    
168     100 FORMAT(f7.2, 4f8.2)
169    
170     RETURN
171     END

  ViewVC Help
Powered by ViewVC 1.1.22