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 1601 for trunk/NEMO/OPA_SRC/TRA/tradmp.F90 – NEMO

Ignore:
Timestamp:
2009-08-11T12:09:19+02:00 (15 years ago)
Author:
ctlod
Message:

Doctor naming of OPA namelist variables , see ticket: #526

File:
1 edited

Legend:

Unmodified
Added
Removed
  • trunk/NEMO/OPA_SRC/TRA/tradmp.F90

    r1438 r1601  
    44   !! Ocean physics: internal restoring trend on active tracers (T and S) 
    55   !!====================================================================== 
    6    !! History :  5.0  !  91-03  (O. Marti, G. Madec)  Original code 
    7    !!                 !  92-06  (M. Imbard)  doctor norme 
    8    !!                 !  96-01  (G. Madec)  statement function for e3 
    9    !!                 !  97-05  (G. Madec)  macro-tasked on jk-slab 
    10    !!                 !  98-07  (M. Imbard, G. Madec) ORCA version 
    11    !!            7.0  !  01-02  (M. Imbard)  cofdis, Original code 
    12    !!            8.1  !  01-02  (G. Madec, E. Durand)  cleaning 
    13    !!            8.5  !  02-08  (G. Madec, E. Durand)  free form + modules 
     6   !! History :  OPA  ! 1991-03  (O. Marti, G. Madec)  Original code 
     7   !!                 ! 1992-06  (M. Imbard)  doctor norme 
     8   !!                 ! 1996-01  (G. Madec)  statement function for e3 
     9   !!                 ! 1997-05  (G. Madec)  macro-tasked on jk-slab 
     10   !!                 ! 1998-07  (M. Imbard, G. Madec) ORCA version 
     11   !!            7.0  ! 2001-02  (M. Imbard)  cofdis, Original code 
     12   !!            8.1  ! 2001-02  (G. Madec, E. Durand)  cleaning 
     13   !!  NEMO      1.0  ! 2002-08  (G. Madec, E. Durand)  free form + modules 
     14   !!            3.2  ! 2009-08  (G. Madec, C. Talandier)  DOCTOR norm for namelist parameter 
    1415   !!---------------------------------------------------------------------- 
    1516#if   defined key_tradmp   ||   defined key_esopa 
    1617   !!---------------------------------------------------------------------- 
    1718   !!   key_tradmp                                         internal damping 
    18    !!---------------------------------------------------------------------- 
    1919   !!---------------------------------------------------------------------- 
    2020   !!   tra_dmp      : update the tracer trend with the internal damping 
     
    2929   USE trdmod_oce      ! ocean variables trends 
    3030   USE zdf_oce         ! ocean vertical physics 
    31    USE in_out_manager  ! I/O manager 
    3231   USE phycst          ! Define parameters for the routines 
    3332   USE dtatem          ! temperature data 
    3433   USE dtasal          ! salinity data 
    3534   USE zdfmxl          ! mixed layer depth 
     35   USE in_out_manager  ! I/O manager 
    3636   USE lib_mpp         ! distribued memory computing 
    3737   USE prtctl          ! Print control 
     
    4040   PRIVATE 
    4141 
    42    PUBLIC tra_dmp      ! routine called by step.F90 
     42   PUBLIC   tra_dmp    ! routine called by step.F90 
    4343 
    4444#if ! defined key_agrif 
     
    4949   REAL(wp), PUBLIC, DIMENSION(jpi,jpj,jpk) ::   resto    !: restoring coeff. on T and S (s-1) 
    5050    
    51    !!* newtonian damping namelist (mandmp)  
    52    INTEGER  ::   ndmp   =   -1    ! = 0/-1/'latitude' for damping over T and S 
    53    INTEGER  ::   ndmpf  =    2    ! = 1 create a damping.coeff NetCDF file  
    54    INTEGER  ::   nmldmp =    0    ! = 0/1/2 flag for damping in the mixed layer 
    55    REAL(wp) ::   sdmp   =   50.   ! surface time scale for internal damping (days) 
    56    REAL(wp) ::   bdmp   =  360.   ! bottom time scale for internal damping (days) 
    57    REAL(wp) ::   hdmp   =  800.   ! depth of transition between sdmp and bdmp (meters) 
     51   !                             !!* Namelist namtra_dmp : T & S newtonian damping * 
     52   INTEGER  ::   nn_hdmp =   -1   ! = 0/-1/'latitude' for damping over T and S 
     53   INTEGER  ::   nn_zdmp =    0   ! = 0/1/2 flag for damping in the mixed layer 
     54   REAL(wp) ::   rn_surf =   50.  ! surface time scale for internal damping        [days] 
     55   REAL(wp) ::   rn_bot  =  360.  ! bottom time scale for internal damping         [days] 
     56   REAL(wp) ::   rn_dep  =  800.  ! depth of transition between rn_surf and rn_bot [meters] 
     57   INTEGER  ::   nn_file =    2   ! = 1 create a damping.coeff NetCDF file  
    5858 
    5959   !! * Substitutions 
     
    6161#  include "vectopt_loop_substitute.h90" 
    6262   !!---------------------------------------------------------------------- 
    63    !!   OPA 9.0 , LOCEAN-IPSL (2006)  
     63   !! NEMO/OPA 3.2 , LOCEAN-IPSL (2009)  
    6464   !! $Id$  
    6565   !! Software governed by the CeCILL licence (modipsl/doc/NEMO_CeCILL.txt) 
     
    8484      !!      below the well mixed layer (nlmdmp=2) 
    8585      !! 
    86       !! ** Action  : - update the tracer trends (ta,sa) with the newtonian  
    87       !!                damping trends. 
    88       !!              - save the trends in (ttrd,strd) ('key_trdtra') 
     86      !! ** Action  : - (ta,sa)   tracer trends updated with the damping trend 
    8987      !!---------------------------------------------------------------------- 
    9088      USE oce, ONLY :   ztrdt => ua   ! use ua as 3D workspace    
    9189      USE oce, ONLY :   ztrds => va   ! use va as 3D workspace    
    9290      !! 
    93       INTEGER, INTENT( in ) ::   kt   ! ocean time-step index 
    94       !! 
    95       INTEGER  ::   ji, jj, jk            ! dummy loop indices 
    96       REAL(wp) ::   ztest, zta, zsa       ! temporary scalars 
     91      INTEGER, INTENT(in) ::   kt   ! ocean time-step index 
     92      !! 
     93      INTEGER ::   ji, jj, jk   ! dummy loop indices 
    9794      !!---------------------------------------------------------------------- 
    9895 
     
    104101      ENDIF 
    105102 
    106       ! 1. Newtonian damping trends on tracer fields 
    107       ! -------------------------------------------- 
    108       !    compute the newtonian damping trends depending on nmldmp 
    109  
    110       SELECT CASE ( nmldmp ) 
     103      SELECT CASE ( nn_zdmp )  
    111104      ! 
    112       CASE( 0 )                ! newtonian damping throughout the water column 
     105      CASE( 0 )                   !==  newtonian damping throughout the water column  ==! 
    113106         DO jk = 1, jpkm1 
    114107            DO jj = 2, jpjm1 
    115108               DO ji = fs_2, fs_jpim1   ! vector opt. 
    116                   zta = resto(ji,jj,jk) * ( t_dta(ji,jj,jk) - tb(ji,jj,jk) ) 
    117                   zsa = resto(ji,jj,jk) * ( s_dta(ji,jj,jk) - sb(ji,jj,jk) ) 
    118                   ! add the trends to the general tracer trends 
    119                   ta(ji,jj,jk) = ta(ji,jj,jk) + zta 
    120                   sa(ji,jj,jk) = sa(ji,jj,jk) + zsa 
    121                   ! save the salinity trend (used in flx to close the salt budget) 
     109                  ta(ji,jj,jk) = ta(ji,jj,jk) + resto(ji,jj,jk) * ( t_dta(ji,jj,jk) - tb(ji,jj,jk) ) 
     110                  sa(ji,jj,jk) = sa(ji,jj,jk) + resto(ji,jj,jk) * ( s_dta(ji,jj,jk) - sb(ji,jj,jk) ) 
    122111               END DO 
    123112            END DO 
    124113         END DO 
    125114         ! 
    126       CASE ( 1 )                ! no damping in the turbocline (avt > 5 cm2/s) 
     115      CASE ( 1 )                  !==  no damping in the turbocline (avt > 5 cm2/s)  ==! 
    127116         DO jk = 1, jpkm1 
    128117            DO jj = 2, jpjm1 
    129118               DO ji = fs_2, fs_jpim1   ! vector opt. 
    130                   ztest = avt(ji,jj,jk) - 5.e-4 
    131                   IF( ztest < 0. ) THEN 
    132                      zta = resto(ji,jj,jk) * ( t_dta(ji,jj,jk) - tb(ji,jj,jk) ) 
    133                      zsa = resto(ji,jj,jk) * ( s_dta(ji,jj,jk) - sb(ji,jj,jk) ) 
    134                   ELSE 
    135                      zta = 0.e0 
    136                      zsa = 0.e0 
     119                  IF( avt(ji,jj,jk) <= 5.e-4 ) THEN 
     120                     ta(ji,jj,jk) = ta(ji,jj,jk) + resto(ji,jj,jk) * ( t_dta(ji,jj,jk) - tb(ji,jj,jk) ) 
     121                     sa(ji,jj,jk) = sa(ji,jj,jk) + resto(ji,jj,jk) * ( s_dta(ji,jj,jk) - sb(ji,jj,jk) ) 
    137122                  ENDIF 
    138                   ! add the trends to the general tracer trends 
    139                   ta(ji,jj,jk) = ta(ji,jj,jk) + zta 
    140                   sa(ji,jj,jk) = sa(ji,jj,jk) + zsa 
    141                   ! save the salinity trend (used in flx to close the salt budget) 
    142123               END DO 
    143124            END DO 
    144125         END DO 
    145126         ! 
    146       CASE ( 2 )                ! no damping in the mixed layer  
     127      CASE ( 2 )                  !==  no damping in the mixed layer   ==! 
    147128         DO jk = 1, jpkm1 
    148129            DO jj = 2, jpjm1 
    149130               DO ji = fs_2, fs_jpim1   ! vector opt. 
    150131                  IF( fsdept(ji,jj,jk) >= hmlp (ji,jj) ) THEN 
    151                      zta = resto(ji,jj,jk) * ( t_dta(ji,jj,jk) - tb(ji,jj,jk) ) 
    152                      zsa = resto(ji,jj,jk) * ( s_dta(ji,jj,jk) - sb(ji,jj,jk) ) 
    153                   ELSE 
    154                      zta = 0.e0 
    155                      zsa = 0.e0 
     132                     ta(ji,jj,jk) = ta(ji,jj,jk) + resto(ji,jj,jk) * ( t_dta(ji,jj,jk) - tb(ji,jj,jk) ) 
     133                     sa(ji,jj,jk) = sa(ji,jj,jk) + resto(ji,jj,jk) * ( s_dta(ji,jj,jk) - sb(ji,jj,jk) ) 
    156134                  ENDIF 
    157                   ! add the trends to the general tracer trends 
    158                   ta(ji,jj,jk) = ta(ji,jj,jk) + zta 
    159                   sa(ji,jj,jk) = sa(ji,jj,jk) + zsa 
    160                   ! save the salinity trend (used in flx to close the salt budget) 
    161135               END DO 
    162136            END DO 
     
    165139      END SELECT 
    166140 
    167       IF( l_trdtra )   THEN          ! save the damping tracer trends for diagnostic 
     141      IF( l_trdtra )   THEN       ! trend diagnostic 
    168142         ztrdt(:,:,:) = ta(:,:,:) - ztrdt(:,:,:) 
    169143         ztrds(:,:,:) = sa(:,:,:) - ztrds(:,:,:) 
    170          CALL trd_mod(ztrdt, ztrds, jptra_trd_dmp, 'TRA', kt) 
     144         CALL trd_mod( ztrdt, ztrds, jptra_trd_dmp, 'TRA', kt ) 
    171145      ENDIF 
    172       !                              ! Control print 
     146      !                           ! Control print 
    173147      IF(ln_ctl)   CALL prt_ctl( tab3d_1=ta, clinfo1=' dmp  - Ta: ', mask1=tmask,   & 
    174148         &                       tab3d_2=sa, clinfo2=       ' Sa: ', mask2=tmask, clinfo3='tra' ) 
     
    184158      !! 
    185159      !! ** Method  :   read the nammbf namelist and check the parameters 
    186       !!      called by tra_dmp at the first timestep (nit000) 
    187       !!---------------------------------------------------------------------- 
    188       NAMELIST/namtdp/ ndmp, ndmpf, nmldmp, sdmp, bdmp, hdmp 
    189       !!---------------------------------------------------------------------- 
    190  
    191       REWIND ( numnam )                  ! Read Namelist namtdp : temperature and salinity damping term 
    192       READ   ( numnam, namtdp ) 
    193       IF( lzoom )   nmldmp = 0           ! restoring to climatology at closed north or south boundaries 
     160      !!---------------------------------------------------------------------- 
     161      NAMELIST/namtra_dmp/ nn_hdmp, nn_zdmp, rn_surf, rn_bot, rn_dep, nn_file 
     162      !!---------------------------------------------------------------------- 
     163 
     164      REWIND ( numnam )                  ! Read Namelist namtra_dmp : temperature and salinity damping term 
     165      READ   ( numnam, namtra_dmp ) 
     166      IF( lzoom )   nn_zdmp = 0           ! restoring to climatology at closed north or south boundaries 
    194167 
    195168      IF(lwp) THEN                       ! Namelist print 
     
    197170         WRITE(numout,*) 'tra_dmp : T and S newtonian damping' 
    198171         WRITE(numout,*) '~~~~~~~' 
    199          WRITE(numout,*) '       Namelist namtdp : set damping parameter' 
    200          WRITE(numout,*) '          T and S damping option         ndmp   = ', ndmp 
    201          WRITE(numout,*) '          create a damping.coeff file    ndmpf  = ', ndmpf 
    202          WRITE(numout,*) '          mixed layer damping option     nmldmp = ', nmldmp, '(zoom: forced to 0)' 
    203          WRITE(numout,*) '          surface time scale (days)      sdmp   = ', sdmp 
    204          WRITE(numout,*) '          bottom time scale (days)       bdmp   = ', bdmp 
    205          WRITE(numout,*) '          depth of transition (meters)   hdmp   = ', hdmp 
     172         WRITE(numout,*) '   Namelist namtra_dmp : set damping parameter' 
     173         WRITE(numout,*) '      T and S damping option         nn_hdmp = ', nn_hdmp 
     174         WRITE(numout,*) '      mixed layer damping option     nn_zdmp = ', nn_zdmp, '(zoom: forced to 0)' 
     175         WRITE(numout,*) '      surface time scale (days)      rn_surf = ', rn_surf 
     176         WRITE(numout,*) '      bottom time scale (days)       rn_bot  = ', rn_bot 
     177         WRITE(numout,*) '      depth of transition (meters)   rn_dep  = ', rn_dep 
     178         WRITE(numout,*) '      create a damping.coeff file    nn_file = ', nn_file 
    206179      ENDIF 
    207180 
    208       SELECT CASE ( ndmp ) 
    209       CASE (  -1  )   ;   IF(lwp) WRITE(numout,*) '          tracer damping in the Med & Red seas only' 
    210       CASE ( 1:90 )   ;   IF(lwp) WRITE(numout,*) '          tracer damping poleward of', ndmp, ' degrees' 
     181      SELECT CASE ( nn_hdmp ) 
     182      CASE (  -1  )   ;   IF(lwp) WRITE(numout,*) '   tracer damping in the Med & Red seas only' 
     183      CASE ( 1:90 )   ;   IF(lwp) WRITE(numout,*) '   tracer damping poleward of', nn_hdmp, ' degrees' 
    211184      CASE DEFAULT 
    212          WRITE(ctmp1,*) '          bad flag value for ndmp = ', ndmp 
     185         WRITE(ctmp1,*) '          bad flag value for nn_hdmp = ', nn_hdmp 
    213186         CALL ctl_stop(ctmp1) 
    214187      END SELECT 
    215188 
    216       SELECT CASE ( nmldmp ) 
    217       CASE ( 0 )   ;   IF(lwp) WRITE(numout,*) '          tracer damping throughout the water column' 
    218       CASE ( 1 )   ;   IF(lwp) WRITE(numout,*) '          no tracer damping in the turbocline (avt > 5 cm2/s)' 
    219       CASE ( 2 )   ;   IF(lwp) WRITE(numout,*) '          no tracer damping in the mixed layer' 
     189      SELECT CASE ( nn_zdmp ) 
     190      CASE ( 0 )   ;   IF(lwp) WRITE(numout,*) '   tracer damping throughout the water column' 
     191      CASE ( 1 )   ;   IF(lwp) WRITE(numout,*) '   no tracer damping in the turbocline (avt > 5 cm2/s)' 
     192      CASE ( 2 )   ;   IF(lwp) WRITE(numout,*) '   no tracer damping in the mixed layer' 
    220193      CASE DEFAULT 
    221          WRITE(ctmp1,*) '          bad flag value for nmldmp = ', nmldmp 
     194         WRITE(ctmp1,*) 'bad flag value for nn_zdmp = ', nn_zdmp 
    222195         CALL ctl_stop(ctmp1) 
    223196      END SELECT 
     
    241214      !! 
    242215      !! ** Method  : - set along closed boundary due to zoom a damping over 
    243       !!      6 points with a max time scale of 5 days. 
     216      !!                6 points with a max time scale of 5 days. 
    244217      !!              - ORCA arctic/antarctic zoom: set the damping along 
    245       !!      south/north boundary over a latitude strip. 
     218      !!                south/north boundary over a latitude strip. 
    246219      !! 
    247220      !! ** Action  : - resto, the damping coeff. for T and S 
     
    270243      END DO 
    271244 
    272  
    273       IF( lzoom_arct .AND. lzoom_anta ) THEN 
    274          ! 
    275          ! ==================================================== 
    276          !  ORCA configuration : arctic zoom or antarctic zoom 
    277          ! ==================================================== 
    278  
     245      !                                           ! ==================================================== 
     246      IF( lzoom_arct .AND. lzoom_anta ) THEN      !  ORCA configuration : arctic zoom or antarctic zoom 
     247         !                                        ! ==================================================== 
    279248         IF(lwp) WRITE(numout,*) 
    280249         IF(lwp .AND. lzoom_arct ) WRITE(numout,*) '              dtacof_zoom : ORCA    Arctic zoom' 
    281250         IF(lwp .AND. lzoom_arct ) WRITE(numout,*) '              dtacof_zoom : ORCA Antarctic zoom' 
    282251         IF(lwp) WRITE(numout,*) 
    283  
    284          ! ... Initialization :  
    285          !     zlat0 : latitude strip where resto decreases 
    286          !     zlat1 : resto = 1 before zlat1 
    287          !     zlat2 : resto decreases from 1 to 0 between zlat1 and zlat2 
     252         ! 
     253         !                          ! Initialization :  
    288254         resto(:,:,:) = 0.e0 
    289          zlat0 = 10. 
    290          zlat1 = 30. 
    291          zlat2 = zlat1 + zlat0 
    292  
    293          ! ... Compute arrays resto ; value for internal damping : 5 days 
    294          DO jk = 2, jpkm1 
     255         zlat0 = 10.                     ! zlat0 : latitude strip where resto decreases 
     256         zlat1 = 30.                     ! zlat1 : resto = 1 before zlat1 
     257         zlat2 = zlat1 + zlat0           ! zlat2 : resto decreases from 1 to 0 between zlat1 and zlat2 
     258 
     259         DO jk = 2, jpkm1           ! Compute arrays resto ; value for internal damping : 5 days 
    295260            DO jj = 1, jpj 
    296261               DO ji = 1, jpi 
    297262                  zlat = ABS( gphit(ji,jj) ) 
    298                   IF ( zlat1 <= zlat .AND. zlat <= zlat2 ) THEN 
    299                      resto(ji,jj,jk) = 0.5 * ( 1./(5.*rday) ) *   & 
    300                         ( 1. - cos(rpi*(zlat2-zlat)/zlat0) )  
    301                   ELSE IF ( zlat < zlat1 ) THEN 
     263                  IF( zlat1 <= zlat .AND. zlat <= zlat2 ) THEN 
     264                     resto(ji,jj,jk) = 0.5 * ( 1./(5.*rday) ) * ( 1. - cos(rpi*(zlat2-zlat)/zlat0) )  
     265                  ELSEIF( zlat < zlat1 ) THEN 
    302266                     resto(ji,jj,jk) = 1./(5.*rday) 
    303267                  ENDIF 
     
    307271         ! 
    308272      ENDIF 
    309  
    310       ! ... Mask resto array 
     273      !                             ! Mask resto array 
    311274      resto(:,:,:) = resto(:,:,:) * tmask(:,:,:) 
    312275      ! 
     
    321284      !! 
    322285      !! ** Method  :   Arrays defining the damping are computed for each grid 
    323       !!      point for temperature and salinity (resto) 
    324       !!      Damping depends on distance to coast, depth and latitude 
     286      !!                point for temperature and salinity (resto) 
     287      !!                Damping depends on distance to coast, depth and latitude 
    325288      !! 
    326289      !! ** Action  : - resto, the damping coeff. for T and S 
     
    330293      !! 
    331294      INTEGER ::   ji, jj, jk                   ! dummy loop indices 
    332       INTEGER ::   ii0, ii1, ij0, ij1           !    "          " 
     295      INTEGER ::   ii0, ii1, ij0, ij1           !    -          - 
    333296      INTEGER ::   inum0                        ! logical unit for file restoring damping term 
    334297      INTEGER ::   icot                         ! logical unit for file distance to the coast 
    335298      REAL(wp) ::   zinfl, zlon                 ! temporary scalars 
    336       REAL(wp) ::   zlat, zlat0, zlat1, zlat2   !    "         " 
    337       REAL(wp) ::   zsdmp, zbdmp                !    "         " 
     299      REAL(wp) ::   zlat, zlat0, zlat1, zlat2   !    -         - 
     300      REAL(wp) ::   zsdmp, zbdmp                !    -         - 
    338301      REAL(wp), DIMENSION(jpk)         ::   zhfac 
    339302      REAL(wp), DIMENSION(jpi,jpj)     ::   zmrs 
     
    350313 
    351314      ! ... Initialization :  
    352       !   zdct()      : distant to the coastline 
    353       !   resto()     : array of restoring coeff. on T and S 
    354  
    355315      resto(:,:,:) = 0.e0 
    356316 
    357       IF ( ndmp > 0 ) THEN 
    358  
    359          !    ------------------------------------ 
    360          !     Damping poleward of 'ndmp' degrees 
    361          !    ------------------------------------ 
    362  
     317      !                           !-----------------------------------------! 
     318      IF( nn_hdmp > 0 ) THEN      !  Damping poleward of 'nn_hdmp' degrees  ! 
     319         !                        !-----------------------------------------! 
    363320         IF(lwp) WRITE(numout,*) 
    364          IF(lwp) WRITE(numout,*) '              Damping poleward of ', ndmp,' deg.' 
    365          IF(lwp) WRITE(numout,*) 
    366  
    367          ! ... Distance to coast (zdct) 
    368  
    369          IF(lwp) WRITE(numout,*) 
    370          IF(lwp) WRITE(numout,*) ' dtacof : distance to coast file' 
     321         IF(lwp) WRITE(numout,*) '              Damping poleward of ', nn_hdmp,' deg.' 
     322         ! 
    371323         CALL iom_open ( 'dist.coast.nc', icot, ldstop = .FALSE. ) 
    372          IF( icot > 0 ) THEN 
    373             CALL iom_get ( icot, jpdom_data, 'Tcoast', zdct ) 
    374             CALL iom_close (icot) 
    375          ELSE 
    376             !   ... Compute and save the distance-to-coast array (output in zdct) 
     324         ! 
     325         IF( icot > 0 ) THEN          ! distance-to-coast read in file 
     326            CALL iom_get  ( icot, jpdom_data, 'Tcoast', zdct ) 
     327            CALL iom_close( icot ) 
     328         ELSE                         ! distance-to-coast computed and saved in file (output in zdct) 
    377329            CALL cofdis( zdct ) 
    378330         ENDIF 
    379331 
    380          ! ... Compute arrays resto  
    381          !      zinfl : distance of influence for damping term 
    382          !      zlat0 : latitude strip where resto decreases 
    383          !      zlat1 : resto = 0 between -zlat1 and zlat1 
    384          !      zlat2 : resto increases from 0 to 1 between |zlat1| and |zlat2| 
    385          !          and resto = 1 between |zlat2| and 90 deg. 
    386          zinfl = 1000.e3 
    387          zlat0 = 10 
    388          zlat1 = ndmp 
    389          zlat2 = zlat1 + zlat0 
     332         !                            ! Compute arrays resto  
     333         zinfl = 1000.e3                   ! distance of influence for damping term 
     334         zlat0 = 10.                       ! latitude strip where resto decreases 
     335         zlat1 = REAL( nn_hdmp )           ! resto = 0 between -zlat1 and zlat1 
     336         zlat2 = zlat1 + zlat0             ! resto increases from 0 to 1 between |zlat1| and |zlat2| 
    390337 
    391338         DO jj = 1, jpj 
     
    400347         END DO 
    401348 
    402          !   ... North Indian ocean (20N/30N x 45E/100E) : resto=0 
    403          IF ( ndmp == 20 ) THEN 
     349         IF ( nn_hdmp == 20 ) THEN       ! North Indian ocean (20N/30N x 45E/100E) : resto=0 
    404350            DO jj = 1, jpj 
    405351               DO ji = 1, jpi 
    406352                  zlat = gphit(ji,jj) 
    407353                  zlon = MOD( glamt(ji,jj), 360. ) 
    408                   IF ( zlat1 < zlat .AND. zlat < zlat2 .AND.   & 
    409                      45.  < zlon .AND. zlon < 100. ) THEN 
    410                      resto(ji,jj,1) = 0. 
     354                  IF ( zlat1 < zlat .AND. zlat < zlat2 .AND. 45. < zlon .AND. zlon < 100. ) THEN 
     355                     resto(ji,jj,1) = 0.e0 
    411356                  ENDIF 
    412357               END DO 
     
    414359         ENDIF 
    415360 
    416          zsdmp = 1./(sdmp * rday) 
    417          zbdmp = 1./(bdmp * rday) 
     361         zsdmp = 1./(rn_surf * rday) 
     362         zbdmp = 1./(rn_bot * rday) 
    418363         DO jk = 2, jpkm1 
    419364            DO jj = 1, jpj 
     
    423368                  resto(ji,jj,jk) = resto(ji,jj,1) * 0.5 * ( 1. - COS( rpi*zdct(ji,jj,jk)/zinfl) ) 
    424369                  !   ... Vertical variation from zsdmp (sea surface) to zbdmp (bottom) 
    425                   resto(ji,jj,jk) = resto(ji,jj,jk)      * ( zbdmp + (zsdmp-zbdmp)*EXP(-fsdept(ji,jj,jk)/hdmp) ) 
     370                  resto(ji,jj,jk) = resto(ji,jj,jk)      * ( zbdmp + (zsdmp-zbdmp)*EXP(-fsdept(ji,jj,jk)/rn_dep) ) 
    426371               END DO 
    427372            END DO 
     
    431376 
    432377 
    433       IF( cp_cfg == "orca" .AND. ( ndmp > 0 .OR. ndmp == -1 ) ) THEN 
     378      IF( cp_cfg == "orca" .AND. ( nn_hdmp > 0 .OR. nn_hdmp == -1 ) ) THEN 
    434379 
    435380         !                                         ! ========================= 
     
    520465               zmrs( ji , mj0(ij0):mj1(ij1) ) = 0.1 * ABS( FLOAT(ji - mi1(ii1)) ) 
    521466            END DO  
    522             zsdmp = 1./(sdmp * rday) 
    523             zbdmp = 1./(bdmp * rday) 
     467            zsdmp = 1./(rn_surf * rday) 
     468            zbdmp = 1./(rn_bot * rday) 
    524469            DO jk = 1, jpk 
    525                zhfac (jk) = ( zbdmp + (zsdmp-zbdmp) * EXP(-fsdept(1,1,jk)/hdmp) ) 
     470               zhfac (jk) = ( zbdmp + (zsdmp-zbdmp) * EXP(-fsdept(1,1,jk)/rn_dep) ) 
    526471            END DO 
    527472            !                                       ! ======================== 
     
    540485         resto(:,:, 1 ) = 0.e0 
    541486         resto(:,:,jpk) = 0.e0 
    542  
    543       ELSE 
    544          !    ------------ 
    545          !     No damping 
    546          !    ------------ 
    547          CALL ctl_stop( 'Choose a correct value of ndmp or DO NOT defined key_tradmp' ) 
     487         !                         !--------------------! 
     488      ELSE                         !     No damping     ! 
     489         !                         !--------------------! 
     490         CALL ctl_stop( 'Choose a correct value of nn_hdmp or DO NOT defined key_tradmp' ) 
    548491      ENDIF 
    549492 
    550       !    ---------------------------- 
    551       !     Create Print damping array 
    552       !    ---------------------------- 
    553  
    554       ! ndmpf   : = 1 create a damping.coeff NetCDF file 
    555  
    556       IF( ndmpf == 1 ) THEN 
     493      !                            !--------------------------------! 
     494      IF( nn_file == 1 ) THEN      !  save damping coef. in a file  ! 
     495         !                         !--------------------------------! 
    557496         IF(lwp) WRITE(numout,*) '              create damping.coeff.nc file' 
    558497         CALL iom_open  ( 'damping.coeff', inum0, ldwrt = .TRUE., kiolib = jprstlib ) 
Note: See TracChangeset for help on using the changeset viewer.