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

Diff of /MITgcm/pkg/cfc/cfc11_forcing.F

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

revision 1.2 by stephd, Tue May 3 17:02:26 2005 UTC revision 1.11 by jmc, Thu Jun 6 15:48:42 2013 UTC
# Line 1  Line 1 
1    C $Header$
2    C $Name$
3    
4  C modified for external_forcing_DIC.F  August 1999  C modified for external_forcing_DIC.F  August 1999
 CCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCC  
5  c  c
6  c modified swd Oct 01 and Feb 02, for use as package for c40_patch1  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  c modified to use with c44 and ptracers: swd May 2002
# Line 7  c modified to have carbonate and biologi Line 9  c modified to have carbonate and biologi
9  c modified for cfc: swd Sep 2003  c modified for cfc: swd Sep 2003
10  C  C
11    
 #include "CPP_OPTIONS.h"  
12  #include "GCHEM_OPTIONS.h"  #include "GCHEM_OPTIONS.h"
13    #define OCMIP_GRAD
14    #undef STEPH_GRAD
15    
16  CStartOfInterFace  CStartOfInterFace
17        SUBROUTINE CFC11_FORCING( PTR_CFC11, GCFC11,        SUBROUTINE CFC11_FORCING( PTR_CFC11, GCFC11,
18       &                            bi,bj,imin,imax,jmin,jmax,       &                            bi,bj,imin,imax,jmin,jmax,
19       &                             myIter,myTime,myThid)       &                             myIter,myTime,myThid)
20    
21  C     /==========================================================\  C     /==========================================================\
22  C     | SUBROUTINE CFC11_FORCING                                   |  C     | SUBROUTINE CFC11_FORCING                                   |
23  C     | o Calculate the changes to CFC11 through air-sea  fluxes   |    C     | o Calculate the changes to CFC11 through air-sea  fluxes   |
24  C     |==========================================================|  C     |==========================================================|
25        IMPLICIT NONE        IMPLICIT NONE
26    
27  C     == GLobal variables ==  C     == GLobal variables ==
28  #include "SIZE.h"  #include "SIZE.h"
 #include "DYNVARS.h"  
29  #include "EEPARAMS.h"  #include "EEPARAMS.h"
30  #include "PARAMS.h"  #include "PARAMS.h"
31  #include "GRID.h"  #include "GRID.h"
32  #include "CFC.h"  #include "CFC.h"
33    #include "PTRACERS_SIZE.h"
34    #include "PTRACERS_PARAMS.h"
35    
36  C     == Routine arguments ==  C     == Routine arguments ==
37        INTEGER myIter        INTEGER myIter
# Line 43  C     == Local variables == Line 47  C     == Local variables ==
47        _RL  SURCFC11(1-OLx:sNx+OLx,1-OLy:sNy+OLy)        _RL  SURCFC11(1-OLx:sNx+OLx,1-OLy:sNy+OLy)
48        _RL  xintp(1-OLy:sNy+OLy)        _RL  xintp(1-OLy:sNy+OLy)
49         INTEGER I,J         INTEGER I,J
50         INTEGER myYear, lastYear, thisYear         _RL myYear
51           INTEGER lastYear, thisYear
52         _RL dtinc, aWght, bWght         _RL dtinc, aWght, bWght
53         _RL ACFC11north, ACFC11south         _RL ACFC11north, ACFC11south
54         _RL maxYear         INTEGER maxYear
55    #ifdef STEPH_GRAD
56         _RL a1, a2         _RL a1, a2
57    #endif
58         _RL yNorth, ySouth         _RL yNorth, ySouth
         
59    
60           DO j=1-OLy,sNy+OLy           DO j=1-OLy,sNy+OLy
61            DO i=1-OLx,sNx+OLx            DO i=1-OLx,sNx+OLx
# Line 57  C     == Local variables == Line 63  C     == Local variables ==
63            ENDDO            ENDDO
64           ENDDO           ENDDO
65    
66  c find atmospheric CFC  C find atmospheric CFC
67         myYear=float(myIter-nIter0)*deltaTclock         myYear=float(myIter-PTRACERS_Iter0)*deltaTclock
68       &                       /(360.d0*24.d0*3600.d0)       &                       /(360.d0*24.d0*3600.d0)
69         lastYear=1+int(myYear+0.5)         lastYear=1+int(myYear+0.5)
70         thisYear=lastYear+1         thisYear=lastYear+1
71         maxYear=cfc_yearend-cfc_yearbeg         maxYear=cfc_yearend-cfc_yearbeg
72         if (thisYear.lt.maxYear) then         if (thisYear.lt.maxYear) then
73           dtinc=myYear-float(lastYear-1)           dtinc=myYear-(lastYear-1.d0)
74           aWght=0.5d0+dtinc           aWght=0.5d0+dtinc
75           bWght=1.d0-aWght           bWght=1.d0-aWght
76  c        IF (bi*bj.eq.1)  c        IF (bi*bj.eq.1)
77  c       &write(0,*) 'myYear = ',myYear,lastYear,dtinc,aWght  c    &      write(0,*) 'myYear = ',myYear,lastYear,dtinc,aWght
78           ACFC11north = ACFC11(lastYear,1)*bWght           ACFC11north = ACFC11(lastYear,1)*bWght
79       &                + ACFC11(thisYear,1)*aWght       &                + ACFC11(thisYear,1)*aWght
80           ACFC11south = ACFC11(lastYear,2)*bWght           ACFC11south = ACFC11(lastYear,2)*bWght
81       &                + ACFC11(thisYear,2)*aWght       &                + ACFC11(thisYear,2)*aWght
82         else         else
83           ACFC11north = ACFC11(thisYear,1)           ACFC11north = ACFC11(maxYear,1)
84           ACFC11south = ACFC11(thisYear,1)           ACFC11south = ACFC11(maxYear,2)
85         endif         endif
86  c      print*,'ACFC11north,ACFC11south', ACFC11north,ACFC11south,  c      print*,'YEAR,ACFC11north,ACFC11south',  myYear,
87  c    &                                   lastYear,thisYear  c    &        ACFC11north,ACFC11south
88  c provide gradient between N and S values  C provide gradient between N and S values
89  #define OCMIP_GRAD  
90  #undef STEPH_GRAD  C STEPH S INITIAL VERSION
 c STEPH'S INITIAL VERSION  
91  #ifdef STEPH_GRAD  #ifdef STEPH_GRAD
92         DO j=1-OLy,sNy+OLy         DO j=1-OLy,sNy+OLy
93            DO i=1-OLx,sNx+OLx          DO i=1-OLx,sNx+OLx
94             if ((j.gt.int(sNy/2)+3.and.j.le.sNy).or.j.lt.1) then            if ((j.gt.int(sNy/2)+3.and.j.le.sNy).or.j.lt.1) then
95               ATMOSCFC11(i,j,bi,bj)=ACFC11north               ATMOSCFC11(i,j,bi,bj)=ACFC11north
96             endif            endif
97             if (j.ge.int(sNy/2)-3.and.j.le.int(sNy/2)+3) then            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               a1=(float(j-int(sNy/2)+3)+.5)/7
99               a2=1.d0-a1               a2=1.d0-a1
100               ATMOSCFC11(i,j,bi,bj)=a1*ACFC11south +               ATMOSCFC11(i,j,bi,bj)=a1*ACFC11south +
101       &                             a2*ACFC11north       &                             a2*ACFC11north
102             endif            endif
103             if ((j.lt.int(sNy/2)-3.and.j.gt.0).or.j.gt.sNy) then            if ((j.lt.int(sNy/2)-3.and.j.gt.0).or.j.gt.sNy) then
104               ATMOSCFC11(i,j,bi,bj)=ACFC11south               ATMOSCFC11(i,j,bi,bj)=ACFC11south
105             endif            endif
106            ENDDO          ENDDO
107         ENDDO         ENDDO
108  #endif  #endif
109  c OCMIP VERSION  C OCMIP VERSION
110  #ifdef OCMIP_GRAD  #ifdef OCMIP_GRAD
111         yNorth =  10.0         yNorth =  10.0
112         ySouth = -10.0         ySouth = -10.0
# Line 123  c OCMIP VERSION Line 128  c OCMIP VERSION
128  c         print*,'QQ cfc11', j, ATMOSCFC11(1,j,bi,bj)  c         print*,'QQ cfc11', j, ATMOSCFC11(1,j,bi,bj)
129         ENDDO         ENDDO
130  #endif  #endif
131  c cfc11 air-sea interaction  C cfc11 air-sea interaction
132         CALL CFC11_SURFFORCING( PTR_CFC11, SURCFC11,         CALL CFC11_SURFFORCING( PTR_CFC11, SURCFC11,
133       &                    bi,bj,imin,imax,jmin,jmax,       &                    bi,bj,imin,imax,jmin,jmax,
134       &                    myIter,myTime,myThid)       &                    myIter,myTime,myThid)
# Line 137  c cfc11 air-sea interaction Line 142  c cfc11 air-sea interaction
142  #endif  #endif
143  #endif  #endif
144    
 c  
145         RETURN         RETURN
146         END         END

Legend:
Removed from v.1.2  
changed lines
  Added in v.1.11

  ViewVC Help
Powered by ViewVC 1.1.22