New URL for NEMO forge!   http://forge.nemo-ocean.eu

Since March 2022 along with NEMO 4.2 release, the code development moved to a self-hosted GitLab.
This present forge is now archived and remained online for history.
iceforcing.F90 in NEMO/trunk/NEMOGCM/NEMO/ICE_SRC – NEMO

source: NEMO/trunk/NEMOGCM/NEMO/ICE_SRC/iceforcing.F90 @ 9594

Last change on this file since 9594 was 9570, checked in by nicolasmartin, 6 years ago

Global renaming for core routines (./NEMO)

  • Folders
    • LIM_SRC_3 -> ICE_SRC
    • OPA_SRC -> OCE_SRC
  • CPP key: key_lim3 -> key_si3
  • Modules, (sub)routines and variables names
    • MPI: mpi_comm_opa -> mpi_comm_oce, MPI_COMM_OPA -> MPI_COMM_OCE, mpi_init_opa -> mpi_init_oce
    • AGRIF: agrif_opa_* -> agrif_oce_*, agrif_lim3_* -> agrif_si3_* and few more
    • TOP-PISCES: p.zlim -> p.zice, namp.zlim -> namp.zice
  • Comments
    • NEMO/OPA -> NEMO/OCE
    • ESIM|LIM3 -> SI3
File size: 16.9 KB
Line 
1MODULE iceforcing
2   !!======================================================================
3   !!                       ***  MODULE  iceforcing  ***
4   !! Sea-Ice :   air-ice forcing fields
5   !!=====================================================================
6   !! History :  4.0  ! 2017-08  (C. Rousset) Original code
7   !!----------------------------------------------------------------------
8#if defined key_si3
9   !!----------------------------------------------------------------------
10   !!   'key_si3' :                                     SI3 sea-ice model
11   !!----------------------------------------------------------------------
12   USE oce            ! ocean dynamics and tracers
13   USE dom_oce        ! ocean space and time domain
14   USE ice            ! sea-ice: variables
15   USE sbc_oce        ! Surface boundary condition: ocean fields
16   USE sbc_ice        ! Surface boundary condition: ice   fields
17   USE usrdef_sbc     ! Surface boundary condition: user defined
18   USE sbcblk         ! Surface boundary condition: bulk
19   USE sbccpl         ! Surface boundary condition: coupled interface
20   USE icealb         ! sea-ice: albedo
21   !
22   USE in_out_manager ! I/O manager
23   USE iom            ! I/O manager library
24   USE lib_mpp        ! MPP library
25   USE lib_fortran    ! fortran utilities (glob_sum + no signed zero)
26   USE lbclnk         ! lateral boundary conditions (or mpp links)
27   USE timing         ! Timing
28
29   IMPLICIT NONE
30   PRIVATE
31
32   PUBLIC ice_forcing_tau   ! called by icestp.F90
33   PUBLIC ice_forcing_flx   ! called by icestp.F90
34   PUBLIC ice_forcing_init  ! called by icestp.F90
35
36   !! * Substitutions
37#  include "vectopt_loop_substitute.h90"
38   !!----------------------------------------------------------------------
39   !! NEMO/ICE 4.0 , UCL NEMO Consortium (2017)
40   !! $Id: icestp.F90 8319 2017-07-11 15:00:44Z clem $
41   !! Software governed by the CeCILL licence     (NEMOGCM/NEMO_CeCILL.txt)
42   !!----------------------------------------------------------------------
43CONTAINS
44
45   SUBROUTINE ice_forcing_tau( kt, ksbc, utau_ice, vtau_ice )
46      !!-------------------------------------------------------------------
47      !!                  ***  ROUTINE ice_forcing_tau  ***
48      !!
49      !! ** Purpose : provide surface boundary condition for sea ice (momentum)
50      !!
51      !! ** Action  : It provides the following fields:
52      !!              utau_ice, vtau_ice : surface ice stress (U- & V-points) [N/m2]
53      !!-------------------------------------------------------------------
54      INTEGER                     , INTENT(in   ) ::   kt                   ! ocean time step
55      INTEGER                     , INTENT(in   ) ::   ksbc                 ! type of sbc flux
56      REAL(wp), DIMENSION(jpi,jpj), INTENT(  out) ::   utau_ice, vtau_ice   ! air-ice stress   [N/m2]
57      !!
58      INTEGER  ::   ji, jj                 ! dummy loop index
59      REAL(wp), DIMENSION(jpi,jpj) ::   zutau_ice, zvtau_ice 
60      !!-------------------------------------------------------------------
61      !
62      IF( ln_timing )   CALL timing_start('ice_forcing')
63      !
64      IF( kt == nit000 .AND. lwp ) THEN
65         WRITE(numout,*)
66         WRITE(numout,*)'ice_forcing_tau: Surface boundary condition for sea ice (momentum)'
67         WRITE(numout,*)'~~~~~~~~~~~~~~~'
68      ENDIF
69      !
70      SELECT CASE( ksbc )
71         CASE( jp_usr     )   ;    CALL usrdef_sbc_ice_tau( kt )                 ! user defined formulation
72         CASE( jp_blk     )   ;    CALL blk_ice_tau                              ! Bulk         formulation
73         CASE( jp_purecpl )   ;    CALL sbc_cpl_ice_tau( utau_ice , vtau_ice )   ! Coupled      formulation
74      END SELECT
75      !
76      IF( ln_mixcpl) THEN                                                        ! Case of a mixed Bulk/Coupled formulation
77                                   CALL sbc_cpl_ice_tau( zutau_ice , zvtau_ice )
78         DO jj = 2, jpjm1
79            DO ji = 2, jpim1
80               utau_ice(ji,jj) = utau_ice(ji,jj) * xcplmask(ji,jj,0) + zutau_ice(ji,jj) * ( 1. - xcplmask(ji,jj,0) )
81               vtau_ice(ji,jj) = vtau_ice(ji,jj) * xcplmask(ji,jj,0) + zvtau_ice(ji,jj) * ( 1. - xcplmask(ji,jj,0) )
82            END DO
83         END DO
84         CALL lbc_lnk_multi( utau_ice, 'U', -1., vtau_ice, 'V', -1. )
85      ENDIF
86      !
87      IF( ln_timing )   CALL timing_stop('ice_forcing')
88      !
89   END SUBROUTINE ice_forcing_tau
90
91   
92   SUBROUTINE ice_forcing_flx( kt, ksbc )
93      !!-------------------------------------------------------------------
94      !!                  ***  ROUTINE ice_forcing_flx  ***
95      !!
96      !! ** Purpose : provide surface boundary condition for sea ice (flux)
97      !!
98      !! ** Action  : It provides the following fields used in sea ice model:
99      !!                emp_oce , emp_ice                        = E-P over ocean and sea ice                    [Kg/m2/s]
100      !!                sprecip                                  = solid precipitation                           [Kg/m2/s]
101      !!                evap_ice                                 = sublimation                                   [Kg/m2/s]
102      !!                qsr_tot , qns_tot                        = solar & non solar heat flux (total)           [W/m2]
103      !!                qsr_ice , qns_ice                        = solar & non solar heat flux over ice          [W/m2]
104      !!                dqns_ice                                 = non solar  heat sensistivity                  [W/m2]
105      !!                qemp_oce, qemp_ice, qprec_ice, qevap_ice = sensible heat (associated with evap & precip) [W/m2]
106      !!            + some fields that are not used outside this module:
107      !!                qla_ice                                  = latent heat flux over ice                     [W/m2]
108      !!                dqla_ice                                 = latent heat sensistivity                      [W/m2]
109      !!                tprecip                                  = total  precipitation                          [Kg/m2/s]
110      !!                alb_ice                                  = albedo above sea ice
111      !!-------------------------------------------------------------------
112      INTEGER, INTENT(in) ::   kt     ! ocean time step
113      INTEGER, INTENT(in) ::   ksbc   ! flux formulation (user defined, bulk or Pure Coupled)
114      !
115      INTEGER  ::   ji, jj, jl                                ! dummy loop index
116      REAL(wp), DIMENSION(jpi,jpj,jpl) ::   zalb_os, zalb_cs  ! ice albedo under overcast/clear sky
117      REAL(wp), DIMENSION(jpi,jpj)     ::   zalb              ! 2D workspace
118      !!--------------------------------------------------------------------
119      !
120      IF( ln_timing )   CALL timing_start('ice_forcing_flx')
121
122      IF( kt == nit000 .AND. lwp ) THEN
123         WRITE(numout,*)
124         WRITE(numout,*)'ice_forcing_flx: Surface boundary condition for sea ice (flux)'
125         WRITE(numout,*)'~~~~~~~~~~~~~~~'
126      ENDIF
127
128      ! --- cloud-sky and overcast-sky ice albedos --- !
129      CALL ice_alb( t_su, h_i, h_s, ln_pnd_alb, a_ip_frac, h_ip, zalb_cs, zalb_os )
130
131      ! albedo depends on cloud fraction because of non-linear spectral effects
132!!gm cldf_ice is a real, DOCTOR naming rule: start with cd means CHARACTER passed in argument !
133      alb_ice(:,:,:) = ( 1. - cldf_ice ) * zalb_cs(:,:,:) + cldf_ice * zalb_os(:,:,:)
134      !
135      !
136      SELECT CASE( ksbc )   !== fluxes over sea ice ==!
137      !
138      CASE( jp_usr )              !--- user defined formulation
139                                  CALL usrdef_sbc_ice_flx( kt, h_s, h_i )
140      CASE( jp_blk )              !--- bulk formulation
141                                  CALL blk_ice_flx    ( t_su, h_s, h_i, alb_ice )    !
142         IF( ln_mixcpl        )   CALL sbc_cpl_ice_flx( picefr=at_i_b, palbi=alb_ice, psst=sst_m, pist=t_su, phs=h_s, phi=h_i )
143         IF( nn_flxdist /= -1 )   CALL ice_flx_dist   ( t_su, alb_ice, qns_ice, qsr_ice, dqns_ice, evap_ice, devap_ice, nn_flxdist )
144         SELECT CASE( nice_jules )
145         CASE( np_jules_ACTIVE )  !    compute conduction flux and surface temperature (as in Jules surface module)
146                                  CALL blk_ice_qcn    ( nn_virtual_itd, t_su, t_bo, h_s, h_i )
147         END SELECT
148      CASE ( jp_purecpl )         !--- coupled formulation
149                                  CALL sbc_cpl_ice_flx( picefr=at_i_b, palbi=alb_ice, psst=sst_m, pist=t_su, phs=h_s, phi=h_i )
150         IF( nn_flxdist /= -1 )   CALL ice_flx_dist   ( t_su, alb_ice, qns_ice, qsr_ice, dqns_ice, evap_ice, devap_ice, nn_flxdist )
151      END SELECT
152
153      !--- output ice albedo and surface albedo ---!
154      IF( iom_use('icealb') ) THEN
155         WHERE( at_i_b <= epsi06 )   ;   zalb(:,:) = rn_alb_oce
156         ELSEWHERE                   ;   zalb(:,:) = SUM( alb_ice * a_i_b, dim=3 ) / at_i_b
157         END WHERE
158         CALL iom_put( "icealb" , zalb(:,:) )
159      ENDIF
160      IF( iom_use('albedo') ) THEN
161         zalb(:,:) = SUM( alb_ice * a_i_b, dim=3 ) + rn_alb_oce * ( 1._wp - at_i_b )
162         CALL iom_put( "albedo" , zalb(:,:) )
163      ENDIF
164      !
165      IF( ln_timing )   CALL timing_stop('ice_forcing_flx')
166      !
167   END SUBROUTINE ice_forcing_flx
168
169
170   SUBROUTINE ice_flx_dist( ptn_ice, palb_ice, pqns_ice, pqsr_ice, pdqn_ice, pevap_ice, pdevap_ice, k_iceflx )
171      !!-------------------------------------------------------------------
172      !!                  ***  ROUTINE ice_flx_dist  ***
173      !!
174      !! ** Purpose :   update the ice surface boundary condition by averaging
175      !!              and/or redistributing fluxes on ice categories
176      !!
177      !! ** Method  :   average then redistribute
178      !!
179      !! ** Action  :   depends on k_iceflx
180      !!                = -1  Do nothing (needs N(cat) fluxes)
181      !!                =  0  Average N(cat) fluxes then apply the average over the N(cat) ice
182      !!                =  1  Average N(cat) fluxes then redistribute over the N(cat) ice
183      !!                                                 using T-ice and albedo sensitivity
184      !!                =  2  Redistribute a single flux over categories
185      !!-------------------------------------------------------------------
186      INTEGER                   , INTENT(in   ) ::   k_iceflx   ! redistributor
187      REAL(wp), DIMENSION(:,:,:), INTENT(in   ) ::   ptn_ice    ! ice surface temperature
188      REAL(wp), DIMENSION(:,:,:), INTENT(in   ) ::   palb_ice   ! ice albedo
189      REAL(wp), DIMENSION(:,:,:), INTENT(inout) ::   pqns_ice   ! non solar flux
190      REAL(wp), DIMENSION(:,:,:), INTENT(inout) ::   pqsr_ice   ! net solar flux
191      REAL(wp), DIMENSION(:,:,:), INTENT(inout) ::   pdqn_ice   ! non solar flux sensitivity
192      REAL(wp), DIMENSION(:,:,:), INTENT(inout) ::   pevap_ice  ! sublimation
193      REAL(wp), DIMENSION(:,:,:), INTENT(inout) ::   pdevap_ice ! sublimation sensitivity
194      !
195      INTEGER  ::   jl      ! dummy loop index
196      !
197      REAL(wp), DIMENSION(jpi,jpj) ::   z1_at_i   ! inverse of concentration
198      !
199      REAL(wp), ALLOCATABLE, DIMENSION(:,:) ::   z_qsr_m   ! Mean solar heat flux over all categories
200      REAL(wp), ALLOCATABLE, DIMENSION(:,:) ::   z_qns_m   ! Mean non solar heat flux over all categories
201      REAL(wp), ALLOCATABLE, DIMENSION(:,:) ::   z_evap_m  ! Mean sublimation over all categories
202      REAL(wp), ALLOCATABLE, DIMENSION(:,:) ::   z_dqn_m   ! Mean d(qns)/dT over all categories
203      REAL(wp), ALLOCATABLE, DIMENSION(:,:) ::   z_devap_m ! Mean d(evap)/dT over all categories
204      REAL(wp), ALLOCATABLE, DIMENSION(:,:) ::   zalb_m    ! Mean albedo over all categories
205      REAL(wp), ALLOCATABLE, DIMENSION(:,:) ::   ztem_m    ! Mean temperature over all categories
206      !!----------------------------------------------------------------------
207      !
208      WHERE ( at_i (:,:) > 0._wp )   ; z1_at_i(:,:) = 1._wp / at_i (:,:)
209      ELSEWHERE                      ; z1_at_i(:,:) = 0._wp
210      END WHERE
211     
212      SELECT CASE( k_iceflx )       !==  averaged on all ice categories  ==!
213      !
214      CASE( 0 , 1 )
215         !
216         ALLOCATE( z_qns_m(jpi,jpj), z_qsr_m(jpi,jpj), z_dqn_m(jpi,jpj), z_evap_m(jpi,jpj), z_devap_m(jpi,jpj) ) 
217         !
218         z_qns_m  (:,:) = SUM( a_i(:,:,:) * pqns_ice  (:,:,:) , dim=3 ) * z1_at_i(:,:)
219         z_qsr_m  (:,:) = SUM( a_i(:,:,:) * pqsr_ice  (:,:,:) , dim=3 ) * z1_at_i(:,:)
220         z_dqn_m  (:,:) = SUM( a_i(:,:,:) * pdqn_ice  (:,:,:) , dim=3 ) * z1_at_i(:,:)
221         z_evap_m (:,:) = SUM( a_i(:,:,:) * pevap_ice (:,:,:) , dim=3 ) * z1_at_i(:,:)
222         z_devap_m(:,:) = SUM( a_i(:,:,:) * pdevap_ice(:,:,:) , dim=3 ) * z1_at_i(:,:)
223         DO jl = 1, jpl
224            pqns_ice  (:,:,jl) = z_qns_m (:,:)
225            pqsr_ice  (:,:,jl) = z_qsr_m (:,:)
226            pdqn_ice  (:,:,jl) = z_dqn_m  (:,:)
227            pevap_ice (:,:,jl) = z_evap_m(:,:)
228            pdevap_ice(:,:,jl) = z_devap_m(:,:)
229         END DO
230         !
231         DEALLOCATE( z_qns_m, z_qsr_m, z_dqn_m, z_evap_m, z_devap_m ) 
232         !
233      END SELECT
234      !
235      SELECT CASE( k_iceflx )       !==  redistribution on all ice categories  ==!
236      !
237      CASE( 1 , 2 )
238         !
239         ALLOCATE( zalb_m(jpi,jpj), ztem_m(jpi,jpj) ) 
240         !
241         zalb_m(:,:) = SUM( a_i(:,:,:) * palb_ice(:,:,:) , dim=3 ) * z1_at_i(:,:)
242         ztem_m(:,:) = SUM( a_i(:,:,:) * ptn_ice (:,:,:) , dim=3 ) * z1_at_i(:,:)
243         DO jl = 1, jpl
244            pqns_ice (:,:,jl) = pqns_ice (:,:,jl) + pdqn_ice  (:,:,jl) * ( ptn_ice(:,:,jl) - ztem_m(:,:) )
245            pevap_ice(:,:,jl) = pevap_ice(:,:,jl) + pdevap_ice(:,:,jl) * ( ptn_ice(:,:,jl) - ztem_m(:,:) )
246            pqsr_ice (:,:,jl) = pqsr_ice (:,:,jl) * ( 1._wp - palb_ice(:,:,jl) ) / ( 1._wp - zalb_m(:,:) )
247         END DO
248         !
249         DEALLOCATE( zalb_m, ztem_m ) 
250         !
251      END SELECT
252      !
253   END SUBROUTINE ice_flx_dist
254
255
256   SUBROUTINE ice_forcing_init
257      !!-------------------------------------------------------------------
258      !!                  ***  ROUTINE ice_forcing_init  ***
259      !!
260      !! ** Purpose :   Physical constants and parameters linked to the ice dynamics
261      !!     
262      !! ** Method  :   Read the namforcing namelist and check the ice-dynamic
263      !!              parameter values called at the first timestep (nit000)
264      !!
265      !! ** input   :   Namelist namforcing
266      !!-------------------------------------------------------------------
267      INTEGER ::   ios, ioptio   ! Local integer
268      !!
269      NAMELIST/namforcing/ rn_cio, rn_blow_s, nn_flxdist, nice_jules
270      !!-------------------------------------------------------------------
271      !
272      REWIND( numnam_ice_ref )         ! Namelist namforcing in reference namelist : Ice dynamics
273      READ  ( numnam_ice_ref, namforcing, IOSTAT = ios, ERR = 901)
274901   IF( ios /= 0 )   CALL ctl_nam ( ios , 'namforcing in reference namelist', lwp )
275      REWIND( numnam_ice_cfg )         ! Namelist namforcing in configuration namelist : Ice dynamics
276      READ  ( numnam_ice_cfg, namforcing, IOSTAT = ios, ERR = 902 )
277902   IF( ios >  0 )   CALL ctl_nam ( ios , 'namforcing in configuration namelist', lwp )
278      IF(lwm) WRITE( numoni, namforcing )
279      !
280      IF(lwp) THEN                     ! control print
281         WRITE(numout,*)
282         WRITE(numout,*) 'ice_forcing_init: ice parameters for ice dynamics '
283         WRITE(numout,*) '~~~~~~~~~~~~~~~~'
284         WRITE(numout,*) '   Namelist namforcing:'
285         WRITE(numout,*) '      drag coefficient for oceanic stress              rn_cio     = ', rn_cio
286         WRITE(numout,*) '      coefficient for ice-lead partition of snowfall   rn_blow_s  = ', rn_blow_s
287         WRITE(numout,*) '      Multicategory heat flux formulation              nn_flxdist = ', nn_flxdist
288         WRITE(numout,*) '      Jules coupling (0=no, 1=emulated, 2=active)      nice_jules = ', nice_jules
289      ENDIF
290      !
291      IF(lwp) WRITE(numout,*)
292      SELECT CASE( nn_flxdist )         ! SI3 Multi-category heat flux formulation
293      CASE( -1  )
294         IF(lwp) WRITE(numout,*) '   SI3: use per-category fluxes (nn_flxdist = -1) '
295      CASE(  0  )
296         IF(lwp) WRITE(numout,*) '   SI3: use average per-category fluxes (nn_flxdist = 0) '
297      CASE(  1  )
298         IF(lwp) WRITE(numout,*) '   SI3: use average then redistribute per-category fluxes (nn_flxdist = 1) '
299         IF( ln_cpl )         CALL ctl_stop( 'ice_thd_init: the chosen nn_flxdist for SI3 in coupled mode must be /=1' )
300      CASE(  2  )
301         IF(lwp) WRITE(numout,*) '   SI3: Redistribute a single flux over categories (nn_flxdist = 2) '
302         IF( .NOT. ln_cpl )   CALL ctl_stop( 'ice_thd_init: the chosen nn_flxdist for SI3 in forced mode must be /=2' )
303      CASE DEFAULT
304         CALL ctl_stop( 'ice_thd_init: SI3 option, nn_flxdist, should be between -1 and 2' )
305      END SELECT
306      !
307   END SUBROUTINE ice_forcing_init
308
309#else
310   !!----------------------------------------------------------------------
311   !!   Default option :         Empty module         NO SI3 sea-ice model
312   !!----------------------------------------------------------------------
313#endif
314
315   !!======================================================================
316END MODULE iceforcing
Note: See TracBrowser for help on using the repository browser.