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

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

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


Revision 1.7 - (show annotations) (download)
Tue Dec 6 17:01:06 2005 UTC (18 years, 6 months ago) by stephd
Branch: MAIN
CVS Tags: checkpoint58l_post, checkpoint58e_post, checkpoint57y_post, checkpoint58h_post, checkpoint57y_pre, checkpoint58j_post, checkpoint58, checkpoint58f_post, checkpoint58d_post, checkpoint58c_post, checkpoint58a_post, checkpoint58i_post, checkpoint58g_post, checkpoint57z_post, checkpoint58k_post, checkpoint58b_post, checkpoint58m_post
Changes since 1.6: +1 -1 lines
o last year had wrong N/S values; also was one year too short

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

  ViewVC Help
Powered by ViewVC 1.1.22