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.
Changeset 2528 for trunk/NEMOGCM/NEMO/OPA_SRC/SBC/sbcice_lim_2.F90 – NEMO

Ignore:
Timestamp:
2010-12-27T18:33:53+01:00 (14 years ago)
Author:
rblod
Message:

Update NEMOGCM from branch nemo_v3_3_beta

File:
1 edited

Legend:

Unmodified
Added
Removed
  • trunk/NEMOGCM/NEMO/OPA_SRC/SBC/sbcice_lim_2.F90

    r2090 r2528  
    22   !!====================================================================== 
    33   !!                       ***  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 
     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 
    76   !!====================================================================== 
    87   !! History :  1.0   !  06-2006  (G. Madec)  from icestp_2.F90 
    98   !!            3.0   !  08-2008  (S. Masson, E. .... ) coupled interface 
     9   !!            3.3   !  05-2009  (G.Garric) addition of the lim2_evp case 
    1010   !!---------------------------------------------------------------------- 
    1111#if defined key_lim2 
    1212   !!---------------------------------------------------------------------- 
    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 
     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 
    2219   USE ice_2 
    2320   USE par_ice_2 
     
    2522   USE dom_ice_2 
    2623 
    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 
     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 
    3229   USE albedo 
    3330 
    34    USE phycst          ! Define parameters for the routines 
    35    USE eosbn2          ! equation of state 
     31   USE phycst           ! Define parameters for the routines 
     32   USE eosbn2           ! equation of state 
    3633   USE limdyn_2 
    3734   USE limtrp_2 
    3835   USE limdmp_2 
    3936   USE limthd_2 
    40    USE limsbc_2        ! sea surface boundary condition 
     37   USE limsbc_2         ! sea surface boundary condition 
    4138   USE limdia_2 
    4239   USE limwri_2 
    4340   USE limrst_2 
    4441 
    45    USE lbclnk 
    46    USE iom             ! I/O manager library 
    47    USE in_out_manager  ! I/O manager 
    48    USE prtctl          ! Print control 
     42   USE c1d              ! 1D vertical configuration 
     43 
     44   USE lbclnk           ! lateral boundary condition - MPP link 
     45   USE lib_mpp          ! MPP library 
     46   USE iom              ! I/O manager library 
     47   USE in_out_manager   ! I/O manager 
     48   USE prtctl           ! Print control 
    4949 
    5050   IMPLICIT NONE 
     
    5252 
    5353   PUBLIC sbc_ice_lim_2 ! routine called by sbcmod.F90 
    54     
    55    CHARACTER(len=1) ::   cl_grid = 'B'     ! type of grid used in ice dynamics 
    5654 
    5755   !! * Substitutions 
     
    5957#  include "vectopt_loop_substitute.h90" 
    6058   !!---------------------------------------------------------------------- 
    61    !! NEMO/SBC  3.0 , LOCEAN-IPSL (2008)  
     59   !! NEMO/OPA 3.3 , NEMO Consortium (2010) 
    6260   !! $Id$ 
    63    !! Software governed by the CeCILL licence (modipsl/doc/NEMO_CeCILL.txt) 
    64    !!---------------------------------------------------------------------- 
    65  
     61   !! Software governed by the CeCILL licence     (NEMOGCM/NEMO_CeCILL.txt) 
     62   !!---------------------------------------------------------------------- 
    6663CONTAINS 
    6764 
     
    9996         IF(lwp) WRITE(numout,*) 'sbc_ice_lim_2 : update ocean surface boudary condition'  
    10097         IF(lwp) WRITE(numout,*) '~~~~~~~~~~~~~   via Louvain la Neuve Ice Model (LIM) time stepping' 
    101  
     98         ! 
    10299         CALL ice_init_2 
    103  
    104100      ENDIF 
    105101 
    106       IF( MOD( kt-1, nn_fsbc ) == 0 ) THEN 
    107          ! 
     102      !                                        !----------------------! 
     103      IF( MOD( kt-1, nn_fsbc ) == 0 ) THEN     !  Ice time-step only  ! 
     104         !                                     !----------------------! 
     105         !  Bulk Formulea ! 
     106         !----------------! 
    108107         ! ... mean surface ocean current at ice dynamics point 
    109          !     B-grid dynamics :  I-point  
    110          DO jj = 2, jpj 
    111             DO ji = 2, jpi   ! B grid : no vector opt. 
    112                u_oce(ji,jj) = 0.5 * ( ssu_m(ji-1,jj  ) + ssu_m(ji-1,jj-1) ) * tmu(ji,jj) 
    113                v_oce(ji,jj) = 0.5 * ( ssv_m(ji  ,jj-1) + ssv_m(ji-1,jj-1) ) * tmu(ji,jj) 
     108         SELECT CASE( cp_ice_msh ) 
     109         CASE( 'I' )                  !== B-grid ice dynamics :   I-point (i.e. F-point with sea-ice indexation) 
     110            DO jj = 2, jpj 
     111               DO ji = 2, jpi   ! NO vector opt. possible 
     112                  u_oce(ji,jj) = 0.5_wp * ( ssu_m(ji-1,jj  ) + ssu_m(ji-1,jj-1) ) * tmu(ji,jj) 
     113                  v_oce(ji,jj) = 0.5_wp * ( ssv_m(ji  ,jj-1) + ssv_m(ji-1,jj-1) ) * tmu(ji,jj) 
     114               END DO 
    114115            END DO 
    115          END DO 
    116          CALL lbc_lnk( u_oce, 'I', -1. )   ! I-point (i.e. F-point with ice indices) 
    117          CALL lbc_lnk( v_oce, 'I', -1. )   ! I-point (i.e. F-point with ice indices) 
     116            CALL lbc_lnk( u_oce, 'I', -1. )   ! I-point (i.e. F-point with ice indices) 
     117            CALL lbc_lnk( v_oce, 'I', -1. )   ! I-point (i.e. F-point with ice indices) 
     118            ! 
     119         CASE( 'C' )                  !== C-grid ice dynamics :   U & V-points (same as ocean) 
     120            u_oce(:,:) = ssu_m(:,:)                     ! mean surface ocean current at ice velocity point 
     121            v_oce(:,:) = ssv_m(:,:) 
     122            ! 
     123         END SELECT 
    118124 
    119125         ! ... masked sea surface freezing temperature [Kelvin] (set to rt0 over land) 
     
    144150               &                      qla_ice    , dqns_ice   , dqla_ice   ,            & 
    145151               &                      tprecip    , sprecip    ,                         & 
    146                &                      fr1_i0     , fr2_i0     , cl_grid    , jpl  ) 
     152               &                      fr1_i0     , fr2_i0     , cp_ice_msh , jpl  ) 
    147153 
    148154         CASE( 4 )           ! CORE bulk formulation 
     
    151157               &                      qla_ice    , dqns_ice   , dqla_ice   ,            & 
    152158               &                      tprecip    , sprecip    ,                         & 
    153                &                      fr1_i0     , fr2_i0     , cl_grid    , jpl  ) 
     159               &                      fr1_i0     , fr2_i0     , cp_ice_msh , jpl  ) 
    154160         CASE( 5 )           ! Coupled formulation : atmosphere-ice stress only (fluxes provided after ice dynamics) 
    155161            CALL sbc_cpl_ice_tau( utau_ice , vtau_ice ) 
     
    172178         !  Ice model step  ! 
    173179         ! ---------------- ! 
    174  
    175                                         CALL lim_rst_opn_2  ( kt )      ! Open Ice restart file 
    176          IF( .NOT. lk_c1d ) THEN                                        ! 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 
     180         numit = numit + nn_fsbc                           ! Ice model time step 
     181 
     182                           CALL lim_rst_opn_2  ( kt )  ! Open Ice restart file 
     183         IF( .NOT. lk_c1d ) THEN                       ! Ice dynamics & transport (except in 1D case) 
     184                           CALL lim_dyn_2      ( kt )      ! Ice dynamics    ( rheology/dynamics ) 
     185                           CALL lim_trp_2      ( kt )      ! Ice transport   ( Advection/diffusion ) 
     186           IF( ln_limdmp ) CALL lim_dmp_2      ( kt )      ! Ice damping  
     187         END IF 
    181188#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,   & 
     189         !                                             ! Ice surface fluxes in coupled mode  
     190         IF( ksbc == 5 )   CALL sbc_cpl_ice_flx( reshape( frld, (/jpi,jpj,1/) ),                 & 
     191      &                                                   qns_tot, qns_ice, qsr_tot , qsr_ice,   & 
     192      &                                                   emp_tot, emp_ice, dqns_ice, sprecip,   & 
    185193      !                                      optional arguments, used only in 'mixed oce-ice' case 
    186       &                                                       palbi = zalb_ice_cs, psst = sst_m, pist = sist ) 
     194      &                                                   palbi = zalb_ice_cs, psst = sst_m, pist = sist ) 
    187195#endif 
    188                                         CALL lim_thd_2      ( kt )      ! Ice thermodynamics  
    189                                         CALL lim_sbc_2      ( kt )      ! Ice/Ocean Mass & Heat fluxes  
     196                           CALL lim_thd_2      ( kt )      ! Ice thermodynamics  
     197                           CALL lim_sbc_flx_2  ( kt )      ! update surface ocean mass, heat & salt fluxes  
    190198 
    191199         IF( ( MOD( kt+nn_fsbc-1, ninfo ) == 0 .OR. ntmoy == 1 ) .AND. .NOT. lk_mpp )   & 
    192             &                           CALL lim_dia_2      ( kt )      ! Ice Diagnostics 
     200            &              CALL lim_dia_2      ( kt )      ! Ice Diagnostics 
    193201# if ! defined key_iomput 
    194                                         CALL lim_wri_2      ( kt )      ! Ice outputs 
     202                           CALL lim_wri_2      ( kt )      ! Ice outputs 
    195203# endif 
    196          IF( lrst_ice )                 CALL lim_rst_write_2( kt )      ! Ice restart file 
     204         IF( lrst_ice  )   CALL lim_rst_write_2( kt )      ! Ice restart file 
    197205         ! 
    198       ENDIF 
     206      ENDIF                                    ! End sea-ice time step only 
     207      ! 
     208      !                                        !--------------------------! 
     209      !                                        !  at all ocean time step  ! 
     210      !                                        !--------------------------! 
     211      !                                                
     212      !                                              ! Update surface ocean stresses (only in ice-dynamic case) 
     213      !                                                   ! otherwise the atm.-ocean stresses are used everywhere 
     214      IF( ln_limdyn    )   CALL lim_sbc_tau_2( kt, ub(:,:,1), vb(:,:,1) )  ! using before instantaneous surf. currents 
    199215      ! 
    200216   END SUBROUTINE sbc_ice_lim_2 
Note: See TracChangeset for help on using the changeset viewer.