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 trunk/NEMO/OPA_SRC/SBC – NEMO

source: trunk/NEMO/OPA_SRC/SBC/sbcice_lim_2.F90 @ 1270

Last change on this file since 1270 was 1270, checked in by rblod, 15 years ago

Light bug in blk_ice, see ticket #289

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