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/2021/dev_r14116_HPC-10_mcastril_Mixed_Precision_implementation/src/TOP/PISCES/SED – NEMO

source: NEMO/branches/2021/dev_r14116_HPC-10_mcastril_Mixed_Precision_implementation/src/TOP/PISCES/SED/trcdmp_sed.F90 @ 15648

Last change on this file since 15648 was 15648, checked in by sparonuz, 2 years ago

Updated name preprocessor function CASTWP to CASTDP

File size: 7.1 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          ! 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 "do_loop_substitute.h90"
38#  include "single_precision_substitute.h90"
39   !!----------------------------------------------------------------------
40   !! NEMO/TOP 3.3 , NEMO Consortium (2010)
41   !! $Id: trcdmp.F90 7646 2017-02-06 09:25:03Z timgraham $
42   !! Software governed by the CeCILL licence     (NEMOGCM/NEMO_CeCILL.txt)
43   !!----------------------------------------------------------------------
44CONTAINS
45
46   INTEGER FUNCTION trc_dmp_sed_alloc()
47      !!----------------------------------------------------------------------
48      !!                   ***  ROUTINE trc_dmp_alloc  ***
49      !!----------------------------------------------------------------------
50      ALLOCATE( restosed(jpi,jpj,jpk) , STAT=trc_dmp_sed_alloc )
51      !
52      IF( trc_dmp_sed_alloc /= 0 )   CALL ctl_warn('trc_dmp_sed_alloc: failed to allocate array')
53      !
54   END FUNCTION trc_dmp_sed_alloc
55
56
57   SUBROUTINE trc_dmp_sed( kt, Kbb, Kmm, Krhs )
58      !!----------------------------------------------------------------------
59      !!                   ***  ROUTINE trc_dmp_sed  ***
60      !!                 
61      !! ** Purpose :   Compute the passive tracer trend due to a newtonian damping
62      !!      of the tracer field towards given data field and add it to the
63      !!      general tracer trends.
64      !!
65      !! ** Method  :   Newtonian damping towards trdta computed
66      !!      and add to the general tracer trends:
67      !!                     tr(Kmm) = tr(Krhs) + restotr * (trdta - tr(Kbb))
68      !!         The trend is computed either throughout the water column
69      !!      (nlmdmptr=0) or in area of weak vertical mixing (nlmdmptr=1) or
70      !!      below the well mixed layer (nlmdmptr=2)
71      !!
72      !! ** Action  : - update the tracer trends tr(Krhs) with the newtonian
73      !!                damping trends.
74      !!              - save the trends ('key_trdmxl_trc')
75      !!----------------------------------------------------------------------
76      INTEGER, INTENT(in) ::   kt              ! ocean time-step index
77      INTEGER, INTENT(in) ::   Kbb, Kmm, Krhs  ! time level index
78      !
79      INTEGER ::   ji, jj, jk, jn, jl, ikt   ! dummy loop indices
80      CHARACTER (len=22) ::   charout
81      REAL(dp), DIMENSION(jpi,jpj,jpk) ::   ztrcdta   ! 3D  workspace
82      !!----------------------------------------------------------------------
83      !
84      IF( ln_timing )  CALL timing_start('trc_dmp_sed')
85      !
86      !
87      IF( nb_trcdta > 0 ) THEN  ! Initialisation of tracer from a file that may also be used for damping
88         !
89         DO jn = 1, jptra                                           ! tracer loop
90            !                                                       ! ===========
91            IF( ln_trc_ini(jn) ) THEN      ! update passive tracers arrays with input data read from file
92               !
93               jl = n_trc_index(jn) 
94               CALL trc_dta( kt, jl, ztrcdta )   ! read tracer data at nit000
95               !
96               DO_2D( 1, 1, 1, 1 )
97                  ikt = mbkt(ji,jj)
98                  tr(ji,jj,ikt,jn,Kbb) = ztrcdta(ji,jj,ikt) + ( tr(ji,jj,ikt,jn,Kbb) -  ztrcdta(ji,jj,ikt) )     &
99                  &                  * exp( -restosed(ji,jj,ikt) * dtsed )
100               END_2D
101               !
102            ENDIF
103         END DO                                                     ! tracer loop
104         !                                                          ! ===========
105      ENDIF
106      !
107      !                                          ! print mean trends (used for debugging)
108      IF( sn_cfctl%l_prttrc ) THEN
109         WRITE(charout, FMT="('dmp ')")
110         CALL prt_ctl_info( charout, cdcomp = 'top' )
111         CALL prt_ctl( tab4d_1=CASTDP(tr(:,:,:,:,Krhs)), mask1=tmask, clinfo=ctrcnm,clinfo3='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, Kbb, Kmm, Krhs )   ! Empty routine
151      INTEGER, INTENT(in) :: kt
152      INTEGER, INTENT(in) :: Kbb, Kmm, Krhs
153      WRITE(*,*) 'trc_dmp_sed: You should not have seen this print! error?', kt
154   END SUBROUTINE trc_dmp_sed
155#endif
156
157   !!======================================================================
158END MODULE trcdmp_sed
Note: See TracBrowser for help on using the repository browser.