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 3066 for branches/2011/dev_UKM0_2011/NEMOGCM/NEMO/OPA_SRC/SBC – NEMO

Ignore:
Timestamp:
2011-11-09T14:09:37+01:00 (13 years ago)
Author:
rfurner
Message:

ticket #885 adding changes from branches/2011/dev_r2802_UKMO8_cice between r2802 and r3041

Location:
branches/2011/dev_UKM0_2011/NEMOGCM/NEMO/OPA_SRC/SBC
Files:
3 edited
1 copied

Legend:

Unmodified
Added
Removed
  • branches/2011/dev_UKM0_2011/NEMOGCM/NEMO/OPA_SRC/SBC/sbc_ice.F90

    r2777 r3066  
    66   !! History :  3.0  ! 2006-08  (G. Madec)  Surface module 
    77   !!            3.2  ! 2009-06  (S. Masson) merge with ice_oce 
    8    !!            4.0  ! 2011-01  (A. R. Porter, STFC Daresbury) dynamical allocation 
     8   !!            3.3.1! 2011-01  (A. R. Porter, STFC Daresbury) dynamical allocation 
     9   !!            3.4  ! 2011-11  (C. Harris) CICE added as an option 
    910   !!---------------------------------------------------------------------- 
    10 #if defined key_lim3 || defined key_lim2 
     11#if defined key_lim3 || defined key_lim2 || defined key_cice 
    1112   !!---------------------------------------------------------------------- 
    1213   !!   'key_lim2' or 'key_lim3' :             LIM-2 or LIM-3 sea-ice model 
     
    1920   USE par_ice_2        ! LIM-2 parameters 
    2021# endif 
     22# if defined key_cice  
     23   USE ice_domain_size, only: ncat  
     24#endif 
    2125   USE lib_mpp          ! MPP library 
    2226   USE in_out_manager   ! I/O manager 
     
    3034   LOGICAL         , PUBLIC, PARAMETER ::   lk_lim2    = .TRUE.   !: LIM-2 ice model 
    3135   LOGICAL         , PUBLIC, PARAMETER ::   lk_lim3    = .FALSE.  !: no LIM-3 
     36   LOGICAL         , PUBLIC, PARAMETER ::   lk_cice    = .FALSE.  !: no CICE  
    3237#  if defined key_lim2_vp 
    3338   CHARACTER(len=1), PUBLIC, PARAMETER ::   cp_ice_msh = 'I'      !: VP : 'I'-grid ice-velocity (B-grid lower left corner) 
     
    3944   LOGICAL         , PUBLIC, PARAMETER ::   lk_lim2    = .FALSE.  !: no LIM-2 
    4045   LOGICAL         , PUBLIC, PARAMETER ::   lk_lim3    = .TRUE.   !: LIM-3 ice model 
     46   LOGICAL         , PUBLIC, PARAMETER ::   lk_cice    = .FALSE.  !: no CICE  
    4147   CHARACTER(len=1), PUBLIC, PARAMETER ::   cp_ice_msh = 'C'      !: 'C'-grid ice-velocity 
    4248# endif 
     49# if defined  key_cice 
     50   LOGICAL         , PUBLIC, PARAMETER ::   lk_lim2    = .FALSE.  !: no LIM-2 
     51   LOGICAL         , PUBLIC, PARAMETER ::   lk_lim3    = .FALSE.  !: no LIM-3 
     52   LOGICAL         , PUBLIC, PARAMETER ::   lk_cice    = .TRUE.   !: CICE ice model 
     53   CHARACTER(len=1), PUBLIC            ::   cp_ice_msh = 'F'      !: 'F'-grid ice-velocity 
     54# endif 
    4355 
     56#if defined key_lim3 || defined key_lim2  
    4457   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:,:) ::   qns_ice   !: non solar heat flux over ice                  [W/m2] 
    4558   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:,:) ::   qsr_ice   !: solar heat flux over ice                      [W/m2] 
     
    6073# endif 
    6174 
     75#elif defined key_cice 
     76   ! 
     77   ! for consistency with LIM, these are declared with three dimensions 
     78   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:,:) ::   qlw_ice            !: incoming long-wave 
     79   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:,:) ::   qla_ice            !: latent flux over ice           [W/m2] 
     80   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:,:) ::   qsr_ice            !: solar heat flux over ice       [W/m2] 
     81   ! 
     82   ! other forcing arrays are two dimensional 
     83   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:)   ::   ss_iou             !: x ice-ocean surface stress at NEMO U point 
     84   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:)   ::   ss_iov             !: y ice-ocean surface stress at NEMO V point 
     85   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:)   ::   emp_ice            !: sublimation-snow budget over ice    [kg/m2] 
     86   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:)   ::   tatm_ice           !: air temperature 
     87   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:)   ::   qatm_ice           !: specific humidity 
     88   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:)   ::   wndi_ice           !: i wind at T point 
     89   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:)   ::   wndj_ice           !: j wind at T point 
     90   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:)   ::   nfrzmlt            !: NEMO frzmlt 
     91   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:)   ::   fr_iu              !: ice fraction at NEMO U point 
     92   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:)   ::   fr_iv              !: ice fraction at NEMO V point 
     93   ! 
     94   ! finally, arrays corresponding to different ice categories 
     95   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:,:) ::   a_i                !: category ice fraction 
     96   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:,:) ::   topmelt           !: category topmelt 
     97   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:,:) ::   botmelt           !: category botmelt 
     98#endif 
     99 
    62100   !!---------------------------------------------------------------------- 
    63101   !! NEMO/OPA 4.0 , NEMO Consortium (2011) 
     
    71109      !!                     ***  FUNCTION sbc_ice_alloc  *** 
    72110      !!---------------------------------------------------------------------- 
     111#if defined key_lim3 || defined key_lim2 
    73112      ALLOCATE( qns_ice (jpi,jpj,jpl) , qsr_ice (jpi,jpj,jpl) ,     & 
    74113         &      qla_ice (jpi,jpj,jpl) , dqla_ice(jpi,jpj,jpl) ,     & 
     
    77116         &      utau_ice(jpi,jpj)     , vtau_ice(jpi,jpj)     ,     & 
    78117         &      fr1_i0  (jpi,jpj)     , fr2_i0  (jpi,jpj)     ,     & 
    79 # if defined key_lim3 
     118#if defined key_lim3 
    80119         &      emp_ice(jpi,jpj)      , tatm_ice(jpi,jpj)     , STAT= sbc_ice_alloc ) 
    81 # else 
     120#else 
    82121         &      emp_ice(jpi,jpj)                              , STAT= sbc_ice_alloc ) 
    83 # endif 
     122#endif 
     123#elif defined key_cice 
     124      ALLOCATE( qla_ice(jpi,jpj,1)    , qlw_ice(jpi,jpj,1)    , qsr_ice(jpi,jpj,1)    , & 
     125                wndi_ice(jpi,jpj)     , tatm_ice(jpi,jpj)     , qatm_ice(jpi,jpj)     , & 
     126                wndj_ice(jpi,jpj)     , nfrzmlt(jpi,jpj)      , ss_iou(jpi,jpj)       , & 
     127                ss_iov(jpi,jpj)       , fr_iu(jpi,jpj)        , fr_iv(jpi,jpj)        , & 
     128                a_i(jpi,jpj,ncat)     , topmelt(jpi,jpj,ncat) , botmelt(jpi,jpj,ncat), STAT= sbc_ice_alloc ) 
     129#endif 
    84130         ! 
    85131      IF( lk_mpp            )   CALL mpp_sum ( sbc_ice_alloc ) 
     
    89135#else 
    90136   !!---------------------------------------------------------------------- 
    91    !!   Default option                      NO LIM 2.0 or 3.0 sea-ice model 
     137   !!   Default option                      NO LIM 2.0 or 3.0 or CICE sea-ice model 
    92138   !!---------------------------------------------------------------------- 
    93139   LOGICAL         , PUBLIC, PARAMETER ::   lk_lim2    = .FALSE.  !: no LIM-2 ice model 
    94140   LOGICAL         , PUBLIC, PARAMETER ::   lk_lim3    = .FALSE.  !: no LIM-3 ice model 
     141   LOGICAL         , PUBLIC, PARAMETER ::   lk_cice    = .FALSE.  !: no CICE  ice model 
    95142   CHARACTER(len=1), PUBLIC, PARAMETER ::   cp_ice_msh = '-'      !: no grid ice-velocity 
    96143#endif 
  • branches/2011/dev_UKM0_2011/NEMOGCM/NEMO/OPA_SRC/SBC/sbcblk_core.F90

    r2777 r3066  
    1414   !!            3.2  !  2009-04  (B. Lemaire)  Introduce iom_put 
    1515   !!            3.3  !  2010-10  (S. Masson)  add diurnal cycle 
     16   !!            3.4  !  2011-11  (C. Harris) Fill arrays required by CICE 
    1617   !!---------------------------------------------------------------------- 
    1718 
     
    3435   USE lbclnk          ! ocean lateral boundary conditions (or mpp link) 
    3536   USE prtctl          ! Print control 
    36 #if defined key_lim3 
     37#if defined key_lim3 || defined key_cice 
    3738   USE sbc_ice         ! Surface boundary condition: ice fields 
    3839#endif 
     
    182183      !                                                        ! surface ocean fluxes computed with CLIO bulk formulea 
    183184      IF( MOD( kt - 1, nn_fsbc ) == 0 )   CALL blk_oce_core( sf, sst_m, ssu_m, ssv_m ) 
     185 
     186#if defined key_cice 
     187      IF( MOD( kt - 1, nn_fsbc ) == 0 )   THEN 
     188         qlw_ice(:,:,1)   = sf(jp_qlw)%fnow(:,:,1)  
     189         qsr_ice(:,:,1)   = sf(jp_qsr)%fnow(:,:,1) 
     190         tatm_ice(:,:)    = sf(jp_tair)%fnow(:,:,1)          
     191         qatm_ice(:,:)    = sf(jp_humi)%fnow(:,:,1) 
     192         tprecip(:,:)     = sf(jp_prec)%fnow(:,:,1) * rn_pfac 
     193         sprecip(:,:)     = sf(jp_snow)%fnow(:,:,1) * rn_pfac 
     194         wndi_ice(:,:)    = sf(jp_wndi)%fnow(:,:,1) 
     195         wndj_ice(:,:)    = sf(jp_wndj)%fnow(:,:,1) 
     196      ENDIF 
     197#endif 
    184198      ! 
    185199   END SUBROUTINE sbc_blk_core 
  • branches/2011/dev_UKM0_2011/NEMOGCM/NEMO/OPA_SRC/SBC/sbcmod.F90

    r3062 r3066  
    1111   !!             -   ! 2010-11  (G. Madec) ice-ocean stress always computed at each ocean time-step 
    1212   !!             -   ! 2010-10  (J. Chanut, C. Bricaud, G. Madec)  add the surface pressure forcing 
     13   !!            3.4  ! 2011-11  (C. Harris) CICE added as an option 
    1314   !!---------------------------------------------------------------------- 
    1415 
     
    3233   USE sbcice_lim       ! surface boundary condition: LIM 3.0 sea-ice model 
    3334   USE sbcice_lim_2     ! surface boundary condition: LIM 2.0 sea-ice model 
     35   USE sbcice_cice      ! surface boundary condition: CICE    sea-ice model 
    3436   USE sbccpl           ! surface boundary condition: coupled florulation 
    3537   USE cpl_oasis3, ONLY:lk_cpl      ! are we in coupled mode? 
     
    9496        IF( lk_lim2 )   nn_ice      = 2 
    9597        IF( lk_lim3 )   nn_ice      = 3 
     98        IF( lk_cice )   nn_ice      = 4 
    9699      ENDIF 
    97100      IF( cp_cfg == 'gyre' ) THEN            ! GYRE configuration 
     
    144147         &  CALL ctl_warn( 'nn_fsbc is NOT a multiple of the number of time steps in a day' ) 
    145148      ! 
    146       IF( nn_ice == 2 .AND. .NOT.( ln_blk_clio .OR. ln_blk_core .OR. lk_cpl ) )   & 
    147          &   CALL ctl_stop( 'sea-ice model requires a bulk formulation or coupled configuration' ) 
     149      IF( ( nn_ice == 2 .OR. nn_ice ==3 ) .AND. .NOT.( ln_blk_clio .OR. ln_blk_core .OR. lk_cpl ) )   & 
     150         &   CALL ctl_stop( 'LIM sea-ice model requires a bulk formulation or coupled configuration' ) 
     151      IF( nn_ice == 4 .AND. .NOT.( ln_blk_core .OR. lk_cpl ) )   & 
     152         &   CALL ctl_stop( 'CICE sea-ice model requires ln_blk_core or lk_cpl' ) 
     153      IF( nn_ice == 4 .AND. ( .NOT. ( cp_cfg == 'orca' ) .OR. lk_agrif ) )   & 
     154         &   CALL ctl_stop( 'CICE sea-ice model currently only available in a global ORCA configuration without AGRIF' ) 
    148155       
    149156      IF( ln_dm2dc )   nday_qsr = -1   ! initialisation flag 
     
    182189         IF( nsbc ==  5 )   WRITE(numout,*) '              coupled formulation' 
    183190      ENDIF 
     191 
     192      IF( nn_ice == 4 )   CALL cice_sbc_init (nsbc) 
    184193      ! 
    185194   END SUBROUTINE sbc_init 
     
    256265         !                                                      
    257266      CASE(  3 )   ;       CALL sbc_ice_lim  ( kt, nsbc )            ! LIM-3 ice model 
     267         ! 
     268      CASE(  4 )   ;       CALL sbc_ice_cice ( kt, nsbc )            ! CICE ice model 
    258269      END SELECT                                               
    259270 
     
    338349            &         tab2d_2=vtau      , clinfo2=' vtau     - : ', mask2=vmask, ovlap=1 ) 
    339350      ENDIF 
     351 
     352      IF( kt == nitend )   CALL sbc_final         ! Close down surface module if necessary 
    340353      ! 
    341354   END SUBROUTINE sbc 
     355 
     356   SUBROUTINE sbc_final 
     357      !!--------------------------------------------------------------------- 
     358      !!                    ***  ROUTINE sbc_final  *** 
     359      !!--------------------------------------------------------------------- 
     360 
     361      !----------------------------------------------------------------- 
     362      ! Finalize CICE (if used) 
     363      !----------------------------------------------------------------- 
     364 
     365      IF( nn_ice == 4 )   CALL cice_sbc_final 
     366      ! 
     367   END SUBROUTINE sbc_final 
    342368 
    343369   !!====================================================================== 
Note: See TracChangeset for help on using the changeset viewer.