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/UKMO/dev_r5107_hadgem3_cplfld/trunk/NEMOGCM/NEMO/OPA_SRC/TRA – NEMO

source: branches/UKMO/dev_r5107_hadgem3_cplfld/trunk/NEMOGCM/NEMO/OPA_SRC/TRA/trabbc.F90 @ 5473

Last change on this file since 5473 was 5473, checked in by cguiavarch, 9 years ago

Clear svn keywords from UKMO/dev_r5107_hadgem3_cplfld

File size: 8.4 KB
Line 
1MODULE trabbc
2   !!==============================================================================
3   !!                       ***  MODULE  trabbc  ***
4   !! Ocean active tracers:  bottom boundary condition (geothermal heat flux)
5   !!==============================================================================
6   !! History :  OPA  ! 1999-10 (G. Madec)  original code
7   !!   NEMO     1.0  ! 2002-08 (G. Madec)  free form + modules
8   !!             -   ! 2002-11 (A. Bozec)  tra_bbc_init: original code
9   !!            3.3  ! 2010-10 (G. Madec)  dynamical allocation + suppression of key_trabbc
10   !!             -   ! 2010-11 (G. Madec)  use mbkt array (deepest ocean t-level)
11   !!----------------------------------------------------------------------
12
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 variables
18   USE dom_oce         ! domain: ocean
19   USE phycst          ! physical constants
20   USE trd_oce         ! trends: ocean variables
21   USE trdtra          ! trends manager: tracers
22   USE in_out_manager  ! I/O manager
23   USE prtctl          ! Print control
24   USE wrk_nemo        ! Memory Allocation
25   USE timing          ! Timing
26
27   IMPLICIT NONE
28   PRIVATE
29
30   PUBLIC tra_bbc          ! routine called by step.F90
31   PUBLIC tra_bbc_init     ! routine called by opa.F90
32
33   !                                 !!* Namelist nambbc: bottom boundary condition *
34   LOGICAL, PUBLIC ::   ln_trabbc     !: Geothermal heat flux flag
35   INTEGER         ::   nn_geoflx     !  Geothermal flux (=1:constant flux, =2:read in file )
36   REAL(wp)        ::   rn_geoflx_cst !  Constant value of geothermal heat flux
37
38   REAL(wp), PUBLIC, DIMENSION(:,:), ALLOCATABLE ::   qgh_trd0   ! geothermal heating trend
39 
40   !! * Substitutions
41#  include "domzgr_substitute.h90"
42   !!----------------------------------------------------------------------
43   !! NEMO/OPA 3.3 , NEMO Consortium (2010)
44   !! $Id$
45   !! Software governed by the CeCILL licence     (NEMOGCM/NEMO_CeCILL.txt)
46   !!----------------------------------------------------------------------
47CONTAINS
48
49   SUBROUTINE tra_bbc( kt )
50      !!----------------------------------------------------------------------
51      !!                  ***  ROUTINE tra_bbc  ***
52      !!
53      !! ** Purpose :   Compute the bottom boundary contition on temperature
54      !!              associated with geothermal heating and add it to the
55      !!              general trend of temperature equations.
56      !!
57      !! ** Method  :   The geothermal heat flux set to its constant value of
58      !!              86.4 mW/m2 (Stein and Stein 1992, Huang 1999).
59      !!       The temperature trend associated to this heat flux through the
60      !!       ocean bottom can be computed once and is added to the temperature
61      !!       trend juste above the bottom at each time step:
62      !!            ta = ta + Qsf / (rau0 rcp e3T) for k= mbkt
63      !!       Where Qsf is the geothermal heat flux.
64      !!
65      !! ** Action  : - update the temperature trends (ta) with the trend of
66      !!                the ocean bottom boundary condition
67      !!
68      !! References : Stein, C. A., and S. Stein, 1992, Nature, 359, 123-129.
69      !!              Emile-Geay and Madec, 2009, Ocean Science.
70      !!----------------------------------------------------------------------
71      INTEGER, INTENT(in) ::   kt   ! ocean time-step index
72      !!
73      INTEGER  ::   ji, jj, ik    ! dummy loop indices
74      REAL(wp) ::   zqgh_trd      ! geothermal heat flux trend
75      REAL(wp), POINTER, DIMENSION(:,:,:) ::   ztrdt
76      !!----------------------------------------------------------------------
77      !
78      IF( nn_timing == 1 )  CALL timing_start('tra_bbc')
79      !
80      IF( l_trdtra )   THEN         ! Save ta and sa trends
81         CALL wrk_alloc( jpi, jpj, jpk, ztrdt )
82         ztrdt(:,:,:) = tsa(:,:,:,jp_tem)
83      ENDIF
84      !
85      !                             !  Add the geothermal heat flux trend on temperature
86      DO jj = 2, jpjm1
87         DO ji = 2, jpim1
88            ik = mbkt(ji,jj)
89            zqgh_trd = qgh_trd0(ji,jj) / fse3t(ji,jj,ik)
90            tsa(ji,jj,ik,jp_tem) = tsa(ji,jj,ik,jp_tem) + zqgh_trd
91         END DO
92      END DO
93      !
94      IF( l_trdtra ) THEN        ! Save the geothermal heat flux trend for diagnostics
95         ztrdt(:,:,:) = tsa(:,:,:,jp_tem) - ztrdt(:,:,:)
96         CALL trd_tra( kt, 'TRA', jp_tem, jptra_bbc, ztrdt )
97         CALL wrk_dealloc( jpi, jpj, jpk, ztrdt )
98      ENDIF
99      !
100      IF(ln_ctl)   CALL prt_ctl( tab3d_1=tsa(:,:,:,jp_tem), clinfo1=' bbc  - Ta: ', mask1=tmask, clinfo3='tra-ta' )
101      !
102      IF( nn_timing == 1 )  CALL timing_stop('tra_bbc')
103      !
104   END SUBROUTINE tra_bbc
105
106
107   SUBROUTINE tra_bbc_init
108      !!----------------------------------------------------------------------
109      !!                  ***  ROUTINE tra_bbc_init  ***
110      !!
111      !! ** Purpose :   Compute once for all the trend associated with geothermal
112      !!              heating that will be applied at each time step at the
113      !!              last ocean level
114      !!
115      !! ** Method  :   Read the nambbc namelist and check the parameters.
116      !!
117      !! ** Input   : - Namlist nambbc
118      !!              - NetCDF file  : geothermal_heating.nc ( if necessary )
119      !!
120      !! ** Action  : - read/fix the geothermal heat qgh_trd0
121      !!----------------------------------------------------------------------
122      USE iom
123      !!
124      INTEGER  ::   ji, jj              ! dummy loop indices
125      INTEGER  ::   inum                ! temporary logical unit
126      INTEGER  ::   ios                 ! Local integer output status for namelist read
127      !
128      NAMELIST/nambbc/ln_trabbc, nn_geoflx, rn_geoflx_cst 
129      !!----------------------------------------------------------------------
130
131      REWIND( numnam_ref )              ! Namelist nambbc in reference namelist : Bottom momentum boundary condition
132      READ  ( numnam_ref, nambbc, IOSTAT = ios, ERR = 901)
133901   IF( ios /= 0 ) CALL ctl_nam ( ios , 'nambbc in reference namelist', lwp )
134
135      REWIND( numnam_cfg )              ! Namelist nambbc in configuration namelist : Bottom momentum boundary condition
136      READ  ( numnam_cfg, nambbc, IOSTAT = ios, ERR = 902 )
137902   IF( ios /= 0 ) CALL ctl_nam ( ios , 'nambbc in configuration namelist', lwp )
138      IF(lwm) WRITE ( numond, nambbc )
139
140      IF(lwp) THEN                     ! Control print
141         WRITE(numout,*)
142         WRITE(numout,*) 'tra_bbc : Bottom Boundary Condition (bbc), apply a Geothermal heating'
143         WRITE(numout,*) '~~~~~~~   '
144         WRITE(numout,*) '   Namelist nambbc : set bbc parameters'
145         WRITE(numout,*) '      Apply a geothermal heating at ocean bottom   ln_trabbc     = ', ln_trabbc
146         WRITE(numout,*) '      type of geothermal flux                      nn_geoflx     = ', nn_geoflx
147         WRITE(numout,*) '      Constant geothermal flux value               rn_geoflx_cst = ', rn_geoflx_cst
148         WRITE(numout,*)
149      ENDIF
150
151      IF( ln_trabbc ) THEN             !==  geothermal heating  ==!
152         !
153         ALLOCATE( qgh_trd0(jpi,jpj) )    ! allocation
154         !
155         SELECT CASE ( nn_geoflx )        ! geothermal heat flux / (rauO * Cp)
156         !
157         CASE ( 1 )                          !* constant flux
158            IF(lwp) WRITE(numout,*) '      *** constant heat flux  =   ', rn_geoflx_cst
159            qgh_trd0(:,:) = r1_rau0_rcp * rn_geoflx_cst
160            !
161         CASE ( 2 )                          !* variable geothermal heat flux : read the geothermal fluxes in mW/m2
162            IF(lwp) WRITE(numout,*) '      *** variable geothermal heat flux'
163            CALL iom_open ( 'geothermal_heating.nc', inum )
164            CALL iom_get  ( inum, jpdom_data, 'heatflow', qgh_trd0 )
165            CALL iom_close( inum )
166            qgh_trd0(:,:) = r1_rau0_rcp * qgh_trd0(:,:) * 1.e-3     ! conversion in W/m2
167            !
168         CASE DEFAULT
169            WRITE(ctmp1,*) '     bad flag value for nn_geoflx = ', nn_geoflx
170            CALL ctl_stop( ctmp1 )
171            !
172         END SELECT
173         !
174      ELSE
175         IF(lwp) WRITE(numout,*) '      *** no geothermal heat flux'
176      ENDIF
177      !
178   END SUBROUTINE tra_bbc_init
179
180   !!======================================================================
181END MODULE trabbc
Note: See TracBrowser for help on using the repository browser.