ROMS
Loading...
Searching...
No Matches
seaice.F
Go to the documentation of this file.
1#include "cppdefs.h"
2 MODULE seaice_mod
3#ifdef ICE_MODEL
4!
5!git $Id$
6!=======================================================================
7! Copyright (c) 2002-2025 The ROMS Group !
8! Licensed under a MIT/X style license W. Paul Budgell !
9! See License_ROMS.md Katherine Hedstrom !
10!================================================== Hernan G. Arango ===
11! !
12! This module is the primary driver routine for the ROMS nonlinear !
13! sea ice model (Budgell, 2005; Durski and Kurapov, 2019, 2020). !
14! It advances forward the one-layer sea-ice and snow model. The ice !
15! thickness is defined as a single category within each grid cell !
16! with a possible layer of snow and or meltwater resting above. !
17! !
18!=======================================================================
19!
20 USE mod_param
21 USE mod_parallel
22 USE mod_scalars
23 USE mod_stepping
24 USE mod_ice
25 USE mod_forces
26!
27 USE ice_spdiw_mod, ONLY : ice_spdiw
28 USE ice_vbc_mod, ONLY : ice_vbc
29# ifdef ICE_THERMO
30 USE ice_thermo_mod, ONLY : ice_thermo
31# endif
32# if defined ICE_MOMENTUM && defined ICE_EVP
33 USE ice_evp_mod, ONLY : ice_evp
34 USE ice_evp_sig_mod, ONLY : ice_evp_sig
35 USE ice_elastic_mod, ONLY : ice_elastic
36# endif
37# ifdef ICE_ADVECT
38 USE ice_advect_mod, ONLY : ice_advect
39 USE ice_enthalpy_mod, ONLY : ice_enthalpy
40# endif
41# if defined ICE_ADVECT || defined ICE_THERMO
42 USE ice_limit_mod, ONLY : ice_limit
43# endif
45!
46 implicit none
47!
48 PUBLIC :: seaice
49 PRIVATE
50!
51 CONTAINS
52!
53 SUBROUTINE seaice (model)
54!
55!=======================================================================
56! !
57! Sea-ice model timestepping driver. !
58! !
59!=======================================================================
60!
61! Imported variable declarations.
62!
63 integer, intent(in) :: model
64!
65! Local variable declarations.
66!
67 integer :: tile
68 integer :: ig, ng, nl, my_iEVP, nelas
69!
70 real(r8), parameter :: dt_large = 1.0e+23_r8
71!
72 character (len=*), parameter :: MyFile = &
73 & __FILE__
74!
75!=======================================================================
76! Timestep sea-ice model equations.
77!=======================================================================
78!
79! In nesting applications, the number of nesting layers (NestLayers) is
80! used to facilitate refinement grids and composite/refinament grids
81! combinations. Otherwise, the solution it is looped once for a single
82! grid application (NestLayers = 1).
83!
84 nest_layer : DO nl=1,nestlayers
85!
86!-----------------------------------------------------------------------
87! Compute the ice-ocean shear.
88!-----------------------------------------------------------------------
89!
90 DO ig=1,gridsinlayer(nl)
91 ng=gridnumber(ig,nl)
92 liold(ng)=linew(ng)
93 linew(ng)=3-liold(ng)
94 DO tile=first_tile(ng),last_tile(ng),+1
95 CALL ice_spdiw (ng, tile, model)
96 END DO
97!$OMP BARRIER
98 END DO
99!
100!-----------------------------------------------------------------------
101! Compute the stresses on the ice from the air and water.
102!-----------------------------------------------------------------------
103!
104 DO ig=1,gridsinlayer(nl)
105 ng=gridnumber(ig,nl)
106 DO tile=first_tile(ng),last_tile(ng),+1
107 CALL ice_vbc (ng, tile, model)
108 END DO
109!$OMP BARRIER
110 END DO
111
112# ifdef ICE_MOMENTUM
113# ifdef ICE_EVP
114!
115!-----------------------------------------------------------------------
116! Compute the internal ice stresses according to the
117! Elastic-Viscous-Plastic (EVP) rheology.
118!-----------------------------------------------------------------------
119!
120 DO ig=1,gridsinlayer(nl)
121 ng=gridnumber(ig,nl)
122 nelas=nevp(ng)
123 liuol(ng)=liunw(ng)
124 liunw(ng)=3-liuol(ng)
125 dtevp(ng)=dtice(ng)/real(nevp(ng), r8)
126
127 DO my_ievp=1,nelas
128 lieol(ng)=lienw(ng)
129 lienw(ng)=3-lieol(ng)
130 ievp(ng)=my_ievp
131!
132! Compute EVP rheology parameters.
133!
134 DO tile=first_tile(ng),last_tile(ng),+1
135 CALL ice_evp (ng, tile, model)
136 END DO
137!$OMP BARRIER
138!
139! Time-step the EVP stresses term.
140!
141 DO tile=last_tile(ng),first_tile(ng),-1
142 CALL ice_evp_sig (ng, tile, model)
143 END DO
144!$OMP BARRIER
145!
146! Time-step the ice momentum equations.
147!
148 DO tile=first_tile(ng),last_tile(ng),+1
149 CALL ice_elastic (ng, tile, model)
150 END DO
151!$OMP BARRIER
152 END DO
153 END DO
154
155# else
156 WRITE (stdout,'(4a)') 'SEAICE: An ice rheology must be ' &
157 & 'defined if ', uppercase('ice_momentum'), &
158 & ' option is specified'
159 exit_flag=5
160 IF ((founderror(exit_flag, noerror, __line__, myfile)) RETURN
161# endif
162# endif
163
164# ifdef ICE_ADVECT
165!
166!-----------------------------------------------------------------------
167! Compute the enthalpy of the combined ice/brine system.
168!-----------------------------------------------------------------------
169!
170 DO ig=1,gridsinlayer(nl)
171 ng=gridnumber(ig,nl)
172 DO tile=first_tile(ng),last_tile(ng),+1
173 CALL ice_enthalpy (ng, tile, model)
174 END DO
175!$OMP BARRIER
176 END DO
177!
178!-----------------------------------------------------------------------
179! Compute the advection of the ice tracer fields. Impose limiter for
180! monotonic positive definitive advection.
181!-----------------------------------------------------------------------
182!
183 DO ig=1,gridsinlayer(nl)
184 ng=gridnumber(ig,nl)
185 DO tile=first_tile(ng),last_tile(ng),+1
186 CALL ice_advect (ng, tile, model)
187 CALL ice_limit (ng, tile, model)
188 END DO
189!$OMP BARRIER
190 END DO
191# endif
192
193# ifdef ICE_THERMO
194!
195!-----------------------------------------------------------------------
196! Compute the ice thermodynamics.
197!-----------------------------------------------------------------------
198!
199 DO ig=1,gridsinlayer(nl)
200 ng=gridnumber(ig,nl)
201 DO tile=first_tile(ng),last_tile(ng),+1
202 CALL ice_thermo (ng, tile, model)
203 CALL ice_limit(ng, tile, model)
204 END DO
205!$OMP BARRIER
206 END DO
207# endif
208
209 END DO nest_layer
210!
211 RETURN
212 END SUBROUTINE seaice
213!
214#endif
215 END MODULE seaice_mod
subroutine, public ice_advect(ng, tile, model)
Definition ice_smolar.h:46
subroutine, public ice_thermo(ng, tile, model)
Definition ice_mk.h:109
integer, dimension(:), allocatable dtice
Definition ice_mod.h:217
integer, dimension(:), allocatable ievp
Definition ice_mod.h:212
integer, dimension(:), allocatable dtevp
Definition ice_mod.h:218
integer, dimension(:), allocatable nevp
Definition ice_mod.h:213
integer, dimension(:), allocatable first_tile
integer, dimension(:), allocatable last_tile
integer, dimension(:,:), allocatable gridnumber
Definition mod_param.F:127
integer nestlayers
Definition mod_param.F:118
integer, dimension(:), allocatable gridsinlayer
Definition mod_param.F:122
integer exit_flag
integer noerror
character(len(sinp)) function, public uppercase(sinp)
Definition strings.F:582
logical function, public founderror(flag, noerr, line, routine)
Definition strings.F:52