4#if defined ICE_ADVECT || defined ICE_THERMO
37 SUBROUTINE ice_limit (ng, tile, model)
44 integer,
intent(in) :: ng, tile, model
48 character (len=*),
parameter :: MyFile = &
54 CALL wclock_on (ng, model, 42, __line__, myfile)
56 CALL ice_limit_tile (ng, tile, model, &
57 & lbi, ubi, lbj, ubj, &
58 & imins, imaxs, jmins, jmaxs, &
59 & liold(ng), linew(ng), &
62 CALL wclock_off (ng, model, 42, __line__, myfile)
66 END SUBROUTINE ice_limit
69 SUBROUTINE ice_limit_tile (ng, tile, model, &
70 & LBi, UBi, LBj, UBj, &
71 & IminS, ImaxS, JminS, JmaxS, &
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
84 real(r8),
intent(inout) :: Si(LBi:,LBj:,:,:)
86 real(r8),
intent(inout) :: Si(LBi:UBi,LBj:UBj,2,nIceS)
93# include "set_bounds.h"
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
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
124 si(i,j,linew,
isilog)=1.0_r8
132 CALL ice_bc2d_tile (ng, tile, model,
isaice, &
133 & lbi, ubi, lbj, ubj, &
134 & imins, imaxs, jmins, jmaxs, &
141 CALL ice_bc2d_tile (ng, tile, model,
ishice, &
142 & lbi, ubi, lbj, ubj, &
143 & imins, imaxs, jmins, jmaxs, &
150 CALL ice_bc2d_tile (ng, tile, model,
ishsno, &
151 & lbi, ubi, lbj, ubj, &
152 & imins, imaxs, jmins, jmaxs, &
159 CALL ice_bc2d_tile (ng, tile, model,
ishmel, &
160 & lbi, ubi, lbj, ubj, &
161 & imins, imaxs, jmins, jmaxs, &
168 CALL ice_bc2d_tile (ng, tile, model,
isiage, &
169 & lbi, ubi, lbj, ubj, &
170 & imins, imaxs, jmins, jmaxs, &
178 CALL ice_bc2d_tile (ng, tile, model,
isiphy, &
179 & lbi, ubi, lbj, ubj, &
180 & imins, imaxs, jmins, jmaxs, &
187 CALL ice_bc2d_tile (ng, tile, model,
isino3, &
188 & lbi, ubi, lbj, ubj, &
189 & imins, imaxs, jmins, jmaxs, &
197 & lbi, ubi, lbj, ubj, &
198 & imins, imaxs, jmins, jmaxs, &
206 CALL ice_tibc_tile (ng, tile, model, &
207 & lbi, ubi, lbj, ubj, &
217 & lbi, ubi, lbj, ubj, &
221 & lbi, ubi, lbj, ubj, &
225 & lbi, ubi, lbj, ubj, &
229 & lbi, ubi, lbj, ubj, &
233 & lbi, ubi, lbj, ubj, &
237 & lbi, ubi, lbj, ubj, &
242 & lbi, ubi, lbj, ubj, &
246 & lbi, ubi, lbj, ubj, &
250 & lbi, ubi, lbj, ubj, &
254 & lbi, ubi, lbj, ubj, &
262 & lbi, ubi, lbj, ubj, &
270 & lbi, ubi, lbj, ubj, &
276 & lbi, ubi, lbj, ubj, &
285 END SUBROUTINE ice_limit_tile
subroutine exchange_r2d_tile(ng, tile, lbi, ubi, lbj, ubj, a)
integer, parameter isvice
integer, parameter isino3
integer, parameter isenth
integer, parameter ishsno
type(t_ice), dimension(:), allocatable ice
integer, parameter istice
integer, parameter isiphy
integer, dimension(nices) ibice
integer, parameter isilog
integer, parameter ishmel
integer, parameter isiage
integer, parameter isaice
real(r8), dimension(:), allocatable max_ai
integer, parameter isinh4
integer, parameter isuice
integer, parameter ishice
type(t_lbc), dimension(:,:,:), allocatable lbc
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)
recursive subroutine wclock_on(ng, model, region, line, routine)