source: CONFIG/UNIFORM/v6/IPSLCM6/SOURCES/NEMO/sbcice_lim_2.F90 @ 2128

Last change on this file since 2128 was 2113, checked in by omamce, 11 years ago

O.M.

  • Add coupled interface for LIM3
  • Closea : spread Black Sea outflow on several points
  • stpctl : prevent Salinity to be below 0.1 PSS
File size: 14.1 KB
Line 
1MODULE sbcice_lim_2
2   !!======================================================================
3   !!                       ***  MODULE  sbcice_lim_2  ***
4   !! Surface module :  update surface ocean boundary condition over ice covered area using LIM sea-ice model
5   !! Sea-Ice model  :  LIM-2 Sea ice model time-stepping
6   !!======================================================================
7   !! History :  1.0   !  06-2006  (G. Madec)  from icestp_2.F90
8   !!            3.0   !  08-2008  (S. Masson, E. .... ) coupled interface
9   !!            3.3   !  05-2009  (G.Garric) addition of the lim2_evp case
10   !!----------------------------------------------------------------------
11#if defined key_lim2
12   !!----------------------------------------------------------------------
13   !!   'key_lim2' :                                    LIM-2 sea-ice model
14   !!----------------------------------------------------------------------
15   !!   sbc_ice_lim_2   : sea-ice model time-stepping and update ocean sbc over ice-covered area
16   !!----------------------------------------------------------------------
17   USE oce              ! ocean dynamics and tracers
18   USE dom_oce          ! ocean space and time domain
19   USE ice_2
20   USE par_ice_2
21   USE iceini_2
22   USE dom_ice_2
23
24   USE sbc_oce          ! Surface boundary condition: ocean fields
25   USE sbc_ice          ! Surface boundary condition: ice   fields
26   USE sbcblk_core      ! Surface boundary condition: CORE bulk
27   USE sbcblk_clio      ! Surface boundary condition: CLIO bulk
28   USE sbccpl           ! Surface boundary condition: coupled interface
29   USE albedo
30
31   USE phycst           ! Define parameters for the routines
32   USE eosbn2           ! equation of state
33   USE limdyn_2
34   USE limtrp_2
35   USE limdmp_2
36   USE limthd_2
37   USE limsbc_2         ! sea surface boundary condition
38   USE limdia_2
39   USE limwri_2
40   USE limrst_2
41
42   USE c1d              ! 1D vertical configuration
43
44   USE lbclnk           ! lateral boundary condition - MPP link
45   USE lib_mpp          ! MPP library
46   USE wrk_nemo         ! work arrays
47   USE iom              ! I/O manager library
48   USE in_out_manager   ! I/O manager
49   USE prtctl           ! Print control
50
51# if defined key_agrif
52   USE agrif_ice
53   USE agrif_lim2_update
54# endif
55
56   IMPLICIT NONE
57   PRIVATE
58
59   REAL (kind=wp), SAVE :: rdt_ice_dyn, rdt_ice_thermo
60
61   PUBLIC sbc_ice_lim_2 ! routine called by sbcmod.F90
62
63   !! * Substitutions
64#  include "domzgr_substitute.h90"
65#  include "vectopt_loop_substitute.h90"
66   !!----------------------------------------------------------------------
67   !! NEMO/OPA 3.3 , NEMO Consortium (2010)
68   !! $Id: sbcice_lim_2.F90 3680 2012-11-27 14:42:24Z rblod $
69   !! Software governed by the CeCILL licence     (NEMOGCM/NEMO_CeCILL.txt)
70   !!----------------------------------------------------------------------
71CONTAINS
72
73   SUBROUTINE sbc_ice_lim_2( kt, ksbc )
74      !!---------------------------------------------------------------------
75      !!                  ***  ROUTINE sbc_ice_lim_2  ***
76      !!                   
77      !! ** Purpose :   update the ocean surface boundary condition via the
78      !!                Louvain la Neuve Sea Ice Model time stepping
79      !!
80      !! ** Method  :   ice model time stepping
81      !!              - call the ice dynamics routine
82      !!              - call the ice advection/diffusion routine
83      !!              - call the ice thermodynamics routine
84      !!              - call the routine that computes mass and
85      !!                heat fluxes at the ice/ocean interface
86      !!              - save the outputs
87      !!              - save the outputs for restart when necessary
88      !!
89      !! ** Action  : - time evolution of the LIM sea-ice model
90      !!              - update all sbc variables below sea-ice:
91      !!                utau, vtau, taum, wndm, qns , qsr, emp , sfx
92      !!---------------------------------------------------------------------
93      INTEGER, INTENT(in) ::   kt      ! ocean time step
94      INTEGER, INTENT(in) ::   ksbc    ! type of sbc ( =3 CLIO bulk ; =4 CORE bulk ; =5 coupled )
95      !!
96      INTEGER  ::   ji, jj   ! dummy loop indices
97      REAL(wp), DIMENSION(:,:,:), POINTER :: zalb_ice_os   ! albedo of the ice under overcast sky
98      REAL(wp), DIMENSION(:,:,:), POINTER :: zalb_ice_cs   ! albedo of ice under clear sky
99      REAL(wp), DIMENSION(:,:,:), POINTER :: zsist         ! surface ice temperature (K)
100      !!----------------------------------------------------------------------
101
102      CALL wrk_alloc( jpi,jpj,1, zalb_ice_os, zalb_ice_cs, zsist )
103
104      IF( kt == nit000 ) THEN
105         IF(lwp) WRITE(numout,*)
106         IF(lwp) WRITE(numout,*) 'sbc_ice_lim_2 : update ocean surface boudary condition' 
107         IF(lwp) WRITE(numout,*) '~~~~~~~~~~~~~   via Louvain la Neuve Ice Model (LIM) time stepping'
108         !
109         CALL ice_init_2
110         !
111         rdt_ice_dyn    = rdt_ice * REAL ( nn_ice_dyn, wp)
112         rdt_ice_thermo = rdt_ice
113         !
114         IF(lwp) WRITE(numout,*) 'nn_ice_dyn     : ', nn_ice_dyn
115         IF(lwp) WRITE(numout,*) 'rdt_ice        : ', rdt_ice
116         IF(lwp) WRITE(numout,*) 'rdt_ice_thermo : ', rdt_ice_thermo
117         IF(lwp) WRITE(numout,*) 'rdt_ice_dyn    : ', rdt_ice_dyn
118         !
119# if defined key_agrif
120         IF( .NOT. Agrif_Root() ) CALL Agrif_InitValues_cont_lim2   ! AGRIF: set the meshes
121# endif
122      ENDIF
123
124      !                                        !----------------------!
125      IF( MOD( kt-1, nn_fsbc ) == 0 ) THEN     !  Ice time-step only  !
126         !                                     !----------------------!
127
128         IF(lwp) WRITE(numout,*) 'sbc_ice_lim_2 : pas de temps glace : ', kt
129         
130# if defined key_agrif
131         IF( .NOT. Agrif_Root() ) lim_nbstep = MOD(lim_nbstep,Agrif_rhot()&
132         &*Agrif_PArent(nn_fsbc)/REAL(nn_fsbc)) + 1
133# endif
134         !  Bulk Formulea !
135         !----------------!
136         ! ... mean surface ocean current at ice dynamics point
137         SELECT CASE( cp_ice_msh )
138         CASE( 'I' )                  !== B-grid ice dynamics :   I-point (i.e. F-point with sea-ice indexation)
139            DO jj = 2, jpj
140               DO ji = 2, jpi   ! NO vector opt. possible
141                  u_oce(ji,jj) = 0.5_wp * ( ssu_m(ji-1,jj  ) + ssu_m(ji-1,jj-1) ) * tmu(ji,jj)
142                  v_oce(ji,jj) = 0.5_wp * ( ssv_m(ji  ,jj-1) + ssv_m(ji-1,jj-1) ) * tmu(ji,jj)
143               END DO
144            END DO
145            CALL lbc_lnk( u_oce, 'I', -1. )   ! I-point (i.e. F-point with ice indices)
146            CALL lbc_lnk( v_oce, 'I', -1. )   ! I-point (i.e. F-point with ice indices)
147            !
148         CASE( 'C' )                  !== C-grid ice dynamics :   U & V-points (same as ocean)
149            u_oce(:,:) = ssu_m(:,:)                     ! mean surface ocean current at ice velocity point
150            v_oce(:,:) = ssv_m(:,:)
151            !
152         END SELECT
153
154         ! ... masked sea surface freezing temperature [Kelvin] (set to rt0 over land)
155         tfu(:,:) = tfreez( sss_m ) +  rt0 
156
157         zsist (:,:,1) = sist (:,:) + rt0 * ( 1. - tmask(:,:,1) )
158
159         ! ... ice albedo (clear sky and overcast sky)
160         CALL albedo_ice( zsist, reshape( hicif, (/jpi,jpj,1/) ), &
161                                 reshape( hsnif, (/jpi,jpj,1/) ), &
162                          zalb_ice_cs, zalb_ice_os )
163
164         ! ... Sea-ice surface boundary conditions output from bulk formulae :
165         !     - utau_ice   ! surface ice stress i-component (I-point)   [N/m2]
166         !     - vtau_ice   ! surface ice stress j-component (I-point)   [N/m2]
167         !     - qns_ice    ! non solar heat flux over ice   (T-point)   [W/m2]
168         !     - qsr_ice    !     solar heat flux over ice   (T-point)   [W/m2]
169         !     - qla_ice    ! latent    heat flux over ice   (T-point)   [W/m2]
170         !     - dqns_ice   ! non solar heat sensistivity    (T-point)   [W/m2]
171         !     - dqla_ice   ! latent    heat sensistivity    (T-point)   [W/m2]
172         !     - tprecip    ! total precipitation            (T-point)   [Kg/m2/s]
173         !     - sprecip    ! solid precipitation            (T-point)   [Kg/m2/s]
174         !     - fr1_i0     ! 1sr fraction of qsr penetration in ice     [%]
175         !     - fr2_i0     ! 2nd fraction of qsr penetration in ice     [%]
176         !
177         SELECT CASE( ksbc )
178         CASE( 3 )           ! CLIO bulk formulation
179            CALL blk_ice_clio( zsist, zalb_ice_cs, zalb_ice_os,                         &
180               &                      utau_ice   , vtau_ice   , qns_ice    , qsr_ice,   &
181               &                      qla_ice    , dqns_ice   , dqla_ice   ,            &
182               &                      tprecip    , sprecip    ,                         &
183               &                      fr1_i0     , fr2_i0     , cp_ice_msh , jpl  )
184
185         CASE( 4 )           ! CORE bulk formulation
186            CALL blk_ice_core( zsist, u_ice      , v_ice      , zalb_ice_cs,            &
187               &                      utau_ice   , vtau_ice   , qns_ice    , qsr_ice,   &
188               &                      qla_ice    , dqns_ice   , dqla_ice   ,            &
189               &                      tprecip    , sprecip    ,                         &
190               &                      fr1_i0     , fr2_i0     , cp_ice_msh , jpl  )
191         CASE( 5 )           ! Coupled formulation : atmosphere-ice stress only (fluxes provided after ice dynamics)
192            CALL sbc_cpl_ice_tau( utau_ice , vtau_ice )
193         END SELECT
194
195         CALL iom_put( 'utau_ice', utau_ice )     ! Wind stress over ice along i-axis at I-point
196         CALL iom_put( 'vtau_ice', vtau_ice )     ! Wind stress over ice along j-axis at I-point
197
198         IF(ln_ctl) THEN         ! print mean trends (used for debugging)
199            CALL prt_ctl_info( 'Ice Forcings ' )
200            CALL prt_ctl( tab2d_1=tprecip ,clinfo1=' sbc_ice_lim: precip  : ', tab2d_2=sprecip , clinfo2=' Snow    : ' )
201            CALL prt_ctl( tab2d_1=utau_ice,clinfo1=' sbc_ice_lim: utau_ice: ', tab2d_2=vtau_ice, clinfo2=' vtau_ice: ' )
202            CALL prt_ctl( tab2d_1=sst_m   ,clinfo1=' sbc_ice_lim: sst     : ', tab2d_2=sss_m   , clinfo2=' sss     : ' )
203            CALL prt_ctl( tab2d_1=u_oce   ,clinfo1=' sbc_ice_lim: u_io    : ', tab2d_2=v_oce   , clinfo2=' v_io    : ' )
204            CALL prt_ctl( tab2d_1=hsnif   ,clinfo1=' sbc_ice_lim: hsnif  1: ', tab2d_2=hicif   , clinfo2=' hicif   : ' )
205            CALL prt_ctl( tab2d_1=frld    ,clinfo1=' sbc_ice_lim: frld   1: ', tab2d_2=sist    , clinfo2=' sist    : ' )
206         ENDIF
207
208         ! ---------------- !
209         !  Ice model step  !
210         ! ---------------- !
211         numit = numit + nn_fsbc                           ! Ice model time step
212
213                           CALL lim_rst_opn_2  ( kt )  ! Open Ice restart file
214         IF( .NOT. lk_c1d ) THEN                       ! Ice dynamics & transport (except in 1D case)
215            ! - Test OM, call ice dynamics every nn_ice_dyn ice time steps
216            IF( MOD( kt-1, nn_fsbc*nn_ice_dyn ) == 0 ) THEN
217                           IF(lwp) WRITE(numout,*) 'sbc_ice_lim_2 : pas de temps glace dynamique : ', kt
218                           rdt_ice = rdt_ice_dyn
219                           CALL lim_dyn_2      ( kt )      ! Ice dynamics    ( rheology/dynamics )
220                           CALL lim_trp_2      ( kt )      ! Ice transport   ( Advection/diffusion )
221                           rdt_ice = rdt_ice_thermo           
222            END IF
223           rdt_ice = rdt_ice_thermo
224           IF( ln_limdmp ) CALL lim_dmp_2      ( kt )      ! Ice damping
225         END IF
226#if defined key_coupled
227         !                                             ! Ice surface fluxes in coupled mode
228         IF( ksbc == 5 )   THEN
229            a_i(:,:,1)=fr_i
230            CALL sbc_cpl_ice_flx( frld,                                              &
231            !                                optional arguments, used only in 'mixed oce-ice' case
232            &                                             palbi = zalb_ice_cs, psst = sst_m, pist = zsist )
233            sprecip(:,:) = - emp_ice(:,:)   ! Ugly patch, WARNING, in coupled mode, sublimation included in snow (parsub = 0.)
234         ENDIF
235#endif
236                           rdt_ice = rdt_ice_thermo
237                           CALL lim_thd_2      ( kt )      ! Ice thermodynamics
238                           CALL lim_sbc_flx_2  ( kt )      ! update surface ocean mass, heat & salt fluxes
239
240         IF( ( MOD( kt+nn_fsbc-1, ninfo ) == 0 .OR. ntmoy == 1 ) .AND. .NOT. lk_mpp )   &
241            &              CALL lim_dia_2      ( kt )      ! Ice Diagnostics
242# if ! defined key_iomput
243                           CALL lim_wri_2      ( kt )      ! Ice outputs
244# endif
245         IF( lrst_ice  )   CALL lim_rst_write_2( kt )      ! Ice restart file
246         !
247# if defined key_agrif && defined key_lim2
248         IF( .NOT. Agrif_Root() )   CALL agrif_update_lim2( kt )
249# endif
250         !
251      ENDIF                                    ! End sea-ice time step only
252      !
253      !                                        !--------------------------!
254      !                                        !  at all ocean time step  !
255      !                                        !--------------------------!
256      !                                               
257      !                                              ! Update surface ocean stresses (only in ice-dynamic case)
258      !                                                   ! otherwise the atm.-ocean stresses are used everywhere
259      IF( ln_limdyn    )   CALL lim_sbc_tau_2( kt, ub(:,:,1), vb(:,:,1) )  ! using before instantaneous surf. currents
260      !
261      CALL wrk_dealloc( jpi,jpj,1, zalb_ice_os, zalb_ice_cs, zsist )
262      !
263   END SUBROUTINE sbc_ice_lim_2
264
265#else
266   !!----------------------------------------------------------------------
267   !!   Default option           Dummy module      NO LIM 2.0 sea-ice model
268   !!----------------------------------------------------------------------
269CONTAINS
270   SUBROUTINE sbc_ice_lim_2 ( kt, ksbc )     ! Dummy routine
271      INTEGER, INTENT(in) ::   kt, ksbc   
272      WRITE(*,*) 'sbc_ice_lim_2: You should not have seen this print! error?', kt, ksbc
273   END SUBROUTINE sbc_ice_lim_2
274#endif
275
276   !!======================================================================
277END MODULE sbcice_lim_2
Note: See TracBrowser for help on using the repository browser.