ROMS
Loading...
Searching...
No Matches
ice_limit.F
Go to the documentation of this file.
1#include "cppdefs.h"
3
4#if defined ICE_ADVECT || defined ICE_THERMO
5!
6!git $Id$
7!=======================================================================
8! Copyright (c) 2002-2025 The ROMS Group !
9! Licensed under a MIT/X style license W. Paul Budgell !
10! See License_ROMS.md Katherine Hedstrom !
11!================================================== Hernan G. Arango ===
12! !
13! It imposes positiveness on ice tracer variables. Thus, it does not !
14! allow negative ice concentration or thickness. !
15! !
16!======================================================================!
17!
18 USE mod_param
19 USE mod_ice
20 USE mod_scalars
21!
23 USE ice_bc2d_mod, ONLY : ice_bc2d_tile
24 USE ice_tibc_mod, ONLY : ice_tibc_tile
25# ifdef DISTRIBUTE
27# endif
28!
29 implicit none
30!
31 PRIVATE
32 PUBLIC ice_limit
33!
34 CONTAINS
35!
36!***********************************************************************
37 SUBROUTINE ice_limit (ng, tile, model)
38!***********************************************************************
39!
40 USE mod_stepping
41!
42! Imported variable declarations.
43!
44 integer, intent(in) :: ng, tile, model
45!
46! Local variable declarations.
47!
48 character (len=*), parameter :: MyFile = &
49 & __FILE__
50!
51# include "tile.h"
52!
53# ifdef PROFILE
54 CALL wclock_on (ng, model, 42, __line__, myfile)
55# endif
56 CALL ice_limit_tile (ng, tile, model, &
57 & lbi, ubi, lbj, ubj, &
58 & imins, imaxs, jmins, jmaxs, &
59 & liold(ng), linew(ng), &
60 & ice(ng) % Si)
61# ifdef PROFILE
62 CALL wclock_off (ng, model, 42, __line__, myfile)
63# endif
64!
65 RETURN
66 END SUBROUTINE ice_limit
67!
68!***********************************************************************
69 SUBROUTINE ice_limit_tile (ng, tile, model, &
70 & LBi, UBi, LBj, UBj, &
71 & IminS, ImaxS, JminS, JmaxS, &
72 & liold, linew, &
73 & Si)
74!***********************************************************************
75!
76! Imported variable declarations.
77!
78 integer, intent(in) :: ng, tile, model
79 integer, intent(in) :: LBi, UBi, LBj, UBj
80 integer, intent(in) :: IminS, ImaxS, JminS, JmaxS
81 integer, intent(inout) :: liold, linew
82!
83# ifdef ASSUMED_SHAPE
84 real(r8), intent(inout) :: Si(LBi:,LBj:,:,:)
85# else
86 real(r8), intent(inout) :: Si(LBi:UBi,LBj:UBj,2,nIceS)
87# endif
88!
89! Local variable definitions
90!
91 integer :: i, j
92
93# include "set_bounds.h"
94!
95!-----------------------------------------------------------------------
96! Impose positive concentration and thicknesses.
97!-----------------------------------------------------------------------
98!
99 DO j=jstr,jend
100 DO i=istr,iend
101 si(i,j,linew,isaice)=min(si(i,j,linew,isaice), max_ai(ng))
102 si(i,j,linew,isaice)=max(si(i,j,linew,isaice), 0.0_r8)
103 si(i,j,linew,ishice)=max(si(i,j,linew,ishice), 0.0_r8)
104 si(i,j,linew,ishsno)=max(si(i,j,linew,ishsno), 0.0_r8)
105 si(i,j,linew,ishmel)=max(si(i,j,linew,ishmel), 0.0_r8)
106 si(i,j,linew,istice)=max(si(i,j,linew,istice),-70.0_r8)
107 si(i,j,linew,isiage)=max(si(i,j,linew,isiage), 0.0_r8)
108 IF ((si(i,j,linew,isaice).le.0.0_r8).or. &
109 & (si(i,j,linew,ishice).le.0.0_r8)) THEN
110 si(i,j,linew,isaice)=0.0_r8
111 si(i,j,linew,ishice)=0.0_r8
112 si(i,j,linew,ishmel)=0.0_r8
113 si(i,j,linew,ishsno)=0.0_r8
114 si(i,j,linew,isiage)=0.0_r8
115 END IF
116# ifdef ICE_BIO
117 si(i,j,linew,isiphy)=max(si(i,j,linew,isiphy), 0.0_r8)
118 si(i,j,linew,isino3)=max(si(i,j,linew,isino3), 0.0_r8)
119 si(i,j,linew,isinh4)=max(si(i,j,linew,isinh4), 0.0_r8)
120 IF ((si(i,j,linew,isaice).le.0.5_r8).or. &
121 & (si(i,j,linew,ishice).le.0.02_r8)) THEN
122 si(i,j,linew,isilog)=-1.0_r8
123 ELSE
124 si(i,j,linew,isilog)=1.0_r8
125 END IF
126# endif
127 END DO
128 END DO
129!
130! Set lateral boundary conditions.
131!
132 CALL ice_bc2d_tile (ng, tile, model, isaice, &
133 & lbi, ubi, lbj, ubj, &
134 & imins, imaxs, jmins, jmaxs, &
135 & liold, linew, &
136 & si(:,:,:,isuice), &
137 & si(:,:,:,isvice), &
138 & si(:,:,:,isaice), &
139 & lbc(:,ibice(isaice),ng))
140
141 CALL ice_bc2d_tile (ng, tile, model, ishice, &
142 & lbi, ubi, lbj, ubj, &
143 & imins, imaxs, jmins, jmaxs, &
144 & liold, linew, &
145 & si(:,:,:,isuice), &
146 & si(:,:,:,isvice), &
147 & si(:,:,:,ishice), &
148 & lbc(:,ibice(ishice),ng))
149
150 CALL ice_bc2d_tile (ng, tile, model, ishsno, &
151 & lbi, ubi, lbj, ubj, &
152 & imins, imaxs, jmins, jmaxs, &
153 & liold, linew, &
154 & si(:,:,:,isuice), &
155 & si(:,:,:,isvice), &
156 & si(:,:,:,ishsno), &
157 & lbc(:,ibice(ishsno),ng))
158
159 CALL ice_bc2d_tile (ng, tile, model, ishmel, &
160 & lbi, ubi, lbj, ubj, &
161 & imins, imaxs, jmins, jmaxs, &
162 & liold, linew, &
163 & si(:,:,:,isuice), &
164 & si(:,:,:,isvice), &
165 & si(:,:,:,ishmel), &
166 & lbc(:,ibice(ishmel),ng))
167
168 CALL ice_bc2d_tile (ng, tile, model, isiage, &
169 & lbi, ubi, lbj, ubj, &
170 & imins, imaxs, jmins, jmaxs, &
171 & liold, linew, &
172 & si(:,:,:,isuice), &
173 & si(:,:,:,isvice), &
174 & si(:,:,:,isiage), &
175 & lbc(:,ibice(isiage),ng))
176
177# ifdef ICE_BIO
178 CALL ice_bc2d_tile (ng, tile, model, isiphy, &
179 & lbi, ubi, lbj, ubj, &
180 & imins, imaxs, jmins, jmaxs, &
181 & liold, linew, &
182 & si(:,:,:,isuice), &
183 & si(:,:,:,isvice), &
184 & si(:,:,:,isiphy), &
185 & lbc(:,ibice(isiphy),ng))
186
187 CALL ice_bc2d_tile (ng, tile, model, isino3, &
188 & lbi, ubi, lbj, ubj, &
189 & imins, imaxs, jmins, jmaxs, &
190 & liold, linew, &
191 & si(:,:,:,isuice), &
192 & si(:,:,:,isvice), &
193 & si(:,:,:,isino3), &
194 & lbc(:,ibice(isino3),ng))
195
196 CALL ice_bc2d_tile (ng, tile, inlm, isinh4, &
197 & lbi, ubi, lbj, ubj, &
198 & imins, imaxs, jmins, jmaxs, &
199 & liold, linew, &
200 & si(:,:,:,isuice), &
201 & si(:,:,:,isvice), &
202 & si(:,:,:,isinh4), &
203 & lbc(:,ibice(isinh4),ng))
204# endif
205
206 CALL ice_tibc_tile (ng, tile, model, &
207 & lbi, ubi, lbj, ubj, &
208 & liold, linew, &
209 & si(:,:,:,isuice), &
210 & si(:,:,:,isvice), &
211 & si(:,:,:,ishice), &
212 & si(:,:,:,istice), &
213 & si(:,:,:,isenth))
214!
215 IF (ewperiodic(ng).or.nsperiodic(ng)) THEN
216 CALL exchange_r2d_tile (ng, tile, &
217 & lbi, ubi, lbj, ubj, &
218 & si(:,:,linew,isaice))
219
220 CALL exchange_r2d_tile (ng, tile, &
221 & lbi, ubi, lbj, ubj, &
222 & si(:,:,linew,ishice))
223
224 CALL exchange_r2d_tile (ng, tile, &
225 & lbi, ubi, lbj, ubj, &
226 & si(:,:,linew,ishsno))
227
228 CALL exchange_r2d_tile (ng, tile, &
229 & lbi, ubi, lbj, ubj, &
230 & si(:,:,linew,istice))
231
232 CALL exchange_r2d_tile (ng, tile, &
233 & lbi, ubi, lbj, ubj, &
234 & si(:,:,linew,ishmel))
235
236 CALL exchange_r2d_tile (ng, tile, &
237 & lbi, ubi, lbj, ubj, &
238 & si(:,:,linew,isiage))
239
240# ifdef ICE_BIO
241 CALL exchange_r2d_tile (ng, tile, &
242 & lbi, ubi, lbj, ubj, &
243 & si(:,:,linew,isiphy))
244
245 CALL exchange_r2d_tile (ng, tile, &
246 & lbi, ubi, lbj, ubj, &
247 & si(:,:,linew,isino3))
248
249 CALL exchange_r2d_tile (ng, tile, &
250 & lbi, ubi, lbj, ubj, &
251 & si(:,:,linew,isinh4))
252
253 CALL exchange_r2d_tile (ng, tile, &
254 & lbi, ubi, lbj, ubj, &
255 & si(:,:,linew,isilog))
256# endif
257 END IF
258
259# ifdef DISTRIBUTE
260!
261 CALL mp_exchange2d (ng, tile, inlm, 4, &
262 & lbi, ubi, lbj, ubj, &
263 & nghostpoints, ewperiodic(ng), nsperiodic(ng), &
264 & si(:,:,linew,isaice), &
265 & si(:,:,linew,ishice), &
266 & si(:,:,linew,ishsno), &
267 & si(:,:,linew,ishmel))
268
269 CALL mp_exchange2d (ng, tile, inlm, 1, &
270 & lbi, ubi, lbj, ubj, &
271 & nghostpoints, ewperiodic(ng), nsperiodic(ng), &
272 & si(:,:,linew,istice))
273
274# ifdef ICE_BIO
275 CALL mp_exchange2d (ng, tile, inlm, 3, &
276 & lbi, ubi, lbj, ubj, &
277 & nghostpoints, ewperiodic(ng), nsperiodic(ng), &
278 & si(:,:,linew,isiphy), &
279 & si(:,:,linew,isino3), &
280 & si(:,:,linew,isinh4))
281# endif
282# endif
283!
284 RETURN
285 END SUBROUTINE ice_limit_tile
286#endif
287 END MODULE ice_limit_mod
subroutine exchange_r2d_tile(ng, tile, lbi, ubi, lbj, ubj, a)
integer, parameter isvice
Definition ice_mod.h:147
integer, parameter isino3
Definition ice_mod.h:154
integer, parameter isenth
Definition ice_mod.h:148
integer, parameter ishsno
Definition ice_mod.h:140
type(t_ice), dimension(:), allocatable ice
Definition ice_mod.h:283
integer, parameter istice
Definition ice_mod.h:145
integer, parameter isiphy
Definition ice_mod.h:153
integer, dimension(nices) ibice
Definition ice_mod.h:162
integer, parameter isilog
Definition ice_mod.h:156
integer, parameter ishmel
Definition ice_mod.h:139
integer, parameter isiage
Definition ice_mod.h:141
integer, parameter isaice
Definition ice_mod.h:137
real(r8), dimension(:), allocatable max_ai
Definition ice_mod.h:242
integer, parameter isinh4
Definition ice_mod.h:155
integer, parameter isuice
Definition ice_mod.h:146
integer, parameter ishice
Definition ice_mod.h:138
integer, parameter inlm
Definition mod_param.F:662
integer nghostpoints
Definition mod_param.F:710
type(t_lbc), dimension(:,:,:), allocatable lbc
Definition mod_param.F:375
logical, dimension(:), allocatable ewperiodic
logical, dimension(:), allocatable nsperiodic
subroutine mp_exchange2d(ng, tile, model, nvar, lbi, ubi, lbj, ubj, nghost, ew_periodic, ns_periodic, a, b, c, d)
recursive subroutine wclock_off(ng, model, region, line, routine)
Definition timers.F:148
recursive subroutine wclock_on(ng, model, region, line, routine)
Definition timers.F:3