/[MITgcm]/MITgcm/pkg/atm2d/relax_add.F
ViewVC logotype

Annotation of /MITgcm/pkg/atm2d/relax_add.F

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


Revision 1.3 - (hide annotations) (download)
Mon Oct 8 23:48:28 2007 UTC (16 years, 8 months ago) by jmc
Branch: MAIN
CVS Tags: checkpoint60, checkpoint61, checkpoint62, checkpoint59q, checkpoint59p, checkpoint59r, checkpoint59m, checkpoint59l, checkpoint59o, checkpoint59n, checkpoint59i, checkpoint59k, checkpoint59j, checkpoint62c, checkpoint62b, checkpoint62a, checkpoint62g, checkpoint62f, checkpoint62e, checkpoint62d, checkpoint61f, checkpoint61g, checkpoint61d, checkpoint61e, checkpoint61b, checkpoint61c, checkpoint61a, checkpoint61n, checkpoint61o, checkpoint61l, checkpoint61m, checkpoint61j, checkpoint61k, checkpoint61h, checkpoint61i, checkpoint61v, checkpoint61w, checkpoint61t, checkpoint61u, checkpoint61r, checkpoint61s, checkpoint61p, checkpoint61q, checkpoint61z, checkpoint61x, checkpoint61y
Changes since 1.2: +7 -4 lines
add missing cvs $Header:$ or $Name:$

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

  ViewVC Help
Powered by ViewVC 1.1.22