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

Last change on this file since 527 was 503, checked in by opalod, 18 years ago

nemo_v1_update_064 : CT : general trends update including the addition of mean windows analysis possibility in the mixed layer

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