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/2019/dev_r10721_KERNEL-02_Storkey_Coward_IMMERSE_first_steps/src/OCE/TRA – NEMO

source: NEMO/branches/2019/dev_r10721_KERNEL-02_Storkey_Coward_IMMERSE_first_steps/src/OCE/TRA/trabbc.F90 @ 10985

Last change on this file since 10985 was 10985, checked in by acc, 5 years ago

2019/dev_r10721_KERNEL-02_Storkey_Coward_IMMERSE_first_steps : interface changes to tra and trc routines for design compliance and consistency. Fully SETTE tested (non-AGRIF, only)

  • Property svn:keywords set to Id
File size: 9.6 KB
RevLine 
[3]1MODULE trabbc
2   !!==============================================================================
3   !!                       ***  MODULE  trabbc  ***
[2528]4   !! Ocean active tracers:  bottom boundary condition (geothermal heat flux)
[3]5   !!==============================================================================
[2528]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)
[503]11   !!----------------------------------------------------------------------
[2528]12
[3]13   !!----------------------------------------------------------------------
[6140]14   !!   tra_bbc       : update the tracer trend at ocean bottom
15   !!   tra_bbc_init  : initialization of geothermal heat flux trend
[3]16   !!----------------------------------------------------------------------
[6140]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
[3]30
31   IMPLICIT NONE
32   PRIVATE
33
34   PUBLIC tra_bbc          ! routine called by step.F90
[2528]35   PUBLIC tra_bbc_init     ! routine called by opa.F90
[3]36
[4147]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
[3]41
[6140]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)
[3]45 
46   !!----------------------------------------------------------------------
[9598]47   !! NEMO/OCE 4.0 , NEMO Consortium (2018)
[5217]48   !! $Id$
[10068]49   !! Software governed by the CeCILL license (see ./LICENSE)
[3]50   !!----------------------------------------------------------------------
51CONTAINS
52
[10985]53   SUBROUTINE tra_bbc( kt, Kmm, pts, Krhs )
[3]54      !!----------------------------------------------------------------------
55      !!                  ***  ROUTINE tra_bbc  ***
56      !!
57      !! ** Purpose :   Compute the bottom boundary contition on temperature
[1601]58      !!              associated with geothermal heating and add it to the
59      !!              general trend of temperature equations.
[3]60      !!
61      !! ** Method  :   The geothermal heat flux set to its constant value of
[1601]62      !!              86.4 mW/m2 (Stein and Stein 1992, Huang 1999).
[3]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:
[2528]66      !!            ta = ta + Qsf / (rau0 rcp e3T) for k= mbkt
[3]67      !!       Where Qsf is the geothermal heat flux.
68      !!
[6140]69      !! ** Action  : - update the temperature trends with geothermal heating trend
70      !!              - send the trend for further diagnostics (ln_trdtra=T)
[3]71      !!
[503]72      !! References : Stein, C. A., and S. Stein, 1992, Nature, 359, 123-129.
[1601]73      !!              Emile-Geay and Madec, 2009, Ocean Science.
[503]74      !!----------------------------------------------------------------------
[10985]75      INTEGER,                                   INTENT(in   ) :: kt         ! ocean time-step index
76      INTEGER,                                   INTENT(in   ) :: Kmm, Krhs  ! time level indices
77      REAL(wp), DIMENSION(jpi,jpj,jpk,jpts,jpt), INTENT(inout) :: pts        ! active tracers and RHS of tracer equation
[6140]78      !
[7753]79      INTEGER  ::   ji, jj    ! dummy loop indices
[9019]80      REAL(wp), ALLOCATABLE, DIMENSION(:,:,:) ::   ztrdt   ! 3D workspace
[3]81      !!----------------------------------------------------------------------
[2528]82      !
[9019]83      IF( ln_timing )   CALL timing_start('tra_bbc')
[3294]84      !
[6140]85      IF( l_trdtra )   THEN         ! Save the input temperature trend
[9019]86         ALLOCATE( ztrdt(jpi,jpj,jpk) )
[10985]87         ztrdt(:,:,:) = pts(:,:,:,jp_tem,Krhs)
[503]88      ENDIF
[6140]89      !                             !  Add the geothermal trend on temperature
[2528]90      DO jj = 2, jpjm1
91         DO ji = 2, jpim1
[10985]92            pts(ji,jj,mbkt(ji,jj),jp_tem,Krhs) = pts(ji,jj,mbkt(ji,jj),jp_tem,Krhs) + qgh_trd0(ji,jj) / e3t(ji,jj,mbkt(ji,jj),Kmm)
[3]93         END DO
[2528]94      END DO
95      !
[10985]96      CALL lbc_lnk( 'trabbc', pts(:,:,:,jp_tem,Krhs) , 'T', 1. )
[5397]97      !
[6140]98      IF( l_trdtra ) THEN        ! Send the trend for diagnostics
[10985]99         ztrdt(:,:,:) = pts(:,:,:,jp_tem,Krhs) - ztrdt(:,:,:)
[10946]100         CALL trd_tra( kt, Kmm, Krhs, 'TRA', jp_tem, jptra_bbc, ztrdt )
[9019]101         DEALLOCATE( ztrdt )
[3]102      ENDIF
[503]103      !
[10985]104      IF(ln_ctl)   CALL prt_ctl( tab3d_1=pts(:,:,:,jp_tem,Krhs), clinfo1=' bbc  - Ta: ', mask1=tmask, clinfo3='tra-ta' )
[503]105      !
[9019]106      IF( ln_timing )   CALL timing_stop('tra_bbc')
[3294]107      !
[3]108   END SUBROUTINE tra_bbc
109
110
111   SUBROUTINE tra_bbc_init
112      !!----------------------------------------------------------------------
113      !!                  ***  ROUTINE tra_bbc_init  ***
114      !!
[1601]115      !! ** Purpose :   Compute once for all the trend associated with geothermal
116      !!              heating that will be applied at each time step at the
117      !!              last ocean level
[3]118      !!
119      !! ** Method  :   Read the nambbc namelist and check the parameters.
120      !!
121      !! ** Input   : - Namlist nambbc
122      !!              - NetCDF file  : geothermal_heating.nc ( if necessary )
123      !!
[592]124      !! ** Action  : - read/fix the geothermal heat qgh_trd0
[3]125      !!----------------------------------------------------------------------
126      INTEGER  ::   ji, jj              ! dummy loop indices
[473]127      INTEGER  ::   inum                ! temporary logical unit
[4147]128      INTEGER  ::   ios                 ! Local integer output status for namelist read
[5397]129      INTEGER  ::   ierror              ! local integer
[4990]130      !
[5397]131      TYPE(FLD_N)        ::   sn_qgh    ! informations about the geotherm. field to be read
132      CHARACTER(len=256) ::   cn_dir    ! Root directory for location of ssr files
[9019]133      !!
[5397]134      NAMELIST/nambbc/ln_trabbc, nn_geoflx, rn_geoflx_cst, sn_qgh, cn_dir 
[3]135      !!----------------------------------------------------------------------
[6140]136      !
[4147]137      REWIND( numnam_ref )              ! Namelist nambbc in reference namelist : Bottom momentum boundary condition
138      READ  ( numnam_ref, nambbc, IOSTAT = ios, ERR = 901)
[6140]139901   IF( ios /= 0 )   CALL ctl_nam ( ios , 'nambbc in reference namelist', lwp )
140      !
[4147]141      REWIND( numnam_cfg )              ! Namelist nambbc in configuration namelist : Bottom momentum boundary condition
142      READ  ( numnam_cfg, nambbc, IOSTAT = ios, ERR = 902 )
[9168]143902   IF( ios >  0 )   CALL ctl_nam ( ios , 'nambbc in configuration namelist', lwp )
[4624]144      IF(lwm) WRITE ( numond, nambbc )
[6140]145      !
[2528]146      IF(lwp) THEN                     ! Control print
[1601]147         WRITE(numout,*)
[2528]148         WRITE(numout,*) 'tra_bbc : Bottom Boundary Condition (bbc), apply a Geothermal heating'
[1601]149         WRITE(numout,*) '~~~~~~~   '
150         WRITE(numout,*) '   Namelist nambbc : set bbc parameters'
[2528]151         WRITE(numout,*) '      Apply a geothermal heating at ocean bottom   ln_trabbc     = ', ln_trabbc
152         WRITE(numout,*) '      type of geothermal flux                      nn_geoflx     = ', nn_geoflx
153         WRITE(numout,*) '      Constant geothermal flux value               rn_geoflx_cst = ', rn_geoflx_cst
[1601]154         WRITE(numout,*)
155      ENDIF
[6140]156      !
[2528]157      IF( ln_trabbc ) THEN             !==  geothermal heating  ==!
[503]158         !
[2528]159         ALLOCATE( qgh_trd0(jpi,jpj) )    ! allocation
[503]160         !
[2528]161         SELECT CASE ( nn_geoflx )        ! geothermal heat flux / (rauO * Cp)
[503]162         !
[2528]163         CASE ( 1 )                          !* constant flux
[9190]164            IF(lwp) WRITE(numout,*) '   ==>>>   constant heat flux  =   ', rn_geoflx_cst
[7753]165            qgh_trd0(:,:) = r1_rau0_rcp * rn_geoflx_cst
[2528]166            !
167         CASE ( 2 )                          !* variable geothermal heat flux : read the geothermal fluxes in mW/m2
[9190]168            IF(lwp) WRITE(numout,*) '   ==>>>   variable geothermal heat flux'
[2528]169            !
[5397]170            ALLOCATE( sf_qgh(1), STAT=ierror )
171            IF( ierror > 0 ) THEN
172               CALL ctl_stop( 'tra_bbc_init: unable to allocate sf_qgh structure' )   ;
173               RETURN
174            ENDIF
175            ALLOCATE( sf_qgh(1)%fnow(jpi,jpj,1)   )
[9019]176            IF( sn_qgh%ln_tint )   ALLOCATE( sf_qgh(1)%fdta(jpi,jpj,1,2) )
[5397]177            ! fill sf_chl with sn_chl and control print
178            CALL fld_fill( sf_qgh, (/ sn_qgh /), cn_dir, 'tra_bbc_init',   &
[7646]179               &          'bottom temperature boundary condition', 'nambbc', no_print )
[5397]180
181            CALL fld_read( nit000, 1, sf_qgh )                         ! Read qgh data
[7753]182            qgh_trd0(:,:) = r1_rau0_rcp * sf_qgh(1)%fnow(:,:,1) * 1.e-3 ! conversion in W/m2
[5397]183            !
[2528]184         CASE DEFAULT
185            WRITE(ctmp1,*) '     bad flag value for nn_geoflx = ', nn_geoflx
186            CALL ctl_stop( ctmp1 )
187         END SELECT
[503]188         !
[2528]189      ELSE
[9190]190         IF(lwp) WRITE(numout,*) '   ==>>>   no geothermal heat flux'
[2528]191      ENDIF
[1601]192      !
[3]193   END SUBROUTINE tra_bbc_init
194
195   !!======================================================================
196END MODULE trabbc
Note: See TracBrowser for help on using the repository browser.