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

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

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


Revision 1.2 - (hide annotations) (download)
Wed May 4 19:57:16 2005 UTC (19 years ago) by stephd
Branch: MAIN
CVS Tags: checkpoint58l_post, checkpoint57t_post, checkpoint57o_post, checkpoint58e_post, checkpoint57v_post, checkpoint57m_post, checkpoint57s_post, checkpoint57k_post, checkpoint57i_post, checkpoint57y_post, checkpoint58h_post, checkpoint57y_pre, checkpoint58j_post, checkpoint57r_post, checkpoint58, checkpoint57h_done, checkpoint58f_post, checkpoint57x_post, checkpoint57n_post, checkpoint58d_post, checkpoint58c_post, checkpoint57w_post, checkpoint57p_post, checkpint57u_post, checkpoint58a_post, checkpoint58i_post, checkpoint57q_post, checkpoint58g_post, checkpoint57z_post, checkpoint58k_post, checkpoint57j_post, checkpoint58b_post, checkpoint57h_pre, checkpoint58m_post, checkpoint57l_post, checkpoint57h_post
Changes since 1.1: +1 -1 lines
o include effect of ice cover, change piston velocity to resemble
  Wannikof (1992) parameterization

1 stephd 1.1 #include "CPP_OPTIONS.h"
2     #include "GCHEM_OPTIONS.h"
3    
4     CStartOfInterFace
5     SUBROUTINE cfc11_SURFFORCING( PTR_cfc11, surfcfc11,
6     I bi,bj,iMin,iMax,jMin,jMax,
7     I myIter, myTime, myThid )
8     C /==========================================================\
9     C | SUBROUTINE CFC11_SURFFORCING |
10     C |==========================================================|
11     IMPLICIT NONE
12    
13     C == GLobal variables ==
14     #include "SIZE.h"
15     #include "DYNVARS.h"
16     #include "EEPARAMS.h"
17     #include "PARAMS.h"
18     #include "GRID.h"
19     #include "FFIELDS.h"
20     #include "CFC.h"
21    
22     C == Routine arguments ==
23     INTEGER myIter, myThid
24     _RL myTime
25     _RL PTR_cfc11(1-OLx:sNx+OLx,1-OLy:sNy+OLy,Nr)
26     _RL surfcfc11(1-OLx:sNx+OLx,1-OLy:sNy+OLy)
27     INTEGER iMin,iMax,jMin,jMax, bi, bj
28    
29     #ifdef ALLOW_PTRACERS
30     #ifdef ALLOW_CFC
31    
32    
33     C == Local variables ==
34     C I, J, K - Loop counters
35     INTEGER I,J,K
36     C Solubility relation coefficients
37     _RL SchmidtNocfc11(1-OLx:sNx+OLx,1-OLy:sNy+OLy)
38     _RL SolCFC11(1-OLx:sNx+OLx,1-OLy:sNy+OLy)
39     _RL cfc11sat(1-OLx:sNx+OLx,1-OLy:sNy+OLy)
40     _RL Kwexch(1-OLx:sNx+OLx,1-OLy:sNy+OLy)
41     _RL Fluxcfc11(1-OLx:sNx+OLx,1-OLy:sNy+OLy)
42     _RL Csat(1-OLx:sNx+OLx,1-OLy:sNy+OLy)
43     _RL ttemp, ttemp2
44    
45     K=1
46    
47     C calculate SCHMIDT NO. for O2
48     DO j=jMin,jMax
49     DO i=iMin,iMax
50     IF (hFacC(i,j,k,bi,bj).NE.0.) THEN
51     C calculate SCHMIDT NO. for CFC11
52     SchmidtNocfc11(i,j) =
53     & sca_11_1
54     & + sca_11_2 * theta(i,j,k,bi,bj)
55     & + sca_11_3 * theta(i,j,k,bi,bj)*theta(i,j,k,bi,bj)
56     & + sca_11_4 * theta(i,j,k,bi,bj)*theta(i,j,k,bi,bj)
57     & *theta(i,j,k,bi,bj)
58     c calculate solubility for CFC11
59     ttemp=( theta(i,j,k,bi,bj) + 273.16)* 0.01
60     ttemp2=( B3_11 * ttemp + B2_11 )*
61     & ttemp + B1_11
62     SolCFC11(i,j)
63     & = exp ( A1_11
64     & + A2_11 / ttemp
65     & + A3_11 * log( ttemp )
66     & + A4_11 * ttemp * ttemp
67     & + Salt(i,j,k,bi,bj)* ttemp2 )
68     c conversion from mol/(l * atm) to mol/(m^3 * atm)
69     SolCFC11(i,j) = 1000. * SolCFC11(i,j)
70     c conversion from mol/(m^3 * atm) to mol/(m3 * pptv)
71     SolCFC11(i,j) = 1.0e-12 * SolCFC11(i,j)
72     C Determine surface flux (Fcfc11)
73     Csat(i,j) = SolCFC11(i,j)*AtmosP(i,j,bi,bj)
74     & *AtmosCFC11(i,j,bi,bj)
75 stephd 1.2 Kwexch(i,j) = (1.0 - fice(i,j,bi,bj))*pisvel(i,j,bi,bj)
76 stephd 1.1 & / sqrt(SchmidtNoCFC11(i,j)/660.0)
77     FluxCFC11(i,j) =
78     & Kwexch(i,j)*(Csat(i,j) - PTR_CFC11(i,j,1))
79    
80     ELSE
81     FluxCFC11(i,j) = 0.d0
82     ENDIF
83    
84    
85     ENDDO
86     ENDDO
87    
88     C update surface tendencies
89     DO j=jMin,jMax
90     DO i=iMin,iMax
91     SURFCFC11(i,j)=
92     & maskC(i,j,1,bi,bj)*FluxCFC11(i,j)*recip_drF(1)
93     ENDDO
94     ENDDO
95     #endif
96     #endif
97    
98    
99     RETURN
100     END
101    

  ViewVC Help
Powered by ViewVC 1.1.22