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

Annotation of /MITgcm/pkg/cfc/cfc12_forcing.F

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


Revision 1.10 - (hide annotations) (download)
Tue Mar 16 00:14:47 2010 UTC (14 years, 2 months ago) by jmc
Branch: MAIN
CVS Tags: checkpoint64h, checkpoint64a, checkpoint64c, checkpoint64b, checkpoint64e, checkpoint64d, checkpoint64g, checkpoint64f, checkpoint63p, checkpoint63q, checkpoint63r, checkpoint63s, checkpoint63l, checkpoint63m, checkpoint63n, checkpoint63o, checkpoint63h, checkpoint63i, checkpoint63j, checkpoint63k, checkpoint63d, checkpoint63e, checkpoint63f, checkpoint63g, checkpoint63a, checkpoint63b, checkpoint63c, checkpoint64, checkpoint63, checkpoint62g, checkpoint62f, checkpoint62e, checkpoint62d, checkpoint62k, checkpoint62j, checkpoint62i, checkpoint62h, checkpoint62o, checkpoint62n, checkpoint62m, checkpoint62l, checkpoint62s, checkpoint62r, checkpoint62q, checkpoint62p, checkpoint62w, checkpoint62v, checkpoint62u, checkpoint62t, checkpoint62z, checkpoint62y, checkpoint62x
Changes since 1.9: +2 -2 lines
avoid unbalanced quote (single or double) in commented line

1 jmc 1.10 C $Header: /u/gcmpack/MITgcm/pkg/cfc/cfc12_forcing.F,v 1.9 2007/11/05 18:55:44 jmc Exp $
2 jmc 1.8 C $Name: $
3    
4 stephd 1.1 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 jmc 1.8 #define OCMIP_GRAD
14     #undef STEPH_GRAD
15 stephd 1.1
16     CStartOfInterFace
17 jmc 1.9 SUBROUTINE CFC12_FORCING( PTR_CFC12, GCFC12,
18 stephd 1.1 & bi,bj,imin,imax,jmin,jmax,
19     & myIter,myTime,myThid)
20    
21     C /==========================================================\
22     C | SUBROUTINE CFC12_FORCING |
23 jmc 1.9 C | o Calculate the changes to CFC12 through air-sea fluxes |
24 stephd 1.1 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 jmc 1.5 #include "PTRACERS_SIZE.h"
34 jmc 1.9 #include "PTRACERS_PARAMS.h"
35 stephd 1.1
36     C == Routine arguments ==
37     INTEGER myIter
38     _RL myTime
39     INTEGER myThid
40     _RL PTR_CFC12(1-OLx:sNx+OLx,1-OLy:sNy+OLy,Nr)
41     _RL GCFC12(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 SURCFC12(1-OLx:sNx+OLx,1-OLy:sNy+OLy)
48 stephd 1.2 _RL xintp(1-OLy:sNy+OLy)
49 stephd 1.1 INTEGER I,J
50 ce107 1.6 _RL myYear
51     INTEGER lastYear, thisYear
52 stephd 1.1 _RL dtinc, aWght, bWght
53     _RL ACFC12north, ACFC12south
54 ce107 1.6 INTEGER maxYear
55 jmc 1.8 #ifdef STEPH_GRAD
56 stephd 1.1 _RL a1, a2
57 jmc 1.8 #endif
58 stephd 1.2 _RL yNorth, ySouth
59 stephd 1.1
60     DO j=1-OLy,sNy+OLy
61     DO i=1-OLx,sNx+OLx
62     SURCFC12(i,j)=0.d0
63     ENDDO
64     ENDDO
65    
66 jmc 1.8 C find atmospheric CFC
67 jmc 1.5 myYear=float(myIter-PTRACERS_Iter0)*deltaTclock
68 stephd 1.1 & /(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 stephd 1.3 dtinc=myYear-(lastYear-1.d0)
74 stephd 1.1 aWght=0.5d0+dtinc
75     bWght=1.d0-aWght
76     c IF (bi*bj.eq.1)
77 stephd 1.3 c & write(0,*) 'myYear = ',myYear,lastYear,dtinc,aWght
78 stephd 1.1 ACFC12north = ACFC12(lastYear,1)*bWght
79     & + ACFC12(thisYear,1)*aWght
80     ACFC12south = ACFC12(lastYear,2)*bWght
81     & + ACFC12(thisYear,2)*aWght
82     else
83 stephd 1.4 ACFC12north = ACFC12(maxYear,1)
84 stephd 1.7 ACFC12south = ACFC12(maxYear,2)
85 stephd 1.1 endif
86 stephd 1.3 print*,'YEAR,ACFC12north,ACFC12south', myYear,
87     & ACFC12north,ACFC12south
88 jmc 1.8 C provide gradient between N and S values
89    
90 jmc 1.10 C STEPH S INITIAL VERSION
91 stephd 1.2 #ifdef STEPH_GRAD
92 stephd 1.1 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     ATMOSCFC12(i,j,bi,bj)=ACFC12north
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     ATMOSCFC12(i,j,bi,bj)=a1*ACFC12south +
101     & a2*ACFC12north
102     endif
103     if ((j.lt.int(sNy/2)-3.and.j.gt.0).or.j.gt.sNy) then
104     ATMOSCFC12(i,j,bi,bj)=ACFC12south
105     endif
106     ENDDO
107     ENDDO
108 stephd 1.2 #endif
109 jmc 1.8 C OCMIP VERSION
110 stephd 1.2 #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     ATMOSCFC12(i,j,bi,bj)= xintp(j) * ACFC12north
125     & + (1.0 - xintp(j))*ACFC12south
126 stephd 1.1
127 stephd 1.2 ENDDO
128     c print*,'QQ cfc12', j, ATMOSCFC12(1,j,bi,bj)
129     ENDDO
130     #endif
131 jmc 1.8 C cfc12 air-sea interaction
132 stephd 1.1 CALL CFC12_SURFFORCING( PTR_CFC12, SURCFC12,
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     GCFC12(i,j,1)=GCFC12(i,j,1)+SURCFC12(i,j)
139     ENDDO
140     ENDDO
141    
142     #endif
143     #endif
144    
145     RETURN
146     END

  ViewVC Help
Powered by ViewVC 1.1.22