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 for NEMO/branches/2019/ENHANCE-02_ISF_nemo/src/OCE/ISF – NEMO

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/src/OCE/ISF
Files:
13 edited
1 moved

Legend:

Unmodified
Added
Removed
  • 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  ------------------------------------- 
Note: See TracChangeset for help on using the changeset viewer.