/[MITgcm]/MITgcm_contrib/dgoldberg/streamice/streamice_advect_thickness.F
ViewVC logotype

Contents of /MITgcm_contrib/dgoldberg/streamice/streamice_advect_thickness.F

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


Revision 1.7 - (show annotations) (download)
Thu Mar 7 15:12:19 2013 UTC (12 years, 4 months ago) by dgoldberg
Branch: MAIN
Changes since 1.6: +4 -2 lines
mult mass bal by timestep (in years)

1 C $Header: /u/gcmpack/MITgcm_contrib/dgoldberg/streamice/streamice_advect_thickness.F,v 1.6 2013/01/09 21:56:18 dgoldberg Exp $
2 C $Name: $
3
4 #include "STREAMICE_OPTIONS.h"
5
6 C---+----1----+----2----+----3----+----4----+----5----+----6----+----7-|--+----|
7
8
9 CBOP
10 SUBROUTINE STREAMICE_ADVECT_THICKNESS ( myThid, time_step )
11
12 C /============================================================\
13 C | SUBROUTINE |
14 C | o |
15 C |============================================================|
16 C | |
17 C \============================================================/
18 IMPLICIT NONE
19
20 C === Global variables ===
21 #include "SIZE.h"
22 #include "GRID.h"
23 #include "EEPARAMS.h"
24 #include "PARAMS.h"
25 #include "STREAMICE.h"
26 #include "STREAMICE_ADV.h"
27 #ifdef ALLOW_AUTODIFF_TAMC
28 # include "tamc.h"
29 #endif
30
31 INTEGER myThid
32 _RL time_step
33
34 #ifdef ALLOW_STREAMICE
35
36 INTEGER i, j, bi, bj
37 _RL thick_bd
38 _RL SLOPE_LIMITER
39 _RL sec_per_year, time_step_loc, MR, SMB, TMB
40 CHARACTER*(MAX_LEN_MBUF) msgBuf
41 external SLOPE_LIMITER
42
43 sec_per_year = 365.*86400.
44
45 time_step_loc = time_step / sec_per_year
46
47 PRINT *, "time_step_loc ", time_step_loc
48
49 #ifdef ALLOW_AUTODIFF_TAMC
50 CADJ STORE streamice_hmask = comlev1, key=ikey_dynamics
51 #endif
52
53 DO bj=myByLo(myThid),myByHi(myThid)
54 DO bi=myBxLo(myThid),myBxHi(myThid)
55 DO j=1-OLy,sNy+OLy
56 DO i=1-OLx,sNx+OLx
57 H_streamice_prev(i,j,bi,bj) =
58 & H_streamice(i,j,bi,bj)
59 hflux_x_SI (i,j,bi,bj) = 0. _d 0
60 hflux_y_SI (i,j,bi,bj) = 0. _d 0
61 hflux_x_SI2 (i,j,bi,bj) = 0. _d 0
62 hflux_y_SI2 (i,j,bi,bj) = 0. _d 0
63 IF (STREAMICE_hmask(i,j,bi,bj).eq.1.0) THEN
64 h_after_uflux_SI (i,j,bi,bj) =
65 & H_streamice (i,j,bi,bj)
66 ENDIF
67
68 thick_bd = h_bdry_values_SI (i,j,bi,bj)
69 IF (thick_bd .ne. 0. _d 0) THEN
70 h_after_uflux_SI (i,j,bi,bj) = thick_bd
71 ENDIF
72 ENDDO
73 ENDDO
74 ENDDO
75 ENDDO
76
77
78 #ifdef ALLOW_AUTODIFF_TAMC
79 CADJ STORE h_after_uflux_si = comlev1, key=ikey_dynamics
80 CADJ STORE streamice_hmask = comlev1, key=ikey_dynamics
81 #endif
82
83 CALL STREAMICE_ADVECT_THICKNESS_X ( myThid,
84 O hflux_x_SI,
85 O h_after_uflux_SI,
86 I time_step_loc )
87
88
89
90 DO bj=myByLo(myThid),myByHi(myThid)
91 DO bi=myBxLo(myThid),myBxHi(myThid)
92 DO j=1-OLy,sNy+OLy
93 DO i=1-OLx,sNx+OLx
94 h_after_vflux_SI (i,j,bi,bj) =
95 & h_after_uflux_SI (i,j,bi,bj)
96 ENDDO
97 ENDDO
98 ENDDO
99 ENDDO
100
101 #ifdef ALLOW_AUTODIFF_TAMC
102 CADJ STORE h_after_vflux_si = comlev1, key=ikey_dynamics
103 CADJ STORE streamice_hmask = comlev1, key=ikey_dynamics
104 #endif
105
106 CALL STREAMICE_ADVECT_THICKNESS_Y ( myThid,
107 O hflux_y_SI,
108 O h_after_vflux_SI,
109 I time_step_loc )
110
111
112
113 DO bj=myByLo(myThid),myByHi(myThid)
114 DO bi=myBxLo(myThid),myBxHi(myThid)
115 DO j=1-OLy,sNy+OLy
116 DO i=1-OLx,sNx+OLx
117 IF (STREAMICE_hmask(i,j,bi,bj).eq.1.0) THEN
118 H_streamice (i,j,bi,bj) =
119 & h_after_vflux_SI (i,j,bi,bj)
120 ENDIF
121 ENDDO
122 ENDDO
123 ENDDO
124 ENDDO
125
126
127
128 CALL STREAMICE_ADV_FRONT ( myThid, time_step_loc )
129
130
131 ! NOW WE APPLY MELT RATES !!
132 ! THIS MAY BE MOVED TO A SEPARATE SUBROUTINE
133
134 DO bj=myByLo(myThid),myByHi(myThid)
135 DO bi=myBxLo(myThid),myBxHi(myThid)
136 DO j=1-OLy,sNy+OLy
137 DO i=1-OLx,sNx+OLx
138 IF (STREAMICE_hmask(i,j,bi,bj).eq.1.0 .or.
139 & STREAMICE_hmask(i,j,bi,bj).eq.2.0) THEN
140 MR = (1.-float_frac_streamice(i,j,bi,bj)) *
141 & BDOT_STREAMICE(i,j,bi,bj)
142 SMB = ADOT_STREAMICE(i,j,bi,bj)
143 TMB = SMB - MR
144 IF ((TMB.lt.0.0) .and.
145 & (MR * time_step_loc .gt.
146 & H_streamice (i,j,bi,bj))) THEN
147 H_streamice (i,j,bi,bj) = 0. _d 0
148 STREAMICE_hmask(i,j,bi,bj) = 0.
149 ELSE
150 H_streamice (i,j,bi,bj) =
151 & H_streamice (i,j,bi,bj) + TMB * time_step_loc
152 ENDIF
153 ENDIF
154 ENDDO
155 ENDDO
156 ENDDO
157 ENDDO
158
159
160 WRITE(msgBuf,'(A)') 'END STREAMICE_ADVECT_THICKNESS'
161 CALL PRINT_MESSAGE( msgBuf, standardMessageUnit,
162 & SQUEEZE_RIGHT , 1)
163
164 #endif
165 END
166

  ViewVC Help
Powered by ViewVC 1.1.22