/[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.8 - (show annotations) (download)
Sun Aug 6 01:29:12 2006 UTC (17 years, 10 months ago) by jmc
Branch: MAIN
CVS Tags: checkpoint58u_post, checkpoint58w_post, checkpoint58r_post, checkpoint58n_post, checkpoint58x_post, checkpoint58t_post, checkpoint58q_post, checkpoint59e, checkpoint59d, checkpoint59g, checkpoint59f, checkpoint59a, checkpoint59c, checkpoint59b, checkpoint59i, checkpoint59h, checkpoint59, checkpoint58o_post, checkpoint58y_post, checkpoint58v_post, checkpoint58s_post, checkpoint58p_post
Changes since 1.7: +13 -10 lines
add "_d 0" ; remove unneeded header files ; add BARRIER after initialisation

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

  ViewVC Help
Powered by ViewVC 1.1.22