/[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.2 - (show annotations) (download)
Tue May 3 17:02:26 2005 UTC (19 years, 1 month ago) by stephd
Branch: MAIN
Changes since 1.1: +30 -0 lines
o add N-S gradient of atmospheric CFC values according to OCMIP specifications

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

  ViewVC Help
Powered by ViewVC 1.1.22