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 NEMO/branches/UKMO/NEMO_4.0.1_coast_wdcpl/src/OCE/TRA – NEMO

source: NEMO/branches/UKMO/NEMO_4.0.1_coast_wdcpl/src/OCE/TRA/trabbc.F90 @ 15336

Last change on this file since 15336 was 15336, checked in by jmedwards01, 3 years ago

First version of branch.

File size: 9.5 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   !!            x.y  ! 2021-10 (J. M. Edwards) Add bottom coupling
12   !!----------------------------------------------------------------------
13
14   !!----------------------------------------------------------------------
15   !!   tra_bbc       : update the tracer trend at ocean bottom
16   !!   tra_bbc_init  : initialization of geothermal heat flux trend
17   !!----------------------------------------------------------------------
18   USE oce            ! ocean variables
19   USE dom_oce        ! domain: ocean
20   USE phycst         ! physical constants
21   USE trd_oce        ! trends: ocean variables
22   USE trdtra         ! trends manager: tracers
23   !
24   USE in_out_manager ! I/O manager
25   USE iom            ! xIOS
26   USE fldread        ! read input fields
27   USE lbclnk         ! ocean lateral boundary conditions (or mpp link)
28   USE lib_mpp        ! distributed memory computing library
29   USE prtctl         ! Print control
30   USE timing         ! Timing
31
32   IMPLICIT NONE
33   PRIVATE
34
35   PUBLIC tra_bbc          ! routine called by step.F90
36   PUBLIC tra_bbc_init     ! routine called by opa.F90
37
38   !                                 !!* Namelist nambbc: bottom boundary condition *
39   LOGICAL, PUBLIC ::   ln_trabbc     !: Geothermal heat flux flag
40   INTEGER         ::   nn_geoflx     !  Geothermal flux (=1:constant flux, =2:read in file )
41   REAL(wp)        ::   rn_geoflx_cst !  Constant value of geothermal heat flux
42
43   REAL(wp), PUBLIC , ALLOCATABLE, DIMENSION(:,:) ::   qgh_trd0   ! geothermal heating trend
44
45   TYPE(FLD), ALLOCATABLE, DIMENSION(:) ::   sf_qgh   ! structure of input qgh (file informations, fields read)
46 
47   !!----------------------------------------------------------------------
48   !! NEMO/OCE 4.0 , NEMO Consortium (2018)
49   !! $Id$
50   !! Software governed by the CeCILL license (see ./LICENSE)
51   !!----------------------------------------------------------------------
52CONTAINS
53
54   SUBROUTINE tra_bbc( kt )
55      !!----------------------------------------------------------------------
56      !!                  ***  ROUTINE tra_bbc  ***
57      !!
58      !! ** Purpose :   Compute the bottom boundary contition on temperature
59      !!              associated with geothermal heating and add it to the
60      !!              general trend of temperature equations.
61      !!
62      !! ** Method  :   The geothermal heat flux set to its constant value of
63      !!              86.4 mW/m2 (Stein and Stein 1992, Huang 1999).
64      !!       The temperature trend associated to this heat flux through the
65      !!       ocean bottom can be computed once and is added to the temperature
66      !!       trend juste above the bottom at each time step:
67      !!            ta = ta + Qsf / (rau0 rcp e3T) for k= mbkt
68      !!       Where Qsf is the geothermal heat flux.
69      !!
70      !! ** Action  : - update the temperature trends with geothermal heating trend
71      !!              - send the trend for further diagnostics (ln_trdtra=T)
72      !!
73      !! References : Stein, C. A., and S. Stein, 1992, Nature, 359, 123-129.
74      !!              Emile-Geay and Madec, 2009, Ocean Science.
75      !!----------------------------------------------------------------------
76      INTEGER, INTENT(in) ::   kt   ! ocean time-step index
77      !
78      INTEGER  ::   ji, jj    ! dummy loop indices
79      REAL(wp), ALLOCATABLE, DIMENSION(:,:,:) ::   ztrdt   ! 3D workspace
80      !!----------------------------------------------------------------------
81      !
82      IF( ln_timing )   CALL timing_start('tra_bbc')
83      !
84      IF( l_trdtra )   THEN         ! Save the input temperature trend
85         ALLOCATE( ztrdt(jpi,jpj,jpk) )
86         ztrdt(:,:,:) = tsa(:,:,:,jp_tem)
87      ENDIF
88      !                             !  Add the geothermal trend on temperature
89      DO jj = 2, jpjm1
90         DO ji = 2, jpim1
91            tsa(ji,jj,mbkt(ji,jj),jp_tem) = tsa(ji,jj,mbkt(ji,jj),jp_tem) + qgh_trd0(ji,jj) / e3t_n(ji,jj,mbkt(ji,jj))
92!@!         Provisional dummy calculation
93            gfx_bed(ji, jj) = 1.0e2 * ( tsa(ji,jj,mbkt(ji,jj),jp_tem) - t_bed(ji,jj))
94         END DO
95      END DO
96      !
97      CALL lbc_lnk( 'trabbc', tsa(:,:,:,jp_tem) , 'T', 1. )
98      !
99      IF( l_trdtra ) THEN        ! Send the trend for diagnostics
100         ztrdt(:,:,:) = tsa(:,:,:,jp_tem) - ztrdt(:,:,:)
101         CALL trd_tra( kt, 'TRA', jp_tem, jptra_bbc, ztrdt )
102         DEALLOCATE( ztrdt )
103      ENDIF
104      !
105      IF(ln_ctl)   CALL prt_ctl( tab3d_1=tsa(:,:,:,jp_tem), clinfo1=' bbc  - Ta: ', mask1=tmask, clinfo3='tra-ta' )
106      !
107      IF( ln_timing )   CALL timing_stop('tra_bbc')
108      !
109   END SUBROUTINE tra_bbc
110
111
112   SUBROUTINE tra_bbc_init
113      !!----------------------------------------------------------------------
114      !!                  ***  ROUTINE tra_bbc_init  ***
115      !!
116      !! ** Purpose :   Compute once for all the trend associated with geothermal
117      !!              heating that will be applied at each time step at the
118      !!              last ocean level
119      !!
120      !! ** Method  :   Read the nambbc namelist and check the parameters.
121      !!
122      !! ** Input   : - Namlist nambbc
123      !!              - NetCDF file  : geothermal_heating.nc ( if necessary )
124      !!
125      !! ** Action  : - read/fix the geothermal heat qgh_trd0
126      !!----------------------------------------------------------------------
127      INTEGER  ::   ji, jj              ! dummy loop indices
128      INTEGER  ::   inum                ! temporary logical unit
129      INTEGER  ::   ios                 ! Local integer output status for namelist read
130      INTEGER  ::   ierror              ! local integer
131      !
132      TYPE(FLD_N)        ::   sn_qgh    ! informations about the geotherm. field to be read
133      CHARACTER(len=256) ::   cn_dir    ! Root directory for location of ssr files
134      !!
135      NAMELIST/nambbc/ln_trabbc, nn_geoflx, rn_geoflx_cst, sn_qgh, cn_dir 
136      !!----------------------------------------------------------------------
137      !
138      REWIND( numnam_ref )              ! Namelist nambbc in reference namelist : Bottom momentum boundary condition
139      READ  ( numnam_ref, nambbc, IOSTAT = ios, ERR = 901)
140901   IF( ios /= 0 )   CALL ctl_nam ( ios , 'nambbc in reference namelist' )
141      !
142      REWIND( numnam_cfg )              ! Namelist nambbc in configuration namelist : Bottom momentum boundary condition
143      READ  ( numnam_cfg, nambbc, IOSTAT = ios, ERR = 902 )
144902   IF( ios >  0 )   CALL ctl_nam ( ios , 'nambbc in configuration namelist' )
145      IF(lwm) WRITE ( numond, nambbc )
146      !
147      IF(lwp) THEN                     ! Control print
148         WRITE(numout,*)
149         WRITE(numout,*) 'tra_bbc : Bottom Boundary Condition (bbc), apply a Geothermal heating'
150         WRITE(numout,*) '~~~~~~~   '
151         WRITE(numout,*) '   Namelist nambbc : set bbc parameters'
152         WRITE(numout,*) '      Apply a geothermal heating at ocean bottom   ln_trabbc     = ', ln_trabbc
153         WRITE(numout,*) '      type of geothermal flux                      nn_geoflx     = ', nn_geoflx
154         WRITE(numout,*) '      Constant geothermal flux value               rn_geoflx_cst = ', rn_geoflx_cst
155         WRITE(numout,*)
156      ENDIF
157      !
158      IF( ln_trabbc ) THEN             !==  geothermal heating  ==!
159         !
160         ALLOCATE( qgh_trd0(jpi,jpj) )    ! allocation
161         !
162         SELECT CASE ( nn_geoflx )        ! geothermal heat flux / (rauO * Cp)
163         !
164         CASE ( 1 )                          !* constant flux
165            IF(lwp) WRITE(numout,*) '   ==>>>   constant heat flux  =   ', rn_geoflx_cst
166            qgh_trd0(:,:) = r1_rau0_rcp * rn_geoflx_cst
167            !
168         CASE ( 2 )                          !* variable geothermal heat flux : read the geothermal fluxes in mW/m2
169            IF(lwp) WRITE(numout,*) '   ==>>>   variable geothermal heat flux'
170            !
171            ALLOCATE( sf_qgh(1), STAT=ierror )
172            IF( ierror > 0 ) THEN
173               CALL ctl_stop( 'tra_bbc_init: unable to allocate sf_qgh structure' )   ;
174               RETURN
175            ENDIF
176            ALLOCATE( sf_qgh(1)%fnow(jpi,jpj,1)   )
177            IF( sn_qgh%ln_tint )   ALLOCATE( sf_qgh(1)%fdta(jpi,jpj,1,2) )
178            ! fill sf_chl with sn_chl and control print
179            CALL fld_fill( sf_qgh, (/ sn_qgh /), cn_dir, 'tra_bbc_init',   &
180               &          'bottom temperature boundary condition', 'nambbc', no_print )
181
182            CALL fld_read( nit000, 1, sf_qgh )                         ! Read qgh data
183            qgh_trd0(:,:) = r1_rau0_rcp * sf_qgh(1)%fnow(:,:,1) * 1.e-3 ! conversion in W/m2
184            !
185         CASE DEFAULT
186            WRITE(ctmp1,*) '     bad flag value for nn_geoflx = ', nn_geoflx
187            CALL ctl_stop( ctmp1 )
188         END SELECT
189         !
190      ELSE
191         IF(lwp) WRITE(numout,*) '   ==>>>   no geothermal heat flux'
192      ENDIF
193      !
194   END SUBROUTINE tra_bbc_init
195
196   !!======================================================================
197END MODULE trabbc
Note: See TracBrowser for help on using the repository browser.