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_sed.F90 in NEMO/branches/UKMO/NEMO4_beta_mirror/src/TOP/PISCES/SED – NEMO

source: NEMO/branches/UKMO/NEMO4_beta_mirror/src/TOP/PISCES/SED/trcdmp_sed.F90 @ 10321

Last change on this file since 10321 was 10321, checked in by davestorkey, 5 years ago

UKMO/NEMO4_beta_mirror: Update to version 10279 of the trunk.

File size: 6.9 KB
Line 
1MODULE trcdmp_sed
2   !!======================================================================
3   !!                       ***  MODULE  trcdmp  ***
4   !! Ocean physics: internal restoring trend on passive tracers
5   !!======================================================================
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
12   !!----------------------------------------------------------------------
13#if  defined key_top
14   !!----------------------------------------------------------------------
15   !!   trc_dmp      : update the tracer trend with the internal damping
16   !!   trc_dmp_init : initialization, namlist read, parameters control
17   !!----------------------------------------------------------------------
18   USE oce_trc         ! ocean dynamics and tracers variables
19   USE trc             ! ocean passive tracers variables
20   USE sed , ONLY : dtsed => dtsed      ! ocean dynamics and tracers variables
21   USE trc             ! ocean passive tracers variables
22   USE trcdta
23   USE prtctl_trc      ! Print control for debbuging
24   USE iom
25
26
27   IMPLICIT NONE
28   PRIVATE
29
30   PUBLIC trc_dmp_sed     
31   PUBLIC trc_dmp_sed_alloc 
32   PUBLIC trc_dmp_sed_ini   
33
34   REAL(wp), ALLOCATABLE, SAVE, DIMENSION(:,:,:) ::   restosed   ! restoring coeff. on tracers (s-1)
35
36   !! * Substitutions
37#  include "vectopt_loop_substitute.h90"
38   !!----------------------------------------------------------------------
39   !! NEMO/TOP 3.3 , NEMO Consortium (2010)
40   !! $Id$
41   !! Software governed by the CeCILL licence     (NEMOGCM/NEMO_CeCILL.txt)
42   !!----------------------------------------------------------------------
43CONTAINS
44
45   INTEGER FUNCTION trc_dmp_sed_alloc()
46      !!----------------------------------------------------------------------
47      !!                   ***  ROUTINE trc_dmp_alloc  ***
48      !!----------------------------------------------------------------------
49      ALLOCATE( restosed(jpi,jpj,jpk) , STAT=trc_dmp_sed_alloc )
50      !
51      IF( trc_dmp_sed_alloc /= 0 )   CALL ctl_warn('trc_dmp_sed_alloc: failed to allocate array')
52      !
53   END FUNCTION trc_dmp_sed_alloc
54
55
56   SUBROUTINE trc_dmp_sed( kt )
57      !!----------------------------------------------------------------------
58      !!                   ***  ROUTINE trc_dmp_sed  ***
59      !!                 
60      !! ** Purpose :   Compute the passive tracer trend due to a newtonian damping
61      !!      of the tracer field towards given data field and add it to the
62      !!      general tracer trends.
63      !!
64      !! ** Method  :   Newtonian damping towards trdta computed
65      !!      and add to the general tracer trends:
66      !!                     trn = tra + restotr * (trdta - trb)
67      !!         The trend is computed either throughout the water column
68      !!      (nlmdmptr=0) or in area of weak vertical mixing (nlmdmptr=1) or
69      !!      below the well mixed layer (nlmdmptr=2)
70      !!
71      !! ** Action  : - update the tracer trends tra with the newtonian
72      !!                damping trends.
73      !!              - save the trends ('key_trdmxl_trc')
74      !!----------------------------------------------------------------------
75      INTEGER, INTENT(in) ::   kt   ! ocean time-step index
76      !
77      INTEGER ::   ji, jj, jk, jn, jl, ikt   ! dummy loop indices
78      CHARACTER (len=22) ::   charout
79      REAL(wp), DIMENSION(jpi,jpj,jpk) ::   ztrcdta   ! 3D  workspace
80      !!----------------------------------------------------------------------
81      !
82      IF( ln_timing )  CALL timing_start('trc_dmp_sed')
83      !
84      !
85      IF( nb_trcdta > 0 ) THEN  ! Initialisation of tracer from a file that may also be used for damping
86         !
87         DO jn = 1, jptra                                           ! tracer loop
88            !                                                       ! ===========
89            IF( ln_trc_ini(jn) ) THEN      ! update passive tracers arrays with input data read from file
90               !
91               jl = n_trc_index(jn) 
92               CALL trc_dta( kt, sf_trcdta(jl), rf_trfac(jl), ztrcdta )   ! read tracer data at nit000
93               !
94               DO jj = 1, jpj
95                  DO ji = 1, jpi   ! vector opt.
96                     ikt = mbkt(ji,jj)
97                     trb(ji,jj,ikt,jn) = ztrcdta(ji,jj,ikt) + ( trb(ji,jj,ikt,jn) -  ztrcdta(ji,jj,ikt) )     &
98                     &                  * exp( -restosed(ji,jj,ikt) * dtsed )
99                  END DO
100               END DO
101               !
102            ENDIF
103         END DO                                                     ! tracer loop
104         !                                                          ! ===========
105      ENDIF
106      !
107      !                                          ! print mean trends (used for debugging)
108      IF( ln_ctl ) THEN
109         WRITE(charout, FMT="('dmp ')")
110         CALL prt_ctl_trc_info(charout)
111         CALL prt_ctl_trc( tab4d=tra, mask=tmask, clinfo=ctrcnm, clinfo2='trd' )
112      ENDIF
113      !
114      IF( ln_timing )  CALL timing_stop('trc_dmp_sed')
115      !
116   END SUBROUTINE trc_dmp_sed
117
118
119   SUBROUTINE trc_dmp_sed_ini
120      !!----------------------------------------------------------------------
121      !!                  ***  ROUTINE trc_dmp_ini  ***
122      !!
123      !! ** Purpose :   Initialization for the newtonian damping
124      !!
125      !! ** Method  :   read the nammbf namelist and check the parameters
126      !!              called by trc_dmp at the first timestep (nittrc000)
127      !!----------------------------------------------------------------------
128      !!----------------------------------------------------------------------
129      !
130      IF( ln_timing )  CALL timing_start('trc_dmp_sed_ini')
131
132      IF (lwp) WRITE(numout,*) '   tracer damping throughout the water column'
133      !
134      IF( trc_dmp_sed_alloc() /= 0 )   CALL ctl_stop( 'STOP', 'trc_dmp_sed_ini: unable to allocate arrays' )
135      !
136      IF( .NOT.lk_c1d ) THEN
137         !Read in mask from file
138          restosed(:,:,:) = 0.5 / rday
139         !
140      ENDIF
141      IF( ln_timing )  CALL timing_stop('trc_dmp_sed_ini')
142     !
143   END SUBROUTINE trc_dmp_sed_ini
144
145#else
146   !!----------------------------------------------------------------------
147   !!  Dummy module :                                     No passive tracer
148   !!----------------------------------------------------------------------
149CONTAINS
150   SUBROUTINE trc_dmp_sed( kt )        ! Empty routine
151      INTEGER, INTENT(in) :: kt
152      WRITE(*,*) 'trc_dmp_sed: You should not have seen this print! error?', kt
153   END SUBROUTINE trc_dmp_sed
154#endif
155
156   !!======================================================================
157END MODULE trcdmp_sed
Note: See TracBrowser for help on using the repository browser.