/[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.4 - (show annotations) (download)
Tue Sep 4 21:11:44 2012 UTC (12 years, 10 months ago) by dgoldberg
Branch: MAIN
Changes since 1.3: +26 -5 lines
recent changes.. DNG

1 C $Header: /u/gcmpack/MITgcm_contrib/dgoldberg/streamice/streamice_advect_thickness.F,v 1.3 2012/07/26 16:13: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
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 #ifdef ALLOW_AUTODIFF_TAMC
48 CADJ STORE streamice_hmask = comlev1, key=ikey_dynamics
49 #endif
50
51 DO bj=myByLo(myThid),myByHi(myThid)
52 DO bi=myBxLo(myThid),myBxHi(myThid)
53 DO j=1-OLy,sNy+OLy
54 DO i=1-OLx,sNx+OLx
55 hflux_x_SI (i,j,bi,bj) = 0. _d 0
56 hflux_y_SI (i,j,bi,bj) = 0. _d 0
57 hflux_x_SI2 (i,j,bi,bj) = 0. _d 0
58 hflux_y_SI2 (i,j,bi,bj) = 0. _d 0
59 IF (STREAMICE_hmask(i,j,bi,bj).eq.1.0) THEN
60 h_after_uflux_SI (i,j,bi,bj) =
61 & H_streamice (i,j,bi,bj)
62 ENDIF
63
64 thick_bd = h_bdry_values_SI (i,j,bi,bj)
65 IF (thick_bd .ne. 0. _d 0) THEN
66 h_after_uflux_SI (i,j,bi,bj) = thick_bd
67 ENDIF
68 ENDDO
69 ENDDO
70 ENDDO
71 ENDDO
72
73
74
75 #ifdef ALLOW_AUTODIFF_TAMC
76 CADJ STORE h_after_uflux_si = comlev1, key=ikey_dynamics
77 CADJ STORE streamice_hmask = comlev1, key=ikey_dynamics
78 #endif
79
80 CALL STREAMICE_ADVECT_THICKNESS_X ( myThid,
81 O hflux_x_SI,
82 O h_after_uflux_SI,
83 I time_step_loc )
84
85
86
87 DO bj=myByLo(myThid),myByHi(myThid)
88 DO bi=myBxLo(myThid),myBxHi(myThid)
89 DO j=1-OLy,sNy+OLy
90 DO i=1-OLx,sNx+OLx
91 h_after_vflux_SI (i,j,bi,bj) =
92 & h_after_uflux_SI (i,j,bi,bj)
93 ENDDO
94 ENDDO
95 ENDDO
96 ENDDO
97
98 #ifdef ALLOW_AUTODIFF_TAMC
99 CADJ STORE h_after_vflux_si = comlev1, key=ikey_dynamics
100 CADJ STORE streamice_hmask = comlev1, key=ikey_dynamics
101 #endif
102
103 CALL STREAMICE_ADVECT_THICKNESS_Y ( myThid,
104 O hflux_y_SI,
105 O h_after_vflux_SI,
106 I time_step_loc )
107
108
109
110 DO bj=myByLo(myThid),myByHi(myThid)
111 DO bi=myBxLo(myThid),myBxHi(myThid)
112 DO j=1-OLy,sNy+OLy
113 DO i=1-OLx,sNx+OLx
114 IF (STREAMICE_hmask(i,j,bi,bj).eq.1.0) THEN
115 H_streamice (i,j,bi,bj) =
116 & h_after_vflux_SI (i,j,bi,bj)
117 ENDIF
118 ENDDO
119 ENDDO
120 ENDDO
121 ENDDO
122
123
124
125 CALL STREAMICE_ADV_FRONT ( myThid, time_step_loc )
126
127
128 ! NOW WE APPLY MELT RATES !!
129 ! THIS MAY BE MOVED TO A SEPARATE SUBROUTINE
130
131 DO bj=myByLo(myThid),myByHi(myThid)
132 DO bi=myBxLo(myThid),myBxHi(myThid)
133 DO j=1-OLy,sNy+OLy
134 DO i=1-OLx,sNx+OLx
135 IF (STREAMICE_hmask(i,j,bi,bj).eq.1.0 .or.
136 & STREAMICE_hmask(i,j,bi,bj).eq.2.0) THEN
137 MR = (1.-float_frac_streamice(i,j,bi,bj)) *
138 & BDOT_STREAMICE(i,j,bi,bj)
139 IF (MR * time_step_loc .gt.
140 & H_streamice (i,j,bi,bj)) THEN
141 H_streamice (i,j,bi,bj) = 0. _d 0
142 STREAMICE_hmask(i,j,bi,bj) = 0.
143 ELSE
144 H_streamice (i,j,bi,bj) =
145 & H_streamice (i,j,bi,bj) - MR
146 ENDIF
147 ENDIF
148 ENDDO
149 ENDDO
150 ENDDO
151 ENDDO
152
153
154 WRITE(msgBuf,'(A)') 'END STREAMICE_ADVECT_THICKNESS'
155 CALL PRINT_MESSAGE( msgBuf, standardMessageUnit,
156 & SQUEEZE_RIGHT , 1)
157
158 #endif
159 END
160

  ViewVC Help
Powered by ViewVC 1.1.22