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 11423 for NEMO/branches – NEMO

Changeset 11423 for NEMO/branches


Ignore:
Timestamp:
2019-08-08T16:02:49+02:00 (5 years ago)
Author:
mathiot
Message:

ENHANCE-02_ISF_nemo : add UKESM ice sheet coupling method (ticket #2142)

Location:
NEMO/branches/2019/ENHANCE-02_ISF_nemo
Files:
3 deleted
17 edited
1 moved

Legend:

Unmodified
Added
Removed
  • NEMO/branches/2019/ENHANCE-02_ISF_nemo/cfgs/SHARED/namelist_ref

    r11395 r11423  
    436436&namisf       !  Top boundary layer (ISF)                              (ln_isf = T .AND. ln_isfcav: read (ln_read_cfg=T)  
    437437!-----------------------------------------------------------------------                         or set or usr_def_zgr ) 
    438    !                 ! type of top boundary layer  
     438   cn_isfdir = './' 
     439   cn_isfload = 'isomip' 
     440 
    439441   ln_isfcav_mlt = .false.    ! ice shelf melting into the cavity 
    440442      cn_isfcav_mlt = '3eq'   ! ice shelf melting formulation (spe/2eq/3eq/oasis) 
     
    458460      !           !             !  (if <0  months)  !   name    !  (logical)  !  (T/F)  ! 'monthly' ! filename ! pairing  ! filename      ! 
    459461      sn_isfcav_fwf = 'isfmlt_cav',      -12       , 'fwflisf' ,  .false.    , .true.  , 'yearly'  ,    ''    ,   ''     ,    '' 
    460       ! 
    461    ! 
     462 
     463 
    462464   ln_isfpar_mlt = .false.   ! ice shelf melting parametrised 
    463465      cn_isfpar_mlt = 'spe'  ! ice shelf melting parametrisation (spe/bg03/oasis) 
     
    473475      !* 'bg03' case 
    474476      sn_isfpar_Leff = 'isfmlt_par',       0        ,'Leff'     ,  .false.    , .true.  , 'yearly'  ,    ''    ,   ''     ,    '' 
    475       ! 
    476    ! 
    477    !ln_iscpl = .false. 
    478    !   nn_drown    = 10        ! number of iteration of the extrapolation loop (fill the new wet cells) 
    479    !   ln_hsb      = .false.   ! activate conservation module (conservation exact after a time of rn_fiscpl) 
    480    !   nn_fiscpl   = 43800     ! (number of time step) conservation period (maybe should be fix to the coupling frequencey of restart frequency) 
     477 
     478    
     479   ln_isfcpl = .false. 
     480      nn_drown       = 10        ! number of iteration of the extrapolation loop (fill the new wet cells) 
     481      ln_isfcpl_cons = .false. 
    481482/ 
    482483!----------------------------------------------------------------------- 
  • NEMO/branches/2019/ENHANCE-02_ISF_nemo/src/OCE/DIA/diawri.F90

    r11395 r11423  
    906906      CALL iom_rstput( 0, 0, inum, 'vovecrtz', wn                )    ! now k-velocity 
    907907      CALL iom_rstput( 0, 0, inum, 'risfdep', risfdep          )    ! now k-velocity 
    908       CALL iom_rstput( 0, 0, inum, 'fwfisf_cav', fwfisf_cav          )    ! now k-velocity 
    909       CALL iom_rstput( 0, 0, inum, 'rhisf_cav_tbl', rhisf_tbl_cav    )    ! now k-velocity 
    910       CALL iom_rstput( 0, 0, inum, 'rfrac_cav_tbl', rfrac_tbl_cav    )    ! now k-velocity 
    911       CALL iom_rstput( 0, 0, inum, 'misfkb_cav', REAL(misfkb_cav,8)    )    ! now k-velocity 
    912       CALL iom_rstput( 0, 0, inum, 'misfkt_cav', REAL(misfkt_cav,8)    )    ! now k-velocity 
    913       CALL iom_rstput( 0, 0, inum, 'fwfisf_par', fwfisf_par          )    ! now k-velocity 
    914       CALL iom_rstput( 0, 0, inum, 'rhisf_par_tbl', rhisf_tbl_par    )    ! now k-velocity 
    915       CALL iom_rstput( 0, 0, inum, 'rfrac_par_tbl', rfrac_tbl_par    )    ! now k-velocity 
    916       CALL iom_rstput( 0, 0, inum, 'misfkb_par', REAL(misfkb_par,8)    )    ! now k-velocity 
    917       CALL iom_rstput( 0, 0, inum, 'misfkt_par', REAL(misfkt_par,8)    )    ! now k-velocity 
     908      IF ( ln_isf ) THEN 
     909         IF (ln_isfcav_mlt) THEN 
     910            CALL iom_rstput( 0, 0, inum, 'fwfisf_cav', fwfisf_cav          )    ! now k-velocity 
     911            CALL iom_rstput( 0, 0, inum, 'rhisf_cav_tbl', rhisf_tbl_cav    )    ! now k-velocity 
     912            CALL iom_rstput( 0, 0, inum, 'rfrac_cav_tbl', rfrac_tbl_cav    )    ! now k-velocity 
     913            CALL iom_rstput( 0, 0, inum, 'misfkb_cav', REAL(misfkb_cav,8)    )    ! now k-velocity 
     914            CALL iom_rstput( 0, 0, inum, 'misfkt_cav', REAL(misfkt_cav,8)    )    ! now k-velocity 
     915         END IF 
     916         IF (ln_isfpar_mlt) THEN 
     917            CALL iom_rstput( 0, 0, inum, 'fwfisf_par', fwfisf_par          )    ! now k-velocity 
     918            CALL iom_rstput( 0, 0, inum, 'rhisf_par_tbl', rhisf_tbl_par    )    ! now k-velocity 
     919            CALL iom_rstput( 0, 0, inum, 'rfrac_par_tbl', rfrac_tbl_par    )    ! now k-velocity 
     920            CALL iom_rstput( 0, 0, inum, 'misfkb_par', REAL(misfkb_par,8)    )    ! now k-velocity 
     921            CALL iom_rstput( 0, 0, inum, 'misfkt_par', REAL(misfkt_par,8)    )    ! now k-velocity 
     922         END IF 
     923      END IF 
    918924      IF( ALLOCATED(ahtu) ) THEN 
    919925         CALL iom_rstput( 0, 0, inum,  'ahtu', ahtu              )    ! aht at u-point 
  • NEMO/branches/2019/ENHANCE-02_ISF_nemo/src/OCE/DOM/domvvl.F90

    r10425 r11423  
    1919   !!---------------------------------------------------------------------- 
    2020   USE oce             ! ocean dynamics and tracers 
     21   USE isfcpl 
    2122   USE phycst          ! physical constant 
    2223   USE dom_oce         ! ocean space and time domain 
     
    813814            id4 = iom_varid( numror, 'tilde_e3t_n', ldstop = .FALSE. ) 
    814815            id5 = iom_varid( numror, 'hdiv_lf', ldstop = .FALSE. ) 
     816            ! 
     817            ! coupling with an ice sheet model (grounding/calving line migration) 
     818            IF ( ln_iscpl ) THEN 
     819               ! 
     820               ! extrapolate ssh over new water column if needed 
     821               CALL isfcpl_ssh() 
     822               ! 
     823               ! everything need to compute over new water column 
     824               id1 = 0 ; id2 = 0 ; id3 = 0 ; id4 = 0 ; id5 = 0 
     825               ! 
     826            END IF 
    815827            !                             ! --------- ! 
    816828            !                             ! all cases ! 
  • NEMO/branches/2019/ENHANCE-02_ISF_nemo/src/OCE/DOM/istate.F90

    r10499 r11423  
    2828   USE dtauvd         ! data: U & V current             (dta_uvd routine) 
    2929   USE domvvl          ! varying vertical mesh 
    30    USE iscplrst        ! ice sheet coupling 
    3130   USE wet_dry         ! wetting and drying (needed for wad_istate) 
    3231   USE usrdef_istate   ! User defined initial state 
     
    8685         !                                    ! ------------------- 
    8786         CALL rst_read                        ! Read the restart file 
    88          IF (ln_iscpl)       CALL iscpl_stp   ! extrapolate restart to wet and dry 
    8987         CALL day_init                        ! model calendar (using both namelist and restart infos) 
    9088         ! 
  • NEMO/branches/2019/ENHANCE-02_ISF_nemo/src/OCE/DYN/divhor.F90

    r11395 r11423  
    2323   USE sbcrnf          ! river runoff  
    2424   USE isfhdiv         ! ice shelf 
    25    USE iscplhsb        ! ice sheet / ocean coupling 
    26    USE iscplini        ! ice sheet / ocean coupling 
    2725#if defined key_asminc    
    2826   USE asminc          ! Assimilation increment 
     
    10098      !  
    10199#endif 
    102       IF( ln_isf )   CALL isf_hdiv( hdivn )      !==  ice shelf  ==!   (update hdivn field) 
     100      IF( ln_isf )   CALL isf_hdiv( kt, hdivn )      !==  ice shelf  ==!   (update hdivn field) 
    103101      ! 
    104102      CALL lbc_lnk( 'divhor', hdivn, 'T', 1. )   !   (no sign change) 
  • NEMO/branches/2019/ENHANCE-02_ISF_nemo/src/OCE/ISF/isf.F90

    r11403 r11423  
    2222   PRIVATE 
    2323 
    24    PUBLIC   isf_alloc, isf_alloc_par, isf_alloc_cav 
    25  
    26    ! public in order to be able to output then  
    27  
    28    LOGICAL, PUBLIC :: ln_isfpar_mlt                  !: logical for the computation of melt inside the cavity 
    29    LOGICAL, PUBLIC :: ln_isfcav_mlt                  !: logical for the use of ice shelf parametrisation 
    30    REAL(wp), PUBLIC ::   rn_hisf_tbl                 !: thickness of top boundary layer [m] 
    31    REAL(wp), PUBLIC ::   rn_gammat0                  !: temperature exchange coeficient    [] 
    32    REAL(wp), PUBLIC ::   rn_gammas0                  !: salinity    exchange coeficient    [] 
    33    REAL(wp), PUBLIC ::   rn_htbl                     !: Losch top boundary layer thickness [m] 
    34    CHARACTER(LEN=256), PUBLIC :: cn_isfload          !: ice shelf load computation method 
    35    CHARACTER(LEN=256), PUBLIC :: cn_gammablk         !: gamma formulation 
    36    CHARACTER(LEN=256), PUBLIC :: cn_isfcav_mlt, cn_isfpar_mlt !: melt formulation (cavity/param) 
    37    TYPE(FLD_N), PUBLIC                                  :: sn_isfcav_fwf   !: information about the isf melting file to be read 
    38    TYPE(FLD_N), PUBLIC                                  :: sn_isfpar_fwf   !: information about the isf melting file to be read 
    39    TYPE(FLD_N), PUBLIC                                  :: sn_isfpar_zmax  !: information about the grounding line depth file to be read 
    40    TYPE(FLD_N), PUBLIC                                  :: sn_isfpar_zmin  !: information about the calving   line depth file to be read 
    41    TYPE(FLD_N), PUBLIC                                  :: sn_isfpar_Leff  !: information about the effective length     file to be read 
    42  
    43    LOGICAL, PUBLIC :: l_isfcpl 
    44    ! 
    45    INTEGER , PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:)   ::   misfkt_par, misfkt_cav   !: Level of ice shelf base 
    46    INTEGER , PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:)   ::   misfkb_par, misfkb_cav   !: Level of ice shelf base 
    47    ! 
    48    INTEGER , PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:)   ::   mskisf_par, mskisf_cav   !: Level of ice shelf base 
    49    ! 
    50    REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:)   ::   risfload                     !: ice shelf load 
    51    ! 
    52    REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:)   ::   rhisf_tbl_0                  !: thickness of tbl (initial value)  [m] 
    53    REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:)   ::   rhisf_tbl_cav, rhisf_tbl_par !: thickness of tbl                  [m] 
    54    REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:)   ::   rfrac_tbl_cav, rfrac_tbl_par !: fraction of the deepest cell affect by isf tbl  [] 
    55    REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:)   ::   rhisf0_tbl_par 
    56    ! 
    57    REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:)   ::   fwfisf_cpl 
    58    REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:)   ::   fwfisf_par, fwfisf_par_b !: net fwf from the ice shelf        [kg/m2/s] 
    59    REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:)   ::   fwfisf_cav, fwfisf_cav_b !: net fwf from the ice shelf        [kg/m2/s] 
    60    ! 
    61    REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:)   ::   risfLeff 
    62    REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:,:) ::   risf_cav_tsc_b, risf_cav_tsc     !: before and now T & S isf contents [K.m/s & PSU.m/s]   
    63    REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:,:) ::   risf_par_tsc_b, risf_par_tsc     !: before and now T & S isf contents [K.m/s & PSU.m/s]   
    64  
     24   PUBLIC   isf_alloc, isf_alloc_par, isf_alloc_cav, isf_alloc_cpl 
     25   ! 
     26   !------------------------------------------------------- 
     27   ! 0 :              namelist parameter 
     28   !------------------------------------------------------- 
     29   ! 
     30   ! 0.1 -------- ice shelf cavity parameter -------------- 
     31   CHARACTER(LEN=256), PUBLIC :: cn_isfdir 
     32   CHARACTER(LEN=256), PUBLIC :: cn_isfload      !: ice shelf load computation method 
     33   ! 
     34   ! 0.2 -------- ice shelf cavity melt namelist parameter ------------- 
     35   LOGICAL           , PUBLIC :: ln_isfcav_mlt   !: logical for the use of ice shelf parametrisation 
     36   REAL(wp)          , PUBLIC :: rn_gammat0      !: temperature exchange coeficient    [] 
     37   REAL(wp)          , PUBLIC :: rn_gammas0      !: salinity    exchange coeficient    [] 
     38   REAL(wp)          , PUBLIC :: rn_htbl         !: Losch top boundary layer thickness [m] 
     39   CHARACTER(LEN=256), PUBLIC :: cn_gammablk     !: gamma formulation 
     40   CHARACTER(LEN=256), PUBLIC :: cn_isfcav_mlt   !: melt formulation (cavity/param) 
     41   TYPE(FLD_N)       , PUBLIC :: sn_isfcav_fwf   !: information about the isf melting file to be read 
     42   ! 
     43   ! 0.3 -------- ice shelf param. melt namelist parameter ------------- 
     44   LOGICAL           , PUBLIC :: ln_isfpar_mlt   !: logical for the computation of melt inside the cavity 
     45   CHARACTER(LEN=256), PUBLIC :: cn_isfpar_mlt   !: melt formulation (cavity/param) 
     46   TYPE(FLD_N)       , PUBLIC :: sn_isfpar_fwf   !: information about the isf melting file to be read 
     47   TYPE(FLD_N)       , PUBLIC :: sn_isfpar_zmax  !: information about the grounding line depth file to be read 
     48   TYPE(FLD_N)       , PUBLIC :: sn_isfpar_zmin  !: information about the calving   line depth file to be read 
     49   TYPE(FLD_N)       , PUBLIC :: sn_isfpar_Leff  !: information about the effective length     file to be read 
     50   ! 
     51   ! 0.4 -------- coupling namelist parameter ------------- 
     52   LOGICAL, PUBLIC :: ln_isfcpl      !: 
     53   LOGICAL, PUBLIC :: ln_isfcpl_cons !: 
     54   INTEGER, PUBLIC :: nn_drown       !: 
     55   ! 
     56   !------------------------------------------------------- 
     57   ! 1 :              ice shelf parameter 
     58   !------------------------------------------------------- 
     59   ! 
    6560   REAL(wp), PARAMETER, PUBLIC :: rLfusisf = 0.334e6_wp    !: latent heat of fusion of ice shelf     [J/kg] 
    6661   REAL(wp), PARAMETER, PUBLIC :: rcpisf = 2000.0_wp       !: specific heat of ice shelf             [J/kg/K] 
     
    6863   REAL(wp), PARAMETER, PUBLIC :: rhoisf = 920.0_wp        !: volumic mass of ice shelf              [kg/m3] 
    6964   REAL(wp), PARAMETER, PUBLIC :: rtsurf = -20.0           !: surface temperature                    [C] 
    70    REAL(wp), PARAMETER, PUBLIC :: risf_eps = 1.e-20_wp         
    71  
    72    REAL(wp), PUBLIC            :: risf_lamb1, risf_lamb2, risf_lamb3  ! freezing point linearization coeficient 
    73  
     65   ! 
     66   !------------------------------------------------------- 
     67   ! 2 :              ice shelf global variables 
     68   !------------------------------------------------------- 
     69   ! 
     70   ! 0.1 -------- ice shelf cavity parameter -------------- 
     71   LOGICAL , PUBLIC            :: l_isfoasis 
    7472   REAL(wp), PUBLIC            :: r1_Lfusisf               !: 1/rLfusisf 
    75  
    76    TYPE(FLD)  , PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:) :: sf_isfcav_fwf 
    77    TYPE(FLD)  , PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:) :: sf_isfpar_fwf 
    78  
    79 !: Variable used in fldread to read the forcing file (nn_isf == 4 .OR. nn_isf == 3) 
    80    CHARACTER(len=100), PUBLIC           :: cn_dirisf  = './' !: Root directory for location of ssr files 
    81    TYPE(FLD_N)       , PUBLIC           :: sn_fwfisf         !: information about the isf melting file to be read 
    82    TYPE(FLD), ALLOCATABLE, DIMENSION(:) :: sf_fwfisf 
    83    TYPE(FLD_N)       , PUBLIC           :: sn_rnfisf         !: information about the isf melting param.   file to be read 
    84    TYPE(FLD), ALLOCATABLE, DIMENSION(:) :: sf_rnfisf            
    85     
     73   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:)    ::   risfload                    !: ice shelf load 
     74   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:)    ::   fwfisf_oasis 
     75   ! 
     76   ! 0.2 -------- ice shelf cavity melt namelist parameter ------------- 
     77   INTEGER  , PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:)   :: mskisf_cav                    !: 
     78   INTEGER  , PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:)   :: misfkt_cav   , misfkb_cav     !:  
     79   REAL(wp) , PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:)   :: rhisf_tbl_cav, rfrac_tbl_cav  !:  
     80   REAL(wp) , PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:)   :: fwfisf_cav   , fwfisf_cav_b   !: before and now net fwf from the ice shelf        [kg/m2/s] 
     81   REAL(wp) , PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:,:) :: risf_cav_tsc , risf_cav_tsc_b !: before and now T & S isf contents [K.m/s & PSU.m/s]   
     82   TYPE(FLD), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:)     :: sf_isfcav_fwf                 !: 
     83   ! 
     84   REAL(wp) , PUBLIC                                      :: risf_lamb1, risf_lamb2, risf_lamb3  ! freezing point linearization coeficient 
     85   ! 
     86   ! 0.3 -------- ice shelf param. melt namelist parameter ------------- 
     87   INTEGER  , PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:)   :: mskisf_par                    !: 
     88   INTEGER  , PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:)   :: misfkt_par   , misfkb_par     !: 
     89   REAL(wp) , PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:)   :: rhisf_tbl_par, rfrac_tbl_par  !:  
     90   REAL(wp) , PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:)   :: fwfisf_par   , fwfisf_par_b   !: before and now net fwf from the ice shelf        [kg/m2/s] 
     91   REAL(wp) , PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:,:) :: risf_par_tsc , risf_par_tsc_b !: before and now T & S isf contents [K.m/s & PSU.m/s]   
     92   TYPE(FLD), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:)     :: sf_isfpar_fwf                 !: 
     93   ! 
     94   REAL(wp) , PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:)   :: rhisf0_tbl_par                !: thickness of tbl (initial value)  [m] 
     95   REAL(wp) , PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:)   :: risfLeff                      !: 
     96   ! 
     97   ! 0.4 -------- coupling namelist parameter ------------- 
     98   LOGICAL , PUBLIC                                        :: ll_isfcpl      !: 
     99   LOGICAL , PUBLIC                                        :: ll_isfcpl_cons !: 
     100   INTEGER , PUBLIC                                        ::   nstp_iscpl   !: 
     101   REAL(wp), PUBLIC                                        ::   rdt_iscpl    !:  
     102   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:,:)   ::   risfcpl_vol, risfcpl_cons_vol  !: 
     103   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:,:,:) ::   risfcpl_tsc, risfcpl_cons_tsc  !: 
     104   ! 
    86105   !!---------------------------------------------------------------------- 
    87106   !! NEMO/OCE 4.0 , NEMO Consortium (2018) 
     
    121140      CALL mpp_sum ( 'isf', ierr ) 
    122141      IF( ierr /= 0 )   CALL ctl_stop( 'STOP', 'isf: failed to allocate arrays.' ) 
     142      ! 
    123143   END SUBROUTINE isf_alloc_par 
    124144 
     
    145165      ierr = ierr + ialloc 
    146166      ! 
     167      CALL mpp_sum ( 'isf', ierr ) 
     168      IF( ierr /= 0 )   CALL ctl_stop( 'STOP', 'isf: failed to allocate arrays.' ) 
     169      ! 
     170   END SUBROUTINE isf_alloc_cav 
     171 
     172   SUBROUTINE isf_alloc_cpl() 
     173      !!--------------------------------------------------------------------- 
     174      !!                  ***  ROUTINE isf_alloc_cpl  *** 
     175      !! 
     176      !! ** Purpose :  
     177      !! 
     178      !! ** Method  :  
     179      !! 
     180      !!---------------------------------------------------------------------- 
     181      INTEGER :: ierr, ialloc 
     182      !!---------------------------------------------------------------------- 
     183      ierr = 0 
     184      ! 
     185      ALLOCATE( risfcpl_tsc(jpi,jpj,jpk,jpts)      , risfcpl_vol(jpi,jpj,jpk)      ,             & 
     186         &      risfcpl_cons_tsc(jpi,jpj,jpk,jpts) , risfcpl_cons_vol(jpi,jpj,jpk) , STAT=ialloc ) 
     187      ierr = ierr + ialloc 
     188      ! 
     189      CALL mpp_sum ( 'isf', ierr ) 
     190      IF( ierr /= 0 )   CALL ctl_warn('STOP','isfcpl: failed to allocate arrays.') 
     191      ! 
     192   END SUBROUTINE isf_alloc_cpl 
     193 
     194   SUBROUTINE isf_alloc() 
     195      !!--------------------------------------------------------------------- 
     196      !!                  ***  ROUTINE isf_alloc  *** 
     197      !! 
     198      !! ** Purpose :  
     199      !! 
     200      !! ** Method  :  
     201      !! 
     202      !!---------------------------------------------------------------------- 
     203      INTEGER :: ierr, ialloc 
     204      !!---------------------------------------------------------------------- 
     205      ! 
     206      ierr = 0       ! set to zero if no array to be allocated 
     207      ! 
     208      ALLOCATE(fwfisf_par(jpi,jpj)  , fwfisf_par_b(jpi,jpj), & 
     209         &     fwfisf_cav(jpi,jpj)  , fwfisf_cav_b(jpi,jpj), & 
     210         &     fwfisf_oasis(jpi,jpj),            STAT=ialloc ) 
     211      ierr = ierr + ialloc 
     212      ! 
     213      ALLOCATE(risf_par_tsc(jpi,jpj,jpts), risf_par_tsc_b(jpi,jpj,jpts), STAT=ialloc ) 
     214      ierr = ierr + ialloc 
     215      ! 
     216      ALLOCATE(risf_cav_tsc(jpi,jpj,jpts), risf_cav_tsc_b(jpi,jpj,jpts), STAT=ialloc ) 
     217      ierr = ierr + ialloc 
     218      ! 
     219      ALLOCATE(risfload(jpi,jpj), STAT=ialloc) 
     220      ierr = ierr + ialloc 
     221      ! 
    147222      ALLOCATE( mskisf_cav(jpi,jpj), STAT=ialloc) 
    148223      ierr = ierr + ialloc 
     
    150225      CALL mpp_sum ( 'isf', ierr ) 
    151226      IF( ierr /= 0 )   CALL ctl_stop( 'STOP', 'isf: failed to allocate arrays.' ) 
    152    END SUBROUTINE isf_alloc_cav 
    153  
    154    SUBROUTINE isf_alloc() 
    155       !!--------------------------------------------------------------------- 
    156       !!                  ***  ROUTINE isf_alloc  *** 
    157       !! 
    158       !! ** Purpose :  
    159       !! 
    160       !! ** Method  :  
    161       !! 
    162       !!---------------------------------------------------------------------- 
    163       INTEGER :: ierr, ialloc 
    164       !!---------------------------------------------------------------------- 
    165       ! 
    166       ierr = 0       ! set to zero if no array to be allocated 
    167       ! 
    168       ALLOCATE(fwfisf_par(jpi,jpj), fwfisf_par_b(jpi,jpj), & 
    169          &     fwfisf_cav(jpi,jpj), fwfisf_cav_b(jpi,jpj), & 
    170          &     fwfisf_cpl(jpi,jpj),            STAT=ialloc ) 
    171       ierr = ierr + ialloc 
    172       ! 
    173       ALLOCATE(risf_par_tsc(jpi,jpj,jpts), risf_par_tsc_b(jpi,jpj,jpts), STAT=ialloc ) 
    174       ierr = ierr + ialloc 
    175       ! 
    176       ALLOCATE(risf_cav_tsc(jpi,jpj,jpts), risf_cav_tsc_b(jpi,jpj,jpts), STAT=ialloc ) 
    177       ierr = ierr + ialloc 
    178       ! 
    179       ALLOCATE(risfload(jpi,jpj), STAT=ialloc) 
    180       ierr = ierr + ialloc 
    181       ! 
    182       CALL mpp_sum ( 'isf', ierr ) 
    183       IF( ierr /= 0 )   CALL ctl_stop( 'STOP', 'isf: failed to allocate arrays.' ) 
    184227 
    185228   END SUBROUTINE isf_alloc 
    186    ! 
     229 
    187230END MODULE isf 
  • NEMO/branches/2019/ENHANCE-02_ISF_nemo/src/OCE/ISF/isfcav.F90

    r11403 r11423  
    1717   USE isftbl         ! 
    1818   USE isfcavmlt 
    19    USE isfgammats 
     19   USE isfcavgam 
    2020   USE isfdiags 
    2121   USE dom_oce        ! ocean space and time domain 
    2222   USE phycst         ! physical constants 
    23    USE eosbn2         ! equation of state 
    24    USE zdfdrg         ! vertical physics: top/bottom drag coef. 
     23   USE eosbn2         ! l_useCT 
    2524   ! 
    2625   USE in_out_manager ! I/O manager 
     
    166165         ALLOCATE( sf_isfcav_fwf(1), STAT=ierr ) 
    167166         ALLOCATE( sf_isfcav_fwf(1)%fnow(jpi,jpj,1), sf_isfcav_fwf(1)%fdta(jpi,jpj,1,2) ) 
    168          CALL fld_fill( sf_isfcav_fwf, (/ sn_isfcav_fwf /), cn_dirisf, 'isf_cav_init', 'read fresh water flux isf data', 'namisf' ) 
     167         CALL fld_fill( sf_isfcav_fwf, (/ sn_isfcav_fwf /), cn_isfdir, 'isf_cav_init', 'read fresh water flux isf data', 'namisf' ) 
    169168 
    170169         IF(lwp) WRITE(numout,*) 
  • NEMO/branches/2019/ENHANCE-02_ISF_nemo/src/OCE/ISF/isfcavgam.F90

    r11403 r11423  
    1 MODULE isfgammats 
     1MODULE isfcavgam 
    22   !!====================================================================== 
    33   !!                       ***  MODULE  isfgammats  *** 
     
    229229   END SUBROUTINE gammats_HJ99 
    230230 
    231 END MODULE isfgammats 
     231END MODULE isfcavgam 
  • NEMO/branches/2019/ENHANCE-02_ISF_nemo/src/OCE/ISF/isfcavmlt.F90

    r11403 r11423  
    198198            ! solve the 2nd order equation to find zsfrz 
    199199            zaqe  = risf_lamb1 * (zeps1 + zeps3) 
    200             zaqer = 0.5_wp/MIN(zaqe,-risf_eps) 
     200            zaqer = 0.5_wp/MIN(zaqe,-zeps) 
    201201            zbqe  = zeps1*zeps6+zeps3*zeps7-zeps2 
    202202            zcqe  = zeps2*pstbl(ji,jj) 
     
    248248      REAL(wp), DIMENSION(jpi,jpj), INTENT(in   ) :: pstbl               ! salinity in tbl 
    249249      !!-------------------------------------------------------------------- 
    250       REAL(wp)                     :: zfwf_fld, zfwf_cpl                 ! total fwf in the forcing fields (pattern) and from the cpl interface (amount) 
     250      REAL(wp)                     :: zfwf_fld, zfwf_oasis               ! total fwf in the forcing fields (pattern) and from the oasis interface (amount) 
    251251      REAL(wp), DIMENSION(jpi,jpj) :: ztfrz                              ! tbl freezing temperature 
    252252      REAL(wp), DIMENSION(jpi,jpj) :: zfwf                               ! 2d fwf map after scaling 
     
    266266      ! 
    267267      ! compute glob sum from atm->oce ice shelf fwf 
    268       zfwf_cpl = glob_sum('isfcav_mlt', fwfisf_cpl(:,:)) 
     268      zfwf_oasis = glob_sum('isfcav_mlt', fwfisf_oasis(:,:)) 
    269269      ! 
    270270      ! scale fwf 
    271       zfwf(:,:) = zfwf(:,:) * zfwf_cpl / zfwf_fld 
     271      zfwf(:,:) = zfwf(:,:) * zfwf_oasis / zfwf_fld 
    272272      !  
    273273      ! define fwf and qoce 
     
    281281   !SUBROUTINE isfmlt_3eq_frz_ktm1 
    282282   ! compute tfrz based on sfrz value at kt-1 (need to be SAVED local array) 
     283   ! => should reduce error due to linarisation 
    283284   ! compute qfwf (eq 24) 
    284285   ! compute zqoce, zqlat, zqcon, zqhc 
  • NEMO/branches/2019/ENHANCE-02_ISF_nemo/src/OCE/ISF/isfhdiv.F90

    r11403 r11423  
    44   USE isf 
    55   USE phycst 
     6   USE in_out_manager 
    67 
    78   IMPLICIT NONE 
     
    1314CONTAINS 
    1415 
    15    SUBROUTINE isf_hdiv( phdiv ) 
     16   SUBROUTINE isf_hdiv( kt, phdiv ) 
    1617      !!---------------------------------------------------------------------- 
    1718      !!                  ***  SUBROUTINE isf_hdiv  *** 
     
    2526      REAL(wp), DIMENSION(:,:,:), INTENT( inout ) ::   phdiv   ! horizontal divergence 
    2627      !!---------------------------------------------------------------------- 
     28      INTEGER, INTENT(in) :: kt 
    2729      ! 
    2830      ! ice shelf cavity contribution 
     
    3335      ! 
    3436      ! ice sheet coupling contribution (if conservation needed) 
    35       !IF ( ln_iscpl_hsb  ) CALL isf_hdiv_cpl(hdiv_iscpl, phdivn) 
     37      IF ( ll_isfcpl ) THEN 
     38         ! 
     39         ! correct divergence only for the first time step 
     40         IF ( kt == nit000 ) CALL isf_hdiv_cpl(risfcpl_vol, phdiv) 
     41         ! 
     42         ! correct divergence every time step to remove any trend due to coupling 
     43         IF ( ll_isfcpl_cons ) CALL isf_hdiv_cpl(risfcpl_cons_vol, phdiv) 
     44         ! 
     45      END IF 
    3646      ! 
    3747   END SUBROUTINE isf_hdiv 
     
    8191   END SUBROUTINE isf_hdiv_mlt 
    8292 
     93   SUBROUTINE isf_hdiv_cpl(pqvol, phdiv) 
     94      REAL(wp), DIMENSION(jpi,jpj,jpk), INTENT(inout) :: phdiv 
     95      REAL(wp), DIMENSION(jpi,jpj,jpk), INTENT(in   ) :: pqvol 
     96    
     97   INTEGER :: jk 
     98       
     99      DO jk=1,jpk  
     100         phdiv(:,:,jk) =  phdiv(:,:,jk) + pqvol(:,:,jk) * r1_e1e2t(:,:) / e3t_n(:,:,jk) 
     101      END DO 
     102 
     103   END SUBROUTINE 
     104 
    83105END MODULE isfhdiv 
  • NEMO/branches/2019/ENHANCE-02_ISF_nemo/src/OCE/ISF/isfload.F90

    r11403 r11423  
    9090      ! 
    9191      !                                !- Surface value + ice shelf gradient 
    92       risfload = 0._wp                       ! compute pressure due to ice shelf load  
     92      risfload(:,:) = 0._wp                       ! compute pressure due to ice shelf load  
    9393      DO jj = 1, jpj                         ! (used to compute hpgi/j for all the level from 1 to miku/v) 
    9494         DO ji = 1, jpi                      ! divided by 2 later 
    9595            ikt = mikt(ji,jj) 
    9696            ! 
    97             ! top layer of the ice shelf 
    98             risfload(ji,jj) = risfload(ji,jj) + (znad + zrhd(ji,jj,1) ) * e3w_n(ji,jj,1) 
    99             ! 
    100             ! core layers of the ice shelf 
    101             DO jk = 2, ikt-1 
    102                risfload(ji,jj) = risfload(ji,jj) + (2._wp * znad + zrhd(ji,jj,jk-1) + zrhd(ji,jj,jk)) * e3w_n(ji,jj,jk) 
    103             END DO 
    104             ! 
    105             ! deepest part of the ice shelf (between deepest T point and ice/ocean interface 
    106             risfload(ji,jj) = risfload(ji,jj) + (2._wp * znad + zrhdtop_isf(ji,jj) + zrhd(ji,jj,ikt-1)) & 
    107                &                                              * ( risfdep(ji,jj) - gdept_n(ji,jj,ikt-1) ) 
    108             ! 
     97            IF ( ikt > 1 ) THEN 
     98               ! 
     99               ! top layer of the ice shelf 
     100               risfload(ji,jj) = risfload(ji,jj) + (znad + zrhd(ji,jj,1) ) * e3w_n(ji,jj,1) 
     101               ! 
     102               ! core layers of the ice shelf 
     103               DO jk = 2, ikt-1 
     104                  risfload(ji,jj) = risfload(ji,jj) + (2._wp * znad + zrhd(ji,jj,jk-1) + zrhd(ji,jj,jk)) * e3w_n(ji,jj,jk) 
     105               END DO 
     106               ! 
     107               ! deepest part of the ice shelf (between deepest T point and ice/ocean interface 
     108               risfload(ji,jj) = risfload(ji,jj) + (2._wp * znad + zrhdtop_isf(ji,jj) + zrhd(ji,jj,ikt-1)) & 
     109                  &                                              * ( risfdep(ji,jj) - gdept_n(ji,jj,ikt-1) ) 
     110               ! 
     111            END IF 
    109112         END DO 
    110113      END DO 
    111       ! 
    112       ! mask it  
    113       risfload(:,:) = risfload(:,:) * mskisf_cav(:,:)  ! need to be saved for diaar5 
    114114      ! 
    115115   END SUBROUTINE isf_load_isomip 
  • NEMO/branches/2019/ENHANCE-02_ISF_nemo/src/OCE/ISF/isfpar.F90

    r11403 r11423  
    146146         ALLOCATE( sf_isfpar_fwf(1), STAT=ierr ) 
    147147         ALLOCATE( sf_isfpar_fwf(1)%fnow(jpi,jpj,1), sf_isfpar_fwf(1)%fdta(jpi,jpj,1,2) ) 
    148          CALL fld_fill( sf_isfpar_fwf, (/ sn_isfpar_fwf /), cn_dirisf, 'isf_par_init', 'read fresh water flux isf data', 'namisf' ) 
     148         CALL fld_fill( sf_isfpar_fwf, (/ sn_isfpar_fwf /), cn_isfdir, 'isf_par_init', 'read fresh water flux isf data', 'namisf' ) 
    149149 
    150150         IF(lwp) WRITE(numout,*) 
  • NEMO/branches/2019/ENHANCE-02_ISF_nemo/src/OCE/ISF/isfparmlt.F90

    r11403 r11423  
    162162      !! 
    163163      !! ** Purpose    : - read ice shelf melt from forcing file => pattern 
    164       !!                 - total amount of fwf is given by sbccpl (fwfisf_cpl) 
     164      !!                 - total amount of fwf is given by sbccpl (fwfisf_oasis) 
    165165      !!                 - scale fwf and compute heat fluxes 
    166166      !! 
     
    172172      !!-------------------------------------------------------------------- 
    173173      INTEGER                           :: jk                            ! loop index 
    174       REAL(wp)                          :: zfwf_fld, zfwf_cpl            ! total fwf in the forcing fields (pattern) and from the cpl interface (amount) 
     174      REAL(wp)                          :: zfwf_fld, zfwf_oasis            ! total fwf in the forcing fields (pattern) and from the cpl interface (amount) 
    175175      REAL(wp), DIMENSION(jpi,jpj)      :: ztfrz                         ! tbl freezing temperature 
    176176      REAL(wp), DIMENSION(jpi,jpj)      :: zfwf                          ! 2d fwf map after scaling 
     
    195195      ! 
    196196      ! compute glob sum from atm->oce ice shelf fwf 
    197       zfwf_cpl = glob_sum('isfcav_mlt', fwfisf_cpl(:,:)) 
     197      zfwf_oasis = glob_sum('isfcav_mlt', fwfisf_oasis(:,:)) 
    198198      ! 
    199199      ! scale fwf 
    200       zfwf(:,:) = zfwf(:,:) * zfwf_cpl / zfwf_fld 
     200      zfwf(:,:) = zfwf(:,:) * zfwf_oasis / zfwf_fld 
    201201      !  
    202202      ! define fwf and qoce 
  • NEMO/branches/2019/ENHANCE-02_ISF_nemo/src/OCE/ISF/isfrst.F90

    r11403 r11423  
    2020   PRIVATE 
    2121 
    22    PUBLIC isfrst_read, isfrst_write  ! iceshelf restart read and write  
     22   PUBLIC isfrst_read, isfrst_write ! iceshelf restart read and write  
    2323 
    2424   !!---------------------------------------------------------------------- 
  • NEMO/branches/2019/ENHANCE-02_ISF_nemo/src/OCE/ISF/isfstp.F90

    r11403 r11423  
    3131   USE isfcav         ! ice shelf cavity 
    3232   USE isfload        ! ice shelf load 
     33   USE isfcpl         ! isf variables 
    3334   USE isf            ! isf variables 
    3435 
     
    8788         ! before time step  
    8889         IF ( kt /= nit000 ) THEN  
    89             risf_par_tsc_b (:,:) = risf_par_tsc (:,:) 
    90             fwfisf_par_b(:,:)    = fwfisf_par(:,:) 
     90            risf_par_tsc_b(:,:,:) = risf_par_tsc(:,:,:) 
     91            fwfisf_par_b  (:,:)   = fwfisf_par  (:,:) 
    9192         END IF 
    9293         ! 
     
    100101         IF (lrst_oce) CALL isfrst_write(kt, 'par', risf_par_tsc, fwfisf_par) 
    101102         ! 
     103      END IF 
     104 
     105      IF ( ln_isfcpl ) THEN 
     106         IF (lrst_oce) CALL isfcpl_rst_write(kt) 
    102107      END IF 
    103108      ! 
     
    122127      INTEGER               :: ji, jj 
    123128      !!---------------------------------------------------------------------- 
    124       NAMELIST/namisf/ ln_isfcav_mlt, cn_isfcav_mlt, cn_gammablk, rn_gammat0, rn_gammas0, rn_htbl, sn_isfcav_fwf,  & 
    125          &             ln_isfpar_mlt, cn_isfpar_mlt, sn_isfpar_fwf, sn_isfpar_zmin, sn_isfpar_zmax, sn_isfpar_Leff 
     129      NAMELIST/namisf/ ln_isfcav_mlt, cn_isfcav_mlt, cn_gammablk, rn_gammat0, rn_gammas0, rn_htbl, sn_isfcav_fwf,   & 
     130         &             ln_isfpar_mlt, cn_isfpar_mlt, sn_isfpar_fwf, sn_isfpar_zmin, sn_isfpar_zmax, sn_isfpar_Leff, & 
     131         &             ln_isfcpl    , nn_drown, ln_isfcpl_cons,                                                     & 
     132         &             cn_isfload   , cn_isfdir 
    126133      !!---------------------------------------------------------------------- 
    127134      ! 
     
    130137      ! 
    131138      riceload(:,:)       = 0.0_wp 
    132       fwfisf_cpl(:,:)     = 0.0_wp 
     139      fwfisf_oasis(:,:)   = 0.0_wp 
    133140      fwfisf_par(:,:)     = 0.0_wp    ; fwfisf_par_b(:,:)     = 0.0_wp 
    134141      fwfisf_cav(:,:)     = 0.0_wp    ; fwfisf_cav_b(:,:)     = 0.0_wp 
     
    148155      IF(lwm) WRITE ( numond, namisf ) 
    149156      ! 
    150       IF(lwp) WRITE(numout,*) 
    151       IF(lwp) WRITE(numout,*) 'isf_init : ice shelf initialisation' 
    152       IF(lwp) WRITE(numout,*) '~~~~~~~~~~~~' 
    153       IF(lwp) WRITE(numout,*) '   Namelist namisf :' 
    154       ! 
    155       IF(lwp) WRITE(numout,*) '      melt inside the cavity                  ln_isfcav_mlt   = ', ln_isfcav_mlt 
    156       IF ( ln_isfcav ) THEN 
    157          IF(lwp) WRITE(numout,*) '         melt formulation                        cn_isfcav_mlt   = ', cn_isfcav_mlt 
    158          IF(lwp) WRITE(numout,*) '         thickness of the top boundary layer     rn_htbl     = ', rn_htbl 
    159          IF(lwp) WRITE(numout,*) '         gamma formulation                       cn_gammablk = ', cn_gammablk  
    160          IF ( TRIM(cn_gammablk) .NE. 'spe' ) THEN  
    161             IF(lwp) WRITE(numout,*) '            gammat coefficient                      rn_gammat0  = ', rn_gammat0   
    162             IF(lwp) WRITE(numout,*) '            gammas coefficient                      rn_gammas0  = ', rn_gammas0   
    163             IF(lwp) WRITE(numout,*) '            top drag coef. used (from namdrg_top)   rn_Cd0      = ', r_Cdmin_top  
    164          END IF 
    165       END IF 
    166       ! 
    167       IF(lwp) WRITE(numout,*) '' 
    168       ! 
    169       IF(lwp) WRITE(numout,*) '      ice shelf melt parametrisation          ln_isfpar_mlt    = ', ln_isfpar_mlt 
    170       IF ( ln_isfpar_mlt ) THEN 
    171          IF(lwp) WRITE(numout,*) '         isf parametrisation formulation         cn_isfpar_mlt   = ', cn_isfpar_mlt 
    172       END IF 
    173       IF(lwp) WRITE(numout,*) '' 
    174       ! 
     157      IF (lwp) THEN 
     158         WRITE(numout,*) 
     159         WRITE(numout,*) 'isf_init : ice shelf initialisation' 
     160         WRITE(numout,*) '~~~~~~~~~~~~' 
     161         WRITE(numout,*) '   Namelist namisf :' 
     162         ! 
     163         WRITE(numout,*) '      melt inside the cavity                  ln_isfcav_mlt   = ', ln_isfcav_mlt 
     164         IF ( ln_isfcav ) THEN 
     165            WRITE(numout,*) '         melt formulation                        cn_isfcav_mlt   = ', TRIM(cn_isfcav_mlt) 
     166            WRITE(numout,*) '         thickness of the top boundary layer     rn_htbl     = ', rn_htbl 
     167            WRITE(numout,*) '         gamma formulation                       cn_gammablk = ', TRIM(cn_gammablk)  
     168            IF ( TRIM(cn_gammablk) .NE. 'spe' ) THEN  
     169               WRITE(numout,*) '            gammat coefficient                      rn_gammat0  = ', rn_gammat0   
     170               WRITE(numout,*) '            gammas coefficient                      rn_gammas0  = ', rn_gammas0   
     171               WRITE(numout,*) '            top drag coef. used (from namdrg_top)   rn_Cd0      = ', r_Cdmin_top  
     172            END IF 
     173         END IF 
     174         WRITE(numout,*) '' 
     175         ! 
     176         WRITE(numout,*) '      ice shelf melt parametrisation          ln_isfpar_mlt    = ', ln_isfpar_mlt 
     177         IF ( ln_isfpar_mlt ) THEN 
     178            WRITE(numout,*) '         isf parametrisation formulation         cn_isfpar_mlt   = ', TRIM(cn_isfpar_mlt) 
     179         END IF 
     180         WRITE(numout,*) '' 
     181         ! 
     182         WRITE(numout,*) '      Coupling to an ice sheet model          ln_isfcpl         = ', ln_isfcpl 
     183         IF ( ln_isfcpl ) THEN 
     184            WRITE(numout,*) '         conservation activated ln_isfcpl_cons           = ', ln_isfcpl_cons 
     185            WRITE(numout,*) '            number of call of the extrapolation loop = ', nn_drown 
     186         ENDIF 
     187         ! 
     188         WRITE(numout,*) '      Ice shelf load method                   cn_isfload        = ', TRIM(cn_isfload) 
     189 
     190      END IF 
     191      ! 
     192      !--------------------------------------------------------------------------------------------------------------------- 
    175193      ! sanity check 
    176194      ! melt in the cavity without cavity 
     
    178196         &   CALL ctl_stop('ice shelf melt in the cavity activated (ln_isfcav_mlt) but no cavity detected in domcfg (ln_isfcav), STOP' ) 
    179197      ! 
    180       IF ( ln_cpl ) THEN 
     198      IF ( ln_isfcpl .AND. ln_isfcpl_cons .AND. ln_linssh ) & 
     199         &   CALL ctl_stop( 'The coupling between NEMO and an ice sheet model with the conservation option does not work with the linssh option' ) 
     200      ! 
     201      IF ( l_isfoasis ) THEN 
    181202         ! 
    182203         CALL ctl_stop( ' ln_ctl and ice shelf not tested' ) 
    183204         ! 
    184205         ! NEMO coupled to ATMO model with isf cavity need oasis method for melt computation  
    185          IF ( ln_isfcav_mlt .AND. TRIM(cn_isfcav_mlt) /= 'oasis' ) CALL ctl_stop( 'cn_isfcav_mlt = oasis is the only option availble with ln_cpl' ) 
    186          IF ( ln_isfpar_mlt .AND. TRIM(cn_isfpar_mlt) /= 'oasis' ) CALL ctl_stop( 'cn_isfpar_mlt = oasis is the only option availble with ln_cpl' ) 
     206         IF ( ln_isfcav_mlt .AND. TRIM(cn_isfcav_mlt) /= 'oasis' ) CALL ctl_stop( 'cn_isfcav_mlt = oasis is the only option availble if fwf send by oasis' ) 
     207         IF ( ln_isfpar_mlt .AND. TRIM(cn_isfpar_mlt) /= 'oasis' ) CALL ctl_stop( 'cn_isfpar_mlt = oasis is the only option availble if fwf send by oasis' ) 
    187208         ! 
    188209         ! oasis melt computation not tested (coded but not tested) 
     
    198219      END IF 
    199220      ! 
     221      !--------------------------------------------------------------------------------------------------------------------- 
    200222      ! initialisation ice shelf load 
    201223      IF ( ln_isfcav ) THEN 
     
    212234      r1_Lfusisf =  1._wp / rLfusisf 
    213235      ! 
     236      ll_isfcpl     = .FALSE. 
     237      ll_isfcpl_cons= .FALSE. 
     238      ! 
    214239      ! initialisation melt in the cavity 
    215240      IF ( ln_isfcav_mlt ) THEN 
     
    223248      END IF 
    224249      ! 
     250      !--------------------------------------------------------------------------------------------------------------------- 
    225251      ! initialisation parametrised melt 
    226252      IF ( ln_isfpar_mlt ) THEN 
     
    234260      END IF 
    235261      ! 
     262      !--------------------------------------------------------------------------------------------------------------------- 
     263      ! initialisation ice sheet coupling 
     264      IF( ln_isfcpl ) THEN 
     265 
     266         ! prepare writing restart 
     267         IF( lwxios ) CALL iom_set_rstw_var_active('ssmask') 
     268         IF( lwxios ) CALL iom_set_rstw_var_active('tmask') 
     269         IF( lwxios ) CALL iom_set_rstw_var_active('e3t_n') 
     270         IF( lwxios ) CALL iom_set_rstw_var_active('e3u_n') 
     271         IF( lwxios ) CALL iom_set_rstw_var_active('e3v_n') 
     272 
     273         IF( ln_rstart ) THEN 
     274            ! 
     275            ll_isfcpl = .TRUE. 
     276            ! 
     277            CALL isf_alloc_cpl() 
     278            ! 
     279            ! extrapolation tracer properties 
     280            CALL isfcpl_tra() 
     281            ! 
     282            ! correction of the horizontal divergence and associated temp. and salt content flux 
     283            CALL isfcpl_vol() 
     284            ! 
     285            ! apply the 'conservation' method 
     286            IF ( ln_isfcpl_cons )  THEN 
     287               ll_isfcpl_cons = .TRUE. 
     288               CALL isfcpl_cons() 
     289            END IF 
     290            ! 
     291            ! Need to include in the cpl cons the isfrst_cpl_div contribution 
     292            ! decide how to manage thickness level change in conservation 
     293            ! 
     294            tsb    (:,:,:,:) = tsn (:,:,:,:) 
     295            sshb   (:,:)     = sshn(:,:) 
     296            ! 
     297         END IF 
     298      END IF 
     299          
    236300  END SUBROUTINE isf_stp_init 
    237301   !!====================================================================== 
  • NEMO/branches/2019/ENHANCE-02_ISF_nemo/src/OCE/SBC/sbccpl.F90

    r11403 r11423  
    3636   USE eosbn2         !  
    3737   USE sbcrnf  , ONLY : l_rnfcpl 
    38    USE isf     , ONLY : l_isfcpl, fwfisf_cpl 
     38   USE isf     , ONLY : l_isfoasis, fwfisf_oasis 
    3939#if defined key_cice 
    4040   USE ice_domain_size, only: ncat 
     
    475475 
    476476      IF( srcv(jpr_isf)%laction .AND. ln_isf ) THEN 
    477          l_isfcpl             = .TRUE.                      ! -> no need to read isf in sbcisf 
     477         l_isfoasis = .TRUE.  ! -> isf fwf comes from oasis 
    478478         IF(lwp) WRITE(numout,*) 
    479479         IF(lwp) WRITE(numout,*) '   iceshelf received from oasis ' 
     
    14091409         ! ice shelf fwf 
    14101410         IF( srcv(jpr_isf)%laction )  THEN 
    1411             fwfisf_cpl(:,:) = - frcv(jpr_isf)%z3(:,:,1)  ! fresh water flux from the isf (fwfisf <0 mean melting)   
     1411            fwfisf_oasis(:,:) = - frcv(jpr_isf)%z3(:,:,1)  ! fresh water flux from the isf (fwfisf <0 mean melting)   
    14121412         END IF 
    14131413         
     
    17131713      ENDIF 
    17141714      IF( srcv(jpr_isf)%laction ) THEN   ! iceshelf (fwfisf <0 mean melting) 
    1715         fwfisf_cpl(:,:) = - frcv(jpr_isf)%z3(:,:,1)   
     1715        fwfisf_oasis(:,:) = - frcv(jpr_isf)%z3(:,:,1)   
    17161716      ENDIF 
    17171717 
     
    17521752      ENDIF 
    17531753      IF( srcv(jpr_isf)%laction ) THEN   ! iceshelf (fwfisf <0 mean melting) 
    1754         fwfisf_cpl(:,:) = - frcv(jpr_isf)%z3(:,:,1) 
     1754        fwfisf_oasis(:,:) = - frcv(jpr_isf)%z3(:,:,1) 
    17551755      ENDIF 
    17561756      ! 
  • NEMO/branches/2019/ENHANCE-02_ISF_nemo/src/OCE/TRA/traisf.F90

    r11403 r11423  
    1616   USE isf            ! Ice shelf variable 
    1717   USE isfutils       ! 
    18    USE iscplini       ! Ice sheet coupling 
    1918   ! 
    2019   USE in_out_manager ! I/O manager 
     
    5655      ! 
    5756      ! ice sheet coupling case 
    58       !CALL tra_isf_cpl() 
     57      IF ( ll_isfcpl .AND. kt == nit000 ) CALL tra_isf_cpl(risfcpl_tsc, tsa) 
     58      ! 
     59      ! ice sheet coupling case ( 
     60      IF ( ll_isfcpl_cons ) CALL tra_isf_cpl(risfcpl_cons_tsc, tsa) 
    5961      ! 
    6062      IF( ln_timing )   CALL timing_stop('tra_isf') 
     
    7678      REAL(wp), DIMENSION(jpi,jpj)     , INTENT(in   ) :: phtbl, pfrac 
    7779      REAL(wp), DIMENSION(jpi,jpj,jpts), INTENT(in   ) :: ptsc , ptsc_b 
    78       REAL(wp), DIMENSION(jpi,jpj) :: ztc 
    7980      !!---------------------------------------------------------------------- 
    8081      INTEGER                      :: ji,jj,jk  ! loop index    
     
    107108   END SUBROUTINE tra_isf_mlt 
    108109   ! 
    109    !SUBROUTINE tra_isf_cpl 
    110        ! 
    111 !      !---------------------------------------- 
    112 !      !        Ice Sheet coupling imbalance correction to have conservation 
    113 !      !---------------------------------------- 
    114 !      ! 
    115 !      IF( ln_iscpl .AND. ln_iscpl_hsb) THEN         ! input of heat and salt due to river runoff  
    116 !         DO jk = 1,jpk 
    117 !            DO jj = 2, jpj  
    118 !               DO ji = fs_2, fs_jpim1 
    119 !                  zdep = 1._wp / e3t_n(ji,jj,jk)  
    120 !                  tsa(ji,jj,jk,jp_tem) = tsa(ji,jj,jk,jp_tem) - htsc_iscpl(ji,jj,jk,jp_tem) * zdep 
    121 !                  tsa(ji,jj,jk,jp_sal) = tsa(ji,jj,jk,jp_sal) - htsc_iscpl(ji,jj,jk,jp_sal) * zdep   
    122 !               END DO   
    123 !            END DO   
    124 !         END DO 
    125 !      ENDIF 
    126 !      ! 
    127 !   END SUBROUTINE tra_isf_cpl 
     110   SUBROUTINE tra_isf_cpl( ptsc, ptsa ) 
     111      !!---------------------------------------------------------------------- 
     112      !!                  ***  ROUTINE tra_isf_cpl  *** 
     113      !! 
     114      !! *** Action :: Update tsa with the ice shelf coupling trend  
     115      !! 
     116      !!---------------------------------------------------------------------- 
     117      REAL(wp), DIMENSION(jpi,jpj,jpk,jpts), INTENT(inout) :: ptsa 
     118      !!---------------------------------------------------------------------- 
     119      REAL(wp), DIMENSION(jpi,jpj,jpk,jpts), INTENT(in   ) :: ptsc  !( >0 out ) 
     120      !!---------------------------------------------------------------------- 
     121      INTEGER :: jk 
     122      !!---------------------------------------------------------------------- 
     123      ! 
     124      DO jk = 1,jpk 
     125         ptsa(:,:,jk,jp_tem) = ptsa(:,:,jk,jp_tem) - ptsc(:,:,jk,jp_tem) * r1_e1e2t(:,:) / e3t_n(:,:,jk) 
     126         ptsa(:,:,jk,jp_sal) = ptsa(:,:,jk,jp_sal) - ptsc(:,:,jk,jp_sal) * r1_e1e2t(:,:) / e3t_n(:,:,jk) 
     127      END DO 
     128      ! 
     129   END SUBROUTINE tra_isf_cpl 
    128130   ! 
    129131END MODULE traisf 
  • NEMO/branches/2019/ENHANCE-02_ISF_nemo/tests/ISOMIP/EXPREF/file_def_nemo-oce.xml

    r9572 r11423  
    2727     <field field_ref="ssh"          name="sossheig"  /> 
    2828          <!-- variable for ice shelf --> 
    29           <field field_ref="qlatisf"      name="sohflisf"  /> 
    30           <field field_ref="fwfisf"       name="sowflisf"  /> 
     29          <field field_ref="fwfisf_cav"       name="sowflisf"  /> 
    3130          <field field_ref="isfgammat"    name="sogammat"  /> 
    3231          <field field_ref="isfgammas"    name="sogammas"  /> 
Note: See TracChangeset for help on using the changeset viewer.