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 @ 719

Last change on this file since 719 was 719, checked in by ctlod, 17 years ago

get back to the nemo_v2_3 version for trunk

  • Property svn:eol-style set to native
  • Property svn:keywords set to Author Date Id Revision
File size: 8.8 KB
RevLine 
[3]1MODULE trabbc
2   !!==============================================================================
3   !!                       ***  MODULE  trabbc  ***
4   !! Ocean active tracers:  bottom boundary condition
5   !!==============================================================================
[503]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   !!----------------------------------------------------------------------
[32]10#if   defined key_trabbc   ||   defined key_esopa
[3]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
[503]21   USE trdmod          ! ocean trends
22   USE trdmod_oce      ! ocean variables trends
[3]23   USE in_out_manager  ! I/O manager
[258]24   USE prtctl          ! Print control
[3]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]32   LOGICAL, PUBLIC, PARAMETER ::   lk_trabbc = .TRUE.   !: bbc flag
[3]33
[503]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
[3]37
[503]38   INTEGER , DIMENSION(jpi,jpj) ::   nbotlevt   ! ocean bottom level index at T-pt
[592]39   REAL(wp), DIMENSION(jpi,jpj) ::   qgh_trd0   ! geothermal heating trend
[3]40 
41   !! * Substitutions
42#  include "domzgr_substitute.h90"
43   !!----------------------------------------------------------------------
[503]44   !!  OPA 9.0 , LOCEAN-IPSL (2006)
[719]45   !! $Header$
[503]46   !! Software governed by the CeCILL licence (modipsl/doc/NEMO_CeCILL.txt)
[3]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      !!
[503]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   
[3]74      !!
[503]75      INTEGER, INTENT( in ) ::   kt   ! ocean time-step index
76      !!
[457]77#if defined key_vectopt_loop   &&   ! defined key_mpp_omp
[503]78      INTEGER ::   ji       ! dummy loop indices
[3]79#else
[503]80      INTEGER ::   ji, jj   ! dummy loop indices
[3]81#endif
[592]82      REAL(wp) ::   zqgh_trd  ! geothermal heat flux trend
[3]83      !!----------------------------------------------------------------------
84
[503]85      IF( kt == nit000 )   CALL tra_bbc_init      ! Initialization
[3]86
[503]87      IF( l_trdtra )   THEN         ! Save ta and sa trends
88         ztrdt(:,:,:) = ta(:,:,:) 
89         ztrds(:,:,:) = 0.e0
90      ENDIF
[3]91
[503]92      ! Add the geothermal heat flux trend on temperature
93
[3]94      SELECT CASE ( ngeo_flux )
[503]95      !
[3]96      CASE ( 1:2 )                !  geothermal heat flux
[457]97#if defined key_vectopt_loop   &&   ! defined key_mpp_omp
[3]98         DO ji = jpi+2, jpij-jpi-1   ! vector opt. (forced unrolling)
[592]99            zqgh_trd = ro0cpr * qgh_trd0(ji,1) / fse3t(ji,1,nbotlevt(ji,1) )
100            ta(ji,1,nbotlevt(ji,1)) = ta(ji,1,nbotlevt(ji,1)) + zqgh_trd
[3]101         END DO
102#else
103         DO jj = 2, jpjm1
104            DO ji = 2, jpim1
[592]105               zqgh_trd = ro0cpr * qgh_trd0(ji,jj) / fse3t(ji,jj,nbotlevt(ji,jj))
106               ta(ji,jj,nbotlevt(ji,jj)) = ta(ji,jj,nbotlevt(ji,jj)) + zqgh_trd
[3]107            END DO
108         END DO
109#endif
[503]110      END SELECT
[106]111
[503]112      IF( l_trdtra ) THEN        ! Save the geothermal heat flux trend for diagnostics
113         ztrdt(:,:,:) = ta(:,:,:) - ztrdt(:,:,:)
114         CALL trd_mod( ztrdt, ztrds, jptra_trd_bbc, 'TRA', kt )
[3]115      ENDIF
[503]116      !
117      IF(ln_ctl)   CALL prt_ctl(tab3d_1=ta, clinfo1=' bbc  - Ta: ', mask1=tmask, clinfo3='tra-ta')
118      !
[3]119   END SUBROUTINE tra_bbc
120
121
122   SUBROUTINE tra_bbc_init
123      !!----------------------------------------------------------------------
124      !!                  ***  ROUTINE tra_bbc_init  ***
125      !!
126      !! ** Purpose :   Compute once for all the trend associated with geo-
127      !!      thermal heating that will be applied at each time step at the
128      !!      bottom ocean level
129      !!
130      !! ** Method  :   Read the nambbc namelist and check the parameters.
131      !!      called at the first time step (nit000)
132      !!
133      !! ** Input   : - Namlist nambbc
134      !!              - NetCDF file  : geothermal_heating.nc ( if necessary )
135      !!
[592]136      !! ** Action  : - read/fix the geothermal heat qgh_trd0
[3]137      !!              - compute the bottom ocean level nbotlevt
138      !!----------------------------------------------------------------------
[473]139      USE iom
[503]140      !!
[3]141      INTEGER  ::   ji, jj              ! dummy loop indices
[473]142      INTEGER  ::   inum                ! temporary logical unit
[541]143
144      NAMELIST/nambbc/ngeo_flux, ngeo_flux_const 
[3]145      !!----------------------------------------------------------------------
146
[503]147      REWIND ( numnam )              ! Read Namelist nambbc : bottom momentum boundary condition
[3]148      READ   ( numnam, nambbc )
149
[503]150      !                              ! Control print
[3]151      IF(lwp) WRITE(numout,*)
152      IF(lwp) WRITE(numout,*) 'tra_bbc : tempearture Bottom Boundary Condition (bbc)'
153      IF(lwp) WRITE(numout,*) '~~~~~~~   Geothermal heatflux'
154      IF(lwp) WRITE(numout,*) '          Namelist nambbc : set bbc parameters'
155      IF(lwp) WRITE(numout,*)
156      IF(lwp) WRITE(numout,*) '             Geothermal flux           ngeo_flux       = ', ngeo_flux
157      IF(lwp) WRITE(numout,*) '             Constant geothermal flux  ngeo_flux_const = ', ngeo_flux_const
158      IF(lwp) WRITE(numout,*)
159
[503]160      !                              ! level of the ocean bottom at T-point
[3]161      DO jj = 1, jpj
162         DO ji = 1, jpi
163            nbotlevt(ji,jj) = MAX( mbathy(ji,jj)-1, 1 )
164         END DO
165      END DO
166
[503]167      SELECT CASE ( ngeo_flux )      ! initialization of geothermal heat flux
168      !
[3]169      CASE ( 0 )                ! no geothermal heat flux
170         IF(lwp) WRITE(numout,*)
171         IF(lwp) WRITE(numout,*) '             *** no geothermal heat flux'
[503]172         !
[3]173      CASE ( 1 )                ! constant flux
174         IF(lwp) WRITE(numout,*) '             *** constant heat flux  =   ', ngeo_flux_const
[592]175         qgh_trd0(:,:) = ngeo_flux_const
[503]176         !
[3]177      CASE ( 2 )                ! variable geothermal heat flux
178         ! read the geothermal fluxes in mW/m2
[503]179         !
[473]180         IF(lwp) WRITE(numout,*) '             *** variable geothermal heat flux'
181         CALL iom_open ( 'geothermal_heating.nc', inum )
[592]182         CALL iom_get ( inum, jpdom_data, 'heatflow', qgh_trd0 )
[473]183         CALL iom_close (inum)
[503]184         !
[592]185         qgh_trd0(:,:) = qgh_trd0(:,:) * 1.e-3 ! conversion in W/m2
[503]186         !
[3]187      CASE DEFAULT
[473]188         WRITE(ctmp1,*) '     bad flag value for ngeo_flux = ', ngeo_flux
189         CALL ctl_stop( ctmp1 )
[503]190         !
[3]191      END SELECT
192
193
194   END SUBROUTINE tra_bbc_init
195
196#else
197   !!----------------------------------------------------------------------
198   !!   Default option                                         Empty module
199   !!----------------------------------------------------------------------
[32]200   LOGICAL, PUBLIC, PARAMETER ::   lk_trabbc = .FALSE.  !: bbc flag
[3]201CONTAINS
202   SUBROUTINE tra_bbc( kt )           ! Empty routine
[32]203      WRITE(*,*) 'tra_bbc: You should not have seen this print! error?', kt
[3]204   END SUBROUTINE tra_bbc
205#endif
206
207   !!======================================================================
208END MODULE trabbc
Note: See TracBrowser for help on using the repository browser.