1 | MODULE sbc_ice |
---|
2 | !!====================================================================== |
---|
3 | !! *** MODULE sbc_ice *** |
---|
4 | !! Surface module - SI3 & CICE: parameters & variables defined in memory |
---|
5 | !!====================================================================== |
---|
6 | !! History : 3.0 ! 2006-08 (G. Madec) Surface module |
---|
7 | !! 3.2 ! 2009-06 (S. Masson) merge with ice_oce |
---|
8 | !! 3.3.1 ! 2011-01 (A. R. Porter, STFC Daresbury) dynamical allocation |
---|
9 | !! 3.4 ! 2011-11 (C. Harris) CICE added as an option |
---|
10 | !! 4.0 ! 2018 (many people) SI3 compatibility |
---|
11 | !!---------------------------------------------------------------------- |
---|
12 | #if defined key_si3 || defined key_cice |
---|
13 | !!---------------------------------------------------------------------- |
---|
14 | !! 'key_si3' or 'key_cice' : SI3 or CICE sea-ice model |
---|
15 | !!---------------------------------------------------------------------- |
---|
16 | USE par_oce ! ocean parameters |
---|
17 | USE sbc_oce ! surface boundary condition: ocean |
---|
18 | # if defined key_si3 |
---|
19 | USE ice ! SI3 parameters |
---|
20 | # endif |
---|
21 | # if defined key_cice |
---|
22 | USE ice_domain_size, only: ncat |
---|
23 | #endif |
---|
24 | USE lib_mpp ! MPP library |
---|
25 | USE in_out_manager ! I/O manager |
---|
26 | |
---|
27 | IMPLICIT NONE |
---|
28 | PRIVATE |
---|
29 | |
---|
30 | PUBLIC sbc_ice_alloc ! called in sbcmod.F90 or sbcice_cice.F90 |
---|
31 | |
---|
32 | # if defined key_si3 |
---|
33 | LOGICAL , PUBLIC, PARAMETER :: lk_si3 = .TRUE. !: SI3 ice model |
---|
34 | LOGICAL , PUBLIC, PARAMETER :: lk_cice = .FALSE. !: no CICE |
---|
35 | # endif |
---|
36 | # if defined key_cice |
---|
37 | LOGICAL , PUBLIC, PARAMETER :: lk_si3 = .FALSE. !: no SI3 |
---|
38 | LOGICAL , PUBLIC, PARAMETER :: lk_cice = .TRUE. !: CICE ice model |
---|
39 | # endif |
---|
40 | |
---|
41 | REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:,:) :: qns_ice !: non solar heat flux over ice [W/m2] |
---|
42 | REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:,:) :: qsr_ice !: solar heat flux over ice [W/m2] |
---|
43 | REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:,:) :: qla_ice !: latent flux over ice [W/m2] |
---|
44 | REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:,:) :: dqla_ice !: latent sensibility over ice [W/m2/K] |
---|
45 | REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:,:) :: dqns_ice !: non solar heat flux over ice (LW+SEN+LA) [W/m2/K] |
---|
46 | REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:,:) :: tn_ice !: ice surface temperature [K] |
---|
47 | REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:,:) :: alb_ice !: ice albedo [-] |
---|
48 | |
---|
49 | REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:,:) :: qml_ice !: heat available for snow / ice surface melting [W/m2] |
---|
50 | REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:,:) :: qcn_ice !: heat conduction flux in the layer below surface [W/m2] |
---|
51 | REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:,:) :: qtr_ice_top !: solar flux transmitted below the ice surface [W/m2] |
---|
52 | |
---|
53 | REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:) :: utau_ice !: atmos-ice u-stress. VP: I-pt ; EVP: U,V-pts [N/m2] |
---|
54 | REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:) :: vtau_ice !: atmos-ice v-stress. VP: I-pt ; EVP: U,V-pts [N/m2] |
---|
55 | REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:) :: emp_ice !: sublimation - precip over sea ice [kg/m2/s] |
---|
56 | |
---|
57 | REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:,:) :: topmelt !: category topmelt |
---|
58 | REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:,:) :: botmelt !: category botmelt |
---|
59 | |
---|
60 | #if defined key_si3 |
---|
61 | REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:,:) :: evap_ice !: sublimation [kg/m2/s] |
---|
62 | REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:,:) :: devap_ice !: sublimation sensitivity [kg/m2/s/K] |
---|
63 | REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:) :: qns_oce !: non solar heat flux over ocean [W/m2] |
---|
64 | REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:) :: qsr_oce !: non solar heat flux over ocean [W/m2] |
---|
65 | REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:) :: qemp_oce !: heat flux of precip and evap over ocean [W/m2] |
---|
66 | REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:) :: qemp_ice !: heat flux of precip and evap over ice [W/m2] |
---|
67 | REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:,:) :: qevap_ice !: heat flux of evap over ice [W/m2] |
---|
68 | REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:) :: qprec_ice !: enthalpy of precip over ice [J/m3] |
---|
69 | REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:) :: emp_oce !: evap - precip over ocean [kg/m2/s] |
---|
70 | REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:) :: wndm_ice !: wind speed module at T-point [m/s] |
---|
71 | REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:) :: sstfrz !: wind speed module at T-point [m/s] |
---|
72 | #endif |
---|
73 | |
---|
74 | #if defined key_cice |
---|
75 | ! |
---|
76 | ! for consistency with SI3, these are declared with three dimensions |
---|
77 | REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:,:) :: qlw_ice !: incoming long-wave |
---|
78 | ! |
---|
79 | ! other forcing arrays are two dimensional |
---|
80 | REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:) :: ss_iou !: x ice-ocean surface stress at NEMO U point |
---|
81 | REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:) :: ss_iov !: y ice-ocean surface stress at NEMO V point |
---|
82 | REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:) :: qatm_ice !: specific humidity |
---|
83 | REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:) :: wndi_ice !: i wind at T point |
---|
84 | REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:) :: wndj_ice !: j wind at T point |
---|
85 | REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:) :: nfrzmlt !: NEMO frzmlt |
---|
86 | REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:) :: fr_iu !: ice fraction at NEMO U point |
---|
87 | REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:) :: fr_iv !: ice fraction at NEMO V point |
---|
88 | |
---|
89 | ! variables used in the coupled interface |
---|
90 | INTEGER , PUBLIC, PARAMETER :: jpl = ncat |
---|
91 | REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:) :: u_ice, v_ice ! jpi, jpj |
---|
92 | |
---|
93 | ! already defined in ice.F90 for SI3 |
---|
94 | REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:,:) :: a_i |
---|
95 | REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:,:) :: h_i, h_s |
---|
96 | |
---|
97 | REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:) :: tatm_ice !: air temperature [K] |
---|
98 | #endif |
---|
99 | |
---|
100 | REAL(wp), PUBLIC, SAVE :: cldf_ice = 0.81 !: cloud fraction over sea ice, summer CLIO value [-] |
---|
101 | |
---|
102 | !! arrays relating to embedding ice in the ocean |
---|
103 | REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:) :: snwice_mass !: mass of snow and ice at current ice time step [Kg/m2] |
---|
104 | REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:) :: snwice_mass_b !: mass of snow and ice at previous ice time step [Kg/m2] |
---|
105 | REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:) :: snwice_fmass !: time evolution of mass of snow+ice [Kg/m2/s] |
---|
106 | |
---|
107 | !!---------------------------------------------------------------------- |
---|
108 | !! NEMO/OCE 4.0 , NEMO Consortium (2018) |
---|
109 | !! $Id$ |
---|
110 | !! Software governed by the CeCILL license (see ./LICENSE) |
---|
111 | !!---------------------------------------------------------------------- |
---|
112 | CONTAINS |
---|
113 | |
---|
114 | INTEGER FUNCTION sbc_ice_alloc() |
---|
115 | !!---------------------------------------------------------------------- |
---|
116 | !! *** FUNCTION sbc_ice_alloc *** |
---|
117 | !!---------------------------------------------------------------------- |
---|
118 | INTEGER :: ierr(4) |
---|
119 | !!---------------------------------------------------------------------- |
---|
120 | ierr(:) = 0 |
---|
121 | |
---|
122 | ALLOCATE( snwice_mass(jpi,jpj) , snwice_mass_b(jpi,jpj), snwice_fmass(jpi,jpj) , STAT=ierr(1) ) |
---|
123 | |
---|
124 | #if defined key_si3 |
---|
125 | ALLOCATE( qns_ice (jpi,jpj,jpl) , qsr_ice (jpi,jpj,jpl) , & |
---|
126 | & qla_ice (jpi,jpj,jpl) , dqla_ice (jpi,jpj,jpl) , & |
---|
127 | & dqns_ice(jpi,jpj,jpl) , tn_ice (jpi,jpj,jpl) , alb_ice (jpi,jpj,jpl) , & |
---|
128 | & qml_ice (jpi,jpj,jpl) , qcn_ice (jpi,jpj,jpl) , qtr_ice_top(jpi,jpj,jpl) , & |
---|
129 | & utau_ice(jpi,jpj) , vtau_ice (jpi,jpj) , wndm_ice (jpi,jpj) , & |
---|
130 | & evap_ice(jpi,jpj,jpl) , devap_ice(jpi,jpj,jpl) , qprec_ice (jpi,jpj) , & |
---|
131 | & qemp_ice(jpi,jpj) , qevap_ice(jpi,jpj,jpl) , qemp_oce (jpi,jpj) , & |
---|
132 | & qns_oce (jpi,jpj) , qsr_oce (jpi,jpj) , emp_oce (jpi,jpj) , & |
---|
133 | & emp_ice (jpi,jpj) , sstfrz (jpi,jpj) , STAT= ierr(2) ) |
---|
134 | #endif |
---|
135 | |
---|
136 | #if defined key_cice |
---|
137 | ALLOCATE( qla_ice(jpi,jpj,1) , qlw_ice(jpi,jpj,1) , qsr_ice(jpi,jpj,1) , & |
---|
138 | wndi_ice(jpi,jpj) , tatm_ice(jpi,jpj) , qatm_ice(jpi,jpj) , & |
---|
139 | wndj_ice(jpi,jpj) , nfrzmlt(jpi,jpj) , ss_iou(jpi,jpj) , & |
---|
140 | ss_iov(jpi,jpj) , fr_iu(jpi,jpj) , fr_iv(jpi,jpj) , & |
---|
141 | a_i(jpi,jpj,ncat) , topmelt(jpi,jpj,ncat) , botmelt(jpi,jpj,ncat) , & |
---|
142 | STAT= ierr(2) ) |
---|
143 | IF( ln_cpl ) ALLOCATE( u_ice(jpi,jpj) , tn_ice (jpi,jpj,1) , & |
---|
144 | & v_ice(jpi,jpj) , alb_ice(jpi,jpj,1) , & |
---|
145 | & emp_ice(jpi,jpj) , qns_ice(jpi,jpj,1) , dqns_ice(jpi,jpj,1) , & |
---|
146 | & STAT= ierr(3) ) |
---|
147 | IF( ln_cpl ) ALLOCATE( h_i(jpi,jpj,jpl) , h_s(jpi,jpj,jpl) , STAT=ierr(4) ) |
---|
148 | #endif |
---|
149 | |
---|
150 | sbc_ice_alloc = MAXVAL( ierr ) |
---|
151 | CALL mpp_sum ( 'sbc_ice', sbc_ice_alloc ) |
---|
152 | IF( sbc_ice_alloc > 0 ) CALL ctl_warn('sbc_ice_alloc: allocation of arrays failed') |
---|
153 | END FUNCTION sbc_ice_alloc |
---|
154 | |
---|
155 | #else |
---|
156 | !!---------------------------------------------------------------------- |
---|
157 | !! Default option NO SI3 or CICE sea-ice model |
---|
158 | !!---------------------------------------------------------------------- |
---|
159 | USE lib_mpp ! MPP library |
---|
160 | USE in_out_manager ! I/O manager |
---|
161 | |
---|
162 | IMPLICIT NONE |
---|
163 | PRIVATE |
---|
164 | |
---|
165 | PUBLIC sbc_ice_alloc ! |
---|
166 | |
---|
167 | LOGICAL , PUBLIC, PARAMETER :: lk_si3 = .FALSE. !: no SI3 ice model |
---|
168 | LOGICAL , PUBLIC, PARAMETER :: lk_cice = .FALSE. !: no CICE ice model |
---|
169 | REAL(wp) , PUBLIC, PARAMETER :: cldf_ice = 0.81 !: cloud fraction over sea ice, summer CLIO value [-] |
---|
170 | INTEGER , PUBLIC, PARAMETER :: jpl = 1 |
---|
171 | REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:) :: u_ice, v_ice ! jpi, jpj |
---|
172 | REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:,:) :: tn_ice, alb_ice, qns_ice, dqns_ice ! (jpi,jpj,jpl) |
---|
173 | REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:,:) :: a_i |
---|
174 | REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:) :: emp_ice |
---|
175 | REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:,:) :: qsr_ice |
---|
176 | REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:,:) :: h_i, h_s |
---|
177 | REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:,:) :: topmelt, botmelt |
---|
178 | ! |
---|
179 | !! arrays related to embedding ice in the ocean. |
---|
180 | !! These arrays need to be declared even if no ice model is required. |
---|
181 | !! In the no ice model or traditional levitating ice cases they contain only zeros |
---|
182 | !! --------------------- |
---|
183 | REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:) :: snwice_mass !: mass of snow and ice at current ice time step [Kg/m2] |
---|
184 | REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:) :: snwice_mass_b !: mass of snow and ice at previous ice time step [Kg/m2] |
---|
185 | REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:) :: snwice_fmass !: time evolution of mass of snow+ice [Kg/m2/s] |
---|
186 | !!---------------------------------------------------------------------- |
---|
187 | CONTAINS |
---|
188 | |
---|
189 | INTEGER FUNCTION sbc_ice_alloc() |
---|
190 | !!---------------------------------------------------------------------- |
---|
191 | !! *** FUNCTION sbc_ice_alloc *** |
---|
192 | !!---------------------------------------------------------------------- |
---|
193 | INTEGER :: ierr(1) |
---|
194 | !!---------------------------------------------------------------------- |
---|
195 | ierr(:) = 0 |
---|
196 | ALLOCATE( snwice_mass(jpi,jpj) , snwice_mass_b(jpi,jpj), snwice_fmass(jpi,jpj) , STAT=ierr(1) ) |
---|
197 | sbc_ice_alloc = MAXVAL( ierr ) |
---|
198 | CALL mpp_sum ( 'sbc_ice', sbc_ice_alloc ) |
---|
199 | IF( sbc_ice_alloc > 0 ) CALL ctl_warn('sbc_ice_alloc: allocation of arrays failed') |
---|
200 | END FUNCTION sbc_ice_alloc |
---|
201 | #endif |
---|
202 | |
---|
203 | !!====================================================================== |
---|
204 | END MODULE sbc_ice |
---|