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.
trcbbc.F90 in trunk/NEMO/TOP_SRC/TRP – NEMO

source: trunk/NEMO/TOP_SRC/TRP/trcbbc.F90 @ 202

Last change on this file since 202 was 202, checked in by opalod, 19 years ago

CT : UPDATE142 : Check the consistency between passive tracers transport modules (in TRP directory) and those used for the active tracers

  • Property svn:eol-style set to native
  • Property svn:executable set to *
  • Property svn:keywords set to Author Date Id Revision
File size: 9.9 KB
Line 
1MODULE trcbbc
2   !!==============================================================================
3   !!                       ***  MODULE  trcbbc  ***
4   !! Ocean passive tracers:  bottom boundary condition
5   !!==============================================================================
6#if   defined key_passivetrc && defined key_trcbbc
7   !!----------------------------------------------------------------------
8   !!   'key_trcbbc'                                  geothermal heat flux
9   !!----------------------------------------------------------------------
10   !!   trc_bbc      : update the tracer trend at ocean bottom
11   !!   trc_bbc_init : initialization of geothermal heat flux trend
12   !!----------------------------------------------------------------------
13   !! * Modules used
14   USE oce_trc             ! ocean dynamics and active tracers variables
15   USE trc                 ! ocean passive tracers variables
16 
17   IMPLICIT NONE
18   PRIVATE
19
20   !! * Accessibility
21   PUBLIC trc_bbc          ! routine called by trcstp.F90
22
23   !! to be transfert in the namelist ???!   
24   LOGICAL, PUBLIC, PARAMETER ::   lk_trcbbc = .TRUE.   !: bbc flag
25
26   !! * Module variables
27   INTEGER ::                       & !!! ** bbc namelist (nambbc) **
28      ngeo_trc_flux = 1                    ! Geothermal flux (0:no flux, 1:constant flux,
29      !                                !                  2:read in file )
30   REAL(wp) ::                      & !!! ** bbc namlist **
31      ngeo_trc_flux_const = 86.4e-3        ! Constant value of geothermal heat flux
32
33   INTEGER, DIMENSION(jpi,jpj) ::   &
34      nbotlevt                         ! ocean bottom level index at T-pt
35   REAL(wp), DIMENSION(jpi,jpj) ::  &
36      qgh_trd                          ! geothermal heating trend
37 
38   !! * Substitutions
39#  include "passivetrc_substitute.h90"
40   !!----------------------------------------------------------------------
41   !!  OPA 9.0 , LODYC-IPSL (2003)
42   !!----------------------------------------------------------------------
43
44CONTAINS
45
46   SUBROUTINE trc_bbc( kt )
47      !!----------------------------------------------------------------------
48      !!                  ***  ROUTINE trc_bbc  ***
49      !!
50      !! ** Purpose :   Compute the bottom boundary contition on passive tracer
51      !!      associated with geothermal heating and add it to the general
52      !!      trend of tracers equations.
53      !!
54      !! ** Method  :   The geothermal heat flux set to its constant value of
55      !!       86.4 mW/m2 (Stein and Stein 1992, Huang 1999).
56      !!       The temperature trend associated to this heat flux through the
57      !!       ocean bottom can be computed once and is added to the temperature
58      !!       trend juste above the bottom at each time step:
59      !!            tra = tra + Qsf / (rau0 rcp e3T) for k= mbathy -1
60      !!       Where Qsf is the geothermal heat flux.
61      !!
62      !! ** Action  : - update the temperature trends tra with the trend of
63      !!                the ocean bottom boundary condition
64      !!
65      !! References :
66      !!      Stein, C. A., and S. Stein, 1992, Nature, 359, 123-129.
67      !!
68      !! History :
69      !!   8.1  !  99-10  (G. Madec)  original code
70      !!   8.5  !  02-08  (G. Madec)  free form + modules
71      !!   9.0  !  04-03  (C. Ethe)  adpated for passive tracers
72      !!----------------------------------------------------------------------
73      !! * Arguments
74      INTEGER, INTENT( in ) ::   kt    ! ocean time-step index
75
76      !! * Local declarations
77#if defined key_vectopt_loop   &&   ! defined key_autotasking
78      INTEGER ::   ji, jn                  ! dummy loop indices
79#else
80      INTEGER ::   ji, jj, jn              ! dummy loop indices
81#endif
82      REAL(wp) ::   ztra                ! temporary scalar
83      !!----------------------------------------------------------------------
84
85      ! 0. Initialization
86      IF( kt == nittrc000 )   CALL trc_bbc_init
87
88      ! 1. Add the geothermal heat flux trend on temperature
89
90      SELECT CASE ( ngeo_trc_flux )
91
92      CASE ( 1:2 )                !  geothermal heat flux
93
94         DO jn = 1, jptra
95#if defined key_vectopt_loop   &&   ! defined key_autotasking
96            DO ji = jpi+2, jpij-jpi-1   ! vector opt. (forced unrolling)
97               tra(ji,1,nbotlevt(ji,1),jn) = tra(ji,1,nbotlevt(ji,1),jn) + qgh_trd(ji,1)
98            END DO
99#else
100            DO jj = 2, jpjm1
101               DO ji = 2, jpim1
102                  tra(ji,jj,nbotlevt(ji,jj),jn) = tra(ji,jj,nbotlevt(ji,jj),jn) + qgh_trd(ji,jj)
103               END DO
104            END DO
105#endif
106            IF(l_ctl) THEN         ! print mean trends (used for debugging)
107               ztra = SUM( tra(2:nictl,2:njctl,1:jpkm1,jn) * tmask(2:nictl,2:njctl,1:jpkm1) )
108               WRITE(numout,*) ' trc/bbc  - ',ctrcnm(jn),' : ', ztra-tra_ctl(jn) 
109               tra_ctl(jn) = ztra 
110            ENDIF
111         END DO
112
113      END SELECT
114
115   END SUBROUTINE trc_bbc
116
117
118   SUBROUTINE trc_bbc_init
119      !!----------------------------------------------------------------------
120      !!                  ***  ROUTINE trc_bbc_init  ***
121      !!
122      !! ** Purpose :   Compute once for all the trend associated with geo-
123      !!      thermal heating that will be applied at each time step at the
124      !!      bottom ocean level
125      !!
126      !! ** Method  :   Read the namtrabbc namelist and check the parameters.
127      !!      called at the first time step (nittrc000)
128      !!
129      !! ** Input   : - Namlist namtrcbbc
130      !!              - NetCDF file  : passivetrc_geothermal_heating.nc
131      !!                               ( if necessary )
132      !!
133      !! ** Action  : - compute the heat geothermal trend qgh_trd
134      !!              - compute the bottom ocean level nbotlevt
135      !!
136      !! history :
137      !!  8.5  ! 02-11 (A. Bozec) original code
138      !!----------------------------------------------------------------------
139      !! * Modules used
140      USE ioipsl
141
142      !! * local declarations
143      CHARACTER (len=32) ::   clname
144      INTEGER  ::   ji, jj              ! dummy loop indices
145      INTEGER  ::   inum = 11           ! temporary logical unit
146      INTEGER  ::   itime               ! temporary integers
147      REAL(wp) ::   zdate0, zdt         ! temporary scalars
148      REAL(wp), DIMENSION(1) :: zdept   ! temporary workspace
149      REAL(wp), DIMENSION(jpidta,jpjdta) ::   &
150         zlamt, zphit, zdta   ! temporary workspace
151
152      NAMELIST/namtrcbbc/ngeo_trc_flux, ngeo_trc_flux_const 
153      !!----------------------------------------------------------------------
154
155      ! Read Namelist nambbc : bottom momentum boundary condition
156      REWIND ( numnamtra )
157      READ   ( numnamtra, namtrcbbc )
158
159      ! Control print
160      IF(lwp) WRITE(numout,*)
161      IF(lwp) WRITE(numout,*) 'trc_bbc : Passive tracers Bottom Boundary Condition (bbc)'
162      IF(lwp) WRITE(numout,*) '~~~~~~~   Geothermal heatflux'
163      IF(lwp) WRITE(numout,*) '          Namelist namtrcbbc : set bbc parameters'
164      IF(lwp) WRITE(numout,*)
165      IF(lwp) WRITE(numout,*) '             Geothermal flux           ngeo_trc_flux       = ', ngeo_trc_flux
166      IF(lwp) WRITE(numout,*) '             Constant geothermal flux  ngeo_trc_flux_const = ', ngeo_trc_flux_const
167      IF(lwp) WRITE(numout,*)
168
169      ! level of the ocean bottom at T-point
170
171      DO jj = 1, jpj
172         DO ji = 1, jpi
173            nbotlevt(ji,jj) = MAX( mbathy(ji,jj)-1, 1 )
174         END DO
175      END DO
176
177      ! initialization of geothermal heat flux
178
179      SELECT CASE ( ngeo_trc_flux )
180
181      CASE ( 0 )                ! no geothermal heat flux
182         IF(lwp) WRITE(numout,*)
183         IF(lwp) WRITE(numout,*) '             *** no geothermal heat flux'
184
185      CASE ( 1 )                ! constant flux
186         IF(lwp) WRITE(numout,*) '             *** constant heat flux  =   ', ngeo_trc_flux_const
187         qgh_trd(:,:) = ngeo_trc_flux_const
188
189      CASE ( 2 )                ! variable geothermal heat flux
190         ! read the geothermal fluxes in mW/m2
191         clname = 'passivetrc_geothermal_heating'
192         itime = 1
193         zlamt(:,:) = 0.
194         zphit(:,:) = 0.
195         IF(lwp) WRITE(numout,*) '             *** variable geothermal heat flux read in ', clname, ' file'
196         CALL restini( clname, jpidta, jpjdta, zlamt, zphit, 1, zdept , clname,   &
197                       itime, zdate0, zdt, inum )
198         CALL restget( inum, 'heatflow', jpidta, jpjdta, 1, 0, .FALSE., zdta )
199         DO jj = 1, nlcj
200            DO ji = 1, nlci
201              qgh_trd(ji,jj) = zdta(mig(ji),mjg(jj))
202            END DO
203         END DO
204
205         CALL restclo( inum )
206         qgh_trd(:,:) = qgh_trd(:,:) * 1.e-3 ! conversion in W/m2
207
208      CASE DEFAULT
209         IF(lwp) WRITE(numout,cform_err)
210         IF(lwp) WRITE(numout,*) '     bad flag value for ngeo_trc_flux = ', ngeo_trc_flux
211         nstop = nstop + 1
212
213      END SELECT
214
215      ! geothermal heat flux trend
216
217      SELECT CASE ( ngeo_trc_flux )
218
219      CASE ( 1:2 )                !  geothermal heat flux
220
221#if defined key_vectopt_loop   &&   ! defined key_autotasking
222         DO ji = 1, jpij   ! vector opt. (forced unrolling)
223            qgh_trd(ji,1) = ro0cpr * qgh_trd(ji,1) / fse3t(ji,1,nbotlevt(ji,1) )
224         END DO
225#else
226         DO jj = 1, jpj
227            DO ji = 1, jpi
228               qgh_trd(ji,jj) = ro0cpr * qgh_trd(ji,jj) / fse3t(ji,jj,nbotlevt(ji,jj))
229            END DO
230         END DO
231#endif
232
233      END SELECT
234
235   END SUBROUTINE trc_bbc_init
236
237#else
238   !!----------------------------------------------------------------------
239   !!   Default option                                         Empty module
240   !!----------------------------------------------------------------------
241   LOGICAL, PUBLIC, PARAMETER ::   lk_trcbbc = .FALSE.  !: bbc flag
242CONTAINS
243   SUBROUTINE trc_bbc( kt )           ! Empty routine
244      INTEGER, INTENT(in) :: kt
245      WRITE(*,*) 'trc_bbc: You should not have seen this print! error?', kt
246   END SUBROUTINE trc_bbc
247#endif
248
249   !!======================================================================
250END MODULE trcbbc
Note: See TracBrowser for help on using the repository browser.