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 branches/2017/dev_r8183_ICEMODEL/NEMOGCM/NEMO/LIM_SRC_3 – NEMO

source: branches/2017/dev_r8183_ICEMODEL/NEMOGCM/NEMO/LIM_SRC_3/iceforcing.F90 @ 8531

Last change on this file since 8531 was 8531, checked in by clem, 7 years ago

changes in style - part6 - more clarity (still not finished)

File size: 16.9 KB
RevLine 
[8404]1MODULE iceforcing
2   !!======================================================================
3   !!                       ***  MODULE  iceforcing  ***
[8486]4   !! Sea-Ice :   air-ice forcing fields
[8404]5   !!=====================================================================
6   !! History :  4.0  ! 2017-08  (C. Rousset) Original code
7   !!----------------------------------------------------------------------
8#if defined key_lim3
9   !!----------------------------------------------------------------------
10   !!   'key_lim3' :                                  LIM 3.0 sea-ice model
11   !!----------------------------------------------------------------------
[8486]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     ! user defined: surface boundary condition
18   USE sbcblk         ! Surface boundary condition: bulk
19   USE sbccpl         ! Surface boundary condition: coupled interface
20   USE icealb         ! ice albedo
[8404]21   !
[8486]22   USE iom            ! I/O manager library
23   USE in_out_manager ! I/O manager
24   USE lbclnk         ! lateral boundary condition - MPP link
25   USE lib_mpp        ! MPP library
26   USE lib_fortran    !
27   USE timing         ! Timing
[8404]28
29   IMPLICIT NONE
30   PRIVATE
31
[8531]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
[8404]35
36   !! * Substitutions
37#  include "vectopt_loop_substitute.h90"
38   !!----------------------------------------------------------------------
[8486]39   !! NEMO/ICE 4.0 , UCL NEMO Consortium (2017)
[8404]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 ( 1 = user defined formulation,
56                                       !                    3 = bulk formulation,
57                                       !                    4 = Pure Coupled formulation)
58      REAL(wp), DIMENSION(jpi,jpj), INTENT(out) ::   utau_ice, vtau_ice 
59      !!
60      INTEGER  ::   ji, jj                 ! dummy loop index
61      REAL(wp), DIMENSION(jpi,jpj) ::   zutau_ice, zvtau_ice 
62      !!----------------------------------------------------------------------
63
64      IF( nn_timing == 1 )   CALL timing_start('ice_forcing_tau')
65
[8426]66      IF( kt == nit000 .AND. lwp ) THEN
67         WRITE(numout,*)
[8512]68         WRITE(numout,*)'ice_forcing_tau: Surface boundary condition for sea ice (momentum)'
[8426]69         WRITE(numout,*)'~~~~~~~~~~~~~~~'
70      ENDIF
71
[8404]72      SELECT CASE( ksbc )
73         CASE( jp_usr     )   ;    CALL usrdef_sbc_ice_tau( kt )                 ! user defined formulation
74         CASE( jp_blk     )   ;    CALL blk_ice_tau                              ! Bulk formulation
75         CASE( jp_purecpl )   ;    CALL sbc_cpl_ice_tau( utau_ice , vtau_ice )   ! Coupled   formulation
76      END SELECT
77
78      IF( ln_mixcpl) THEN                                                        ! Case of a mixed Bulk/Coupled formulation
79                                   CALL sbc_cpl_ice_tau( zutau_ice , zvtau_ice )
80         DO jj = 2, jpjm1
81            DO ji = 2, jpim1
82               utau_ice(ji,jj) = utau_ice(ji,jj) * xcplmask(ji,jj,0) + zutau_ice(ji,jj) * ( 1. - xcplmask(ji,jj,0) )
83               vtau_ice(ji,jj) = vtau_ice(ji,jj) * xcplmask(ji,jj,0) + zvtau_ice(ji,jj) * ( 1. - xcplmask(ji,jj,0) )
84            END DO
85         END DO
[8426]86         CALL lbc_lnk_multi( utau_ice, 'U', -1., vtau_ice, 'V', -1. )
[8404]87      ENDIF
88
89      IF( nn_timing == 1 )   CALL timing_stop('ice_forcing_tau')
90      !
91   END SUBROUTINE ice_forcing_tau
92
93   
94   SUBROUTINE ice_forcing_flx( kt, ksbc )
95      !!---------------------------------------------------------------------
96      !!                  ***  ROUTINE ice_forcing_flx  ***
97      !!
98      !! ** Purpose : provide surface boundary condition for sea ice (flux)
99      !!
100      !! ** Action  : It provides the following fields used in sea ice model:
101      !!                fr1_i0  , fr2_i0                         = 1sr & 2nd fraction of qsr penetration in ice  [%]
102      !!                emp_oce , emp_ice                        = E-P over ocean and sea ice                    [Kg/m2/s]
103      !!                sprecip                                  = solid precipitation                           [Kg/m2/s]
104      !!                evap_ice                                 = sublimation                                   [Kg/m2/s]
105      !!                qsr_tot , qns_tot                        = solar & non solar heat flux (total)           [W/m2]
106      !!                qsr_ice , qns_ice                        = solar & non solar heat flux over ice          [W/m2]
107      !!                dqns_ice                                 = non solar  heat sensistivity                  [W/m2]
108      !!                qemp_oce, qemp_ice, qprec_ice, qevap_ice = sensible heat (associated with evap & precip) [W/m2]
109      !!            + some fields that are not used outside this module:
110      !!                qla_ice                                  = latent heat flux over ice                     [W/m2]
111      !!                dqla_ice                                 = latent heat sensistivity                      [W/m2]
112      !!                tprecip                                  = total  precipitation                          [Kg/m2/s]
113      !!                alb_ice                                  = albedo above sea ice
114      !!---------------------------------------------------------------------
[8486]115      INTEGER, INTENT(in) ::   kt     ! ocean time step
116      INTEGER, INTENT(in) ::   ksbc   ! flux formulation (user defined, bulk or Pure Coupled)
117      !
[8404]118      INTEGER  ::   ji, jj, jl                                ! dummy loop index
119      REAL(wp), DIMENSION(jpi,jpj,jpl) ::   zalb_os, zalb_cs  ! ice albedo under overcast/clear sky
120      REAL(wp), DIMENSION(jpi,jpj)     ::   zalb              ! 2D workspace
121      !!----------------------------------------------------------------------
[8486]122      !
[8404]123      IF( nn_timing == 1 )   CALL timing_start('ice_forcing_flx')
124
[8426]125      IF( kt == nit000 .AND. lwp ) THEN
126         WRITE(numout,*)
[8512]127         WRITE(numout,*)'ice_forcing_flx: Surface boundary condition for sea ice (flux)'
[8426]128         WRITE(numout,*)'~~~~~~~~~~~~~~~'
129      ENDIF
130
[8404]131      ! --- cloud-sky and overcast-sky ice albedos --- !
[8426]132      CALL ice_alb( t_su, ht_i, ht_s, a_ip_frac, h_ip, ln_pnd_rad, zalb_cs, zalb_os )
[8404]133
134      ! albedo depends on cloud fraction because of non-linear spectral effects
[8486]135!!gm cldf_ice is a real, DOCTOR naming rule: start with cd means CHARACTER passed in argument !
[8498]136      alb_ice(:,:,:) = ( 1. - cldf_ice ) * zalb_cs(:,:,:) + cldf_ice * zalb_os(:,:,:)
[8404]137     
[8486]138      SELECT CASE( ksbc )      !==  fluxes over sea ice  ==!
139      !
140      CASE( jp_usr )                !--- user defined formulation
141                                CALL usrdef_sbc_ice_flx( kt )
142         !
143      CASE( jp_blk )                !--- bulk formulation
144                                CALL blk_ice_flx( t_su, alb_ice )    !
145         IF( ln_mixcpl      )   CALL sbc_cpl_ice_flx( picefr=at_i_b, palbi=alb_ice, psst=sst_m, pist=t_su )
[8514]146         IF( nn_iceflx /= 2 )   CALL ice_flx_dist( t_su, alb_ice, qns_ice, qsr_ice, dqns_ice, evap_ice, devap_ice, nn_iceflx )
[8486]147         !
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 )
[8514]150         IF( nn_iceflx == 2 )   CALL ice_flx_dist( t_su, alb_ice, qns_ice, qsr_ice, dqns_ice, evap_ice, devap_ice, nn_iceflx )
[8486]151         !
[8404]152      END SELECT
153
[8486]154      IF( iom_use('icealb') ) THEN    !--- output ice albedo
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(:,:) )   ! ice albedo
159      ENDIF
[8404]160
[8486]161      IF( iom_use('albedo') ) THEN  !--- surface albedo
162         zalb(:,:) = SUM( alb_ice * a_i_b, dim=3 ) + rn_alb_oce * ( 1._wp - at_i_b )
163         CALL iom_put( "albedo" , zalb(:,:) )
164      ENDIF
[8404]165      !
[8486]166      IF( nn_timing == 1 )   CALL timing_stop('ice_forcing_flx')
[8404]167      !
168   END SUBROUTINE ice_forcing_flx
169
170
[8514]171   SUBROUTINE ice_flx_dist( ptn_ice, palb_ice, pqns_ice, pqsr_ice, pdqn_ice, pevap_ice, pdevap_ice, k_iceflx )
[8404]172      !!---------------------------------------------------------------------
[8426]173      !!                  ***  ROUTINE ice_flx_dist  ***
[8404]174      !!
[8486]175      !! ** Purpose :   update the ice surface boundary condition by averaging
176      !!              and/or redistributing fluxes on ice categories
[8404]177      !!
178      !! ** Method  :   average then redistribute
179      !!
[8514]180      !! ** Action  :   depends on k_iceflx
181      !!                = -1  Do nothing (needs N(cat) fluxes)
182      !!                =  0  Average N(cat) fluxes then apply the average over the N(cat) ice
183      !!                =  1  Average N(cat) fluxes then redistribute over the N(cat) ice
184      !!                                                 using T-ice and albedo sensitivity
185      !!                =  2  Redistribute a single flux over categories
[8404]186      !!---------------------------------------------------------------------
[8514]187      INTEGER                   , INTENT(in   ) ::   k_iceflx   ! redistributor
[8404]188      REAL(wp), DIMENSION(:,:,:), INTENT(in   ) ::   ptn_ice    ! ice surface temperature
189      REAL(wp), DIMENSION(:,:,:), INTENT(in   ) ::   palb_ice   ! ice albedo
190      REAL(wp), DIMENSION(:,:,:), INTENT(inout) ::   pqns_ice   ! non solar flux
191      REAL(wp), DIMENSION(:,:,:), INTENT(inout) ::   pqsr_ice   ! net solar flux
192      REAL(wp), DIMENSION(:,:,:), INTENT(inout) ::   pdqn_ice   ! non solar flux sensitivity
193      REAL(wp), DIMENSION(:,:,:), INTENT(inout) ::   pevap_ice  ! sublimation
194      REAL(wp), DIMENSION(:,:,:), INTENT(inout) ::   pdevap_ice ! sublimation sensitivity
195      !
196      INTEGER  ::   jl      ! dummy loop index
197      !
[8498]198      REAL(wp), DIMENSION(jpi,jpj) ::   z1_at_i   ! inverse of concentration
[8404]199      !
[8498]200      REAL(wp), ALLOCATABLE, DIMENSION(:,:) ::   z_qsr_m   ! Mean solar heat flux over all categories
201      REAL(wp), ALLOCATABLE, DIMENSION(:,:) ::   z_qns_m   ! Mean non solar heat flux over all categories
202      REAL(wp), ALLOCATABLE, DIMENSION(:,:) ::   z_evap_m  ! Mean sublimation over all categories
203      REAL(wp), ALLOCATABLE, DIMENSION(:,:) ::   z_dqn_m   ! Mean d(qns)/dT over all categories
204      REAL(wp), ALLOCATABLE, DIMENSION(:,:) ::   z_devap_m ! Mean d(evap)/dT over all categories
205      REAL(wp), ALLOCATABLE, DIMENSION(:,:) ::   zalb_m    ! Mean albedo over all categories
206      REAL(wp), ALLOCATABLE, DIMENSION(:,:) ::   ztem_m    ! Mean temperature over all categories
[8404]207      !!----------------------------------------------------------------------
208      !
[8426]209      IF( nn_timing == 1 )  CALL timing_start('ice_flx_dist')
[8404]210      !
[8498]211      WHERE ( at_i (:,:) > 0._wp )   ; z1_at_i(:,:) = 1._wp / at_i (:,:)
212      ELSEWHERE                      ; z1_at_i(:,:) = 0._wp
213      END WHERE
214     
[8514]215      SELECT CASE( k_iceflx )       !==  averaged on all ice categories  ==!
[8486]216      !
[8404]217      CASE( 0 , 1 )
[8498]218         !
219         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) ) 
220         !
221         z_qns_m  (:,:) = SUM( a_i(:,:,:) * pqns_ice  (:,:,:) , dim=3 ) * z1_at_i(:,:)
222         z_qsr_m  (:,:) = SUM( a_i(:,:,:) * pqsr_ice  (:,:,:) , dim=3 ) * z1_at_i(:,:)
223         z_dqn_m  (:,:) = SUM( a_i(:,:,:) * pdqn_ice  (:,:,:) , dim=3 ) * z1_at_i(:,:)
224         z_evap_m (:,:) = SUM( a_i(:,:,:) * pevap_ice (:,:,:) , dim=3 ) * z1_at_i(:,:)
225         z_devap_m(:,:) = SUM( a_i(:,:,:) * pdevap_ice(:,:,:) , dim=3 ) * z1_at_i(:,:)
[8404]226         DO jl = 1, jpl
[8486]227            pqns_ice  (:,:,jl) = z_qns_m (:,:)
228            pqsr_ice  (:,:,jl) = z_qsr_m (:,:)
[8498]229            pdqn_ice  (:,:,jl) = z_dqn_m  (:,:)
[8486]230            pevap_ice (:,:,jl) = z_evap_m(:,:)
[8498]231            pdevap_ice(:,:,jl) = z_devap_m(:,:)
[8404]232         END DO
233         !
[8498]234         DEALLOCATE( z_qns_m, z_qsr_m, z_dqn_m, z_evap_m, z_devap_m ) 
235         !
[8404]236      END SELECT
237      !
[8514]238      SELECT CASE( k_iceflx )       !==  redistribution on all ice categories  ==!
[8498]239      !
[8404]240      CASE( 1 , 2 )
241         !
[8498]242         ALLOCATE( zalb_m(jpi,jpj), ztem_m(jpi,jpj) ) 
243         !
244         zalb_m(:,:) = SUM( a_i(:,:,:) * palb_ice(:,:,:) , dim=3 ) * z1_at_i(:,:)
245         ztem_m(:,:) = SUM( a_i(:,:,:) * ptn_ice (:,:,:) , dim=3 ) * z1_at_i(:,:)
[8404]246         DO jl = 1, jpl
247            pqns_ice (:,:,jl) = pqns_ice (:,:,jl) + pdqn_ice  (:,:,jl) * ( ptn_ice(:,:,jl) - ztem_m(:,:) )
248            pevap_ice(:,:,jl) = pevap_ice(:,:,jl) + pdevap_ice(:,:,jl) * ( ptn_ice(:,:,jl) - ztem_m(:,:) )
249            pqsr_ice (:,:,jl) = pqsr_ice (:,:,jl) * ( 1._wp - palb_ice(:,:,jl) ) / ( 1._wp - zalb_m(:,:) )
250         END DO
251         !
[8498]252         DEALLOCATE( zalb_m, ztem_m ) 
253         !
[8404]254      END SELECT
255      !
[8426]256      IF( nn_timing == 1 )  CALL timing_stop('ice_flx_dist')
[8404]257      !
[8426]258   END SUBROUTINE ice_flx_dist
[8404]259
[8531]260   SUBROUTINE ice_forcing_init
261      !!-------------------------------------------------------------------
262      !!                  ***  ROUTINE ice_forcing_init  ***
263      !!
264      !! ** Purpose : Physical constants and parameters linked to the ice
265      !!      dynamics
266      !!
267      !! ** Method  :  Read the namforcing namelist and check the ice-dynamic
268      !!       parameter values called at the first timestep (nit000)
269      !!
270      !! ** input   :   Namelist namforcing
271      !!-------------------------------------------------------------------
272      INTEGER ::   ios, ioptio   ! Local integer output status for namelist read
273      !!
274      NAMELIST/namforcing/ rn_cio, rn_blow_s, nn_iceflx
275      !!-------------------------------------------------------------------
276      !
277      REWIND( numnam_ice_ref )         ! Namelist namforcing in reference namelist : Ice dynamics
278      READ  ( numnam_ice_ref, namforcing, IOSTAT = ios, ERR = 901)
279901   IF( ios /= 0 ) CALL ctl_nam ( ios , 'namforcing in reference namelist', lwp )
280      !
281      REWIND( numnam_ice_cfg )         ! Namelist namforcing in configuration namelist : Ice dynamics
282      READ  ( numnam_ice_cfg, namforcing, IOSTAT = ios, ERR = 902 )
283902   IF( ios /= 0 ) CALL ctl_nam ( ios , 'namforcing in configuration namelist', lwp )
284      IF(lwm) WRITE ( numoni, namforcing )
285      !
286      IF(lwp) THEN                     ! control print
287         WRITE(numout,*)
288         WRITE(numout,*) 'ice_forcing_init: ice parameters for ice dynamics '
289         WRITE(numout,*) '~~~~~~~~~~~~~~~'
290         WRITE(numout,*) '   Namelist namforcing:'
291         WRITE(numout,*) '      drag coefficient for oceanic stress              rn_cio    = ', rn_cio
292         WRITE(numout,*) '      coefficient for ice-lead partition of snowfall   rn_blow_s = ', rn_blow_s
293         WRITE(numout,*) '      Multicategory heat flux formulation              nn_iceflx = ', nn_iceflx
294      ENDIF
295      !
296      IF(lwp) WRITE(numout,*)
297      SELECT CASE( nn_iceflx )         ! ESIM Multi-category heat flux formulation
298      CASE( -1  )
299         IF(lwp) WRITE(numout,*) '   ESIM: use per-category fluxes (nn_iceflx = -1) '
300         IF( ln_cpl )   CALL ctl_stop( 'ice_thd_init : the chosen nn_iceflx for ESIM in coupled mode must be 0 or 2' )
301      CASE(  0  )
302         IF(lwp) WRITE(numout,*) '   ESIM: use average per-category fluxes (nn_iceflx = 0) '
303      CASE(  1  )
304         IF(lwp) WRITE(numout,*) '   ESIM: use average then redistribute per-category fluxes (nn_iceflx = 1) '
305         IF( ln_cpl )   CALL ctl_stop( 'ice_thd_init : the chosen nn_iceflx for ESIM in coupled mode must be 0 or 2' )
306      CASE(  2  )
307         IF(lwp) WRITE(numout,*) '   ESIM: Redistribute a single flux over categories (nn_iceflx = 2) '
308         IF( .NOT. ln_cpl )   CALL ctl_stop( 'ice_thd_init : the chosen nn_iceflx for ESIM in forced mode cannot be 2' )
309      CASE DEFAULT
310         CALL ctl_stop( 'ice_thd_init: ESIM option, nn_iceflx, should be between -1 and 2' )
311      END SELECT
312      !
313   END SUBROUTINE ice_forcing_init
314
[8486]315#else
316   !!----------------------------------------------------------------------
317   !!   Default option :         Empty module          NO LIM sea-ice model
318   !!----------------------------------------------------------------------
[8404]319#endif
320
321   !!======================================================================
322END MODULE iceforcing
Note: See TracBrowser for help on using the repository browser.