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.
trcdmp.F90 in branches/dev_r2586_dynamic_mem/NEMOGCM/NEMO/TOP_SRC/TRP – NEMO

source: branches/dev_r2586_dynamic_mem/NEMOGCM/NEMO/TOP_SRC/TRP/trcdmp.F90 @ 2633

Last change on this file since 2633 was 2606, checked in by trackstand2, 13 years ago

Module arrays made allocatable

  • Property svn:keywords set to Id
File size: 10.5 KB
RevLine 
[941]1MODULE trcdmp
2   !!======================================================================
3   !!                       ***  MODULE  trcdmp  ***
4   !! Ocean physics: internal restoring trend on passive tracers
5   !!======================================================================
[2528]6   !! History :  OPA  !  1991-03  (O. Marti, G. Madec)  Original code
7   !!                 !  1996-01  (G. Madec) statement function for e3
8   !!                 !  1997-05  (H. Loukos)  adapted for passive tracers
9   !!    NEMO    9.0  !  2004-03  (C. Ethe)    free form + modules
10   !!            3.2  !  2007-02  (C. Deltel)  Diagnose ML trends for passive tracers
11   !!            3.3  !  2010-06  (C. Ethe, G. Madec) merge TRA-TRC
[941]12   !!----------------------------------------------------------------------
[1175]13#if  defined key_top && defined key_trcdmp 
[941]14   !!----------------------------------------------------------------------
[1175]15   !!   key_trcdmp                                         internal damping
16   !!----------------------------------------------------------------------
[941]17   !!   trc_dmp      : update the tracer trend with the internal damping
18   !!   trc_dmp_init : initialization, namlist read, parameters control
19   !!----------------------------------------------------------------------
20   USE oce_trc         ! ocean dynamics and tracers variables
[1175]21   USE trc             ! ocean passive tracers variables
[2528]22   USE trcnam_trp      ! passive tracers transport namelist variables
[941]23   USE trcdta
[2528]24   USE tradmp
[941]25   USE prtctl_trc      ! Print control for debbuging
[2528]26   USE trdtra
[941]27
28   IMPLICIT NONE
29   PRIVATE
30
[2606]31   PUBLIC trc_dmp            ! routine called by step.F90
32   PUBLIC trc_dmp_alloc      ! routine called by nemogcm.F90
[941]33
[1175]34   LOGICAL , PUBLIC, PARAMETER ::   lk_trcdmp = .TRUE.   !: internal damping flag
[2528]35   !                             !!* Namelist namtrc_dmp : passive tracer newtonian damping *
36   INTEGER  ::   nn_hdmp_tr =   -1   ! = 0/-1/'latitude' for damping over passive tracer
37   INTEGER  ::   nn_zdmp_tr =    0   ! = 0/1/2 flag for damping in the mixed layer
38   REAL(wp) ::   rn_surf_tr =   50.  ! surface time scale for internal damping        [days]
39   REAL(wp) ::   rn_bot_tr  =  360.  ! bottom time scale for internal damping         [days]
40   REAL(wp) ::   rn_dep_tr  =  800.  ! depth of transition between rn_surf and rn_bot [meters]
41   INTEGER  ::   nn_file_tr =    2   ! = 1 create a damping.coeff NetCDF file
[941]42
[2606]43   REAL(wp), ALLOCATABLE, SAVE, DIMENSION(:,:,:) ::   restotr   ! restoring coeff. on tracers (s-1)
[2528]44
[941]45   !! * Substitutions
46#  include "top_substitute.h90"
47   !!----------------------------------------------------------------------
[2528]48   !! NEMO/TOP 3.3 , NEMO Consortium (2010)
[1175]49   !! $Header: /home/opalod/NEMOCVSROOT/NEMO/TOP_SRC/TRP/trcdmp.F90,v 1.11 2006/09/01 14:03:49 opalod Exp $
[2528]50   !! Software governed by the CeCILL licence (NEMOGCM/NEMO_CeCILL.txt)
[941]51   !!----------------------------------------------------------------------
52
53CONTAINS
54
[2606]55   FUNCTION trc_dmp_alloc()
56      !!----------------------------------------------------------------------
57      !!                   ***  ROUTINE trc_dmp_alloc  ***
58      !!----------------------------------------------------------------------
59      INTEGER :: trc_dmp_alloc
60      !!----------------------------------------------------------------------
61
62      ALLOCATE(restotr(jpi,jpj,jpk), Stat=trc_dmp_alloc)
63
64      IF(trc_dmp_alloc /= 0)THEN
65         CALL ctl_warn('trc_dmp_alloc : failed to allocate array.')
66      END IF
67
68   END FUNCTION trc_dmp_alloc
69
70
[941]71   SUBROUTINE trc_dmp( kt )
72      !!----------------------------------------------------------------------
73      !!                   ***  ROUTINE trc_dmp  ***
74      !!                 
75      !! ** Purpose :   Compute the passive tracer trend due to a newtonian damping
76      !!      of the tracer field towards given data field and add it to the
77      !!      general tracer trends.
78      !!
79      !! ** Method  :   Newtonian damping towards trdta computed
80      !!      and add to the general tracer trends:
81      !!                     trn = tra + restotr * (trdta - trb)
82      !!         The trend is computed either throughout the water column
83      !!      (nlmdmptr=0) or in area of weak vertical mixing (nlmdmptr=1) or
84      !!      below the well mixed layer (nlmdmptr=2)
85      !!
86      !! ** Action  : - update the tracer trends tra with the newtonian
87      !!                damping trends.
[1175]88      !!              - save the trends ('key_trdmld_trc')
89      !!----------------------------------------------------------------------
[941]90      !!
91      INTEGER, INTENT( in ) ::   kt      ! ocean time-step index
[2528]92      !!
[1175]93      INTEGER  ::   ji, jj, jk, jn       ! dummy loop indices
[2528]94      REAL(wp) ::   ztra                 ! temporary scalars
[941]95      CHARACTER (len=22) :: charout
[2528]96      REAL(wp), DIMENSION(:,:,:), ALLOCATABLE ::   ztrtrd
[941]97      !!----------------------------------------------------------------------
98
99      ! 0. Initialization (first time-step only)
100      !    --------------
[2528]101      IF( kt == nit000 ) CALL trc_dmp_init
[941]102
[2528]103      IF( l_trdtrc )   ALLOCATE( ztrtrd(jpi,jpj,jpk) )   ! temporary save of trends
[1175]104
[941]105      ! 1. Newtonian damping trends on tracer fields
106      ! --------------------------------------------
107      ! Initialize the input fields for newtonian damping
[2528]108      CALL trc_dta( kt )
[1175]109      !                                                          ! ===========
110      DO jn = 1, jptra                                           ! tracer loop
111         !                                                       ! ===========
112         IF( l_trdtrc ) ztrtrd(:,:,:) = tra(:,:,:,jn)    ! save trends
[941]113
114         IF( lutini(jn) ) THEN
[2528]115            !
116            SELECT CASE ( nn_zdmp_trc )
117            !
118            CASE( 0 )                !==  newtonian damping throughout the water column  ==!
[941]119               DO jk = 1, jpkm1
120                  DO jj = 2, jpjm1
121                     DO ji = fs_2, fs_jpim1   ! vector opt.
[2528]122                        ztra = restotr(ji,jj,jk) * ( trdta(ji,jj,jk,jn) - trb(ji,jj,jk,jn) )
[941]123                        tra(ji,jj,jk,jn) = tra(ji,jj,jk,jn) + ztra
124                     END DO
125                  END DO
126               END DO
[2528]127            !
128            CASE ( 1 )                !==  no damping in the turbocline (avt > 5 cm2/s)  ==!
[941]129               DO jk = 1, jpkm1
130                  DO jj = 2, jpjm1
131                     DO ji = fs_2, fs_jpim1   ! vector opt.
[2528]132                        IF( avt(ji,jj,jk) <= 5.e-4 )  THEN
133                           ztra = restotr(ji,jj,jk) * ( trdta(ji,jj,jk,jn) - trb(ji,jj,jk,jn) )
134                           tra(ji,jj,jk,jn) = tra(ji,jj,jk,jn) + ztra
[941]135                        ENDIF
136                     END DO
137                  END DO
138               END DO
[2528]139            !
140            CASE ( 2 )               !==  no damping in the mixed layer   ==!
[941]141               DO jk = 1, jpkm1
142                  DO jj = 2, jpjm1
143                     DO ji = fs_2, fs_jpim1   ! vector opt.
144                        IF( fsdept(ji,jj,jk) >= hmlp (ji,jj) ) THEN
145                           ztra = restotr(ji,jj,jk,jn) * ( trdta(ji,jj,jk,jn) - trb(ji,jj,jk,jn) )
[2528]146                           tra(ji,jj,jk,jn) = tra(ji,jj,jk,jn) + ztra
147                        END IF
[941]148                     END DO
149                  END DO
150               END DO
[2528]151           
[941]152            END SELECT
[2528]153            !
[941]154         ENDIF
[2528]155         !
[1175]156         IF( l_trdtrc ) THEN
157            ztrtrd(:,:,:) = tra(:,:,:,jn) -  ztrtrd(:,:,:)
[2528]158            CALL trd_tra( kt, 'TRC', jn, jptra_trd_dmp, ztrtrd )
[1175]159         END IF
160         !                                                       ! ===========
161      END DO                                                     ! tracer loop
162      !                                                          ! ===========
[2528]163      IF( l_trdtrc )  DEALLOCATE( ztrtrd )
164      !                                          ! print mean trends (used for debugging)
165      IF( ln_ctl )   THEN
166         WRITE(charout, FMT="('dmp ')") ;  CALL prt_ctl_trc_info(charout)
167                                           CALL prt_ctl_trc( tab4d=tra, mask=tmask, clinfo=ctrcnm, clinfo2='trd' )
[941]168      ENDIF
[2528]169      !
[941]170   END SUBROUTINE trc_dmp
171
172
173   SUBROUTINE trc_dmp_init
174      !!----------------------------------------------------------------------
175      !!                  ***  ROUTINE trc_dmp_init  ***
176      !!
177      !! ** Purpose :   Initialization for the newtonian damping
178      !!
179      !! ** Method  :   read the nammbf namelist and check the parameters
180      !!      called by trc_dmp at the first timestep (nit000)
181      !!----------------------------------------------------------------------
182
[2528]183      SELECT CASE ( nn_hdmp_tr )
184      CASE (  -1  )   ;   IF(lwp) WRITE(numout,*) '   tracer damping in the Med & Red seas only'
185      CASE ( 1:90 )   ;   IF(lwp) WRITE(numout,*) '   tracer damping poleward of', nn_hdmp_tr, ' degrees'
[941]186      CASE DEFAULT
[2528]187         WRITE(ctmp1,*) '          bad flag value for nn_hdmp_tr = ', nn_hdmp_tr
[941]188         CALL ctl_stop(ctmp1)
189      END SELECT
190
[2528]191      SELECT CASE ( nn_zdmp_tr )
192      CASE ( 0 )   ;   IF(lwp) WRITE(numout,*) '   tracer damping throughout the water column'
193      CASE ( 1 )   ;   IF(lwp) WRITE(numout,*) '   no tracer damping in the turbocline (avt > 5 cm2/s)'
194      CASE ( 2 )   ;   IF(lwp) WRITE(numout,*) '   no tracer damping in the mixed layer'
[941]195      CASE DEFAULT
[2528]196         WRITE(ctmp1,*) 'bad flag value for nn_zdmp_tr = ', nn_zdmp_tr
[941]197         CALL ctl_stop(ctmp1)
198      END SELECT
199
[2528]200      IF( .NOT. lk_dtatrc )   &
201         &   CALL ctl_stop( 'no passive tracer data define key_dtatrc' )
202
203      IF( .NOT. lk_tradmp )   &
204         &   CALL ctl_stop( 'passive trace damping need key_tradmp to compute damping coef.' )
205      !
206      !                          ! Damping coefficients initialization
207      IF( lzoom ) THEN   ;   CALL dtacof_zoom( restotr )
208      ELSE               ;   CALL dtacof( nn_hdmp_tr, rn_surf_tr, rn_bot_tr, rn_dep_tr,  &
209                             &            nn_file_tr, 'TRC'     , restotr                )
[1175]210      ENDIF
[2528]211      !
[941]212   END SUBROUTINE trc_dmp_init
213#else
214   !!----------------------------------------------------------------------
215   !!   Default key                                     NO internal damping
216   !!----------------------------------------------------------------------
217   LOGICAL , PUBLIC, PARAMETER ::   lk_trcdmp = .FALSE.    !: internal damping flag
218CONTAINS
219   SUBROUTINE trc_dmp( kt )        ! Empty routine
220      INTEGER, INTENT(in) :: kt
221      WRITE(*,*) 'trc_dmp: You should not have seen this print! error?', kt
222   END SUBROUTINE trc_dmp
223#endif
224   !!======================================================================
225END MODULE trcdmp
Note: See TracBrowser for help on using the repository browser.