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/dev_001_GM/NEMO/OPA_SRC/TRA – NEMO

source: branches/dev_001_GM/NEMO/OPA_SRC/TRA/trabbc.F90 @ 786

Last change on this file since 786 was 786, checked in by gm, 16 years ago

dev_001_GM - merge TRC-TRA on OPA only, trabbl & zpshde not done and trdmld not OK - compilation OK

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