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

Changeset 15745


Ignore:
Timestamp:
2022-03-08T18:55:08+01:00 (2 years ago)
Author:
dbruciaferri
Message:

modifications for restoring upper 300 m to EN4

Location:
NEMO/branches/UKMO/tools_r4.0-HEAD_dev_DMP_TOOLS/DMP_TOOLS
Files:
4 edited

Legend:

Unmodified
Added
Removed
  • NEMO/branches/UKMO/tools_r4.0-HEAD_dev_DMP_TOOLS/DMP_TOOLS/namelist

    r4745 r15745  
    11&nam_dmp_create 
    2     cp_cfg = 'orca'            ! Name of model grid (orca and C1D have special options - otherwise ignored) 
    3     cp_cfz = 'antarctic'       ! Name of zoom configuration (arctic and antarctic have some special treatment if lzoom=.true.) 
    4     jp_cfg = 2                 ! Resolution of the model (used for med_red_seas damping) 
    5     lzoom = .false.            ! Zoom configuration or not 
    6     ln_full_field = .false.    ! Calculate coefficient over whole of domain  
    7     ln_med_red_seas = .true.   ! Damping in Med/Red Seas (or local modifications here if ln_full_field=.true.) 
    8     ln_old_31_lev_code = .true.   ! Replicate behaviour of old online code for 31 level model (Med/Red seas damping based on level number instead of depth) 
    9     ln_coast = .true.          ! Reduce near to coastlines  
    10     ln_zero_top_layer = .true. ! No damping in top layer 
    11     ln_custom = .false.        ! Call "custom" module to apply user modifications to the damping coefficient field 
    12     nn_hdmp = 10               ! Damp poleward of this latitude (smooth transition up to maximum damping) 
    13     pn_surf = 0.25             ! Surface Relaxation timescale (days)  
    14     pn_bot = 0.25              ! Bottom relaxation timescale (days) 
    15     pn_dep = 1000              ! Transition depth from upper to deep ocean 
    16     jperio = 2                 ! Lateral boundary condition (as specified in namelist_cfg for model run). 
     2    cp_cfg = 'orca025'           ! Name of model grid (orca and C1D have  
     3                                 ! special options - otherwise ignored) 
     4    cp_cfz = 'antarctic'         ! Name of zoom configuration (arctic and  
     5                                 ! antarctic have some special  
     6                                 ! treatment if lzoom=.true.) 
     7    jp_cfg = 2                   ! Resolution of the model (used for med_red_seas damping) 
     8    lzoom = .false.              ! Zoom configuration or not 
     9    ln_full_field = .true.       ! Calculate coefficient over whole of domain  
     10    ln_med_red_seas = .false.    ! Damping in Med/Red Seas (or local modifications  
     11                                 ! here if ln_full_field=.true.) 
     12    ln_old_31_lev_code = .false. ! Replicate behaviour of old online code for 31 level model  
     13                                 ! (Med/Red seas damping based on level number instead of depth) 
     14    ln_coast = .true.            ! Reduce near to coastlines  
     15    ln_zero_top_layer = .false.  ! No damping in top layer 
     16    ln_custom = .true.           ! Call "custom" module to apply user modifications to  
     17                                 ! the damping coefficient field 
     18    nn_hdmp = 0                  ! Damp poleward of this latitude  
     19                                 ! (smooth transition up to maximum damping) 
     20    pn_surf = 0.25               ! Surface Relaxation timescale (days)  
     21    pn_bot  = 0.                 ! Bottom relaxation timescale (days) 
     22    ln_exp  = .false.             ! Using exponential (T) or logistic (F) 
     23                                 ! vertical decay of restoring 
     24    pn_dep  = 250.               ! Transition depth from upper to deep ocean 
     25                                 ! (value of the sigmoid's midpoint if logistic decay) 
     26    rn_k    = 4.                 ! steepness of logistic curve 
     27    pn_cst  = 200.               ! distance from the coast (km) 
     28    jperio  = 4                  ! Lateral boundary condition  
     29                                 ! (as specified in namelist_cfg for model run). 
    1730/ 
    1831 
  • NEMO/branches/UKMO/tools_r4.0-HEAD_dev_DMP_TOOLS/DMP_TOOLS/src/coast_dist.F90

    r4739 r15745  
    99   CONTAINS 
    1010 
    11    SUBROUTINE coast_dist_weight( presto )  
     11   SUBROUTINE coast_dist_weight( presto, zdct )  
    1212      !!---------------------------------------------------------------------- 
    1313      !!                 *** ROUTINE coast_dist_weight *** 
     
    2020      IMPLICIT NONE 
    2121      REAL(wp), DIMENSION(jpi,jpj), INTENT( inout ) :: presto 
    22       REAL(wp), DIMENSION(jpi,jpj) :: zdct 
    23       REAL(wp) :: zinfl = 1000.e3_wp  ! Distance of influence of coast line (could be 
    24                                   ! a namelist setting) 
    25       INTEGER :: jj, ji           ! dummy loop indices 
     22      REAL(wp), DIMENSION(jpi,jpj), INTENT( in    ) :: zdct 
     23      REAL(wp) :: zinfl = 200.e3_wp  ! Distance of influence of coast line (could be 
     24                                     ! a namelist setting) 
     25      REAL(wp) :: rdct               ! coastal distance factor 
     26      INTEGER  :: jj, ji             ! dummy loop indices 
    2627       
    2728 
    28       CALL cofdis( zdct ) 
     29      zinfl = pn_cst * 1000._wp ! in m 
     30 
     31      !CALL cofdis( zdct ) 
    2932      DO jj = 1, jpj 
    3033         DO ji = 1, jpi 
    31             zdct(ji,jj) = MIN( zinfl, zdct(ji,jj) ) 
    32             presto(ji,jj) = presto(ji, jj) * 0.5_wp * (  1._wp - COS( rpi*zdct(ji,jj)/zinfl) ) 
     34            !zdct(ji,jj) = MIN( zinfl, zdct(ji,jj) ) 
     35            rdct = MIN( zinfl, zdct(ji,jj) ) / zinfl 
     36            !presto(ji,jj) = presto(ji, jj) * 0.5_wp * (  1._wp - COS( rpi*zdct(ji,jj)/zinfl) ) 
     37            presto(ji,jj) = presto(ji, jj) * 0.5_wp * (  1._wp - COS( rpi*rdct) ) 
    3338         END DO 
    3439      END DO 
  • NEMO/branches/UKMO/tools_r4.0-HEAD_dev_DMP_TOOLS/DMP_TOOLS/src/make_dmp_file.F90

    r4745 r15745  
    4949 
    5050  ALLOCATE( resto(jpi, jpj) ) 
     51  ALLOCATE( dcst(jpi, jpj) ) 
    5152 
    5253  !Create output file 
     
    5758  !Calculate surface and bottom damping coefficients 
    5859  zsdmp = 1._wp / ( pn_surf * rday ) 
    59   zbdmp = 1._wp / ( pn_bot  * rday ) 
     60  IF (pn_bot > 0.) THEN 
     61     zbdmp = 1._wp / ( pn_bot  * rday ) 
     62  ELSE 
     63     zbdmp = 0. 
     64  ENDIF 
     65 
     66  ! Calculate distance from the coast 
     67  IF (ln_coast) CALL cofdis( dcst )  
    6068 
    6169  !Loop through levels and read in tmask for each level as starting point for 
     
    7482           DO jj = 1, jpj 
    7583              DO ji = 1, jpi 
    76                  resto(ji,jj) = tmask(ji, jj) * (zbdmp + (zsdmp-zbdmp) * EXP(-gdept(ji,jj)/pn_dep)) 
     84                 IF ( ln_exp ) THEN 
     85                    resto(ji,jj) = tmask(ji, jj) * (zbdmp + (zsdmp-zbdmp) * EXP(-gdept(ji,jj)/pn_dep)) 
     86                 ELSE 
     87                    resto(ji,jj) = tmask(ji, jj) * (zbdmp + (zsdmp-zbdmp) / & 
     88                       &           (1._wp + EXP(rn_k * (gdept(ji,jj) - pn_dep) / 100._wp))) 
     89                 ENDIF  
    7790              END DO 
    7891           END DO 
     
    94107           IF (ln_coast) THEN 
    95108              ! Reduce damping in vicinity of coastlines 
    96               CALL coast_dist_weight(resto) 
     109              CALL coast_dist_weight(resto, dcst) 
    97110           ENDIF 
    98111        ENDIF 
     
    109122        !Any user modifications can be added in the custom module 
    110123        IF ( ln_custom ) THEN 
    111               CALL custom_resto( resto ) 
     124              WHERE (resto(:,:) <= 1.e-07) resto(:,:) = 0._wp 
     125              !CALL custom_resto( resto ) 
    112126        ENDIF 
    113127     ENDIF 
  • NEMO/branches/UKMO/tools_r4.0-HEAD_dev_DMP_TOOLS/DMP_TOOLS/src/utils.F90

    r4739 r15745  
    1919  REAL(wp), DIMENSION(:,:),   ALLOCATABLE :: gphif, glamf 
    2020  REAL(wp), DIMENSION(:,:),   ALLOCATABLE :: tmask, umask, vmask, fmask 
     21  REAL(wp), DIMENSION(:,:),   ALLOCATABLE :: dcst 
    2122  REAL(wp), DIMENSION(:,:),   ALLOCATABLE :: gdept 
    2223  REAL(wp), DIMENSION(:,:),   ALLOCATABLE :: resto 
     
    3738  REAL(KIND=8) :: pn_bot = 1 
    3839  REAL(KIND=8) :: pn_dep = 1000          
     40  REAL(KIND=8) :: pn_cst = 1000 
     41  REAL(KIND=8) :: rn_k = 50 
    3942  INTEGER  :: nn_hdmp = 0                          ! damping option 
    4043  INTEGER  :: jperio = 0                          ! damping option 
     
    4649  LOGICAL :: ln_zero_top_layer = .false. 
    4750  LOGICAL :: ln_custom = .false. 
     51  LOGICAL :: ln_exp = .true. 
    4852 
    49   NAMELIST/nam_dmp_create/cp_cfg, cp_cfz, jp_cfg, lzoom, ln_full_field, & 
     53  NAMELIST/nam_dmp_create/cp_cfg, cp_cfz, jp_cfg, lzoom, ln_full_field,  & 
    5054                          ln_med_red_seas, ln_old_31_lev_code, ln_coast, & 
    51                           ln_zero_top_layer, ln_custom, & 
    52                           pn_surf, pn_bot, pn_dep, nn_hdmp, jperio 
     55                          ln_zero_top_layer, ln_custom, ln_exp,          & 
     56                          pn_surf, pn_bot, pn_dep, rn_k, pn_cst, nn_hdmp, jperio 
    5357 
    5458  CONTAINS  
Note: See TracChangeset for help on using the changeset viewer.