/[MITgcm]/MITgcm/pkg/frazil/frazil_calc_rhs.F
ViewVC logotype

Contents of /MITgcm/pkg/frazil/frazil_calc_rhs.F

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


Revision 1.2 - (show annotations) (download)
Sat Mar 3 16:04:38 2012 UTC (12 years, 2 months ago) by dimitri
Branch: MAIN
Changes since 1.1: +15 -15 lines
changing pkg/frazil forcing terms from K/s to W/m^2

1 C $Header: /u/gcmpack/MITgcm/pkg/frazil/frazil_calc_rhs.F,v 1.1 2012/03/02 01:45:22 dimitri Exp $
2 C $Name: $
3
4 #include "FRAZIL_OPTIONS.h"
5
6 CBOP
7 C !ROUTINE: FRAZIL_CALC_RHS
8
9 C !INTERFACE: ==========================================================
10 SUBROUTINE FRAZIL_CALC_RHS(
11 I myTime, myIter, myThid )
12
13 C !DESCRIPTION:
14 C Check water temperature and if colder than freezing
15 C point bring excess negative heat to the surface.
16
17 C !USES: ===============================================================
18 IMPLICIT NONE
19 #include "SIZE.h"
20 #include "EEPARAMS.h"
21 #include "PARAMS.h"
22 #include "DYNVARS.h"
23 #include "GRID.h"
24 #include "FFIELDS.h"
25 #include "FRAZIL.h"
26
27 C !INPUT/OUTPUT PARAMETERS:
28 C == Routine Arguments ==
29 C myTime - Current time in simulation
30 C myIter - Current iteration number in simulation
31 C myThid :: Thread no. that called this routine.
32 _RL myTime
33 INTEGER myIter
34 INTEGER myThid
35
36 #ifdef ALLOW_FRAZIL
37 C !LOCAL VARIABLES: ====================================================
38 C Tfreezing :: Freezing threshold temperature.
39 INTEGER bi,bj,i,j,k,kTop
40 _RL Tfreezing, Tresid, pLoc, sLoc, tLoc
41 _RL a0, a1, a2, b
42 PARAMETER( a0 = -0.0575 _d 0 )
43 PARAMETER( a1 = 1.710523 _d -3 )
44 PARAMETER( a2 = -2.154996 _d -4 )
45 PARAMETER( b = -7.53 _d -4 )
46
47 _RL SW_TEMP
48 EXTERNAL SW_TEMP
49 CEOP
50
51 C-- Check for water below freezing point.
52 DO bj=myByLo(myThid),myByHi(myThid)
53 DO bi=myBxLo(myThid),myBxHi(myThid)
54 DO j=1-OLy,sNy+OLy
55 DO i=1-OLx,sNx+OLx
56 kTop = kSurfC(i,j,bi,bj)
57 DO k = (kTop+1), Nr
58 IF ( maskC(i,j,k-1,bi,bj) .NE. 0. _d 0 .AND.
59 & maskC(i,j,k, bi,bj) .NE. 0. _d 0 ) THEN
60
61 pLoc = ABS(RC(k))
62 sLoc = MAX(salt(i,j,k,bi,bj), 0. _d 0)
63 tLoc = SW_TEMP(sLoc,theta(i,j,k,bi,bj),pLoc,0. _d 0)
64
65 C Freezing point of seawater
66 C REFERENCE: UNESCO TECH. PAPERS IN THE MARINE SCIENCE NO. 28. 1978
67 C EIGHTH REPORT JPOTS
68 C ANNEX 6 FREEZING POINT OF SEAWATER F.J. MILLERO PP.29-35.
69 C
70 C UNITS:
71 C PRESSURE P DECIBARS
72 C SALINITY S PSS-78
73 C TEMPERATURE TF DEGREES CELSIUS
74 C FREEZING PT.
75 C************************************************************
76 C CHECKVALUE: TF= -2.588567 DEG. C FOR S=40.0, P=500. DECIBARS
77 Tfreezing = (a0 + a1*sqrt(sLoc) + a2*sLoc) * sLoc + b*pLoc
78
79 IF (tLoc .LT. Tfreezing) THEN
80 C Move the negative heat to surface level.
81 Tresid = Tfreezing - tloc
82 FrazilForcingT(i,j,k,bi,bj) =
83 & Tresid / dTtracerLev(k)
84 & * HeatCapacity_Cp * rUnit2mass
85 & * drF(k) * _hFacC(i,j,k,bi,bj)
86 FrazilForcingT(i,j,kTop,bi,bj) =
87 & - Tresid / dTtracerLev(kTop)
88 & * HeatCapacity_Cp * rUnit2mass
89 & * drF(k) * _hFacC(i,j,k,bi,bj)
90 ENDIF
91 ENDIF
92 ENDDO
93 ENDDO
94 ENDDO
95 ENDDO
96 ENDDO
97
98 #endif /* ALLOW_FRAZIL */
99
100 RETURN
101 END

  ViewVC Help
Powered by ViewVC 1.1.22