/[MITgcm]/MITgcm/pkg/thsice/thsice_slab_ocean.F
ViewVC logotype

Contents of /MITgcm/pkg/thsice/thsice_slab_ocean.F

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


Revision 1.10 - (show annotations) (download)
Thu Sep 24 20:08:37 2009 UTC (14 years, 7 months ago) by dfer
Branch: MAIN
CVS Tags: checkpoint64a, checkpoint64c, checkpoint64b, checkpoint64e, checkpoint64d, checkpoint64f, checkpoint63p, checkpoint63q, checkpoint63r, checkpoint63s, checkpoint63l, checkpoint63m, checkpoint63n, checkpoint63o, checkpoint63h, checkpoint63i, checkpoint63j, checkpoint63k, checkpoint63d, checkpoint63e, checkpoint63f, checkpoint63g, checkpoint63a, checkpoint63b, checkpoint63c, checkpoint64, checkpoint62, checkpoint63, checkpoint62c, checkpoint62b, checkpoint62a, checkpoint62g, checkpoint62f, checkpoint62e, checkpoint62d, checkpoint62k, checkpoint62j, checkpoint62i, checkpoint62h, checkpoint62o, checkpoint62n, checkpoint62m, checkpoint62l, checkpoint62s, checkpoint62r, checkpoint62q, checkpoint62p, checkpoint62w, checkpoint62v, checkpoint62u, checkpoint62t, checkpoint62z, checkpoint62y, checkpoint62x, checkpoint61w, checkpoint61z, checkpoint61x, checkpoint61y
Changes since 1.9: +13 -2 lines
Add capacity to read a Q-Flux to be applied in slab-mixed layer thsice_slab_ocean.F
(similar to SST restoring)

1 C $Header: /u/gcmpack/MITgcm/pkg/thsice/thsice_slab_ocean.F,v 1.9 2009/09/23 23:08:44 dfer Exp $
2 C $Name: $
3
4 #include "THSICE_OPTIONS.h"
5
6 CBOP
7 C !ROUTINE: THSICE_SLAB_OCEAN
8 C !INTERFACE:
9 SUBROUTINE THSICE_SLAB_OCEAN(
10 I aim_sWght0, aim_sWght1,
11 O dTsurf,
12 I bi, bj, myTime, myIter, myThid )
13 C !DESCRIPTION: \bv
14 C *==========================================================*
15 C | S/R THSICE_SLAB_OCEAN
16 C | o Slab ocean for atmosphere (and sea-ice) model
17 C *==========================================================*
18 C | o add ocean-surface fluxes + restoring term
19 C | and step forward ocean mixed-layer Temp. & Salinity
20 C *==========================================================*
21 C \ev
22
23 C !USES:
24 IMPLICIT NONE
25
26 C == Global variables ==
27 C-- MITgcm
28 #include "SIZE.h"
29 #include "EEPARAMS.h"
30 #include "PARAMS.h"
31 #include "FFIELDS.h"
32
33 C-- Sea-Ice package
34 #include "THSICE_PARAMS.h"
35 #include "THSICE_VARS.h"
36
37 C-- Physics package
38 #ifdef ALLOW_AIM
39 #include "AIM_FFIELDS.h"
40 #endif
41
42 C !INPUT/OUTPUT PARAMETERS:
43 C == Routine Arguments ==
44 C aim_sWght0 :: weight for time interpolation of surface BC
45 C aim_sWght1 :: 0/1 = time period before/after the current time
46 C dTsurf :: diagnostics of slab-ocean temperature change [K/iter]
47 C bi,bj :: tile indices
48 C myTime :: Current time of simulation ( s )
49 C myIter :: Current iteration number in simulation
50 C myThid :: my Thread number Id.
51 _RL aim_sWght0, aim_sWght1
52 _RL dTsurf(sNx,sNy)
53 _RL myTime
54 INTEGER bi,bj
55 INTEGER myIter, myThid
56 CEOP
57
58 #ifdef ALLOW_THSICE
59
60 C == Local variables ==
61 C i,j :: Loop counters
62 _RL dtFac, fwFac, heatFac
63 #ifdef ALLOW_AIM
64 _RL oceTfreez, locTemp, locQflux, dtFacR
65 #endif
66 INTEGER i,j
67
68 cph the following structure is not supported by TAF
69 cph IF ( .NOT.stepFwd_oceMxL ) RETURN
70 IF ( stepFwd_oceMxL ) THEN
71
72 C-- add heat flux and fresh-water + salt flux :
73 dtFac = ocean_deltaT/rhosw
74 fwFac = ocean_deltaT*sMxL_default/rhosw
75 heatFac = ocean_deltaT/(cpwater*rhosw)
76 DO j=1,sNy
77 DO i=1,sNx
78 IF ( hOceMxL(i,j,bi,bj).NE.0. _d 0 ) THEN
79 dTsurf(i,j) = tOceMxL(i,j,bi,bj)
80 tOceMxL(i,j,bi,bj) = tOceMxL(i,j,bi,bj)
81 & - heatFac*Qnet(i,j,bi,bj) / hOceMxL(i,j,bi,bj)
82 sOceMxL(i,j,bi,bj) = sOceMxL(i,j,bi,bj)
83 & + (fwFac*EmPmR(i,j,bi,bj) - dtFac*saltFlux(i,j,bi,bj))
84 & / hOceMxL(i,j,bi,bj)
85 ENDIF
86 ENDDO
87 ENDDO
88
89 #ifdef ALLOW_AIM
90 IF ( tauRelax_MxL_salt .GT. 0. _d 0 ) THEN
91 C-- add restoring (backward) toward climatological fixed Salinity
92 dtFac = ocean_deltaT/tauRelax_MxL_salt
93 dtFacR = 1. _d 0 /(1. _d 0 + dtFac)
94 DO j=1,sNy
95 DO i=1,sNx
96 IF ( hOceMxL(i,j,bi,bj).NE.0. _d 0 ) THEN
97 sOceMxL(i,j,bi,bj) =
98 & (sOceMxL(i,j,bi,bj) + dtFac*sMxL_default)*dtFacR
99 ENDIF
100 ENDDO
101 ENDDO
102 ENDIF
103 IF ( tauRelax_MxL .GT. 0. _d 0 ) THEN
104 C-- add restoring (backward) toward climatological Temp.
105 dtFac = ocean_deltaT/tauRelax_MxL
106 dtFacR = 1. _d 0 /(1. _d 0 + dtFac)
107 oceTfreez = - 1.9 _d 0
108 DO j=1,sNy
109 DO i=1,sNx
110 IF ( hOceMxL(i,j,bi,bj).NE.0. _d 0 ) THEN
111 oceTfreez = -mu_Tf*sOceMxL(i,j,bi,bj)
112 locTemp = ( aim_sWght0*aim_sst0(i,j,bi,bj)
113 & + aim_sWght1*aim_sst1(i,j,bi,bj)
114 & ) - celsius2K
115 locTemp = MAX( locTemp , oceTfreez )
116 tOceMxL(i,j,bi,bj) =
117 & (tOceMxL(i,j,bi,bj) + dtFac*locTemp)*dtFacR
118 ENDIF
119 ENDDO
120 ENDDO
121 ENDIF
122 DO j=1,sNy
123 DO i=1,sNx
124 IF ( hOceMxL(i,j,bi,bj).NE.0. _d 0 ) THEN
125 locQflux = ( aim_sWght0*aim_qfx0(i,j,bi,bj)
126 & + aim_sWght1*aim_qfx1(i,j,bi,bj)
127 & )
128 tOceMxL(i,j,bi,bj) = tOceMxL(i,j,bi,bj)
129 & + heatFac*locQflux / hOceMxL(i,j,bi,bj)
130 ENDIF
131 ENDDO
132 ENDDO
133 #endif /* ALLOW_AIM */
134
135 C- Diagnose surf. temp. change
136 DO j=1,sNy
137 DO i=1,sNx
138 IF ( hOceMxL(i,j,bi,bj).NE.0. _d 0 ) THEN
139 dTsurf(i,j) = tOceMxL(i,j,bi,bj) - dTsurf(i,j)
140 ENDIF
141 ENDDO
142 ENDDO
143
144 c-- End of IF ( stepFwd_oceMxL ) THEN
145 ENDIF
146
147 #endif /* ALLOW_THSICE */
148
149 RETURN
150 END

  ViewVC Help
Powered by ViewVC 1.1.22