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

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

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


Revision 1.4 - (show annotations) (download)
Tue Aug 21 16:06:22 2007 UTC (17 years, 11 months ago) by jscott
Branch: MAIN
CVS Tags: HEAD
Changes since 1.3: +0 -0 lines
FILE REMOVED
remove old atm2d pkg repository

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

  ViewVC Help
Powered by ViewVC 1.1.22