/[MITgcm]/MITgcm_contrib/jscott/pkg_atm2d/relax_add.F
ViewVC logotype

Annotation of /MITgcm_contrib/jscott/pkg_atm2d/relax_add.F

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


Revision 1.1 - (hide annotations) (download)
Fri Aug 11 18:55:50 2006 UTC (18 years, 11 months ago) by jscott
Branch: MAIN
new 2d atm package

1 jscott 1.1 #include "ctrparam.h"
2     #include "ATM2D_OPTIONS.h"
3    
4     C !INTERFACE:
5     SUBROUTINE RELAX_ADD( wght0, wght1,
6     & intime0, intime1, iftime, myIter, myThid)
7     C *==========================================================*
8     C | |
9     c | |
10     C *==========================================================*
11     IMPLICIT NONE
12    
13     #include "ATMSIZE.h"
14     #include "SIZE.h"
15     #include "EEPARAMS.h"
16     #include "PARAMS.h"
17     #include "GRID.h"
18     #include "THSICE_VARS.h"
19     #include "ATM2D_VARS.h"
20    
21     c include ocean and seaice vars
22    
23     C !INPUT/OUTPUT PARAMETERS:
24     C === Routine arguments ===
25     C myIter - Ocean iteration number
26     C myThid - Thread no. that called this routine.
27     _RL wght0
28     _RL wght1
29     INTEGER intime0
30     INTEGER intime1
31     LOGICAL iftime
32     INTEGER myIter
33     INTEGER myThid
34    
35     C LOCAL VARIABLES:
36     COMMON /OCEANRELAX/
37     & sst0, sst1, sss0, sss1
38    
39     _RS sst0(1-Olx:sNx+Olx,1-Oly:sNy+Oly,1,1)
40     _RS sst1(1-Olx:sNx+Olx,1-Oly:sNy+Oly,1,1)
41     _RS sss0(1-Olx:sNx+Olx,1-Oly:sNy+Oly,1,1)
42     _RS sss1(1-Olx:sNx+Olx,1-Oly:sNy+Oly,1,1)
43     _RL lambdaTheta,lambdaSalt
44     _RS nearIce
45     _RL qrelflux, frelflux
46     _RL sstRelax(1:sNx,1:sNy), sssRelax(1:sNx,1:sNy)
47     INTEGER i,j
48    
49     IF (ifTime) THEN
50    
51     C If the above condition is met then we need to read in
52     C data for the period ahead and the period behind current time.
53    
54     WRITE(*,*) 'S/R RELAX_ADD: Reading new data'
55     IF ( thetaRelaxFile .NE. ' ' ) THEN
56     CALL READ_REC_XY_RS( thetaRelaxFile,sst0,intime0,
57     & myIter,myThid )
58     CALL READ_REC_XY_RS( thetaRelaxFile,sst1,intime1,
59     & myIter,myThid )
60     ENDIF
61     IF ( saltRelaxFile .NE. ' ' ) THEN
62     CALL READ_REC_XY_RS( saltRelaxFile,sss0,intime0,
63     & myIter,myThid )
64     CALL READ_REC_XY_RS( saltRelaxFile,sss1,intime1,
65     & myIter,myThid )
66     ENDIF
67    
68     ENDIF
69    
70     IF ((thetaRelaxFile.NE.' ').OR.(saltRelaxFile.NE.' ')) THEN
71    
72     C-- Interpolate and add to anomaly
73     DO j=1,sNy
74    
75     IF (ntTypeRelax.EQ.0) THEN
76     lambdaTheta = r_tauThetaRelax
77     ELSE
78     lambdaTheta = r_tauThetaRelax/
79     & max(cos(1.5D0*yC(1,j,1,1)*deg2rad),0.D0)
80     ENDIF
81     IF (nsTypeRelax.EQ.0) THEN
82     lambdaSalt = r_tauSaltRelax
83     ELSE
84     lambdaSalt = r_tauSaltRelax/
85     & max(cos(1.5D0*yC(1,j,1,1)*deg2rad),0.D0)
86     ENDIF
87    
88     DO i=1,sNx
89    
90     IF (maskC(i,j,1,1,1).EQ.1.) THEN
91     sstRelax(i,j)= (wght0*sst0(i,j,1,1) + wght1*sst1(i,j,1,1))
92     sssRelax(i,j)= (wght0*sss0(i,j,1,1) + wght1*sss1(i,j,1,1))
93    
94     C Next lines: linearly phase out SST restoring between 2C and -1C
95     C ONLY if seaice is present
96     IF ((sstRelax(i,j).GT.2.0).OR.
97     & (iceMask(i,j,1,1).EQ.0.D0)) THEN
98     nearIce=1.0
99     ELSEIF (sstRelax(i,j).LE.-1.0) THEN
100     nearIce=0.0
101     ELSE
102     nearIce=(sstRelax(i,j)+1.0)/3.0
103     endif
104    
105     IF (iceMask(i,j,1,1).GT.0.D0) THEN
106     PRINT *,'In relax at, sst :',i,j,sstRelax(i,j)
107     PRINT *,'Nearice = ',nearIce
108     ENDIF
109     qrelflux= lambdaTheta*(sstFromOcn(i,j)-sstRelax(i,j))/
110     & (recip_Cp*recip_rhoNil*recip_drF(1))*nearIce
111    
112     qneto_2D(i,j)= qneto_2D(i,j) + qrelflux
113     qneti_2D(i,j)= qneti_2D(i,j) + qrelflux
114    
115     frelflux= -lambdaSalt*(sssFromOcn(i,j)-sssRelax(i,j))/
116     & (convertFW2Salt *recip_drF(1))*nearIce
117    
118     if ((i.eq.JBUGI).and.(j.eq.JBUGJ)) then
119     print *,'Frelflux:',frelflux,sssFromOcn(i,j)-sssRelax(i,j)
120     print *,'Qrelflux:',qrelflux,sstFromOcn(i,j)-sstRelax(i,j)
121     print *,'sss relax:',sssRelax(i,j),sss0(i,j,1,1),sss1(i,j,1,1)
122     print *,'sst relax:',sstRelax(i,j),sst0(i,j,1,1),sst1(i,j,1,1)
123     print *,'ctocn: ',ctocn(JBUGJ+1)
124     endif
125    
126     C or use actual salt instead of convertFW2salt above?
127    
128     IF (frelflux.GT.0.D0) THEN
129     evapo_2D(i,j)= evapo_2D(i,j) - frelflux
130     IF (iceMask(i,j,1,1).GT.0. _d 0)
131     & evapi_2D(i,j)= evapi_2D(i,j) - frelflux
132     ELSE
133     precipo_2D(i,j)= precipo_2D(i,j) + frelflux
134     IF (iceMask(i,j,1,1).GT.0. _d 0)
135     & precipi_2D(i,j)= precipi_2D(i,j) + frelflux
136     ENDIF
137    
138     C IF (iceMask(i,j,1,1).GT.0.D0) THEN
139     C PRINT *,'Frelflux',frelflux,precipi_2D(i,j),atm_precip(j+1)
140     C ENDIF
141    
142     C Diagnostics
143     sum_qrel(i,j)= sum_qrel(i,j) + qrelflux*dtatmo
144     sum_frel(i,j)= sum_frel(i,j) + frelflux*dtatmo
145    
146     ENDIF
147     ENDDO
148     ENDDO
149     ENDIF
150    
151     PRINT *,'***bottom of relaxadd',wght0,wght1,intime0,intime1
152     PRINT *,'evapo_2d: ',evapo_2D(JBUGI,JBUGJ)
153     PRINT *,'precipo_2d: ',precipo_2D(JBUGI,JBUGJ)
154     PRINT *,'qneto_2d: ',qneto_2D(JBUGI,JBUGJ)
155     PRINT *,'SStfrom Ocn: ',sstfromocn(JBUGI,JBUGJ)
156     PRINT *,'SSSfrom Ocn: ',sssfromocn(JBUGI,JBUGJ)
157    
158     RETURN
159     END

  ViewVC Help
Powered by ViewVC 1.1.22