/[MITgcm]/MITgcm/pkg/cfc/cfc11_forcing.F
ViewVC logotype

Annotation of /MITgcm/pkg/cfc/cfc11_forcing.F

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


Revision 1.4 - (hide annotations) (download)
Thu May 5 17:20:33 2005 UTC (19 years, 1 month ago) by stephd
Branch: MAIN
CVS Tags: checkpoint57h_pre
Changes since 1.3: +2 -2 lines
o change so that after last year of data, atmos cfc stays same

1 stephd 1.1 C modified for external_forcing_DIC.F August 1999
2     CCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCC
3     c
4     c modified swd Oct 01 and Feb 02, for use as package for c40_patch1
5     c modified to use with c44 and ptracers: swd May 2002
6     c modified to have carbonate and biological influences: swd June 2002
7     c modified for cfc: swd Sep 2003
8     C
9    
10     #include "CPP_OPTIONS.h"
11     #include "GCHEM_OPTIONS.h"
12    
13     CStartOfInterFace
14     SUBROUTINE CFC11_FORCING( PTR_CFC11, GCFC11,
15     & bi,bj,imin,imax,jmin,jmax,
16     & myIter,myTime,myThid)
17    
18     C /==========================================================\
19     C | SUBROUTINE CFC11_FORCING |
20     C | o Calculate the changes to CFC11 through air-sea fluxes |
21     C |==========================================================|
22     IMPLICIT NONE
23    
24     C == GLobal variables ==
25     #include "SIZE.h"
26     #include "DYNVARS.h"
27     #include "EEPARAMS.h"
28     #include "PARAMS.h"
29     #include "GRID.h"
30     #include "CFC.h"
31 stephd 1.3 #include "GCHEM.h"
32 stephd 1.1
33     C == Routine arguments ==
34     INTEGER myIter
35     _RL myTime
36     INTEGER myThid
37     _RL PTR_CFC11(1-OLx:sNx+OLx,1-OLy:sNy+OLy,Nr)
38     _RL GCFC11(1-OLx:sNx+OLx,1-OLy:sNy+OLy,Nr)
39     INTEGER bi, bj, imin, imax, jmin, jmax
40    
41     #ifdef ALLOW_PTRACERS
42     #ifdef ALLOW_CFC
43     C == Local variables ==
44     _RL SURCFC11(1-OLx:sNx+OLx,1-OLy:sNy+OLy)
45 stephd 1.2 _RL xintp(1-OLy:sNy+OLy)
46 stephd 1.1 INTEGER I,J
47     INTEGER myYear, lastYear, thisYear
48     _RL dtinc, aWght, bWght
49     _RL ACFC11north, ACFC11south
50     _RL maxYear
51     _RL a1, a2
52 stephd 1.2 _RL yNorth, ySouth
53    
54 stephd 1.1
55     DO j=1-OLy,sNy+OLy
56     DO i=1-OLx,sNx+OLx
57     SURCFC11(i,j)=0.d0
58     ENDDO
59     ENDDO
60    
61     c find atmospheric CFC
62 stephd 1.3 myYear=float(myIter-tIter0)*deltaTclock
63 stephd 1.1 & /(360.d0*24.d0*3600.d0)
64     lastYear=1+int(myYear+0.5)
65     thisYear=lastYear+1
66     maxYear=cfc_yearend-cfc_yearbeg
67     if (thisYear.lt.maxYear) then
68     dtinc=myYear-float(lastYear-1)
69     aWght=0.5d0+dtinc
70     bWght=1.d0-aWght
71     c IF (bi*bj.eq.1)
72     c &write(0,*) 'myYear = ',myYear,lastYear,dtinc,aWght
73     ACFC11north = ACFC11(lastYear,1)*bWght
74     & + ACFC11(thisYear,1)*aWght
75     ACFC11south = ACFC11(lastYear,2)*bWght
76     & + ACFC11(thisYear,2)*aWght
77     else
78 stephd 1.4 ACFC11north = ACFC11(maxYear,1)
79     ACFC11south = ACFC11(maxYear,1)
80 stephd 1.1 endif
81     c print*,'ACFC11north,ACFC11south', ACFC11north,ACFC11south,
82     c & lastYear,thisYear
83 stephd 1.2 c provide gradient between N and S values
84     #define OCMIP_GRAD
85     #undef STEPH_GRAD
86     c STEPH'S INITIAL VERSION
87     #ifdef STEPH_GRAD
88 stephd 1.1 DO j=1-OLy,sNy+OLy
89     DO i=1-OLx,sNx+OLx
90     if ((j.gt.int(sNy/2)+3.and.j.le.sNy).or.j.lt.1) then
91     ATMOSCFC11(i,j,bi,bj)=ACFC11north
92     endif
93     if (j.ge.int(sNy/2)-3.and.j.le.int(sNy/2)+3) then
94     a1=(float(j-int(sNy/2)+3)+.5)/7
95     a2=1.d0-a1
96     ATMOSCFC11(i,j,bi,bj)=a1*ACFC11south +
97     & a2*ACFC11north
98     endif
99     if ((j.lt.int(sNy/2)-3.and.j.gt.0).or.j.gt.sNy) then
100     ATMOSCFC11(i,j,bi,bj)=ACFC11south
101     endif
102     ENDDO
103     ENDDO
104 stephd 1.2 #endif
105     c OCMIP VERSION
106     #ifdef OCMIP_GRAD
107     yNorth = 10.0
108     ySouth = -10.0
109     DO j=1-OLy,sNy+OLy
110     i=1
111     IF(yC(i,j,bi,bj) .GE. yNorth) THEN
112     xintp(j) = 1.0
113     ELSE IF(yC(i,j,bi,bj) .LE. ySouth) THEN
114     xintp(j) = 0.0
115     ELSE
116     xintp(j) = (yC(i,j,bi,bj) - ySouth)/
117     & (yNorth - ySouth)
118     ENDIF
119     DO i=1-OLx,sNx+OLx
120     ATMOSCFC11(i,j,bi,bj)= xintp(j) * ACFC11north
121     & + (1.0 - xintp(j))*ACFC11south
122 stephd 1.1
123 stephd 1.2 ENDDO
124     c print*,'QQ cfc11', j, ATMOSCFC11(1,j,bi,bj)
125     ENDDO
126     #endif
127 stephd 1.1 c cfc11 air-sea interaction
128     CALL CFC11_SURFFORCING( PTR_CFC11, SURCFC11,
129     & bi,bj,imin,imax,jmin,jmax,
130     & myIter,myTime,myThid)
131    
132     DO j=1-OLy,sNy+OLy
133     DO i=1-OLx,sNx+OLx
134     GCFC11(i,j,1)=GCFC11(i,j,1)+SURCFC11(i,j)
135     ENDDO
136     ENDDO
137    
138     #endif
139     #endif
140    
141     c
142     RETURN
143     END

  ViewVC Help
Powered by ViewVC 1.1.22