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

Changeset 11987


Ignore:
Timestamp:
2019-11-27T15:50:29+01:00 (4 years ago)
Author:
mathiot
Message:

ENHANCE-02_ISF_nemo: changes needed after Dave's review

Location:
NEMO/branches/2019/ENHANCE-02_ISF_nemo
Files:
36 edited
1 moved

Legend:

Unmodified
Added
Removed
  • NEMO/branches/2019/ENHANCE-02_ISF_nemo/src/OCE/BDY/bdyvol.F90

    r11395 r11987  
    1414   USE bdy_oce        ! ocean open boundary conditions 
    1515   USE sbc_oce        ! ocean surface boundary conditions 
     16   USE isf_oce, ONLY : fwfisf_cav, fwfisf_par  ! ice shelf 
    1617   USE dom_oce        ! ocean space and time domain  
    1718   USE phycst         ! physical constants 
    18    USE isf            ! ice shelf 
    1919   ! 
    2020   USE in_out_manager ! I/O manager 
  • NEMO/branches/2019/ENHANCE-02_ISF_nemo/src/OCE/DIA/diahsb.F90

    r11529 r11987  
    1717   USE phycst         ! physical constants 
    1818   USE sbc_oce        ! surface thermohaline fluxes 
     19   USE isf_oce        ! ice shelf fluxes 
    1920   USE sbcrnf         ! river runoff 
    20    USE isf            ! ice shelves 
    2121   USE domvvl         ! vertical scale factors 
    2222   USE traqsr         ! penetrative solar radiation 
  • NEMO/branches/2019/ENHANCE-02_ISF_nemo/src/OCE/DIA/diawri.F90

    r11876 r11987  
    2626   !!---------------------------------------------------------------------- 
    2727   USE oce            ! ocean dynamics and tracers  
    28    USE isf 
     28   USE isf_oce 
    2929   USE isfcpl 
    3030   USE dom_oce        ! ocean space and time domain 
     
    909909      CALL iom_rstput( 0, 0, inum, 'risfdep', risfdep            )    ! now k-velocity 
    910910      CALL iom_rstput( 0, 0, inum, 'ht_n'   , ht_n               )    ! now k-velocity 
     911 
    911912      IF ( ln_isf ) THEN 
    912913         IF (ln_isfcav_mlt) THEN 
     
    916917            CALL iom_rstput( 0, 0, inum, 'misfkb_cav', REAL(misfkb_cav,8)    )    ! now k-velocity 
    917918            CALL iom_rstput( 0, 0, inum, 'misfkt_cav', REAL(misfkt_cav,8)    )    ! now k-velocity 
     919            CALL iom_rstput( 0, 0, inum, 'mskisf_cav', REAL(mskisf_cav,8), ktype = jp_i1 ) 
    918920         END IF 
    919921         IF (ln_isfpar_mlt) THEN 
     
    924926            CALL iom_rstput( 0, 0, inum, 'misfkb_par', REAL(misfkb_par,8)    )    ! now k-velocity 
    925927            CALL iom_rstput( 0, 0, inum, 'misfkt_par', REAL(misfkt_par,8)    )    ! now k-velocity 
     928            CALL iom_rstput( 0, 0, inum, 'mskisf_par', REAL(mskisf_par,8), ktype = jp_i1 ) 
    926929         END IF 
    927930      END IF 
    928931 
    929       IF ( ln_isf ) THEN 
    930          IF (ln_isfcav_mlt) CALL iom_rstput( 0, 0, inum, 'mskisf_cav', REAL(mskisf_cav,8), ktype = jp_i1 ) 
    931          IF (ln_isfpar_mlt) CALL iom_rstput( 0, 0, inum, 'mskisf_par', REAL(mskisf_par,8), ktype = jp_i1 ) 
    932       END IF 
    933        
    934932      IF( ALLOCATED(ahtu) ) THEN 
    935933         CALL iom_rstput( 0, 0, inum,  'ahtu', ahtu              )    ! aht at u-point 
  • NEMO/branches/2019/ENHANCE-02_ISF_nemo/src/OCE/DOM/domwri.F90

    r11395 r11987  
    1616   !!   dom_stiff      : diagnose maximum grid stiffness/hydrostatic consistency (s-coordinate) 
    1717   !!---------------------------------------------------------------------- 
    18    USE isf             ! ice shelf 
     18   ! 
    1919   USE dom_oce         ! ocean space and time domain 
    2020   USE phycst ,   ONLY :   rsmall 
  • NEMO/branches/2019/ENHANCE-02_ISF_nemo/src/OCE/DYN/divhor.F90

    r11852 r11987  
    1919   !!---------------------------------------------------------------------- 
    2020   USE oce             ! ocean dynamics and tracers 
    21    USE isf 
    22    USE isfutils 
    2321   USE dom_oce         ! ocean space and time domain 
    24    USE sbc_oce, ONLY : ln_rnf ! surface boundary condition: ocean 
    25    USE sbcrnf          ! river runoff  
    26    USE isfhdiv         ! ice shelf 
     22   USE sbc_oce, ONLY : ln_rnf      ! river runoff 
     23   USE sbcrnf , ONLY : sbc_rnf_div ! river runoff  
     24   USE isf_oce, ONLY : ln_isf      ! ice shelf 
     25   USE isfhdiv, ONLY : isf_hdiv    ! ice shelf 
    2726#if defined key_asminc    
    2827   USE asminc          ! Assimilation increment 
  • NEMO/branches/2019/ENHANCE-02_ISF_nemo/src/OCE/DYN/dynhpg.F90

    r11403 r11987  
    3131   !!---------------------------------------------------------------------- 
    3232   USE oce             ! ocean dynamics and tracers 
    33    USE isf             ! ice shelf  (risfload variable) 
    34    USE isfload         ! ice shelf  (isf_load routine ) 
     33   USE isf_oce , ONLY : risfload  ! ice shelf  (risfload variable) 
     34   USE isfload , ONLY : isf_load  ! ice shelf  (isf_load routine ) 
    3535   USE sbc_oce         ! surface variable (only for the flag with ice shelf) 
    3636   USE dom_oce         ! ocean space and time domain 
  • NEMO/branches/2019/ENHANCE-02_ISF_nemo/src/OCE/DYN/dynnxt.F90

    r11931 r11987  
    3434   USE domvvl         ! variable volume 
    3535   USE bdy_oce   , ONLY: ln_bdy 
     36   USE isf_oce   , ONLY: ln_isf     ! ice shelf 
    3637   USE bdydta         ! ocean open boundary conditions 
    3738   USE bdydyn         ! ocean open boundary conditions 
     
    4041   USE trddyn         ! trend manager: dynamics 
    4142   USE trdken         ! trend manager: kinetic energy 
    42    USE isf       , ONLY: ln_isf     ! ice shelf 
    43    USE isfdynnxt , ONLY: isf_dynnxt ! ice shelf  
     43   USE isfdynnxt , ONLY: isf_dynnxt ! ice shelf volume filter correction subroutine  
    4444   ! 
    4545   USE in_out_manager ! I/O manager 
     
    246246            ! PM: we could probably define a generic subroutine to do the in depth correction 
    247247            !     to manage rnf, isf and possibly in the futur icb, tide water glacier (...) 
     248            !     ...(kt, coef, ktop, kbot, hz, fwf_b, fwf) 
    248249            IF ( ln_isf ) CALL isf_dynnxt( kt, atfp * rdt ) 
    249250            ! 
  • NEMO/branches/2019/ENHANCE-02_ISF_nemo/src/OCE/DYN/dynspg_ts.F90

    r11541 r11987  
    3131   USE dom_oce         ! ocean space and time domain 
    3232   USE sbc_oce         ! surface boundary condition: ocean 
     33   USE isf_oce         ! ice shelf variable (fwfisf) 
    3334   USE zdf_oce         ! vertical physics: variables 
    3435   USE zdfdrg          ! vertical physics: top/bottom drag coef. 
    35    USE isf             ! ice shelf variable (fwfisf) 
    36    USE isfutils 
    3736   USE sbcapr          ! surface boundary condition: atmospheric pressure 
    3837   USE dynadv    , ONLY: ln_dynadv_vec 
  • NEMO/branches/2019/ENHANCE-02_ISF_nemo/src/OCE/DYN/sshwzv.F90

    r11931 r11987  
    1717   !!---------------------------------------------------------------------- 
    1818   USE oce            ! ocean dynamics and tracers variables 
    19    USE isf            ! ice shelf 
    20    USE isfutils 
     19   USE isf_oce        ! ice shelf 
    2120   USE dom_oce        ! ocean space and time domain variables  
    2221   USE sbc_oce        ! surface boundary condition: ocean 
  • NEMO/branches/2019/ENHANCE-02_ISF_nemo/src/OCE/ISF/isf_oce.F90

    r11931 r11987  
    1 MODULE isf 
     1MODULE isf_oce 
    22   !!====================================================================== 
    33   !!                       ***  MODULE  sbcisf  *** 
     
    2323   PRIVATE 
    2424 
    25    PUBLIC   isf_alloc, isf_alloc_par, isf_alloc_cav, isf_alloc_cpl 
     25   PUBLIC   isf_alloc, isf_alloc_par, isf_alloc_cav, isf_alloc_cpl, isf_dealloc_cpl 
    2626   ! 
    2727   !------------------------------------------------------- 
     
    7171   !------------------------------------------------------- 
    7272   ! 
    73    ! 0.1 -------- ice shelf cavity parameter -------------- 
     73   ! 2.1 -------- ice shelf cavity parameter -------------- 
    7474   LOGICAL , PUBLIC            :: l_isfoasis 
    7575   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:)    ::   risfload                    !: ice shelf load 
    7676   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:)    ::   fwfisf_oasis 
    7777   ! 
    78    ! 0.2 -------- ice shelf cavity melt namelist parameter ------------- 
     78   ! 2.2 -------- ice shelf cavity melt namelist parameter ------------- 
    7979   INTEGER  , PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:)   :: mskisf_cav                    !: 
    8080   INTEGER  , PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:)   :: misfkt_cav   , misfkb_cav     !:  
     
    8686   REAL(wp) , PUBLIC                                      :: risf_lamb1, risf_lamb2, risf_lamb3  ! freezing point linearization coeficient 
    8787   ! 
    88    ! 0.3 -------- ice shelf param. melt namelist parameter ------------- 
     88   ! 2.3 -------- ice shelf param. melt namelist parameter ------------- 
    8989   INTEGER  , PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:)   :: mskisf_par                    !: 
    9090   INTEGER  , PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:)   :: misfkt_par   , misfkb_par     !: 
     
    9797   REAL(wp) , PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:)   :: risfLeff                      !: 
    9898   ! 
    99    ! 0.4 -------- coupling namelist parameter ------------- 
     99   ! 2.4 -------- coupling namelist parameter ------------- 
    100100   INTEGER , PUBLIC                                        ::   nstp_iscpl   !: 
    101101   REAL(wp), PUBLIC                                        ::   rdt_iscpl    !:  
     
    175175      !!                  ***  ROUTINE isf_alloc_cpl  *** 
    176176      !! 
    177       !! ** Purpose :  
    178       !! 
    179       !! ** Method  :  
     177      !! ** Purpose : allocate array use for the ice sheet coupling 
    180178      !! 
    181179      !!---------------------------------------------------------------------- 
     
    202200   END SUBROUTINE isf_alloc_cpl 
    203201 
     202   SUBROUTINE isf_dealloc_cpl() 
     203      !!--------------------------------------------------------------------- 
     204      !!                  ***  ROUTINE isf_dealloc_cpl  *** 
     205      !! 
     206      !! ** Purpose : de-allocate useless public 3d array used for ice sheet coupling 
     207      !! 
     208      !!---------------------------------------------------------------------- 
     209      INTEGER :: ierr, ialloc 
     210      !!---------------------------------------------------------------------- 
     211      ierr = 0 
     212      ! 
     213      DEALLOCATE( risfcpl_ssh, risfcpl_tsc, risfcpl_vol, STAT=ialloc ) 
     214      ierr = ierr + ialloc 
     215      ! 
     216      CALL mpp_sum ( 'isf', ierr ) 
     217      IF( ierr /= 0 )   CALL ctl_stop('STOP','isfcpl: failed to deallocate arrays.') 
     218      ! 
     219   END SUBROUTINE isf_dealloc_cpl 
     220 
    204221   SUBROUTINE isf_alloc() 
    205222      !!--------------------------------------------------------------------- 
    206223      !!                  ***  ROUTINE isf_alloc  *** 
    207224      !! 
    208       !! ** Purpose :  
    209       !! 
    210       !! ** Method  :  
     225      !! ** Purpose : allocate array used for the ice shelf cavity (cav and par) 
    211226      !! 
    212227      !!---------------------------------------------------------------------- 
     
    247262   END SUBROUTINE isf_alloc 
    248263 
    249 END MODULE isf 
     264END MODULE isf_oce 
  • NEMO/branches/2019/ENHANCE-02_ISF_nemo/src/OCE/ISF/isfcav.F90

    r11931 r11987  
    1313   !!   isf_cav       : update ice shelf melting under ice shelf 
    1414   !!---------------------------------------------------------------------- 
    15    USE isf            ! ice shelf public variables 
     15   USE isf_oce        ! ice shelf public variables 
    1616   ! 
    1717   USE isfrst   , ONLY: isfrst_write, isfrst_read ! ice shelf restart read/write subroutine 
     
    163163      INTEGER :: ierr 
    164164      !!--------------------------------------------------------------------- 
     165      PRINT *, cn_isfcav_mlt 
    165166      ! 
    166167      !============== 
  • NEMO/branches/2019/ENHANCE-02_ISF_nemo/src/OCE/ISF/isfcavgam.F90

    r11931 r11987  
    1010   !!   isfcav_gammats       : compute exchange coeficient gamma  
    1111   !!---------------------------------------------------------------------- 
    12    USE isf 
     12   USE isf_oce 
    1313   USE isfutils, ONLY: debug 
    1414   USE isftbl  , ONLY: isf_tbl 
     
    184184      ! 
    185185      ! compute ustar 
    186       zustar(:,:) = SQRT( pCd * ( putbl(:,:) * putbl(:,:) + pvtbl(:,:) * pvtbl(:,:) + r_ke0_top ) ) 
     186      zustar(:,:) = SQRT( pCd * ( putbl(:,:) * putbl(:,:) + pvtbl(:,:) * pvtbl(:,:) + pke2 ) ) 
    187187      ! 
    188188      ! output ustar 
  • NEMO/branches/2019/ENHANCE-02_ISF_nemo/src/OCE/ISF/isfcavmlt.F90

    r11931 r11987  
    1212   !!---------------------------------------------------------------------- 
    1313 
    14    USE isf                      ! ice shelf 
     14   USE isf_oce                  ! ice shelf 
    1515   USE isftbl , ONLY: isf_tbl   ! ice shelf depth average 
    1616   USE isfutils,ONLY: debug     ! debug subroutine 
  • NEMO/branches/2019/ENHANCE-02_ISF_nemo/src/OCE/ISF/isfcpl.F90

    r11931 r11987  
    1212   !!   isfrst : read/write iceshelf variables in/from restart 
    1313   !!---------------------------------------------------------------------- 
    14    USE isf                              ! ice shelf variable 
     14   USE isf_oce                          ! ice shelf variable 
    1515   USE isfutils, ONLY : debug 
    1616   USE lib_mpp , ONLY: mpp_sum, mpp_max ! mpp routine 
  • NEMO/branches/2019/ENHANCE-02_ISF_nemo/src/OCE/ISF/isfdiags.F90

    r11931 r11987  
    1616   USE in_out_manager ! I/O manager 
    1717   USE dom_oce 
    18    USE isf            ! ice shelf variable 
    19    USE isfutils 
     18   USE isf_oce        ! ice shelf variable 
    2019   USE iom            !  
    2120 
  • NEMO/branches/2019/ENHANCE-02_ISF_nemo/src/OCE/ISF/isfdynnxt.F90

    r11931 r11987  
    1111   !!------------------------------------------------------------------------- 
    1212 
    13    USE isf 
     13   USE isf_oce 
    1414 
    1515   USE phycst , ONLY: r1_rau0                ! physical constant 
  • NEMO/branches/2019/ENHANCE-02_ISF_nemo/src/OCE/ISF/isfhdiv.F90

    r11931 r11987  
    11MODULE isfhdiv 
     2   !!====================================================================== 
     3   !!                       ***  MODULE  isfhdiv  *** 
     4   !! ice shelf horizontal divergence module :  update the horizontal divergence 
     5   !!                   with the ice shelf melt and coupling correction 
     6   !!====================================================================== 
     7   !! History :  4.0  !  2019-09  (P. Mathiot) Original code 
     8   !!---------------------------------------------------------------------- 
    29 
    3    USE isf                    ! ice shelf 
    4    USE isfutils  
     10   !!---------------------------------------------------------------------- 
     11   !!   isf_hdiv    : update the horizontal divergence with the ice shelf  
     12   !!                 melt and coupling correction 
     13   !!---------------------------------------------------------------------- 
     14 
     15   USE isf_oce                ! ice shelf 
     16 
    517   USE dom_oce                ! time and space domain 
    618   USE phycst , ONLY: r1_rau0 ! physical constant 
  • NEMO/branches/2019/ENHANCE-02_ISF_nemo/src/OCE/ISF/isfload.F90

    r11852 r11987  
    1111   !!---------------------------------------------------------------------- 
    1212 
    13    USE isf, ONLY: cn_isfload   ! ice shelf variables 
     13   USE isf_oce, ONLY: cn_isfload                    ! ice shelf variables 
    1414 
    1515   USE dom_oce, ONLY: e3w_n, gdept_n, risfdep, mikt ! vertical scale factor 
    1616   USE eosbn2 , ONLY: eos                           ! eos routine 
    1717 
    18    USE lib_mpp, ONLY: ctl_stop ! ctl_stop routine 
    19    USE in_out_manager  !  
     18   USE lib_mpp, ONLY: ctl_stop                      ! ctl_stop routine 
     19   USE in_out_manager                               !  
    2020 
    2121   IMPLICIT NONE 
  • NEMO/branches/2019/ENHANCE-02_ISF_nemo/src/OCE/ISF/isfpar.F90

    r11931 r11987  
    1414   !!   isfpar       : compute ice shelf melt using a prametrisation of ice shelf cavities 
    1515   !!---------------------------------------------------------------------- 
    16    USE isf            ! ice shelf 
     16   USE isf_oce        ! ice shelf 
    1717   ! 
    1818   USE isfrst   , ONLY: isfrst_write, isfrst_read ! ice shelf restart read/write subroutine 
    1919   USE isftbl   , ONLY: isf_tbl_ktop, isf_tbl_lvl ! ice shelf top boundary layer properties subroutine 
     20   USE isfparmlt, ONLY: isfpar_mlt                ! ice shelf melt formulation subroutine 
     21   USE isfdiags , ONLY: isf_diags_flx             ! ice shelf diags subroutine 
    2022   USE isfutils , ONLY: debug, read_2dcstdta      ! ice shelf debug subroutine 
    21    USE isfparmlt, ONLY: isfpar_mlt     ! ice shelf melt formulation subroutine 
    22    USE isfdiags , ONLY: isf_diags_flx  ! ice shelf diags subroutine 
    2323   ! 
    2424   USE dom_oce  , ONLY: bathy          ! ocean space and time domain 
  • NEMO/branches/2019/ENHANCE-02_ISF_nemo/src/OCE/ISF/isfparmlt.F90

    r11931 r11987  
    88   !!---------------------------------------------------------------------- 
    99 
    10    USE isf            ! ice shelf 
     10   USE isf_oce                  ! ice shelf 
    1111   USE isftbl , ONLY: isf_tbl   ! ice shelf depth average 
    1212 
  • NEMO/branches/2019/ENHANCE-02_ISF_nemo/src/OCE/ISF/isfstp.F90

    r11931 r11987  
    1414   !!---------------------------------------------------------------------- 
    1515   ! 
    16    USE isf            ! isf variables 
     16   USE isf_oce                                      ! isf variables 
    1717   USE isfload, ONLY: isf_load                      ! ice shelf load 
    1818   USE isftbl , ONLY: isf_tbl_lvl                   ! ice shelf boundary layer 
     
    158158         !--------------------------------------------------------------------------------------------------------------------- 
    159159         ! initialisation ice sheet coupling 
    160          IF( ln_isfcpl ) CALL isfcpl_init() 
     160         IF ( ln_isfcpl ) CALL isfcpl_init() 
    161161         ! 
    162162      END IF 
     
    185185            WRITE(numout,*) '      melt inside the cavity                  ln_isfcav_mlt   = ', ln_isfcav_mlt 
    186186            IF ( ln_isfcav_mlt) THEN 
    187                WRITE(numout,*) '         melt formulation                        cn_isfcav_mlt   = ', TRIM(cn_isfcav_mlt) 
    188                WRITE(numout,*) '         thickness of the top boundary layer     rn_htbl     = ', rn_htbl 
    189                WRITE(numout,*) '         gamma formulation                       cn_gammablk = ', TRIM(cn_gammablk)  
     187               WRITE(numout,*) '         melt formulation                         cn_isfcav_mlt= ', TRIM(cn_isfcav_mlt) 
     188               WRITE(numout,*) '         thickness of the top boundary layer      rn_htbl      = ', rn_htbl 
     189               WRITE(numout,*) '         gamma formulation                        cn_gammablk = ', TRIM(cn_gammablk)  
    190190               IF ( TRIM(cn_gammablk) .NE. 'spe' ) THEN  
    191                   WRITE(numout,*) '         gammat coefficient                       rn_gammat0  = ', rn_gammat0   
    192                   WRITE(numout,*) '         gammas coefficient                       rn_gammas0  = ', rn_gammas0   
    193                   WRITE(numout,*) '         top drag coef.    used (from namdrg_top) rn_Cd0      = ', r_Cdmin_top 
    194                   WRITE(numout,*) '         top background ke used (from namdrg_top) rn_ke0      = ', r_ke0_top 
     191                  WRITE(numout,*) '         gammat coefficient                       rn_gammat0   = ', rn_gammat0   
     192                  WRITE(numout,*) '         gammas coefficient                       rn_gammas0   = ', rn_gammas0   
     193                  WRITE(numout,*) '         top background ke used (from namdrg_top) rn_ke0       = ', r_ke0_top 
     194                  WRITE(numout,*) '         top drag coef.    used (from namdrg_top) rn_Cd0       = ', r_Cdmin_top 
    195195               END IF 
    196196            END IF 
     
    222222         IF (ln_isfcav) WRITE(numout,*) '      Ice shelf load method                   cn_isfload        = ', TRIM(cn_isfload) 
    223223         WRITE(numout,*) '' 
     224         FLUSH(numout) 
    224225 
    225226      END IF 
     
    243244      IF ( l_isfoasis .AND. ln_isf ) THEN 
    244245         ! 
    245          CALL ctl_stop( ' OASIS and ice shelf not tested' ) 
     246         CALL ctl_stop( ' ln_ctl and ice shelf not tested' ) 
    246247         ! 
    247248         ! NEMO coupled to ATMO model with isf cavity need oasis method for melt computation  
  • NEMO/branches/2019/ENHANCE-02_ISF_nemo/src/OCE/ISF/isftbl.F90

    r11931 r11987  
    1414   !!---------------------------------------------------------------------- 
    1515 
    16    USE isf    ! ice shelf variables 
     16   USE isf_oce ! ice shelf variables 
    1717 
    1818   USE dom_oce ! vertical scale factor and depth 
  • NEMO/branches/2019/ENHANCE-02_ISF_nemo/src/OCE/ISF/isfutils.F90

    r11931 r11987  
    5454      !!                  ***  ROUTINE isf_debug2d  *** 
    5555      !! 
    56       !! ** Purpose : add debug print 
     56      !! ** Purpose : add debug print for 2d variables 
    5757      !! 
    5858      !!-------------------------- IN  ------------------------------------- 
     
    7777      !!                  ***  ROUTINE isf_debug3d  *** 
    7878      !! 
    79       !! ** Purpose : add debug print 
     79      !! ** Purpose : add debug print for 3d variables 
    8080      !! 
    8181      !!-------------------------- IN  ------------------------------------- 
  • NEMO/branches/2019/ENHANCE-02_ISF_nemo/src/OCE/LDF/ldfslp.F90

    r11395 r11987  
    2121   !!---------------------------------------------------------------------- 
    2222   USE oce            ! ocean dynamics and tracers 
    23    USE isf            ! ice shelf 
     23   USE isf_oce        ! ice shelf 
    2424   USE dom_oce        ! ocean space and time domain 
    2525!   USE ldfdyn         ! lateral diffusion: eddy viscosity coef. 
  • NEMO/branches/2019/ENHANCE-02_ISF_nemo/src/OCE/LDF/ldftra.F90

    r10425 r11987  
    662662                  ! eddies using the isopycnal slopes calculated in ldfslp.F :  
    663663                  ! T^-1 = sqrt(m_jpk(N^2*(r1^2+r2^2)*e3w)) 
    664                   ze3w = e3w_n(ji,jj,jk) * tmask(ji,jj,jk) 
     664                  ze3w = e3w_n(ji,jj,jk) * wmask(ji,jj,jk) 
    665665                  zah(ji,jj) = zah(ji,jj) + zn2 * wslp2(ji,jj,jk) * ze3w 
    666666                  zhw(ji,jj) = zhw(ji,jj) + ze3w 
     
    680680                  ! eddies using the isopycnal slopes calculated in ldfslp.F :  
    681681                  ! T^-1 = sqrt(m_jpk(N^2*(r1^2+r2^2)*e3w)) 
    682                   ze3w = e3w_n(ji,jj,jk) * tmask(ji,jj,jk) 
     682                  ze3w = e3w_n(ji,jj,jk) * wmask(ji,jj,jk) 
    683683                  zah(ji,jj) = zah(ji,jj) + zn2 * ( wslpi(ji,jj,jk) * wslpi(ji,jj,jk)   & 
    684684                     &                            + wslpj(ji,jj,jk) * wslpj(ji,jj,jk) ) * ze3w 
  • NEMO/branches/2019/ENHANCE-02_ISF_nemo/src/OCE/SBC/sbccpl.F90

    r11553 r11987  
    2727   USE sbcwave         ! surface boundary condition: waves 
    2828   USE phycst          ! physical constants 
     29   USE isf_oce , ONLY : l_isfoasis, fwfisf_oasis ! ice shelf boundary condition 
    2930#if defined key_si3 
    3031   USE ice            ! ice variables 
     
    3637   USE eosbn2         !  
    3738   USE sbcrnf  , ONLY : l_rnfcpl 
    38    USE isf     , ONLY : ln_isf, l_isfoasis, fwfisf_oasis 
    3939#if defined key_cice 
    4040   USE ice_domain_size, only: ncat 
  • NEMO/branches/2019/ENHANCE-02_ISF_nemo/src/OCE/SBC/sbcfwb.F90

    r11395 r11987  
    1717   USE dom_oce        ! ocean space and time domain 
    1818   USE sbc_oce        ! surface ocean boundary condition 
     19   USE isf_oce , ONLY : fwfisf_cav, fwfisf_par                    ! ice shelf melting contribution 
    1920   USE sbc_ice , ONLY : snwice_mass, snwice_mass_b, snwice_fmass 
    2021   USE phycst         ! physical constants 
    2122   USE sbcrnf         ! ocean runoffs 
    22    USE isf            ! ice shelf melting contribution 
    2323   USE sbcssr         ! Sea-Surface damping terms 
    2424   ! 
  • NEMO/branches/2019/ENHANCE-02_ISF_nemo/src/OCE/SBC/sbcrnf.F90

    r11395 r11987  
    1919   USE phycst         ! physical constants 
    2020   USE sbc_oce        ! surface boundary condition variables 
    21    USE isf            ! ice shelf 
    2221   USE eosbn2         ! Equation Of State 
    2322   USE closea         ! closed seas 
     
    127126               rnf_tsc(:,:,jp_tem) = sst_m(:,:) * rnf(:,:) * r1_rau0 
    128127            END WHERE 
    129             WHERE( sf_t_rnf(1)%fnow(:,:,1) == -222._wp )             ! where fwf comes from melting of ice shelves or iceberg 
    130                rnf_tsc(:,:,jp_tem) = ztfrz(:,:) * rnf(:,:) * r1_rau0 - rnf(:,:) * rLfusisf * r1_rau0_rcp 
    131             END WHERE 
    132128         ELSE                                                        ! use SST as runoffs temperature 
    133129            !CEOD River is fresh water so must at least be 0 unless we consider ice 
  • NEMO/branches/2019/ENHANCE-02_ISF_nemo/src/OCE/SBC/sbcssm.F90

    r10425 r11987  
    6060      ! 
    6161      !                                        !* surface T-, U-, V- ocean level variables (T, S, depth, velocity) 
    62       DO jj = 1, jpj 
    63          DO ji = 1, jpi 
    64             zts(ji,jj,jp_tem) = tsn(ji,jj,mikt(ji,jj),jp_tem) 
    65             zts(ji,jj,jp_sal) = tsn(ji,jj,mikt(ji,jj),jp_sal) 
    66          END DO 
    67       END DO 
     62      zts(:,:,jp_tem) = tsn(:,:,1,jp_tem) 
     63      zts(:,:,jp_sal) = tsn(:,:,1,jp_sal) 
    6864      ! 
    6965      IF( nn_fsbc == 1 ) THEN                             !   Instantaneous surface fields        ! 
  • NEMO/branches/2019/ENHANCE-02_ISF_nemo/src/OCE/TRA/traisf.F90

    r11931 r11987  
    1212   USE oce            ! ocean dynamics and active tracers 
    1313   USE dom_oce        ! ocean space domain variables 
     14   USE isf_oce        ! Ice shelf variable 
    1415   USE phycst         ! physical constant 
    1516   USE eosbn2         ! Equation Of State 
    16    USE isf            ! Ice shelf variable 
    1717   USE isfutils       ! 
    1818   ! 
  • NEMO/branches/2019/ENHANCE-02_ISF_nemo/src/OCE/TRA/tranxt.F90

    r11931 r11987  
    2828   USE sbc_oce         ! surface boundary condition: ocean 
    2929   USE sbcrnf          ! river runoffs 
    30    USE isf             ! ice shelf melting 
     30   USE isf_oce         ! ice shelf melting 
    3131   USE zdf_oce         ! ocean vertical mixing 
    3232   USE domvvl          ! variable volume 
  • NEMO/branches/2019/ENHANCE-02_ISF_nemo/src/OCE/ZDF/zdfmxl.F90

    r11395 r11987  
    1212   !!---------------------------------------------------------------------- 
    1313   USE oce            ! ocean dynamics and tracers variables 
    14    USE isf            ! ice shelf 
     14   USE isf_oce        ! ice shelf 
    1515   USE dom_oce        ! ocean space and time domain variables 
    1616   USE trc_oce  , ONLY: l_offline         ! ocean space and time domain variables 
  • NEMO/branches/2019/ENHANCE-02_ISF_nemo/src/OCE/step_oce.F90

    r11895 r11987  
    2222   USE sbcwave         ! Wave intialisation 
    2323 
    24    USE isf 
     24   USE isf_oce         ! ice shelf boundary condition 
    2525   USE isfstp          ! ice shelf boundary condition     (isf_stp routine) 
    2626 
  • NEMO/branches/2019/ENHANCE-02_ISF_nemo/tests/ISOMIP+/MY_SRC/isfcavgam.F90

    r11889 r11987  
    1010   !!   isfcav_gammats       : compute exchange coeficient gamma  
    1111   !!---------------------------------------------------------------------- 
    12    USE isf 
     12   USE isf_oce 
    1313   USE isfutils, ONLY: debug 
    1414   USE isftbl  , ONLY: isf_tbl 
     
    5757      !!--------------------------------------------------------------------- 
    5858      ! 
    59       ! compute velocity in the tbl if needed 
     59      !========================================== 
     60      ! 1.: compute velocity in the tbl if needed 
     61      !========================================== 
     62      ! 
    6063      SELECT CASE ( cn_gammablk ) 
    6164      CASE ( 'spe'  )  
     
    7881      END SELECT 
    7982      !  
    80       ! compute gamma 
     83      !========================================== 
     84      ! 2.: compute gamma 
     85      !========================================== 
     86      ! 
    8187      SELECT CASE ( cn_gammablk ) 
    8288      CASE ( 'spe'  ) ! gamma is constant (specified in namelist) 
     
    8692         CALL gammats_AD15 (              zutbl, zvtbl, rCd0_top, rn_vtide**2,               pgt, pgs ) 
    8793      CASE ( 'hj99' ) ! gamma depends of stability of boundary layer and u* 
    88          CALL gammats_HJ99 (pttbl, pstbl, zutbl, zvtbl, rCd0_top, r_ke0_top  , pqoce, pqfwf, pgt, pgs ) 
     94         CALL gammats_HJ99 (pttbl, pstbl, zutbl, zvtbl, rCd0_top, r_ke0_top, pqoce, pqfwf, pgt, pgs ) 
    8995      CASE DEFAULT 
    9096         CALL ctl_stop('STOP','method to compute gamma (cn_gammablk) is unknown (should not see this)') 
    9197      END SELECT 
    9298      ! 
    93       ! ouput exchange coeficient and tbl velocity 
     99      !========================================== 
     100      ! 3.: output and debug 
     101      !========================================== 
     102      ! 
    94103      CALL iom_put('isfgammat', pgt(:,:)) 
    95104      CALL iom_put('isfgammas', pgs(:,:)) 
  • NEMO/branches/2019/ENHANCE-02_ISF_nemo/tests/ISOMIP+/MY_SRC/isfstp.F90

    r11931 r11987  
    1414   !!---------------------------------------------------------------------- 
    1515   ! 
    16    USE isf            ! isf variables 
     16   USE isf_oce                                      ! isf variables 
    1717   USE isfload, ONLY: isf_load                      ! ice shelf load 
    1818   USE isftbl , ONLY: isf_tbl_lvl                   ! ice shelf boundary layer 
     
    2626   ! 
    2727   USE lib_mpp, ONLY: ctl_stop, ctl_nam 
     28   USE fldread, ONLY: FLD, FLD_N 
    2829   USE in_out_manager ! I/O manager 
    2930   USE timing 
     
    6263      IF( ln_timing )   CALL timing_start('isf') 
    6364      ! 
     65      !======================================================================= 
     66      ! 1.: compute melt and associated heat fluxes in the ice shelf cavities 
     67      !======================================================================= 
     68      ! 
    6469      IF ( ln_isfcav_mlt ) THEN 
    6570         ! 
    66          ! before time step  
     71         ! 1.1: before time step  
    6772         IF ( kt /= nit000 ) THEN  
    6873            risf_cav_tsc_b (:,:,:) = risf_cav_tsc (:,:,:) 
     
    7075         END IF 
    7176         ! 
    72          ! compute misfkb, rhisf_tbl, rfrac (deepest level, thickness, fraction of deepest cell affected by tbl) 
     77         ! 1.2: compute misfkb, rhisf_tbl, rfrac (deepest level, thickness, fraction of deepest cell affected by tbl) 
    7378         rhisf_tbl_cav(:,:) = rn_htbl * mskisf_cav(:,:) 
    7479         CALL isf_tbl_lvl(ht_n, e3t_n, misfkt_cav, misfkb_cav, rhisf_tbl_cav, rfrac_tbl_cav) 
    7580         ! 
    76          ! compute ice shelf melt 
     81         ! 1.3: compute ice shelf melt 
    7782         CALL isf_cav( kt, risf_cav_tsc, fwfisf_cav) 
    7883         ! 
    7984      END IF 
    8085      !  
     86      !================================================================================= 
     87      ! 2.: compute melt and associated heat fluxes for not resolved ice shelf cavities 
     88      !================================================================================= 
     89      ! 
    8190      IF ( ln_isfpar_mlt ) THEN 
    8291         ! 
    83          ! before time step  
     92         ! 2.1: before time step  
    8493         IF ( kt /= nit000 ) THEN  
    8594            risf_par_tsc_b(:,:,:) = risf_par_tsc(:,:,:) 
     
    8796         END IF 
    8897         ! 
    89          ! compute misfkb, rhisf_tbl, rfrac (deepest level, thickness, fraction of deepest cell affected by tbl) 
    90          ! by simplicity, we assume the top level where param applied do not change with time 
     98         ! 2.2: compute misfkb, rhisf_tbl, rfrac (deepest level, thickness, fraction of deepest cell affected by tbl) 
     99         ! by simplicity, we assume the top level where param applied do not change with time (done in init part) 
    91100         rhisf_tbl_par(:,:) = rhisf0_tbl_par(:,:) 
    92101         CALL isf_tbl_lvl(ht_n, e3t_n, misfkt_par, misfkb_par, rhisf_tbl_par, rfrac_tbl_par) 
    93102         ! 
    94          ! compute ice shelf melt 
     103         ! 2.3: compute ice shelf melt 
    95104         CALL isf_par( kt, risf_par_tsc, fwfisf_par) 
    96105         ! 
    97106      END IF 
    98107      ! 
    99       IF ( ln_isfcpl ) THEN 
    100          ! after step nit000 + 2 we do not need anymore the risfcpl_ arrays 
    101          IF ( kt == nit000 + 2 ) CALL isf_dealloc_cpl() 
    102  
    103          IF ( lrst_oce ) CALL isfcpl_rst_write(kt) 
    104       END IF 
     108      !================================================================================== 
     109      ! 3.: output specific restart variable in case of coupling with an ice sheet model 
     110      !================================================================================== 
     111      ! 
     112      IF ( ln_isfcpl .AND. lrst_oce ) CALL isfcpl_rst_write(kt) 
    105113      ! 
    106114      IF( ln_timing )   CALL timing_stop('isf') 
     
    177185            WRITE(numout,*) '      melt inside the cavity                  ln_isfcav_mlt   = ', ln_isfcav_mlt 
    178186            IF ( ln_isfcav_mlt) THEN 
    179                WRITE(numout,*) '         melt formulation                        cn_isfcav_mlt   = ', TRIM(cn_isfcav_mlt) 
    180                WRITE(numout,*) '         thickness of the top boundary layer     rn_htbl     = ', rn_htbl 
    181                WRITE(numout,*) '         gamma formulation                       cn_gammablk = ', TRIM(cn_gammablk)  
     187               WRITE(numout,*) '         melt formulation                         cn_isfcav_mlt= ', TRIM(cn_isfcav_mlt) 
     188               WRITE(numout,*) '         thickness of the top boundary layer      rn_htbl      = ', rn_htbl 
     189               WRITE(numout,*) '         gamma formulation                        cn_gammablk = ', TRIM(cn_gammablk)  
    182190               IF ( TRIM(cn_gammablk) .NE. 'spe' ) THEN  
    183                   WRITE(numout,*) '         gammat coefficient                       rn_gammat0  = ', rn_gammat0   
    184                   WRITE(numout,*) '         gammas coefficient                       rn_gammas0  = ', rn_gammas0   
    185                   WRITE(numout,*) '         top background ke used (from namdrg_top) rn_vtide**2 = ', rn_vtide**2 
    186                   WRITE(numout,*) '         top drag coef.    used (from namdrg_top) rn_Cd0      = ', r_Cdmin_top 
     191                  WRITE(numout,*) '         gammat coefficient                       rn_gammat0   = ', rn_gammat0   
     192                  WRITE(numout,*) '         gammas coefficient                       rn_gammas0   = ', rn_gammas0   
     193                  WRITE(numout,*) '         top background ke used (from namdrg_top) rn_vtide**2  = ', rn_vtide**2 
     194                  WRITE(numout,*) '         top drag coef.    used (from namdrg_top) rn_Cd0       = ', r_Cdmin_top 
    187195               END IF 
    188196            END IF 
     
    214222         IF (ln_isfcav) WRITE(numout,*) '      Ice shelf load method                   cn_isfload        = ', TRIM(cn_isfload) 
    215223         WRITE(numout,*) '' 
     224         FLUSH(numout) 
    216225 
    217226      END IF 
  • NEMO/branches/2019/ENHANCE-02_ISF_nemo/tests/ISOMIP+/MY_SRC/sbcfwb.F90

    r11931 r11987  
    1717   USE dom_oce        ! ocean space and time domain 
    1818   USE sbc_oce        ! surface ocean boundary condition 
     19   USE isf_oce        ! ice shelf melting contribution 
    1920   USE sbc_ice , ONLY : snwice_mass, snwice_mass_b, snwice_fmass 
    2021   USE phycst         ! physical constants 
    2122   USE sbcrnf         ! ocean runoffs 
    22    USE isf            ! ice shelf melting contribution 
    2323   USE sbcssr         ! Sea-Surface damping terms 
    24    USE tradmp         ! 
    2524   ! 
    2625   USE in_out_manager ! I/O manager 
  • NEMO/branches/2019/ENHANCE-02_ISF_nemo/tests/demo_cfgs.txt

    r10516 r11987  
    11CANAL OCE 
    22ISOMIP OCE 
     3ISOMIP+ OCE 
    34LOCK_EXCHANGE OCE 
    45OVERFLOW OCE 
Note: See TracChangeset for help on using the changeset viewer.