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.
trabbc.F90 in trunk/NEMO/OPA_SRC/TRA – NEMO

source: trunk/NEMO/OPA_SRC/TRA/trabbc.F90 @ 558

Last change on this file since 558 was 541, checked in by opalod, 18 years ago

nemo_v1_bugfix_065:RB: move namelist declaration for compatibility with Agrif

  • Property svn:eol-style set to native
  • Property svn:keywords set to Author Date Id Revision
File size: 9.2 KB
Line 
1MODULE trabbc
2   !!==============================================================================
3   !!                       ***  MODULE  trabbc  ***
4   !! Ocean active tracers:  bottom boundary condition
5   !!==============================================================================
6   !! History :  8.1  ! 99-10 (G. Madec)  original code
7   !!            8.5  ! 02-08 (G. Madec)  free form + modules
8   !!            8.5  ! 02-11 (A. Bozec)  tra_bbc_init: original code
9   !!----------------------------------------------------------------------
10#if   defined key_trabbc   ||   defined key_esopa
11   !!----------------------------------------------------------------------
12   !!   'key_trabbc'                                  geothermal heat flux
13   !!----------------------------------------------------------------------
14   !!   tra_bbc      : update the tracer trend at ocean bottom
15   !!   tra_bbc_init : initialization of geothermal heat flux trend
16   !!----------------------------------------------------------------------
17   !! * Modules used
18   USE oce             ! ocean dynamics and active tracers
19   USE dom_oce         ! ocean space and time domain
20   USE phycst          ! physical constants
21   USE trdmod          ! ocean trends
22   USE trdmod_oce      ! ocean variables trends
23   USE in_out_manager  ! I/O manager
24   USE prtctl          ! Print control
25
26   IMPLICIT NONE
27   PRIVATE
28
29   PUBLIC tra_bbc          ! routine called by step.F90
30
31   !! to be transfert in the namelist ???!   
32   LOGICAL, PUBLIC, PARAMETER ::   lk_trabbc = .TRUE.   !: bbc flag
33
34   !!* Namelist nambbc: bottom boundary condition
35   INTEGER  ::   ngeo_flux       = 1            ! Geothermal flux (0:no flux, 1:constant flux, 2:read in file )
36   REAL(wp) ::   ngeo_flux_const = 86.4e-3      ! Constant value of geothermal heat flux
37
38   INTEGER , DIMENSION(jpi,jpj) ::   nbotlevt   ! ocean bottom level index at T-pt
39   REAL(wp), DIMENSION(jpi,jpj) ::   qgh_trd    ! geothermal heating trend
40 
41   !! * Substitutions
42#  include "domzgr_substitute.h90"
43   !!----------------------------------------------------------------------
44   !!  OPA 9.0 , LOCEAN-IPSL (2006)
45   !! $Header$
46   !! Software governed by the CeCILL licence (modipsl/doc/NEMO_CeCILL.txt)
47   !!----------------------------------------------------------------------
48
49CONTAINS
50
51   SUBROUTINE tra_bbc( kt )
52      !!----------------------------------------------------------------------
53      !!                  ***  ROUTINE tra_bbc  ***
54      !!
55      !! ** Purpose :   Compute the bottom boundary contition on temperature
56      !!      associated with geothermal heating and add it to the general
57      !!      trend of temperature equations.
58      !!
59      !! ** Method  :   The geothermal heat flux set to its constant value of
60      !!       86.4 mW/m2 (Stein and Stein 1992, Huang 1999).
61      !!       The temperature trend associated to this heat flux through the
62      !!       ocean bottom can be computed once and is added to the temperature
63      !!       trend juste above the bottom at each time step:
64      !!            ta = ta + Qsf / (rau0 rcp e3T) for k= mbathy -1
65      !!       Where Qsf is the geothermal heat flux.
66      !!
67      !! ** Action  : - update the temperature trends (ta) with the trend of
68      !!                the ocean bottom boundary condition
69      !!
70      !! References : Stein, C. A., and S. Stein, 1992, Nature, 359, 123-129.
71      !!----------------------------------------------------------------------
72      USE oce, ONLY :   ztrdt => ua   ! use ua as 3D workspace   
73      USE oce, ONLY :   ztrds => va   ! use va as 3D workspace   
74      !!
75      INTEGER, INTENT( in ) ::   kt   ! ocean time-step index
76      !!
77#if defined key_vectopt_loop   &&   ! defined key_mpp_omp
78      INTEGER ::   ji       ! dummy loop indices
79#else
80      INTEGER ::   ji, jj   ! dummy loop indices
81#endif
82      !!----------------------------------------------------------------------
83
84      IF( kt == nit000 )   CALL tra_bbc_init      ! Initialization
85
86      IF( l_trdtra )   THEN         ! Save ta and sa trends
87         ztrdt(:,:,:) = ta(:,:,:) 
88         ztrds(:,:,:) = 0.e0
89      ENDIF
90
91      ! Add the geothermal heat flux trend on temperature
92
93      SELECT CASE ( ngeo_flux )
94      !
95      CASE ( 1:2 )                !  geothermal heat flux
96#if defined key_vectopt_loop   &&   ! defined key_mpp_omp
97         DO ji = jpi+2, jpij-jpi-1   ! vector opt. (forced unrolling)
98            ta(ji,1,nbotlevt(ji,1)) = ta(ji,1,nbotlevt(ji,1)) + qgh_trd(ji,1)
99         END DO
100#else
101         DO jj = 2, jpjm1
102            DO ji = 2, jpim1
103               ta(ji,jj,nbotlevt(ji,jj)) = ta(ji,jj,nbotlevt(ji,jj)) + qgh_trd(ji,jj)
104            END DO
105         END DO
106#endif
107      END SELECT
108
109      IF( l_trdtra ) THEN        ! Save the geothermal heat flux trend for diagnostics
110         ztrdt(:,:,:) = ta(:,:,:) - ztrdt(:,:,:)
111         CALL trd_mod( ztrdt, ztrds, jptra_trd_bbc, 'TRA', kt )
112      ENDIF
113      !
114      IF(ln_ctl)   CALL prt_ctl(tab3d_1=ta, clinfo1=' bbc  - Ta: ', mask1=tmask, clinfo3='tra-ta')
115      !
116   END SUBROUTINE tra_bbc
117
118
119   SUBROUTINE tra_bbc_init
120      !!----------------------------------------------------------------------
121      !!                  ***  ROUTINE tra_bbc_init  ***
122      !!
123      !! ** Purpose :   Compute once for all the trend associated with geo-
124      !!      thermal heating that will be applied at each time step at the
125      !!      bottom ocean level
126      !!
127      !! ** Method  :   Read the nambbc namelist and check the parameters.
128      !!      called at the first time step (nit000)
129      !!
130      !! ** Input   : - Namlist nambbc
131      !!              - NetCDF file  : geothermal_heating.nc ( if necessary )
132      !!
133      !! ** Action  : - compute the heat geothermal trend qgh_trd
134      !!              - compute the bottom ocean level nbotlevt
135      !!----------------------------------------------------------------------
136      USE iom
137      !!
138      INTEGER  ::   ji, jj              ! dummy loop indices
139      INTEGER  ::   inum                ! temporary logical unit
140
141      NAMELIST/nambbc/ngeo_flux, ngeo_flux_const 
142      !!----------------------------------------------------------------------
143
144      REWIND ( numnam )              ! Read Namelist nambbc : bottom momentum boundary condition
145      READ   ( numnam, nambbc )
146
147      !                              ! Control print
148      IF(lwp) WRITE(numout,*)
149      IF(lwp) WRITE(numout,*) 'tra_bbc : tempearture Bottom Boundary Condition (bbc)'
150      IF(lwp) WRITE(numout,*) '~~~~~~~   Geothermal heatflux'
151      IF(lwp) WRITE(numout,*) '          Namelist nambbc : set bbc parameters'
152      IF(lwp) WRITE(numout,*)
153      IF(lwp) WRITE(numout,*) '             Geothermal flux           ngeo_flux       = ', ngeo_flux
154      IF(lwp) WRITE(numout,*) '             Constant geothermal flux  ngeo_flux_const = ', ngeo_flux_const
155      IF(lwp) WRITE(numout,*)
156
157      !                              ! level of the ocean bottom at T-point
158      DO jj = 1, jpj
159         DO ji = 1, jpi
160            nbotlevt(ji,jj) = MAX( mbathy(ji,jj)-1, 1 )
161         END DO
162      END DO
163
164
165      SELECT CASE ( ngeo_flux )      ! initialization of geothermal heat flux
166      !
167      CASE ( 0 )                ! no geothermal heat flux
168         IF(lwp) WRITE(numout,*)
169         IF(lwp) WRITE(numout,*) '             *** no geothermal heat flux'
170         !
171      CASE ( 1 )                ! constant flux
172         IF(lwp) WRITE(numout,*) '             *** constant heat flux  =   ', ngeo_flux_const
173         qgh_trd(:,:) = ngeo_flux_const
174         !
175      CASE ( 2 )                ! variable geothermal heat flux
176         ! read the geothermal fluxes in mW/m2
177         !
178         IF(lwp) WRITE(numout,*) '             *** variable geothermal heat flux'
179         CALL iom_open ( 'geothermal_heating.nc', inum )
180         CALL iom_get ( inum, jpdom_data, 'heatflow', qgh_trd )
181         CALL iom_close (inum)
182         !
183         qgh_trd(:,:) = qgh_trd(:,:) * 1.e-3 ! conversion in W/m2
184         !
185      CASE DEFAULT
186         WRITE(ctmp1,*) '     bad flag value for ngeo_flux = ', ngeo_flux
187         CALL ctl_stop( ctmp1 )
188         !
189      END SELECT
190
191      ! geothermal heat flux trend
192
193      SELECT CASE ( ngeo_flux )
194      !
195      CASE ( 1:2 )                !  geothermal heat flux
196#if defined key_vectopt_loop   &&   ! defined key_mpp_omp
197         DO ji = 1, jpij   ! vector opt. (forced unrolling)
198            qgh_trd(ji,1) = ro0cpr * qgh_trd(ji,1) / fse3t(ji,1,nbotlevt(ji,1) )
199         END DO
200#else
201         DO jj = 1, jpj
202            DO ji = 1, jpi
203               qgh_trd(ji,jj) = ro0cpr * qgh_trd(ji,jj) / fse3t(ji,jj,nbotlevt(ji,jj))
204            END DO
205         END DO
206#endif
207      END SELECT
208      !
209   END SUBROUTINE tra_bbc_init
210
211#else
212   !!----------------------------------------------------------------------
213   !!   Default option                                         Empty module
214   !!----------------------------------------------------------------------
215   LOGICAL, PUBLIC, PARAMETER ::   lk_trabbc = .FALSE.  !: bbc flag
216CONTAINS
217   SUBROUTINE tra_bbc( kt )           ! Empty routine
218      WRITE(*,*) 'tra_bbc: You should not have seen this print! error?', kt
219   END SUBROUTINE tra_bbc
220#endif
221
222   !!======================================================================
223END MODULE trabbc
Note: See TracBrowser for help on using the repository browser.