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.
sbcice_lim_2.F90 in branches/DEV_r2106_LOCEAN2010/NEMO/OPA_SRC/SBC – NEMO

source: branches/DEV_r2106_LOCEAN2010/NEMO/OPA_SRC/SBC/sbcice_lim_2.F90 @ 2236

Last change on this file since 2236 was 2236, checked in by cetlod, 14 years ago

First guess of NEMO_v3.3

  • Property svn:keywords set to Id
File size: 11.0 KB
Line 
1MODULE sbcice_lim_2
2   !!======================================================================
3   !!                       ***  MODULE  sbcice_lim_2  ***
4   !! Surface module :  update surface ocean boundary condition over ice
5   !!                   covered area using LIM sea-ice model
6   !! Sea-Ice model  :  LIM 2.0 Sea ice model time-stepping
7   !!======================================================================
8   !! History :  1.0   !  06-2006  (G. Madec)  from icestp_2.F90
9   !!            3.0   !  08-2008  (S. Masson, E. .... ) coupled interface
10   !!            3.3   !  05-2009  (G.Garric) addition of the lim2_evp case
11   !!----------------------------------------------------------------------
12#if defined key_lim2
13   !!----------------------------------------------------------------------
14   !!   'key_lim2' :                                  LIM 2.0 sea-ice model
15   !!----------------------------------------------------------------------
16   !!   sbc_ice_lim_2  : sea-ice model time-stepping and
17   !!                    update ocean sbc over ice-covered area
18   !!----------------------------------------------------------------------
19   USE oce             ! ocean dynamics and tracers
20   USE dom_oce         ! ocean space and time domain
21   USE lib_mpp
22   USE ice_2
23   USE par_ice_2
24   USE iceini_2
25   USE dom_ice_2
26
27   USE sbc_oce         ! Surface boundary condition: ocean fields
28   USE sbc_ice         ! Surface boundary condition: ice   fields
29   USE sbcblk_core     ! Surface boundary condition: CORE bulk
30   USE sbcblk_clio     ! Surface boundary condition: CLIO bulk
31   USE sbccpl          ! Surface boundary condition: coupled interface
32   USE albedo
33
34   USE phycst          ! Define parameters for the routines
35   USE eosbn2          ! equation of state
36   USE limdyn_2
37   USE limtrp_2
38   USE limdmp_2
39   USE limthd_2
40   USE limsbc_2        ! sea surface boundary condition
41   USE limdia_2
42   USE limwri_2
43   USE limrst_2
44
45   USE lbclnk
46   USE iom             ! I/O manager library
47   USE in_out_manager  ! I/O manager
48   USE prtctl          ! Print control
49
50   IMPLICIT NONE
51   PRIVATE
52
53   PUBLIC sbc_ice_lim_2 ! routine called by sbcmod.F90
54   
55   !! * Substitutions
56#  include "domzgr_substitute.h90"
57#  include "vectopt_loop_substitute.h90"
58   !!----------------------------------------------------------------------
59   !! NEMO/SBC  3.0 , LOCEAN-IPSL (2008)
60   !! $Id$
61   !! Software governed by the CeCILL licence  (NEMOGCM/License_CeCILL.txt)
62   !!----------------------------------------------------------------------
63
64CONTAINS
65
66   SUBROUTINE sbc_ice_lim_2( kt, ksbc )
67      !!---------------------------------------------------------------------
68      !!                  ***  ROUTINE sbc_ice_lim_2  ***
69      !!                   
70      !! ** Purpose :   update the ocean surface boundary condition via the
71      !!                Louvain la Neuve Sea Ice Model time stepping
72      !!
73      !! ** Method  :   ice model time stepping
74      !!              - call the ice dynamics routine
75      !!              - call the ice advection/diffusion routine
76      !!              - call the ice thermodynamics routine
77      !!              - call the routine that computes mass and
78      !!                heat fluxes at the ice/ocean interface
79      !!              - save the outputs
80      !!              - save the outputs for restart when necessary
81      !!
82      !! ** Action  : - time evolution of the LIM sea-ice model
83      !!              - update all sbc variables below sea-ice:
84      !!                utau, vtau, taum, wndm, qns , qsr, emp , emps
85      !!---------------------------------------------------------------------
86      INTEGER, INTENT(in) ::   kt      ! ocean time step
87      INTEGER, INTENT(in) ::   ksbc    ! type of sbc ( =3 CLIO bulk ; =4 CORE bulk ; =5 coupled )
88      !!
89      INTEGER  ::   ji, jj   ! dummy loop indices
90      REAL(wp), DIMENSION(jpi,jpj,1) ::   zalb_ice_os   ! albedo of the ice under overcast sky
91      REAL(wp), DIMENSION(jpi,jpj,1) ::   zalb_ice_cs   ! albedo of ice under clear sky
92      REAL(wp), DIMENSION(jpi,jpj,1) ::   zsist        ! surface ice temperature (K)
93      !!----------------------------------------------------------------------
94
95      IF( kt == nit000 ) THEN
96         IF(lwp) WRITE(numout,*)
97         IF(lwp) WRITE(numout,*) 'sbc_ice_lim_2 : update ocean surface boudary condition' 
98         IF(lwp) WRITE(numout,*) '~~~~~~~~~~~~~   via Louvain la Neuve Ice Model (LIM) time stepping'
99
100         CALL ice_init_2
101
102      ENDIF
103
104      IF( MOD( kt-1, nn_fsbc ) == 0 ) THEN
105         !
106         ! ... mean surface ocean current at ice dynamics point
107         !     B-grid dynamics :  I-point
108         DO jj = 2, jpj
109            DO ji = 2, jpi   ! B grid : no vector opt.
110               u_oce(ji,jj) = 0.5 * ( ssu_m(ji-1,jj  ) + ssu_m(ji-1,jj-1) ) * tmu(ji,jj)
111               v_oce(ji,jj) = 0.5 * ( ssv_m(ji  ,jj-1) + ssv_m(ji-1,jj-1) ) * tmu(ji,jj)
112            END DO
113         END DO
114         CALL lbc_lnk( u_oce, 'I', -1. )   ! I-point (i.e. F-point with ice indices)
115         CALL lbc_lnk( v_oce, 'I', -1. )   ! I-point (i.e. F-point with ice indices)
116
117         ! ... masked sea surface freezing temperature [Kelvin] (set to rt0 over land)
118         tfu(:,:) = tfreez( sss_m ) +  rt0 
119
120         zsist (:,:,1) = sist (:,:) + rt0 * ( 1. - tmask(:,:,1) )
121
122         ! ... ice albedo (clear sky and overcast sky)
123         CALL albedo_ice( zsist, reshape( hicif, (/jpi,jpj,1/) ), reshape( hsnif, (/jpi,jpj,1/) ), zalb_ice_cs, zalb_ice_os )
124
125         ! ... Sea-ice surface boundary conditions output from bulk formulae :
126         !     - utau_ice   ! surface ice stress i-component (I-point)   [N/m2]
127         !     - vtau_ice   ! surface ice stress j-component (I-point)   [N/m2]
128         !     - qns_ice    ! non solar heat flux over ice   (T-point)   [W/m2]
129         !     - qsr_ice    !     solar heat flux over ice   (T-point)   [W/m2]
130         !     - qla_ice    ! latent    heat flux over ice   (T-point)   [W/m2]
131         !     - dqns_ice   ! non solar heat sensistivity    (T-point)   [W/m2]
132         !     - dqla_ice   ! latent    heat sensistivity    (T-point)   [W/m2]
133         !     - tprecip    ! total precipitation            (T-point)   [Kg/m2/s]
134         !     - sprecip    ! solid precipitation            (T-point)   [Kg/m2/s]
135         !     - fr1_i0     ! 1sr fraction of qsr penetration in ice     [%]
136         !     - fr2_i0     ! 2nd fraction of qsr penetration in ice     [%]
137         !
138         SELECT CASE( ksbc )
139         CASE( 3 )           ! CLIO bulk formulation
140            CALL blk_ice_clio( zsist, zalb_ice_cs, zalb_ice_os,                         &
141               &                      utau_ice   , vtau_ice   , qns_ice    , qsr_ice,   &
142               &                      qla_ice    , dqns_ice   , dqla_ice   ,            &
143               &                      tprecip    , sprecip    ,                         &
144               &                      fr1_i0     , fr2_i0     , cl_grid    , jpl  )
145
146         CASE( 4 )           ! CORE bulk formulation
147            CALL blk_ice_core( zsist, u_ice      , v_ice      , zalb_ice_cs,            &
148               &                      utau_ice   , vtau_ice   , qns_ice    , qsr_ice,   &
149               &                      qla_ice    , dqns_ice   , dqla_ice   ,            &
150               &                      tprecip    , sprecip    ,                         &
151               &                      fr1_i0     , fr2_i0     , cl_grid    , jpl  )
152         CASE( 5 )           ! Coupled formulation : atmosphere-ice stress only (fluxes provided after ice dynamics)
153            CALL sbc_cpl_ice_tau( utau_ice , vtau_ice )
154         END SELECT
155
156         CALL iom_put( 'utau_ice', utau_ice )     ! Wind stress over ice along i-axis at I-point
157         CALL iom_put( 'vtau_ice', vtau_ice )     ! Wind stress over ice along j-axis at I-point
158
159         IF(ln_ctl) THEN         ! print mean trends (used for debugging)
160            CALL prt_ctl_info( 'Ice Forcings ' )
161            CALL prt_ctl( tab2d_1=tprecip ,clinfo1=' sbc_ice_lim: precip  : ', tab2d_2=sprecip , clinfo2=' Snow    : ' )
162            CALL prt_ctl( tab2d_1=utau_ice,clinfo1=' sbc_ice_lim: utau_ice: ', tab2d_2=vtau_ice, clinfo2=' vtau_ice: ' )
163            CALL prt_ctl( tab2d_1=sst_m   ,clinfo1=' sbc_ice_lim: sst     : ', tab2d_2=sss_m   , clinfo2=' sss     : ' )
164            CALL prt_ctl( tab2d_1=u_oce   ,clinfo1=' sbc_ice_lim: u_io    : ', tab2d_2=v_oce   , clinfo2=' v_io    : ' )
165            CALL prt_ctl( tab2d_1=hsnif   ,clinfo1=' sbc_ice_lim: hsnif  1: ', tab2d_2=hicif   , clinfo2=' hicif   : ' )
166            CALL prt_ctl( tab2d_1=frld    ,clinfo1=' sbc_ice_lim: frld   1: ', tab2d_2=sist    , clinfo2=' sist    : ' )
167         ENDIF
168
169         ! ---------------- !
170         !  Ice model step  !
171         ! ---------------- !
172         numit = numit + nn_fsbc                                             ! Ice model time step
173
174                                        CALL lim_rst_opn_2  ( kt )      ! Open Ice restart file
175#if ! defined key_c1d
176            ! Ice dynamics & transport (not in 1D case)
177                                        CALL lim_dyn_2      ( kt )           ! Ice dynamics    ( rheology/dynamics )
178                                        CALL lim_trp_2      ( kt )           ! Ice transport   ( Advection/diffusion )
179            IF( ln_limdmp )             CALL lim_dmp_2      ( kt )           ! Ice damping
180#endif
181#if defined key_coupled
182         IF( ksbc == 5    )             CALL sbc_cpl_ice_flx( reshape( frld, (/jpi,jpj,1/) ),        &
183      &                                                       qns_tot, qns_ice, qsr_tot , qsr_ice,   &
184      &                                                       emp_tot, emp_ice, dqns_ice, sprecip,   &
185      !                                      optional arguments, used only in 'mixed oce-ice' case
186      &                                                       palbi = zalb_ice_cs, psst = sst_m, pist = sist )
187#endif
188                                        CALL lim_thd_2      ( kt )      ! Ice thermodynamics
189                                        CALL lim_sbc_2      ( kt )      ! Ice/Ocean Mass & Heat fluxes
190
191         IF( ( MOD( kt+nn_fsbc-1, ninfo ) == 0 .OR. ntmoy == 1 ) .AND. .NOT. lk_mpp )   &
192            &                           CALL lim_dia_2      ( kt )      ! Ice Diagnostics
193# if ! defined key_iomput
194                                        CALL lim_wri_2      ( kt )      ! Ice outputs
195# endif
196         IF( lrst_ice )                 CALL lim_rst_write_2( kt )      ! Ice restart file
197         !
198      ENDIF
199      !
200   END SUBROUTINE sbc_ice_lim_2
201
202#else
203   !!----------------------------------------------------------------------
204   !!   Default option           Dummy module      NO LIM 2.0 sea-ice model
205   !!----------------------------------------------------------------------
206CONTAINS
207   SUBROUTINE sbc_ice_lim_2 ( kt, ksbc )     ! Dummy routine
208      WRITE(*,*) 'sbc_ice_lim_2: You should not have seen this print! error?', kt, ksbc
209   END SUBROUTINE sbc_ice_lim_2
210#endif
211
212   !!======================================================================
213END MODULE sbcice_lim_2
Note: See TracBrowser for help on using the repository browser.