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 4148 for branches/2013/dev_LOCEAN_2013/NEMOGCM/NEMO/TOP_SRC/TRP – NEMO

Ignore:
Timestamp:
2013-11-04T13:54:28+01:00 (11 years ago)
Author:
cetlod
Message:

merge in trunk changes between r3853 and r3940 and commit the changes, see ticket #1169

Location:
branches/2013/dev_LOCEAN_2013/NEMOGCM/NEMO/TOP_SRC/TRP
Files:
3 edited

Legend:

Unmodified
Added
Removed
  • branches/2013/dev_LOCEAN_2013/NEMOGCM/NEMO/TOP_SRC/TRP/trcdmp.F90

    r4147 r4148  
    1111   !!            3.3  !  2010-06  (C. Ethe, G. Madec) merge TRA-TRC  
    1212   !!---------------------------------------------------------------------- 
    13 #if  defined key_top && defined key_trcdmp  
    14    !!---------------------------------------------------------------------- 
    15    !!   key_trcdmp                                         internal damping 
     13#if  defined key_top  
    1614   !!---------------------------------------------------------------------- 
    1715   !!   trc_dmp      : update the tracer trend with the internal damping 
     
    2523   USE prtctl_trc      ! Print control for debbuging 
    2624   USE trdtra 
     25   USE trdmod_oce 
    2726 
    2827   IMPLICIT NONE 
     
    3029 
    3130   PUBLIC trc_dmp            ! routine called by step.F90 
     31   PUBLIC trc_dmp_clo        ! routine called by step.F90 
    3232   PUBLIC trc_dmp_alloc      ! routine called by nemogcm.F90 
    3333 
    34    LOGICAL , PUBLIC, PARAMETER ::   lk_trcdmp = .TRUE.   !: internal damping flag 
    35  
    36    !                          !!* Namelist namtrc_dmp : passive tracer newtonian damping * 
    37    INTEGER  ::   nn_hdmp_tr    ! = 0/-1/'latitude' for damping over passive tracer 
    38    INTEGER  ::   nn_zdmp_tr    ! = 0/1/2 flag for damping in the mixed layer 
    39    REAL(wp) ::   rn_surf_tr    ! surface time scale for internal damping        [days] 
    40    REAL(wp) ::   rn_bot_tr     ! bottom time scale for internal damping         [days] 
    41    REAL(wp) ::   rn_dep_tr     ! depth of transition between rn_surf and rn_bot [meters] 
    42    INTEGER  ::   nn_file_tr    ! = 1 create a damping.coeff NetCDF file  
    43  
    4434   REAL(wp), ALLOCATABLE, SAVE, DIMENSION(:,:,:) ::   restotr   ! restoring coeff. on tracers (s-1) 
     35 
     36   INTEGER, PARAMETER           ::   npncts   = 5        ! number of closed sea 
     37   INTEGER, DIMENSION(npncts)   ::   nctsi1, nctsj1      ! south-west closed sea limits (i,j) 
     38   INTEGER, DIMENSION(npncts)   ::   nctsi2, nctsj2      ! north-east closed sea limits (i,j) 
    4539 
    4640   !! * Substitutions 
     
    8680      INTEGER, INTENT( in ) ::   kt      ! ocean time-step index 
    8781      !! 
    88       INTEGER  ::   ji, jj, jk, jn       ! dummy loop indices 
     82      INTEGER  ::   ji, jj, jk, jn, jl       ! dummy loop indices 
    8983      REAL(wp) ::   ztra                 ! temporary scalars 
    9084      CHARACTER (len=22) :: charout 
    9185      REAL(wp), POINTER, DIMENSION(:,:,:) ::   ztrtrd 
     86      REAL(wp), POINTER, DIMENSION(:,:,:,:) ::  ztrcdta   ! 4D  workspace 
    9287      !!---------------------------------------------------------------------- 
    9388      ! 
     
    9994 
    10095      IF( l_trdtrc )   CALL wrk_alloc( jpi, jpj, jpk, ztrtrd )   ! temporary save of trends 
    101  
    102       ! 1. Newtonian damping trends on tracer fields 
    103       ! -------------------------------------------- 
    104       ! Initialize the input fields for newtonian damping 
    105       CALL trc_dta( kt ) 
    106       !                                                          ! =========== 
    107       DO jn = 1, jptra                                           ! tracer loop 
    108          !                                                       ! =========== 
    109          IF( l_trdtrc ) ztrtrd(:,:,:) = tra(:,:,:,jn)    ! save trends  
    110  
    111          IF( lutini(jn) ) THEN 
     96      ! 
     97      IF( nb_trcdta > 0 ) THEN  ! Initialisation of tracer from a file that may also be used for damping 
     98         ! 
     99         CALL wrk_alloc( jpi, jpj, jpk, nb_trcdta, ztrcdta )    ! Memory allocation 
     100         CALL trc_dta( kt, ztrcdta )   ! read tracer data at nit000 
     101         !                                                          ! =========== 
     102         DO jn = 1, jptra                                           ! tracer loop 
     103            !                                                       ! =========== 
     104            IF( l_trdtrc ) ztrtrd(:,:,:) = tra(:,:,:,jn)    ! save trends  
    112105            ! 
    113             SELECT CASE ( nn_zdmp_trc ) 
    114             ! 
    115             CASE( 0 )                !==  newtonian damping throughout the water column  ==! 
    116                DO jk = 1, jpkm1 
    117                   DO jj = 2, jpjm1 
    118                      DO ji = fs_2, fs_jpim1   ! vector opt. 
    119                         ztra = restotr(ji,jj,jk) * ( trdta(ji,jj,jk,jn) - trb(ji,jj,jk,jn) ) 
    120                         tra(ji,jj,jk,jn) = tra(ji,jj,jk,jn) + ztra 
     106            IF( ln_trc_ini(jn) ) THEN      ! update passive tracers arrays with input data read from file 
     107                
     108               jl = n_trc_index(jn)  
     109 
     110               SELECT CASE ( nn_zdmp_tr ) 
     111               ! 
     112               CASE( 0 )                !==  newtonian damping throughout the water column  ==! 
     113                  DO jk = 1, jpkm1 
     114                     DO jj = 2, jpjm1 
     115                        DO ji = fs_2, fs_jpim1   ! vector opt. 
     116                           ztra = restotr(ji,jj,jk) * ( ztrcdta(ji,jj,jk,jl) - trb(ji,jj,jk,jn) ) 
     117                           tra(ji,jj,jk,jn) = tra(ji,jj,jk,jn) + ztra 
     118                        END DO 
    121119                     END DO 
    122120                  END DO 
    123                END DO 
    124             ! 
    125             CASE ( 1 )                !==  no damping in the turbocline (avt > 5 cm2/s)  ==! 
    126                DO jk = 1, jpkm1 
    127                   DO jj = 2, jpjm1 
    128                      DO ji = fs_2, fs_jpim1   ! vector opt. 
    129                         IF( avt(ji,jj,jk) <= 5.e-4 )  THEN  
    130                            ztra = restotr(ji,jj,jk) * ( trdta(ji,jj,jk,jn) - trb(ji,jj,jk,jn) ) 
    131                            tra(ji,jj,jk,jn) = tra(ji,jj,jk,jn) + ztra 
    132                         ENDIF 
     121               ! 
     122               CASE ( 1 )                !==  no damping in the turbocline (avt > 5 cm2/s)  ==! 
     123                  DO jk = 1, jpkm1 
     124                     DO jj = 2, jpjm1 
     125                        DO ji = fs_2, fs_jpim1   ! vector opt. 
     126                           IF( avt(ji,jj,jk) <= 5.e-4 )  THEN  
     127                              ztra = restotr(ji,jj,jk) * ( ztrcdta(ji,jj,jk,jl) - trb(ji,jj,jk,jn) ) 
     128                              tra(ji,jj,jk,jn) = tra(ji,jj,jk,jn) + ztra 
     129                           ENDIF 
     130                        END DO 
    133131                     END DO 
    134132                  END DO 
    135                END DO 
    136             ! 
    137             CASE ( 2 )               !==  no damping in the mixed layer   ==!  
    138                DO jk = 1, jpkm1 
    139                   DO jj = 2, jpjm1 
    140                      DO ji = fs_2, fs_jpim1   ! vector opt. 
    141                         IF( fsdept(ji,jj,jk) >= hmlp (ji,jj) ) THEN 
    142                            ztra = restotr(ji,jj,jk,jn) * ( trdta(ji,jj,jk,jn) - trb(ji,jj,jk,jn) ) 
    143                            tra(ji,jj,jk,jn) = tra(ji,jj,jk,jn) + ztra 
    144                         END IF 
     133               ! 
     134               CASE ( 2 )               !==  no damping in the mixed layer   ==!  
     135                  DO jk = 1, jpkm1 
     136                     DO jj = 2, jpjm1 
     137                        DO ji = fs_2, fs_jpim1   ! vector opt. 
     138                           IF( fsdept(ji,jj,jk) >= hmlp (ji,jj) ) THEN 
     139                              ztra = restotr(ji,jj,jk) * ( ztrcdta(ji,jj,jk,jl) - trb(ji,jj,jk,jn) ) 
     140                              tra(ji,jj,jk,jn) = tra(ji,jj,jk,jn) + ztra 
     141                           END IF 
     142                        END DO 
    145143                     END DO 
    146144                  END DO 
    147                END DO 
    148             !   
    149             END SELECT 
    150             !  
    151          ENDIF 
    152          ! 
    153          IF( l_trdtrc ) THEN 
    154             ztrtrd(:,:,:) = tra(:,:,:,jn) -  ztrtrd(:,:,:) 
    155             CALL trd_tra( kt, 'TRC', jn, jptra_trd_dmp, ztrtrd ) 
    156          END IF 
    157          !                                                       ! =========== 
    158       END DO                                                     ! tracer loop 
    159       !                                                          ! =========== 
     145               !   
     146               END SELECT 
     147               !  
     148            ENDIF 
     149            ! 
     150            IF( l_trdtrc ) THEN 
     151               ztrtrd(:,:,:) = tra(:,:,:,jn) -  ztrtrd(:,:,:) 
     152               CALL trd_tra( kt, 'TRC', jn, jptra_trd_dmp, ztrtrd ) 
     153            END IF 
     154            !                                                       ! =========== 
     155         END DO                                                     ! tracer loop 
     156         !                                                          ! =========== 
     157         CALL wrk_dealloc( jpi, jpj, jpk, nb_trcdta, ztrcdta ) 
     158      ENDIF 
     159      ! 
    160160      IF( l_trdtrc )  CALL wrk_dealloc( jpi, jpj, jpk, ztrtrd ) 
    161161      !                                          ! print mean trends (used for debugging) 
     
    168168      ! 
    169169   END SUBROUTINE trc_dmp 
     170 
     171   SUBROUTINE trc_dmp_clo( kt ) 
     172      !!--------------------------------------------------------------------- 
     173      !!                  ***  ROUTINE trc_dmp_clo  *** 
     174      !! 
     175      !! ** Purpose :   Closed sea domain initialization 
     176      !! 
     177      !! ** Method  :   if a closed sea is located only in a model grid point 
     178      !!                we restore to initial data 
     179      !! 
     180      !! ** Action  :   nctsi1(), nctsj1() : south-west closed sea limits (i,j) 
     181      !!                nctsi2(), nctsj2() : north-east Closed sea limits (i,j) 
     182      !!---------------------------------------------------------------------- 
     183      INTEGER, INTENT( in ) ::   kt      ! ocean time-step index 
     184      ! 
     185      INTEGER :: ji, jj, jk, jn, jl, jc                     ! dummy loop indicesa 
     186      REAL(wp), POINTER, DIMENSION(:,:,:,:) ::  ztrcdta     ! 4D  workspace 
     187 
     188      !!---------------------------------------------------------------------- 
     189 
     190      IF( kt == nit000 ) THEN 
     191         ! initial values 
     192         nctsi1(:) = 1  ;  nctsi2(:) = 1 
     193         nctsj1(:) = 1  ;  nctsj2(:) = 1 
     194 
     195         ! set the closed seas (in data domain indices) 
     196         ! ------------------- 
     197 
     198         IF( cp_cfg == "orca" ) THEN 
     199            ! 
     200            SELECT CASE ( jp_cfg ) 
     201            !                                           ! ======================= 
     202            CASE ( 2 )                                  !  ORCA_R2 configuration 
     203               !                                        ! ======================= 
     204               !                                            ! Caspian Sea 
     205               nctsi1(1)   =  11  ;  nctsj1(1)   = 103 
     206               nctsi2(1)   =  17  ;  nctsj2(1)   = 112 
     207               !                                            ! Great North American Lakes 
     208               nctsi1(2)   =  97  ;  nctsj1(2)   = 107 
     209               nctsi2(2)   = 103  ;  nctsj2(2)   = 111 
     210               !                                            ! Black Sea 1 : west part of the Black Sea 
     211               nctsi1(3)   = 174  ;  nctsj1(3)   = 107 
     212               nctsi2(3)   = 181  ;  nctsj2(3)   = 112 
     213              !                                            ! Black Sea 2 : est part of the Black Sea 
     214               nctsi1(4)   =   2  ;  nctsj1(4)   = 107 
     215               nctsi2(4)   =   6  ;  nctsj2(4)   = 112 
     216               !                                            ! Baltic Sea 
     217               nctsi1(5)   =  145 ;  nctsj1(5)   = 116 
     218               nctsi2(5)   =  150 ;  nctsj2(5)   = 126 
     219               !                                        ! ======================= 
     220            CASE ( 4 )                                  !  ORCA_R4 configuration 
     221               !                                        ! ======================= 
     222               !                                            ! Caspian Sea 
     223               nctsi1(1)   =  4  ;  nctsj1(1)   = 53 
     224               nctsi2(1)   =  4  ;  nctsj2(1)   = 56 
     225               !                                            ! Great North American Lakes 
     226               nctsi1(2)   = 49  ;  nctsj1(2)   = 55 
     227               nctsi2(2)   = 51  ;  nctsj2(2)   = 56 
     228               !                                            ! Black Sea 
     229               nctsi1(3)   = 88  ;  nctsj1(3)   = 55 
     230               nctsi2(3)   = 91  ;  nctsj2(3)   = 56 
     231               !                                            ! Baltic Sea 
     232               nctsi1(4)   = 75  ;  nctsj1(4)   = 59 
     233               nctsi2(4)   = 76  ;  nctsj2(4)   = 61 
     234               !                                        ! ======================= 
     235            CASE ( 025 )                                ! ORCA_R025 configuration 
     236               !                                        ! ======================= 
     237                                                     ! Caspian + Aral sea 
     238               nctsi1(1)   = 1330 ; nctsj1(1)   = 645 
     239               nctsi2(1)   = 1400 ; nctsj2(1)   = 795 
     240               !                                        ! Azov Sea 
     241               nctsi1(2)   = 1284 ; nctsj1(2)   = 722 
     242               nctsi2(2)   = 1304 ; nctsj2(2)   = 747 
     243               ! 
     244            END SELECT 
     245            ! 
     246         ENDIF 
     247         ! 
     248 
     249         ! convert the position in local domain indices 
     250         ! -------------------------------------------- 
     251         DO jc = 1, npncts 
     252            nctsi1(jc)   = mi0( nctsi1(jc) ) 
     253            nctsj1(jc)   = mj0( nctsj1(jc) ) 
     254 
     255            nctsi2(jc)   = mi1( nctsi2(jc) ) 
     256            nctsj2(jc)   = mj1( nctsj2(jc) ) 
     257         END DO 
     258         ! 
     259      ENDIF 
     260 
     261      ! Restore close seas values to initial data 
     262      IF( ln_trcdta .AND. nb_trcdta > 0 )  THEN   ! Initialisation of tracer from a file that may also be used for damping 
     263         ! 
     264         IF(lwp)  WRITE(numout,*) 
     265         IF(lwp)  WRITE(numout,*) ' trc_dmp_clo : Restoring of nutrients on close seas at time-step kt = ', kt 
     266         IF(lwp)  WRITE(numout,*) 
     267         ! 
     268         CALL wrk_alloc( jpi, jpj, jpk, nb_trcdta, ztrcdta )   ! Memory allocation 
     269         ! 
     270         CALL trc_dta( kt , ztrcdta )   ! read tracer data at nittrc000 
     271         ! 
     272         DO jn = 1, jptra 
     273            IF( ln_trc_ini(jn) ) THEN      ! update passive tracers arrays with input data read from file 
     274                jl = n_trc_index(jn) 
     275                DO jc = 1, npncts 
     276                   DO jk = 1, jpkm1 
     277                      DO jj = nctsj1(jc), nctsj2(jc) 
     278                         DO ji = nctsi1(jc), nctsi2(jc) 
     279                            trn(ji,jj,jk,jn) = ztrcdta(ji,jj,jk,jl) * tmask(ji,jj,jk) 
     280                            trb(ji,jj,jk,jn) = trn(ji,jj,jk,jn) 
     281                         ENDDO 
     282                      ENDDO 
     283                   ENDDO 
     284                ENDDO 
     285             ENDIF 
     286          ENDDO 
     287          CALL wrk_dealloc( jpi, jpj, jpk, nb_trcdta, ztrcdta ) 
     288      ENDIF 
     289      ! 
     290   END SUBROUTINE trc_dmp_clo 
    170291 
    171292 
     
    199320      END SELECT 
    200321 
    201       IF( .NOT. lk_dtatrc )   & 
    202          &   CALL ctl_stop( 'no passive tracer data define key_dtatrc' ) 
    203  
    204       IF( .NOT. lk_tradmp )   & 
     322      IF( .NOT. ln_tradmp )   & 
    205323         &   CALL ctl_stop( 'passive trace damping need key_tradmp to compute damping coef.' ) 
    206324      ! 
     
    214332      ! 
    215333   END SUBROUTINE trc_dmp_init 
     334 
    216335#else 
    217336   !!---------------------------------------------------------------------- 
    218    !!   Default key                                     NO internal damping 
    219    !!---------------------------------------------------------------------- 
    220    LOGICAL , PUBLIC, PARAMETER ::   lk_trcdmp = .FALSE.    !: internal damping flag 
     337   !!  Dummy module :                                     No passive tracer 
     338   !!---------------------------------------------------------------------- 
    221339CONTAINS 
    222340   SUBROUTINE trc_dmp( kt )        ! Empty routine 
     
    225343   END SUBROUTINE trc_dmp 
    226344#endif 
     345 
     346 
    227347   !!====================================================================== 
    228348END MODULE trcdmp 
  • branches/2013/dev_LOCEAN_2013/NEMOGCM/NEMO/TOP_SRC/TRP/trcnam_trp.F90

    r4147 r4148  
    1313   !!   trc_nam_trp  : read the passive tracer namelist for transport 
    1414   !!---------------------------------------------------------------------- 
    15    USE trc                 ! ocean passive tracers variables 
     15   USE oce_trc              ! shared ocean passive tracers variables 
     16   USE trc                 ! passive tracers variables 
    1617   USE in_out_manager      ! ocean dynamics and active tracers variables 
    1718   USE lib_mpp           ! distributed memory computing library 
     
    4950   INTEGER , PUBLIC ::   nn_trczdf_exp       !: number of sub-time step (explicit time stepping) 
    5051 
    51  
    52 #if defined key_trcdmp 
    5352   !                                                 !!: ** newtonian damping namelist (nam_trcdmp) ** 
    54    INTEGER , PUBLIC ::   nn_hdmp_tr      =   -1       ! = 0/-1/'latitude' for damping over passive tracer 
    55    INTEGER , PUBLIC ::   nn_zdmp_tr      =    0       ! = 0/1/2 flag for damping in the mixed layer 
    56    REAL(wp), PUBLIC ::   rn_surf_tr      =   50.      ! surface time scale for internal damping        [days] 
    57    REAL(wp), PUBLIC ::   rn_bot_tr       =  360.      ! bottom time scale for internal damping         [days] 
    58    REAL(wp), PUBLIC ::   rn_dep_tr       =  800.      ! depth of transition between rn_surf and rn_bot [meters] 
    59    INTEGER , PUBLIC ::   nn_file_tr      =    2       ! = 1 create a damping.coeff NetCDF file  
    60 #endif 
     53   !                          !!* Namelist namtrc_dmp : passive tracer newtonian damping * 
     54   INTEGER , PUBLIC ::   nn_hdmp_tr    ! = 0/-1/'latitude' for damping over passive tracer 
     55   INTEGER , PUBLIC ::   nn_zdmp_tr    ! = 0/1/2 flag for damping in the mixed layer 
     56   REAL(wp), PUBLIC ::   rn_surf_tr    ! surface time scale for internal damping        [days] 
     57   REAL(wp), PUBLIC ::   rn_bot_tr     ! bottom time scale for internal damping         [days] 
     58   REAL(wp), PUBLIC ::   rn_dep_tr     ! depth of transition between rn_surf and rn_bot [meters] 
     59   INTEGER , PUBLIC ::   nn_file_tr    ! = 1 create a damping.coeff NetCDF file 
    6160 
    6261   !!---------------------------------------------------------------------- 
     
    8483      NAMELIST/namtrc_zdf/ ln_trczdf_exp  , nn_trczdf_exp 
    8584      NAMELIST/namtrc_rad/ ln_trcrad 
    86 #if defined key_trcdmp 
    87       NAMELIST/namtrc_dmp/ ln_trcdmp, nn_hdmp_tr, nn_zdmp_tr, rn_surf_tr, & 
     85      NAMELIST/namtrc_dmp/ nn_hdmp_tr, nn_zdmp_tr, rn_surf_tr, & 
    8886        &                  rn_bot_tr , rn_dep_tr , nn_file_tr 
    89 #endif 
    9087      !!---------------------------------------------------------------------- 
    9188 
     
    174171 
    175172 
    176 # if defined key_trcdmp 
    177173      REWIND( numnat_ref )              ! Namelist namtrc_dmp in reference namelist : Passive tracers newtonian damping 
    178174      READ  ( numnat_ref, namtrc_dmp, IOSTAT = ios, ERR = 909) 
     
    184180      WRITE ( numont, namtrc_dmp ) 
    185181 
    186       IF( lzoom )   nn_zdmp_trc = 0           ! restoring to climatology at closed north or south boundaries 
     182      IF( lzoom )   nn_zdmp_tr = 0           ! restoring to climatology at closed north or south boundaries 
    187183 
    188184      IF(lwp) THEN                       ! Namelist print 
     
    191187         WRITE(numout,*) '~~~~~~~' 
    192188         WRITE(numout,*) '   Namelist namtrc_dmp : set damping parameter' 
    193          WRITE(numout,*) '      add a damping term or not      ln_trcdmp = ', ln_trcdmp 
    194189         WRITE(numout,*) '      tracer damping option          nn_hdmp_tr = ', nn_hdmp_tr 
    195190         WRITE(numout,*) '      mixed layer damping option     nn_zdmp_tr = ', nn_zdmp_tr, '(zoom: forced to 0)' 
     
    199194         WRITE(numout,*) '      create a damping.coeff file    nn_file_tr = ', nn_file_tr 
    200195      ENDIF 
    201 #endif 
    202196      ! 
    203197   END SUBROUTINE trc_nam_trp 
  • branches/2013/dev_LOCEAN_2013/NEMOGCM/NEMO/TOP_SRC/TRP/trctrp.F90

    r3680 r4148  
    6666                                CALL trc_sbc( kstp )            ! surface boundary condition 
    6767         IF( lk_trabbl )        CALL trc_bbl( kstp )            ! advective (and/or diffusive) bottom boundary layer scheme 
    68          IF( lk_trcdmp )        CALL trc_dmp( kstp )            ! internal damping trends 
     68         IF( ln_trcdmp )        CALL trc_dmp( kstp )            ! internal damping trends 
     69         IF( ln_trcdmp_clo )    CALL trc_dmp_clo( kstp )        ! internal damping trends on closed seas only 
    6970                                CALL trc_adv( kstp )            ! horizontal & vertical advection  
    7071                                CALL trc_ldf( kstp )            ! lateral mixing 
Note: See TracChangeset for help on using the changeset viewer.