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/2020/dev_r13296_HPC-07_mocavero_mpi3/src/OCE/TRA – NEMO

source: NEMO/branches/2020/dev_r13296_HPC-07_mocavero_mpi3/src/OCE/TRA/trabbc.F90 @ 13630

Last change on this file since 13630 was 13630, checked in by mocavero, 4 years ago

Add neighborhood collectives calls in the NEMO src - ticket #2496

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