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

Last change on this file since 1806 was 1601, checked in by ctlod, 15 years ago

Doctor naming of OPA namelist variables , see ticket: #526

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