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/2017/dev_r7881_no_wrk_alloc/NEMOGCM/NEMO/OPA_SRC/TRA – NEMO

source: branches/2017/dev_r7881_no_wrk_alloc/NEMOGCM/NEMO/OPA_SRC/TRA/trabbc.F90 @ 7910

Last change on this file since 7910 was 7910, checked in by timgraham, 7 years ago

All wrk_alloc removed

  • Property svn:keywords set to Id
File size: 9.2 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   !!----------------------------------------------------------------------
47   !! NEMO/OPA 3.3 , NEMO Consortium (2010)
48   !! $Id$
49   !! Software governed by the CeCILL licence     (NEMOGCM/NEMO_CeCILL.txt)
50   !!----------------------------------------------------------------------
51CONTAINS
52
53   SUBROUTINE tra_bbc( kt )
54      !!----------------------------------------------------------------------
55      !!                  ***  ROUTINE tra_bbc  ***
56      !!
57      !! ** Purpose :   Compute the bottom boundary contition on temperature
58      !!              associated with geothermal heating and add it to the
59      !!              general trend of temperature equations.
60      !!
61      !! ** Method  :   The geothermal heat flux set to its constant value of
62      !!              86.4 mW/m2 (Stein and Stein 1992, Huang 1999).
63      !!       The temperature trend associated to this heat flux through the
64      !!       ocean bottom can be computed once and is added to the temperature
65      !!       trend juste above the bottom at each time step:
66      !!            ta = ta + Qsf / (rau0 rcp e3T) for k= mbkt
67      !!       Where Qsf is the geothermal heat flux.
68      !!
69      !! ** Action  : - update the temperature trends with geothermal heating trend
70      !!              - send the trend for further diagnostics (ln_trdtra=T)
71      !!
72      !! References : Stein, C. A., and S. Stein, 1992, Nature, 359, 123-129.
73      !!              Emile-Geay and Madec, 2009, Ocean Science.
74      !!----------------------------------------------------------------------
75      INTEGER, INTENT(in) ::   kt   ! ocean time-step index
76      !
77      INTEGER  ::   ji, jj    ! dummy loop indices
78      REAL(wp), DIMENSION(jpi,jpj,jpk) ::   ztrdt
79      !!----------------------------------------------------------------------
80      !
81      IF( nn_timing == 1 )  CALL timing_start('tra_bbc')
82      !
83      IF( l_trdtra )   THEN         ! Save the input temperature trend
84         ztrdt(:,:,:) = tsa(:,:,:,jp_tem)
85      ENDIF
86      !                             !  Add the geothermal trend on temperature
87      DO jj = 2, jpjm1
88         DO ji = 2, jpim1
89            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))
90         END DO
91      END DO
92      !
93      CALL lbc_lnk( tsa(:,:,:,jp_tem) , 'T', 1. )
94      !
95      IF( l_trdtra ) THEN        ! Send the trend for diagnostics
96         ztrdt(:,:,:) = tsa(:,:,:,jp_tem) - ztrdt(:,:,:)
97         CALL trd_tra( kt, 'TRA', jp_tem, jptra_bbc, 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      INTEGER  ::   ji, jj              ! dummy loop indices
123      INTEGER  ::   inum                ! temporary logical unit
124      INTEGER  ::   ios                 ! Local integer output status for namelist read
125      INTEGER  ::   ierror              ! local integer
126      !
127      TYPE(FLD_N)        ::   sn_qgh    ! informations about the geotherm. field to be read
128      CHARACTER(len=256) ::   cn_dir    ! Root directory for location of ssr files
129      !
130      NAMELIST/nambbc/ln_trabbc, nn_geoflx, rn_geoflx_cst, sn_qgh, cn_dir 
131      !!----------------------------------------------------------------------
132      !
133      REWIND( numnam_ref )              ! Namelist nambbc in reference namelist : Bottom momentum boundary condition
134      READ  ( numnam_ref, nambbc, IOSTAT = ios, ERR = 901)
135901   IF( ios /= 0 )   CALL ctl_nam ( ios , 'nambbc in reference namelist', lwp )
136      !
137      REWIND( numnam_cfg )              ! Namelist nambbc in configuration namelist : Bottom momentum boundary condition
138      READ  ( numnam_cfg, nambbc, IOSTAT = ios, ERR = 902 )
139902   IF( ios /= 0 )   CALL ctl_nam ( ios , 'nambbc in configuration namelist', lwp )
140      IF(lwm) WRITE ( numond, nambbc )
141      !
142      IF(lwp) THEN                     ! Control print
143         WRITE(numout,*)
144         WRITE(numout,*) 'tra_bbc : Bottom Boundary Condition (bbc), apply a Geothermal heating'
145         WRITE(numout,*) '~~~~~~~   '
146         WRITE(numout,*) '   Namelist nambbc : set bbc parameters'
147         WRITE(numout,*) '      Apply a geothermal heating at ocean bottom   ln_trabbc     = ', ln_trabbc
148         WRITE(numout,*) '      type of geothermal flux                      nn_geoflx     = ', nn_geoflx
149         WRITE(numout,*) '      Constant geothermal flux value               rn_geoflx_cst = ', rn_geoflx_cst
150         WRITE(numout,*)
151      ENDIF
152      !
153      IF( ln_trabbc ) THEN             !==  geothermal heating  ==!
154         !
155         ALLOCATE( qgh_trd0(jpi,jpj) )    ! allocation
156         !
157         SELECT CASE ( nn_geoflx )        ! geothermal heat flux / (rauO * Cp)
158         !
159         CASE ( 1 )                          !* constant flux
160            IF(lwp) WRITE(numout,*) '      *** constant heat flux  =   ', rn_geoflx_cst
161            qgh_trd0(:,:) = r1_rau0_rcp * rn_geoflx_cst
162            !
163         CASE ( 2 )                          !* variable geothermal heat flux : read the geothermal fluxes in mW/m2
164            IF(lwp) WRITE(numout,*) '      *** variable geothermal heat flux'
165            !
166            ALLOCATE( sf_qgh(1), STAT=ierror )
167            IF( ierror > 0 ) THEN
168               CALL ctl_stop( 'tra_bbc_init: unable to allocate sf_qgh structure' )   ;
169               RETURN
170            ENDIF
171            ALLOCATE( sf_qgh(1)%fnow(jpi,jpj,1)   )
172            IF( sn_qgh%ln_tint )ALLOCATE( sf_qgh(1)%fdta(jpi,jpj,1,2) )
173            ! fill sf_chl with sn_chl and control print
174            CALL fld_fill( sf_qgh, (/ sn_qgh /), cn_dir, 'tra_bbc_init',   &
175               &          'bottom temperature boundary condition', 'nambbc', no_print )
176
177            CALL fld_read( nit000, 1, sf_qgh )                         ! Read qgh data
178            qgh_trd0(:,:) = r1_rau0_rcp * sf_qgh(1)%fnow(:,:,1) * 1.e-3 ! conversion in W/m2
179            !
180         CASE DEFAULT
181            WRITE(ctmp1,*) '     bad flag value for nn_geoflx = ', nn_geoflx
182            CALL ctl_stop( ctmp1 )
183         END SELECT
184         !
185      ELSE
186         IF(lwp) WRITE(numout,*) '      *** no geothermal heat flux'
187      ENDIF
188      !
189   END SUBROUTINE tra_bbc_init
190
191   !!======================================================================
192END MODULE trabbc
Note: See TracBrowser for help on using the repository browser.