/[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.11 - (show annotations) (download)
Thu Jun 6 15:48:42 2013 UTC (10 years, 11 months ago) by jmc
Branch: MAIN
Changes since 1.10: +16 -16 lines
same time interpolation for atmospheric CFC-11 as for CFC-12

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

  ViewVC Help
Powered by ViewVC 1.1.22