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.
trcsbc.F90 in branches/2012/dev_r3309_LOCEAN12_Ediag/NEMOGCM/NEMO/TOP_SRC/TRP – NEMO

source: branches/2012/dev_r3309_LOCEAN12_Ediag/NEMOGCM/NEMO/TOP_SRC/TRP/trcsbc.F90 @ 3318

Last change on this file since 3318 was 3318, checked in by gm, 12 years ago

Ediag branche: #927 split TRA/DYN trd computation

  • Property svn:keywords set to Id
File size: 6.0 KB
Line 
1MODULE trcsbc
2   !!==============================================================================
3   !!                       ***  MODULE  trcsbc  ***
4   !! Ocean passive tracers:  surface boundary condition
5   !!======================================================================
6   !! History :  1.0  !  2004-03  (C. Ethe)  adapt trasbc to passive tracers
7   !!            2.0  !  2006-08  (C. Deltel) Diagnose ML trends for passive tracers
8   !!==============================================================================
9#if defined key_top
10   !!----------------------------------------------------------------------
11   !!   'key_top'                                                TOP models
12   !!----------------------------------------------------------------------
13   !!   trc_sbc      : update the tracer trend at ocean surface
14   !!----------------------------------------------------------------------
15   USE oce_trc         ! ocean dynamics and active tracers variables
16   USE trc             ! ocean  passive tracers variables
17   USE prtctl_trc      ! Print control for debbuging
18   USE trd_oce         ! trends: ocean variables
19   USE trdtra          ! trends: tracer manager
20
21   IMPLICIT NONE
22   PRIVATE
23
24   PUBLIC   trc_sbc   ! routine called by step.F90
25
26   !! * Substitutions
27#  include "top_substitute.h90"
28   !!----------------------------------------------------------------------
29   !! NEMO/TOP 3.3 , NEMO Consortium (2010)
30   !! $Id$
31   !! Software governed by the CeCILL licence     (NEMOGCM/NEMO_CeCILL.txt)
32   !!----------------------------------------------------------------------
33CONTAINS
34
35   SUBROUTINE trc_sbc ( kt )
36      !!----------------------------------------------------------------------
37      !!                  ***  ROUTINE trc_sbc  ***
38      !!                   
39      !! ** Purpose :   Compute the tracer surface boundary condition trend of
40      !!      (concentration/dilution effect) and add it to the general
41      !!       trend of tracer equations.
42      !!
43      !! ** Method :    concentration/dilution effect:
44      !!            The surface freshwater flux modify the ocean volume
45      !!         and thus the concentration of a tracer as :
46      !!            tra = tra + emp * trn / e3t   for k=1
47      !!         where emp, the surface freshwater budget (evaporation minus
48      !!         precipitation minus runoff) given in kg/m2/s is divided
49      !!         by 1035 kg/m3 (density of ocean water) to obtain m/s.
50      !!
51      !! ** Action  : - Update the 1st level of tra with the trend associated
52      !!                with the tracer surface boundary condition
53      !!----------------------------------------------------------------------
54      INTEGER, INTENT( in ) ::   kt   ! ocean time-step index
55      !
56      INTEGER  ::   ji, jj, jn     ! dummy loop indices
57      REAL(wp) ::   zsrau, zse3t   ! temporary scalars
58      CHARACTER (len=22) ::   charout
59      REAL(wp), POINTER, DIMENSION(:,:  ) ::   zemps    ! 2D workspace
60      REAL(wp), POINTER, DIMENSION(:,:,:) ::   ztrtrd   ! 3D workspace
61      !!---------------------------------------------------------------------
62      !
63      IF( nn_timing == 1 )  CALL timing_start('trc_sbc')
64      !
65      ! Allocate temporary workspace
66                      CALL wrk_alloc( jpi, jpj,      zemps  )
67      IF( l_trdtrc )  CALL wrk_alloc( jpi, jpj, jpk, ztrtrd )
68
69      IF( kt == nittrc000 ) THEN
70         IF(lwp) WRITE(numout,*)
71         IF(lwp) WRITE(numout,*) 'trc_sbc : Passive tracers surface boundary condition'
72         IF(lwp) WRITE(numout,*) '~~~~~~~ '
73      ENDIF
74
75
76      IF( lk_offline ) THEN          ! emps in dynamical files contains emps - rnf
77         zemps(:,:) = emps(:,:) 
78      ELSE                           ! Concentration dilution effect on tracer due to evaporation, precipitation, and river runoff
79         IF( lk_vvl ) THEN                      ! volume variable
80            zemps(:,:) = emps(:,:) - emp(:,:)   
81!!ch         zemps(:,:) = 0.
82         ELSE                                   ! linear free surface
83            IF( ln_rnf ) THEN  ;  zemps(:,:) = emps(:,:) - rnf(:,:)   !  E-P-R
84            ELSE               ;  zemps(:,:) = emps(:,:)
85            ENDIF
86         ENDIF
87      ENDIF 
88
89      ! 0. initialization
90      zsrau = 1. / rau0
91      DO jn = 1, jptra
92         !
93         IF( l_trdtrc ) ztrtrd(:,:,:) = tra(:,:,:,jn)  ! save trends
94         !                                             ! add the trend to the general tracer trend
95         DO jj = 2, jpj
96            DO ji = fs_2, fs_jpim1   ! vector opt.
97               zse3t = 1. / fse3t(ji,jj,1)
98               tra(ji,jj,1,jn) = tra(ji,jj,1,jn) + zemps(ji,jj) *  zsrau * trn(ji,jj,1,jn) * zse3t
99            END DO
100         END DO
101         
102         IF( l_trdtrc ) THEN
103            ztrtrd(:,:,:) = tra(:,:,:,jn) - ztrtrd(:,:,:)
104            CALL trd_tra( kt, 'TRC', jn, jptra_nsr, ztrtrd )
105         END IF
106         !                                                       ! ===========
107      END DO                                                     ! tracer loop
108      !                                                          ! ===========
109      IF( ln_ctl )   THEN
110         WRITE(charout, FMT="('sbc ')") ;  CALL prt_ctl_trc_info(charout)
111                                           CALL prt_ctl_trc( tab4d=tra, mask=tmask, clinfo=ctrcnm, clinfo2='trd' )
112      ENDIF
113                      CALL wrk_dealloc( jpi, jpj,      zemps  )
114      IF( l_trdtrc )  CALL wrk_dealloc( jpi, jpj, jpk, ztrtrd )
115      !
116      IF( nn_timing == 1 )  CALL timing_stop('trc_sbc')
117      !
118   END SUBROUTINE trc_sbc
119
120#else
121   !!----------------------------------------------------------------------
122   !!   Dummy module :                      NO passive tracer
123   !!----------------------------------------------------------------------
124CONTAINS
125   SUBROUTINE trc_sbc (kt)              ! Empty routine
126      INTEGER, INTENT(in) :: kt
127      WRITE(*,*) 'trc_sbc: You should not have seen this print! error?', kt
128   END SUBROUTINE trc_sbc
129#endif
130   
131   !!======================================================================
132END MODULE trcsbc
Note: See TracBrowser for help on using the repository browser.