/[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.5 - (show annotations) (download)
Thu Oct 4 15:40:16 2012 UTC (12 years, 9 months ago) by dgoldberg
Branch: MAIN
Changes since 1.4: +3 -2 lines
new field and cost function for thickness drift

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

  ViewVC Help
Powered by ViewVC 1.1.22