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 8324 for branches/2017/dev_r8183_ICEMODEL – NEMO

Ignore:
Timestamp:
2017-07-12T15:36:28+02:00 (7 years ago)
Author:
clem
Message:

STEP3 (2): clean separation between sea-ice and ocean

Location:
branches/2017/dev_r8183_ICEMODEL/NEMOGCM/NEMO
Files:
10 edited

Legend:

Unmodified
Added
Removed
  • branches/2017/dev_r8183_ICEMODEL/NEMOGCM/NEMO/LIM_SRC_3/icestp.F90

    r8322 r8324  
    302302      CALL ice_run_init                ! set some ice run parameters 
    303303      ! 
    304       !                                ! Allocate the ice arrays 
     304      !                                ! Allocate the ice arrays (sbc_ice already allocated in sbc_init) 
    305305      ierr =        ice_alloc        ()      ! ice variables 
    306       ierr = ierr + sbc_ice_alloc    ()      ! surface forcing 
    307306      ierr = ierr + thd_ice_alloc    ()      ! thermodynamics 
    308307      IF( ln_limdyn )   ierr = ierr + lim_itd_me_alloc ()      ! ice thickness distribution - mechanics 
  • branches/2017/dev_r8183_ICEMODEL/NEMOGCM/NEMO/LIM_SRC_3/limrhg.F90

    r8319 r8324  
    1919   !!---------------------------------------------------------------------- 
    2020   USE phycst         ! Physical constant 
    21    USE oce     , ONLY :  snwice_mass, snwice_mass_b 
    2221   USE par_oce        ! Ocean parameters 
    2322   USE dom_oce        ! Ocean domain 
    2423   USE sbc_oce , ONLY : ln_ice_embd, nn_fsbc, ssh_m 
    25    USE sbc_ice , ONLY : utau_ice, vtau_ice 
     24   USE sbc_ice , ONLY : utau_ice, vtau_ice, snwice_mass, snwice_mass_b 
    2625   USE ice            ! ice variables 
    2726   USE limitd_me      ! ice strength 
  • branches/2017/dev_r8183_ICEMODEL/NEMOGCM/NEMO/LIM_SRC_3/limrst.F90

    r8321 r8324  
    1717   !!---------------------------------------------------------------------- 
    1818   USE ice            ! sea-ice variables 
    19    USE oce    , ONLY :  snwice_mass, snwice_mass_b 
     19   USE sbc_ice , ONLY :  snwice_mass, snwice_mass_b 
    2020   USE dom_oce        ! ocean domain 
    2121   USE sbc_oce , ONLY : nn_fsbc 
  • branches/2017/dev_r8183_ICEMODEL/NEMOGCM/NEMO/LIM_SRC_3/limsbc.F90

    r8321 r8324  
    2424   !!---------------------------------------------------------------------- 
    2525   USE par_oce        ! ocean parameters 
    26    USE oce     , ONLY : sshn, sshb, snwice_mass, snwice_mass_b, snwice_fmass 
     26   USE oce     , ONLY : sshn, sshb 
    2727   USE phycst         ! physical constants 
    2828   USE dom_oce        ! ocean domain 
    2929   USE ice            ! LIM sea-ice variables 
    30    USE sbc_ice , ONLY : emp_oce, qns_oce, qsr_oce, qemp_oce, emp_ice, qsr_ice, qemp_ice, qevap_ice, alb_ice, tn_ice, cldf_ice 
     30   USE sbc_ice , ONLY : emp_oce, qns_oce, qsr_oce, qemp_oce, emp_ice, qsr_ice, qemp_ice, qevap_ice, alb_ice, tn_ice, cldf_ice,  & 
     31      &                 snwice_mass, snwice_mass_b, snwice_fmass 
    3132   USE sbc_oce , ONLY : nn_fsbc, ln_ice_embd, sfx, fr_i, qsr_tot, qns, qsr, fmmflx, emp, taum, utau, vtau 
    3233   USE sbccpl         ! Surface boundary condition: coupled interface 
  • branches/2017/dev_r8183_ICEMODEL/NEMOGCM/NEMO/OPA_SRC/DYN/dynspg.F90

    r8313 r8324  
    1717   USE phycst         ! physical constants 
    1818   USE sbc_oce        ! surface boundary condition: ocean 
     19   USE sbc_ice , ONLY : snwice_mass, snwice_mass_b 
    1920   USE sbcapr         ! surface boundary condition: atmospheric pressure 
    2021   USE dynspg_exp     ! surface pressure gradient     (dyn_spg_exp routine) 
  • branches/2017/dev_r8183_ICEMODEL/NEMOGCM/NEMO/OPA_SRC/SBC/sbc_ice.F90

    r8321 r8324  
    2727   PRIVATE 
    2828 
    29    PUBLIC sbc_ice_alloc ! called in iceini(_2).F90 
     29   PUBLIC sbc_ice_alloc ! called in sbcmod.F90 
    3030 
    3131# if defined  key_lim3 
     
    103103   REAL(wp), PUBLIC, SAVE ::   cldf_ice = 0.81    !: cloud fraction over sea ice, summer CLIO value   [-] 
    104104 
     105   !! arrays relating to embedding ice in the ocean 
     106   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:)   ::   snwice_mass        !: mass of snow and ice at current  ice time step   [Kg/m2] 
     107   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:)   ::   snwice_mass_b      !: mass of snow and ice at previous ice time step   [Kg/m2] 
     108   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:)   ::   snwice_fmass       !: time evolution of mass of snow+ice               [Kg/m2/s] 
     109 
    105110   !!---------------------------------------------------------------------- 
    106111   !! NEMO/OPA 4.0 , NEMO Consortium (2011) 
     
    114119      !!                     ***  FUNCTION sbc_ice_alloc  *** 
    115120      !!---------------------------------------------------------------------- 
    116       INTEGER :: ierr(5) 
     121      INTEGER :: ierr(4) 
    117122      !!---------------------------------------------------------------------- 
    118123      ierr(:) = 0 
     124 
     125      ALLOCATE( snwice_mass(jpi,jpj) , snwice_mass_b(jpi,jpj), snwice_fmass(jpi,jpj) , STAT=ierr(1) ) 
    119126 
    120127#if defined key_lim3 
     
    127134         &      qemp_ice(jpi,jpj)     , qevap_ice(jpi,jpj,jpl) , qemp_oce (jpi,jpj) ,   & 
    128135         &      qns_oce (jpi,jpj)     , qsr_oce  (jpi,jpj)     , emp_oce (jpi,jpj)  ,   & 
    129          &      emp_ice(jpi,jpj)      ,  STAT= ierr(1) ) 
     136         &      emp_ice(jpi,jpj)      ,  STAT= ierr(2) ) 
    130137#endif 
    131138 
     
    136143                ss_iov(jpi,jpj)       , fr_iu(jpi,jpj)        , fr_iv(jpi,jpj)        , & 
    137144                a_i(jpi,jpj,ncat)     , topmelt(jpi,jpj,ncat) , botmelt(jpi,jpj,ncat) , & 
    138                 STAT= ierr(1) ) 
     145                STAT= ierr(2) ) 
    139146      IF( ln_cpl )   ALLOCATE( u_ice(jpi,jpj)        , fr1_i0(jpi,jpj)       , tn_ice (jpi,jpj,1)    , & 
    140147         &                     v_ice(jpi,jpj)        , fr2_i0(jpi,jpj)       , alb_ice(jpi,jpj,1)    , & 
    141148         &                     emp_ice(jpi,jpj)      , qns_ice(jpi,jpj,1)    , dqns_ice(jpi,jpj,1)   , & 
    142          &                     STAT= ierr(2) ) 
    143        
    144 #endif 
    145          ! 
    146 #if defined key_cice 
    147       IF( ln_cpl )   ALLOCATE( ht_i(jpi,jpj,jpl) , ht_s(jpi,jpj,jpl) , STAT=ierr(5) ) 
     149         &                     STAT= ierr(3) )       
     150      IF( ln_cpl )   ALLOCATE( ht_i(jpi,jpj,jpl) , ht_s(jpi,jpj,jpl) , STAT=ierr(4) ) 
    148151#endif 
    149152 
     
    155158#else 
    156159   !!---------------------------------------------------------------------- 
    157    !!   Default option                      NO LIM 2.0 or 3.0 or CICE sea-ice model 
     160   !!   Default option                      NO LIM3 or CICE sea-ice model 
    158161   !!---------------------------------------------------------------------- 
    159162   USE in_out_manager   ! I/O manager 
     
    173176   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:,:) ::   ht_i, ht_s 
    174177   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:,:) ::   topmelt, botmelt 
     178   ! 
     179   !! arrays relating to embedding ice in the ocean. These arrays need to be declared  
     180   !! even if no ice model is required. In the no ice model or traditional levitating  
     181   !! ice cases they contain only zeros 
     182   !! --------------------- 
     183   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:)   ::   snwice_mass        !: mass of snow and ice at current  ice time step   [Kg/m2] 
     184   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:)   ::   snwice_mass_b      !: mass of snow and ice at previous ice time step   [Kg/m2] 
     185   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:)   ::   snwice_fmass       !: time evolution of mass of snow+ice               [Kg/m2/s] 
    175186 
    176187CONTAINS 
    177188   INTEGER FUNCTION sbc_ice_alloc() 
    178       sbc_ice_alloc = 0 
     189      !!---------------------------------------------------------------------- 
     190      !!                     ***  FUNCTION sbc_ice_alloc  *** 
     191      !!---------------------------------------------------------------------- 
     192      INTEGER :: ierr(1) 
     193      !!---------------------------------------------------------------------- 
     194      ierr(:) = 0 
     195      ALLOCATE( snwice_mass(jpi,jpj) , snwice_mass_b(jpi,jpj), snwice_fmass(jpi,jpj) , STAT=ierr(1) ) 
     196      sbc_ice_alloc = MAXVAL( ierr ) 
     197      IF( lk_mpp            )   CALL mpp_sum ( sbc_ice_alloc ) 
     198      IF( sbc_ice_alloc > 0 )   CALL ctl_warn('sbc_ice_alloc: allocation of arrays failed') 
    179199   END FUNCTION sbc_ice_alloc 
    180200#endif 
  • branches/2017/dev_r8183_ICEMODEL/NEMOGCM/NEMO/OPA_SRC/SBC/sbcfwb.F90

    r8306 r8324  
    1717   USE dom_oce        ! ocean space and time domain 
    1818   USE sbc_oce        ! surface ocean boundary condition 
     19   USE sbc_ice , ONLY : snwice_mass, snwice_mass_b, snwice_fmass 
    1920   USE phycst         ! physical constants 
    2021   USE sbcrnf         ! ocean runoffs 
  • branches/2017/dev_r8183_ICEMODEL/NEMOGCM/NEMO/OPA_SRC/SBC/sbcice_cice.F90

    r8316 r8324  
    199199 
    200200! allocate sbc_ice and sbc_cice arrays 
    201       IF( sbc_ice_alloc()      /= 0 )   CALL ctl_stop( 'STOP', 'sbc_ice_cice_alloc : unable to allocate arrays' ) 
    202201      IF( sbc_ice_cice_alloc() /= 0 )   CALL ctl_stop( 'STOP', 'sbc_ice_cice_alloc : unable to allocate cice arrays' ) 
    203202 
  • branches/2017/dev_r8183_ICEMODEL/NEMOGCM/NEMO/OPA_SRC/SBC/sbcmod.F90

    r8321 r8324  
    210210      !                             !* allocate sbc arrays 
    211211      IF( sbc_oce_alloc() /= 0 )   CALL ctl_stop( 'sbc_init : unable to allocate sbc_oce arrays' ) 
     212      IF( sbc_ice_alloc() /= 0 )   CALL ctl_stop( 'sbc_init : unable to allocate sbc_ice arrays' )               
    212213      ! 
    213214      IF( .NOT.ln_isf ) THEN        !* No ice-shelf in the domain : allocate and set to zero 
     
    306307      ! 
    307308#if defined key_lim3 
    308       IF    ( lk_agrif .AND. nn_ice == 0 ) THEN 
    309                          IF( sbc_ice_alloc() /= 0 )   CALL ctl_stop( 'STOP', 'sbc_ice_alloc : unable to allocate arrays' )  ! clem2017: allocate ice arrays in case agrif + lim + no-ice in child grid               
    310       ELSEIF(                nn_ice == 2 ) THEN   ;   CALL ice_init                ! LIM3 initialization 
    311       ENDIF 
     309      IF( nn_ice == 2 )   CALL ice_init                ! LIM3 initialization 
    312310#endif 
    313       IF    (                nn_ice == 3 )            CALL cice_sbc_init( nsbc )   ! CICE initialization 
    314       ! 
    315       IF( ln_wave     )   CALL sbc_wave_init              ! surface wave initialisation 
     311      IF( nn_ice == 3 )   CALL cice_sbc_init( nsbc )   ! CICE initialization 
     312      ! 
     313      IF( ln_wave     )   CALL sbc_wave_init           ! surface wave initialisation 
    316314      ! 
    317315   END SUBROUTINE sbc_init 
  • branches/2017/dev_r8183_ICEMODEL/NEMOGCM/NEMO/OPA_SRC/oce.F90

    r7646 r8324  
    6565   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:,:) ::   rke          !: kinetic energy 
    6666 
    67    !! arrays relating to embedding ice in the ocean. These arrays need to be declared  
    68    !! even if no ice model is required. In the no ice model or traditional levitating  
    69    !! ice cases they contain only zeros 
    70    !! --------------------- 
    71    REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:)   ::   snwice_mass        !: mass of snow and ice at current  ice time step   [Kg/m2] 
    72    REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:)   ::   snwice_mass_b      !: mass of snow and ice at previous ice time step   [Kg/m2] 
    73    REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:)   ::   snwice_fmass       !: time evolution of mass of snow+ice               [Kg/m2/s] 
    74  
    7567   !! Energy budget of the leads (open water embedded in sea ice) 
    7668   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:)   ::   fraqsr_1lev        !: fraction of solar net radiation absorbed in the first ocean level [-] 
     
    8779      !!                   ***  FUNCTION oce_alloc  *** 
    8880      !!---------------------------------------------------------------------- 
    89       INTEGER :: ierr(7) 
     81      INTEGER :: ierr(6) 
    9082      !!---------------------------------------------------------------------- 
    9183      ! 
     
    110102         &     riceload(jpi,jpj),                             STAT=ierr(2) ) 
    111103         ! 
    112       ALLOCATE( snwice_mass(jpi,jpj) , snwice_mass_b(jpi,jpj), snwice_fmass(jpi,jpj) , STAT=ierr(3) ) 
    113          ! 
    114       ALLOCATE( fraqsr_1lev(jpi,jpj) , STAT=ierr(4) ) 
     104      ALLOCATE( fraqsr_1lev(jpi,jpj) , STAT=ierr(3) ) 
    115105         ! 
    116106      ALLOCATE( ssha_e(jpi,jpj),  sshn_e(jpi,jpj), sshb_e(jpi,jpj), sshbb_e(jpi,jpj), & 
    117107         &        ua_e(jpi,jpj),    un_e(jpi,jpj),   ub_e(jpi,jpj),   ubb_e(jpi,jpj), & 
    118108         &        va_e(jpi,jpj),    vn_e(jpi,jpj),   vb_e(jpi,jpj),   vbb_e(jpi,jpj), & 
    119          &        hu_e(jpi,jpj),   hur_e(jpi,jpj),   hv_e(jpi,jpj),   hvr_e(jpi,jpj), STAT=ierr(5) ) 
     109         &        hu_e(jpi,jpj),   hur_e(jpi,jpj),   hv_e(jpi,jpj),   hvr_e(jpi,jpj), STAT=ierr(4) ) 
    120110         ! 
    121       ALLOCATE( ub2_b(jpi,jpj), vb2_b(jpi,jpj)                                      , STAT=ierr(6) ) 
     111      ALLOCATE( ub2_b(jpi,jpj), vb2_b(jpi,jpj)                                      , STAT=ierr(5) ) 
    122112#if defined key_agrif 
    123       ALLOCATE( ub2_i_b(jpi,jpj), vb2_i_b(jpi,jpj)                                  , STAT=ierr(7) ) 
     113      ALLOCATE( ub2_i_b(jpi,jpj), vb2_i_b(jpi,jpj)                                  , STAT=ierr(6) ) 
    124114#endif 
    125115         ! 
Note: See TracChangeset for help on using the changeset viewer.