/[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.12 - (show annotations) (download)
Fri Jun 7 15:43:31 2013 UTC (10 years, 11 months ago) by jmc
Branch: MAIN
Changes since 1.11: +41 -46 lines
- fix interpolation of atmphspheric CFC between Sorthern and Northern
  hemisphere value
notes: file "cfc11_forcing.F" is derived from cfc12_forcing.F using
 the sed commands:
> s/CFC12/CFC11/g
> s/cfc12/cfc11/g

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
11 #include "GCHEM_OPTIONS.h"
12 #define OCMIP_GRAD
13 #undef STEPH_GRAD
14
15 CStartOfInterFace
16 SUBROUTINE CFC11_FORCING(
17 I pTr_CFC11,
18 U gCFC11,
19 I bi, bj, imin, imax, jmin, jmax,
20 I myIter, myTime, myThid )
21
22 C *==========================================================*
23 C | SUBROUTINE CFC11_FORCING
24 C | o Calculate the changes to CFC11 through air-sea fluxes
25 C *==========================================================*
26 IMPLICIT NONE
27
28 C == GLobal variables ==
29 #include "SIZE.h"
30 #include "EEPARAMS.h"
31 #include "PARAMS.h"
32 #include "GRID.h"
33 #include "CFC.h"
34 #include "PTRACERS_SIZE.h"
35 #include "PTRACERS_PARAMS.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 gSurfCFC11(1-OLx:sNx+OLx,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 _RL recip_dLat, weight
60
61 DO j=1-OLy,sNy+OLy
62 DO i=1-OLx,sNx+OLx
63 gSurfCFC11(i,j) = 0. _d 0
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-(lastYear-1.d0)
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*,'YEAR,ACFC11north,ACFC11south', myYear,
88 c & ACFC11north,ACFC11south
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 recip_dLat = 1. _d 0 / ( yNorth - ySouth )
115 DO j=1-OLy,sNy+OLy
116 DO i=1-OLx,sNx+OLx
117 weight = ( yC(i,j,bi,bj) - ySouth )*recip_dLat
118 weight = MAX( zeroRL, MIN( oneRL, weight ) )
119 ATMOSCFC11(i,j,bi,bj)= weight * ACFC11north
120 & + ( oneRL - weight )*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, gSurfCFC11,
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) + gSurfCFC11(i,j)
134 ENDDO
135 ENDDO
136
137 #endif /* ALLOW_CFC */
138 #endif /* ALLOW_PTRACERS */
139
140 RETURN
141 END

  ViewVC Help
Powered by ViewVC 1.1.22