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 branches/nemo_v3_3_beta/NEMOGCM/NEMO/OPA_SRC/TRA – NEMO

source: branches/nemo_v3_3_beta/NEMOGCM/NEMO/OPA_SRC/TRA/trabbc.F90 @ 2281

Last change on this file since 2281 was 2281, checked in by smasson, 14 years ago

set proper svn properties to all files...

  • Property svn:keywords set to Id
File size: 8.7 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   USE oce             ! ocean dynamics and active tracers
18   USE dom_oce         ! ocean space and time domain
19   USE phycst          ! physical constants
20   USE trdmod_oce      ! ocean trends
21   USE trdtra      ! ocean trends
22   USE in_out_manager  ! I/O manager
23   USE prtctl          ! Print control
24
25   IMPLICIT NONE
26   PRIVATE
27
28   PUBLIC tra_bbc          ! routine called by step.F90
29   PUBLIC tra_bbc_init     ! routine called by opa.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  ::   nn_geoflx     = 1            ! Geothermal flux (0:no flux, 1:constant flux, 2:read in file )
36   REAL(wp) ::   rn_geoflx_cst = 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), PUBLIC, DIMENSION(jpi,jpj) ::   qgh_trd0   ! geothermal heating trend
40 
41   !! * Substitutions
42#  include "domzgr_substitute.h90"
43   !!----------------------------------------------------------------------
44   !! NEMO/OPA 3.2 , LOCEAN-IPSL (2009)
45   !! $Id$
46   !! Software governed by the CeCILL licence  (NEMOGCM/License_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
57      !!              general 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      !!              Emile-Geay and Madec, 2009, Ocean Science.
72      !!----------------------------------------------------------------------
73      !!
74      INTEGER, INTENT( in ) ::   kt   ! ocean time-step index
75      !!
76      INTEGER  ::   ji, jj, ik    ! dummy loop indices
77      REAL(wp) ::   zqgh_trd  ! geothermal heat flux trend
78      REAL(wp), DIMENSION(:,:,:), ALLOCATABLE ::  ztrdt, ztrds
79      !!----------------------------------------------------------------------
80
81      IF( l_trdtra )   THEN         ! Save ta and sa trends
82         ALLOCATE( ztrdt(jpi,jpj,jpk) )     ;   ztrdt(:,:,:) = tsa(:,:,:,jp_tem)
83         ALLOCATE( ztrds(jpi,jpj,jpk) )     ;   ztrds(:,:,:) = 0.
84      ENDIF
85
86      ! Add the geothermal heat flux trend on temperature
87
88      SELECT CASE ( nn_geoflx )
89      !
90      CASE ( 1:2 )                !  geothermal heat flux
91#if defined key_vectopt_loop
92         DO jj = 1, 1
93            DO ji = jpi+2, jpij-jpi-1   ! vector opt. (forced unrolling)
94#else
95         DO jj = 2, jpjm1
96            DO ji = 2, jpim1
97#endif
98               ik = nbotlevt(ji,jj)
99               zqgh_trd = ro0cpr * qgh_trd0(ji,jj) / fse3t(ji,jj,ik)
100               tsa(ji,jj,ik,jp_tem) = tsa(ji,jj,ik,jp_tem) + zqgh_trd
101            END DO
102         END DO
103      END SELECT
104
105      IF( l_trdtra ) THEN        ! Save the geothermal heat flux trend for diagnostics
106         ztrdt(:,:,:) = tsa(:,:,:,jp_tem) - ztrdt(:,:,:)
107         CALL trd_tra( kt, 'TRA', jp_tem, jptra_trd_bbc, ztrdt )
108         CALL trd_tra( kt, 'TRA', jp_sal, jptra_trd_bbc, ztrds )
109         DEALLOCATE( ztrdt )   ;     DEALLOCATE( ztrds )
110      ENDIF
111      !
112      IF(ln_ctl)   CALL prt_ctl( tab3d_1=tsa(:,:,:,jp_tem), clinfo1=' bbc  - Ta: ', mask1=tmask, clinfo3='tra-ta' )
113      !
114   END SUBROUTINE tra_bbc
115
116
117   SUBROUTINE tra_bbc_init
118      !!----------------------------------------------------------------------
119      !!                  ***  ROUTINE tra_bbc_init  ***
120      !!
121      !! ** Purpose :   Compute once for all the trend associated with geothermal
122      !!              heating that will be applied at each time step at the
123      !!              last ocean level
124      !!
125      !! ** Method  :   Read the nambbc namelist and check the parameters.
126      !!
127      !! ** Input   : - Namlist nambbc
128      !!              - NetCDF file  : geothermal_heating.nc ( if necessary )
129      !!
130      !! ** Action  : - read/fix the geothermal heat qgh_trd0
131      !!              - compute the bottom ocean level nbotlevt
132      !!----------------------------------------------------------------------
133      USE iom
134      !!
135      INTEGER  ::   ji, jj              ! dummy loop indices
136      INTEGER  ::   inum                ! temporary logical unit
137      !!
138      NAMELIST/nambbc/nn_geoflx, rn_geoflx_cst 
139      !!----------------------------------------------------------------------
140
141      REWIND ( numnam )              ! Read Namelist nambbc : bottom momentum boundary condition
142      READ   ( numnam, nambbc )
143
144      IF(lwp) THEN                   ! Control print
145         WRITE(numout,*)
146         WRITE(numout,*) 'tra_bbc : temperature Bottom Boundary Condition (bbc), Geothermal heatflux'
147         WRITE(numout,*) '~~~~~~~   '
148         WRITE(numout,*) '   Namelist nambbc : set bbc parameters'
149         WRITE(numout,*) '      Geothermal flux            nn_geoflx     = ', nn_geoflx
150         WRITE(numout,*) '      Constant geothermal flux   rn_geoflx_cst = ', rn_geoflx_cst
151         WRITE(numout,*)
152      ENDIF
153
154      !                              ! level of the ocean bottom at T-point
155      DO jj = 1, jpj
156         DO ji = 1, jpi
157            nbotlevt(ji,jj) = MAX( mbathy(ji,jj)-1, 1 )
158         END DO
159      END DO
160
161      SELECT CASE ( nn_geoflx )      ! initialization of geothermal heat flux
162      !
163      CASE ( 0 )                ! no geothermal heat flux
164         IF(lwp) WRITE(numout,*) '      *** no geothermal heat flux'
165         !
166      CASE ( 1 )                ! constant flux
167         IF(lwp) WRITE(numout,*) '      *** constant heat flux  =   ', rn_geoflx_cst
168         !
169         qgh_trd0(:,:) = rn_geoflx_cst
170         !
171      CASE ( 2 )                ! variable geothermal heat flux : read the geothermal fluxes in mW/m2
172         IF(lwp) WRITE(numout,*) '      *** variable geothermal heat flux'
173         CALL iom_open ( 'geothermal_heating.nc', inum )
174         CALL iom_get  ( inum, jpdom_data, 'heatflow', qgh_trd0 )
175         CALL iom_close( inum )
176         !
177         qgh_trd0(:,:) = qgh_trd0(:,:) * 1.e-3 ! conversion in W/m2
178         !
179      CASE DEFAULT
180         WRITE(ctmp1,*) '     bad flag value for nn_geoflx = ', nn_geoflx
181         CALL ctl_stop( ctmp1 )
182         !
183      END SELECT
184      !
185   END SUBROUTINE tra_bbc_init
186
187#else
188   !!----------------------------------------------------------------------
189   !!   Default option                                         Empty module
190   !!----------------------------------------------------------------------
191   LOGICAL, PUBLIC, PARAMETER ::   lk_trabbc = .FALSE.  !: bbc flag
192CONTAINS
193   SUBROUTINE tra_bbc( kt )           ! Empty routine
194      WRITE(*,*) 'tra_bbc: You should not have seen this print! error?', kt
195   END SUBROUTINE tra_bbc
196   SUBROUTINE tra_bbc_init           ! Empty routine
197   END SUBROUTINE tra_bbc_init
198#endif
199
200   !!======================================================================
201END MODULE trabbc
Note: See TracBrowser for help on using the repository browser.