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 2874 – NEMO

Changeset 2874


Ignore:
Timestamp:
2011-09-28T12:19:59+02:00 (13 years ago)
Author:
charris
Message:

Code for running NEMO with CICE (for fully coupled mode this should be used in combination with dev_r2802_UKMO8_sbccpl). Changes are described briefly below.

physct: Constants modified to be consistent with CICE

nemogcm / prtctl / mppini: Changes to NEMO decomposition (activated using key_nemocice_decomp) to produce 'square' options in CICE. Can run without this key / code but this requires a global gather / scatter in the NEMO-CICE coupling which gets very slow on large processors numbers.

sbc_ice: CICE options and arrays added

sbcmod: CICE option added, including calls for initialising and finalising CICE.

sbcblk_core: Make sure necessary forcing field are available for CICE

sbcice_cice: Main CICE coupling code.

Location:
branches/2011/dev_r2802_UKMO8_cice/NEMOGCM/NEMO/OPA_SRC
Files:
1 added
7 edited

Legend:

Unmodified
Added
Removed
  • branches/2011/dev_r2802_UKMO8_cice/NEMOGCM/NEMO/OPA_SRC/DOM/phycst.F90

    r2528 r2874  
    4848#endif 
    4949 
     50#if defined key_cice 
     51   REAL(wp), PUBLIC ::   rau0     = 1026._wp      !: reference volumic mass (density)  (kg/m3) 
     52#else 
    5053   REAL(wp), PUBLIC ::   rau0     = 1035._wp      !: reference volumic mass (density)  (kg/m3) 
     54#endif 
    5155   REAL(wp), PUBLIC ::   rau0r                    !: reference specific volume         (m3/kg) 
    5256   REAL(wp), PUBLIC ::   rcp      =    4.e+3_wp   !: ocean specific heat 
    5357   REAL(wp), PUBLIC ::   ro0cpr                   !: = 1. / ( rau0 * rcp ) 
    5458 
    55 #if defined key_lim3 
     59#if defined key_lim3 || defined key_cice 
    5660   REAL(wp), PUBLIC ::   rcdsn   =   0.31_wp      !: thermal conductivity of snow 
    5761   REAL(wp), PUBLIC ::   rcdic   =   2.034396_wp  !: thermal conductivity of fresh ice 
     
    100104      rsiyea = 365.25 * rday * 2. * rpi / 6.283076 
    101105      rsiday = rday / ( 1. + rday / rsiyea ) 
     106#if defined key_cice 
     107      omega =  7.292116e-05 
     108#else 
    102109      omega  = 2. * rpi / rsiday  
     110#endif 
    103111 
    104112      rau0r  = 1. /   rau0   
  • branches/2011/dev_r2802_UKMO8_cice/NEMOGCM/NEMO/OPA_SRC/IOM/prtctl.F90

    r2715 r2874  
    434434 
    435435      ijpi = ( jpiglo-2*jpreci + (isplt-1) ) / isplt + 2*jpreci 
     436#if defined key_nemocice_decomp 
     437      ijpj = ( jpjglo+1-2*jprecj + (jsplt-1) ) / jsplt + 2*jprecj  
     438#else 
    436439      ijpj = ( jpjglo-2*jprecj + (jsplt-1) ) / jsplt + 2*jprecj 
     440#endif 
    437441 
    438442      ALLOCATE(ilcitl (isplt,jsplt)) 
     
    445449 
    446450      IF(  irestil == 0 )   irestil = isplt 
     451#if defined key_nemocice_decomp 
     452 
     453      ! In order to match CICE the size of domains in NEMO has to be changed 
     454      ! The last line of blocks (west) will have fewer points  
     455      DO jj = 1, jsplt  
     456         DO ji=1, isplt-1  
     457            ilcitl(ji,jj) = ijpi  
     458         END DO  
     459         ilcitl(isplt,jj) = jpiglo - (isplt - 1) * (ijpi - nrecil) 
     460      END DO  
     461 
     462#else  
     463 
    447464      DO jj = 1, jsplt 
    448465         DO ji = 1, irestil 
     
    453470         END DO 
    454471      END DO 
     472 
     473#endif 
    455474       
    456475      IF( irestjl == 0 )   irestjl = jsplt 
     476#if defined key_nemocice_decomp  
     477 
     478      ! Same change to domains in North-South direction as in East-West.  
     479      DO ji = 1, isplt  
     480         DO jj=1, jsplt-1  
     481            ilcjtl(ji,jj) = ijpj  
     482         END DO  
     483         ilcjtl(ji,jsplt) = jpjglo - (jsplt - 1) * (ijpj - nrecjl) 
     484      END DO  
     485 
     486#else  
     487 
    457488      DO ji = 1, isplt 
    458489         DO jj = 1, irestjl 
     
    463494         END DO 
    464495      END DO 
    465        
     496 
     497#endif 
    466498      zidom = nrecil 
    467499      DO ji = 1, isplt 
  • branches/2011/dev_r2802_UKMO8_cice/NEMOGCM/NEMO/OPA_SRC/LBC/mppini.F90

    r2715 r2874  
    152152 
    153153      IF(  iresti == 0 )   iresti = jpni 
     154 
     155#if defined key_nemocice_decomp 
     156      ! In order to match CICE the size of domains in NEMO has to be changed 
     157      ! The last line of blocks (west) will have fewer points 
     158 
     159      DO jj = 1, jpnj 
     160         DO ji=1, jpni-1 
     161            ilcit(ji,jj) = jpi 
     162         END DO 
     163         ilcit(jpni,jj) = jpiglo - (jpni - 1) * (jpi - nreci) 
     164      END DO 
     165 
     166#else 
     167 
    154168      DO jj = 1, jpnj 
    155169         DO ji = 1, iresti 
     
    161175      END DO 
    162176       
     177#endif 
    163178      IF( irestj == 0 )   irestj = jpnj 
     179 
     180#if defined key_nemocice_decomp 
     181      ! Same change to domains in North-South direction as in East-West.  
     182      DO ji=1,jpni 
     183         DO jj=1,jpnj-1 
     184            ilcjt(ji,jj) = jpj 
     185         END DO 
     186         ilcjt(ji,jpnj) = jpjglo - (jpnj - 1) * (jpj - nrecj) 
     187      END DO 
     188 
     189#else 
     190 
    164191      DO ji = 1, jpni 
    165192         DO jj = 1, irestj 
     
    171198      END DO 
    172199       
     200#endif 
    173201      IF(lwp) THEN 
    174202         WRITE(numout,*) 
  • branches/2011/dev_r2802_UKMO8_cice/NEMOGCM/NEMO/OPA_SRC/SBC/sbc_ice.F90

    r2777 r2874  
    88   !!            4.0  ! 2011-01  (A. R. Porter, STFC Daresbury) dynamical allocation 
    99   !!---------------------------------------------------------------------- 
    10 #if defined key_lim3 || defined key_lim2 
     10#if defined key_lim3 || defined key_lim2 || defined key_cice 
    1111   !!---------------------------------------------------------------------- 
    1212   !!   'key_lim2' or 'key_lim3' :             LIM-2 or LIM-3 sea-ice model 
     
    1919   USE par_ice_2        ! LIM-2 parameters 
    2020# endif 
     21# if defined key_cice  
     22   USE ice_domain_size, only: ncat  
     23#endif 
    2124   USE lib_mpp          ! MPP library 
    2225   USE in_out_manager   ! I/O manager 
     
    3033   LOGICAL         , PUBLIC, PARAMETER ::   lk_lim2    = .TRUE.   !: LIM-2 ice model 
    3134   LOGICAL         , PUBLIC, PARAMETER ::   lk_lim3    = .FALSE.  !: no LIM-3 
     35   LOGICAL         , PUBLIC, PARAMETER ::   lk_cice    = .FALSE.  !: no CICE  
    3236#  if defined key_lim2_vp 
    3337   CHARACTER(len=1), PUBLIC, PARAMETER ::   cp_ice_msh = 'I'      !: VP : 'I'-grid ice-velocity (B-grid lower left corner) 
     
    3943   LOGICAL         , PUBLIC, PARAMETER ::   lk_lim2    = .FALSE.  !: no LIM-2 
    4044   LOGICAL         , PUBLIC, PARAMETER ::   lk_lim3    = .TRUE.   !: LIM-3 ice model 
     45   LOGICAL         , PUBLIC, PARAMETER ::   lk_cice    = .FALSE.  !: no CICE  
    4146   CHARACTER(len=1), PUBLIC, PARAMETER ::   cp_ice_msh = 'C'      !: 'C'-grid ice-velocity 
    4247# endif 
     48# if defined  key_cice 
     49   LOGICAL         , PUBLIC, PARAMETER ::   lk_lim2    = .FALSE.  !: no LIM-2 
     50   LOGICAL         , PUBLIC, PARAMETER ::   lk_lim3    = .FALSE.  !: no LIM-3 
     51   LOGICAL         , PUBLIC, PARAMETER ::   lk_cice    = .TRUE.   !: CICE ice model 
     52   CHARACTER(len=1), PUBLIC            ::   cp_ice_msh = 'F'      !: 'F'-grid ice-velocity 
     53# endif 
    4354 
     55#if defined key_lim3 || defined key_lim2  
    4456   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:,:) ::   qns_ice   !: non solar heat flux over ice                  [W/m2] 
    4557   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:,:) ::   qsr_ice   !: solar heat flux over ice                      [W/m2] 
     
    6072# endif 
    6173 
     74#elif defined key_cice 
     75   ! 
     76   ! for consistency with LIM, these are declared with three dimensions 
     77   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:,:) ::   qlw_ice            !: incoming long-wave 
     78   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:,:) ::   qla_ice            !: latent flux over ice           [W/m2] 
     79   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:,:) ::   qsr_ice            !: solar heat flux over ice       [W/m2] 
     80   ! 
     81   ! other forcing arrays are two dimensional 
     82   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:)   ::   ss_iou             !: x ice-ocean surface stress at NEMO U point 
     83   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:)   ::   ss_iov             !: y ice-ocean surface stress at NEMO V point 
     84   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:)   ::   tatm_ice           !: air temperature 
     85   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:)   ::   qatm_ice           !: specific humidity 
     86   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:)   ::   wndi_ice           !: i wind at T point 
     87   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:)   ::   wndj_ice           !: j wind at T point 
     88   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:)   ::   nfrzmlt            !: NEMO frzmlt 
     89   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:)   ::   fr_iu              !: ice fraction at NEMO U point 
     90   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:)   ::   fr_iv              !: ice fraction at NEMO V point 
     91   ! 
     92   ! finally, arrays corresponding to different ice categories 
     93   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:,:) ::   a_i                !: category ice fraction 
     94   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:,:) ::   topmelt           !: category topmelt 
     95   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:,:) ::   botmelt           !: category botmelt 
     96#endif 
     97 
    6298   !!---------------------------------------------------------------------- 
    6399   !! NEMO/OPA 4.0 , NEMO Consortium (2011) 
     
    71107      !!                     ***  FUNCTION sbc_ice_alloc  *** 
    72108      !!---------------------------------------------------------------------- 
     109#if defined key_lim3 || defined key_lim2 
    73110      ALLOCATE( qns_ice (jpi,jpj,jpl) , qsr_ice (jpi,jpj,jpl) ,     & 
    74111         &      qla_ice (jpi,jpj,jpl) , dqla_ice(jpi,jpj,jpl) ,     & 
     
    77114         &      utau_ice(jpi,jpj)     , vtau_ice(jpi,jpj)     ,     & 
    78115         &      fr1_i0  (jpi,jpj)     , fr2_i0  (jpi,jpj)     ,     & 
    79 # if defined key_lim3 
     116#if defined key_lim3 
    80117         &      emp_ice(jpi,jpj)      , tatm_ice(jpi,jpj)     , STAT= sbc_ice_alloc ) 
    81 # else 
     118#else 
    82119         &      emp_ice(jpi,jpj)                              , STAT= sbc_ice_alloc ) 
    83 # endif 
     120#endif 
     121#elif defined key_cice 
     122      ALLOCATE( qla_ice(jpi,jpj,1)    , qlw_ice(jpi,jpj,1)    , qsr_ice(jpi,jpj,1)    , & 
     123                wndi_ice(jpi,jpj)     , tatm_ice(jpi,jpj)     , qatm_ice(jpi,jpj)     , & 
     124                wndj_ice(jpi,jpj)     , nfrzmlt(jpi,jpj)      , ss_iou(jpi,jpj)       , & 
     125                ss_iov(jpi,jpj)       , fr_iu(jpi,jpj)        , fr_iv(jpi,jpj)        , & 
     126                a_i(jpi,jpj,ncat)     , topmelt(jpi,jpj,ncat) , botmelt(jpi,jpj,ncat), STAT= sbc_ice_alloc ) 
     127#endif 
    84128         ! 
    85129      IF( lk_mpp            )   CALL mpp_sum ( sbc_ice_alloc ) 
     
    89133#else 
    90134   !!---------------------------------------------------------------------- 
    91    !!   Default option                      NO LIM 2.0 or 3.0 sea-ice model 
     135   !!   Default option                      NO LIM 2.0 or 3.0 or CICE sea-ice model 
    92136   !!---------------------------------------------------------------------- 
    93137   LOGICAL         , PUBLIC, PARAMETER ::   lk_lim2    = .FALSE.  !: no LIM-2 ice model 
    94138   LOGICAL         , PUBLIC, PARAMETER ::   lk_lim3    = .FALSE.  !: no LIM-3 ice model 
     139   LOGICAL         , PUBLIC, PARAMETER ::   lk_cice    = .FALSE.  !: no CICE  ice model 
    95140   CHARACTER(len=1), PUBLIC, PARAMETER ::   cp_ice_msh = '-'      !: no grid ice-velocity 
    96141#endif 
  • branches/2011/dev_r2802_UKMO8_cice/NEMOGCM/NEMO/OPA_SRC/SBC/sbcblk_core.F90

    r2777 r2874  
    3434   USE lbclnk          ! ocean lateral boundary conditions (or mpp link) 
    3535   USE prtctl          ! Print control 
    36 #if defined key_lim3 
     36#if defined key_lim3 || defined key_cice 
    3737   USE sbc_ice         ! Surface boundary condition: ice fields 
    3838#endif 
     
    182182      !                                                        ! surface ocean fluxes computed with CLIO bulk formulea 
    183183      IF( MOD( kt - 1, nn_fsbc ) == 0 )   CALL blk_oce_core( sf, sst_m, ssu_m, ssv_m ) 
     184 
     185#if defined key_cice 
     186      IF( MOD( kt - 1, nn_fsbc ) == 0 )   THEN 
     187         qlw_ice(:,:,1)   = sf(jp_qlw)%fnow(:,:,1)  
     188         qsr_ice(:,:,1)   = sf(jp_qsr)%fnow(:,:,1) 
     189         tatm_ice(:,:)    = sf(jp_tair)%fnow(:,:,1)          
     190         qatm_ice(:,:)    = sf(jp_humi)%fnow(:,:,1) 
     191         tprecip(:,:)     = sf(jp_prec)%fnow(:,:,1) * rn_pfac 
     192         sprecip(:,:)     = sf(jp_snow)%fnow(:,:,1) * rn_pfac 
     193         wndi_ice(:,:)    = sf(jp_wndi)%fnow(:,:,1) 
     194         wndj_ice(:,:)    = sf(jp_wndj)%fnow(:,:,1) 
     195      ENDIF 
     196#endif 
    184197      ! 
    185198   END SUBROUTINE sbc_blk_core 
  • branches/2011/dev_r2802_UKMO8_cice/NEMOGCM/NEMO/OPA_SRC/SBC/sbcmod.F90

    r2715 r2874  
    3232   USE sbcice_lim       ! surface boundary condition: LIM 3.0 sea-ice model 
    3333   USE sbcice_lim_2     ! surface boundary condition: LIM 2.0 sea-ice model 
     34   USE sbcice_cice      ! surface boundary condition: CICE    sea-ice model 
    3435   USE sbccpl           ! surface boundary condition: coupled florulation 
    3536   USE cpl_oasis3, ONLY:lk_cpl      ! are we in coupled mode? 
     
    9495        IF( lk_lim2 )   nn_ice      = 2 
    9596        IF( lk_lim3 )   nn_ice      = 3 
     97        IF( lk_cice )   nn_ice      = 4 
    9698      ENDIF 
    9799      IF( cp_cfg == 'gyre' ) THEN            ! GYRE configuration 
     
    144146         &  CALL ctl_warn( 'nn_fsbc is NOT a multiple of the number of time steps in a day' ) 
    145147      ! 
    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' ) 
     148      IF( ( nn_ice == 2 .OR. nn_ice ==3 ) .AND. .NOT.( ln_blk_clio .OR. ln_blk_core .OR. lk_cpl ) )   & 
     149         &   CALL ctl_stop( 'LIM sea-ice model requires a bulk formulation or coupled configuration' ) 
     150      IF( nn_ice == 4 .AND. .NOT.( ln_flx .OR. ln_blk_core .OR. lk_cpl ) )   & 
     151         &   CALL ctl_stop( 'CICE sea-ice model requires ln_blk_core, ln_flx or ln_cpl' ) 
    148152       
    149153      IF( ln_dm2dc )   nday_qsr = -1   ! initialisation flag 
     
    182186         IF( nsbc ==  5 )   WRITE(numout,*) '              coupled formulation' 
    183187      ENDIF 
     188 
     189      IF( nn_ice == 4 )   CALL cice_sbc_init (nsbc) 
    184190      ! 
    185191   END SUBROUTINE sbc_init 
     
    256262         !                                                      
    257263      CASE(  3 )   ;       CALL sbc_ice_lim  ( kt, nsbc )            ! LIM-3 ice model 
     264         ! 
     265      CASE(  4 )   ;       CALL sbc_ice_cice ( kt, nsbc )            ! CICE ice model 
    258266      END SELECT                                               
    259267 
     
    338346            &         tab2d_2=vtau      , clinfo2=' vtau     - : ', mask2=vmask, ovlap=1 ) 
    339347      ENDIF 
     348 
     349      IF( kt == nitend )   CALL sbc_final         ! Close down surface module if necessary 
    340350      ! 
    341351   END SUBROUTINE sbc 
     352 
     353   SUBROUTINE sbc_final 
     354      !!--------------------------------------------------------------------- 
     355      !!                    ***  ROUTINE sbc_final  *** 
     356      !!--------------------------------------------------------------------- 
     357 
     358      !----------------------------------------------------------------- 
     359      ! Finalize CICE (if used) 
     360      !----------------------------------------------------------------- 
     361 
     362      IF( nn_ice == 4 )   CALL cice_sbc_final 
     363      ! 
     364   END SUBROUTINE sbc_final 
    342365 
    343366   !!====================================================================== 
  • branches/2011/dev_r2802_UKMO8_cice/NEMOGCM/NEMO/OPA_SRC/nemogcm.F90

    r2715 r2874  
    245245      IF( Agrif_Root() ) THEN 
    246246         jpi = ( jpiglo-2*jpreci + (jpni-1) ) / jpni + 2*jpreci   ! first  dim. 
     247#if defined key_nemocice_decomp 
     248         jpj = ( jpjglo+1-2*jprecj + (jpnj-1) ) / jpnj + 2*jprecj ! second dim.  
     249#else 
    247250         jpj = ( jpjglo-2*jprecj + (jpnj-1) ) / jpnj + 2*jprecj   ! second dim. 
     251#endif 
    248252         jpk = jpkdta                                             ! third dim 
    249253         jpim1 = jpi-1                                            ! inner domain indices 
Note: See TracChangeset for help on using the changeset viewer.