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.
Changeset 1601 for trunk/NEMO/OPA_SRC/TRA/trabbc.F90 – NEMO

Ignore:
Timestamp:
2009-08-11T12:09:19+02:00 (15 years ago)
Author:
ctlod
Message:

Doctor naming of OPA namelist variables , see ticket: #526

File:
1 edited

Legend:

Unmodified
Added
Removed
  • trunk/NEMO/OPA_SRC/TRA/trabbc.F90

    r1152 r1601  
    1515   !!   tra_bbc_init : initialization of geothermal heat flux trend 
    1616   !!---------------------------------------------------------------------- 
    17    !! * Modules used 
    1817   USE oce             ! ocean dynamics and active tracers 
    1918   USE dom_oce         ! ocean space and time domain 
     
    3231   LOGICAL, PUBLIC, PARAMETER ::   lk_trabbc = .TRUE.   !: bbc flag 
    3332 
    34    !!* Namelist nambbc: bottom boundary condition 
    35    INTEGER  ::   ngeo_flux       = 1            ! Geothermal flux (0:no flux, 1:constant flux, 2:read in file ) 
    36    REAL(wp) ::   ngeo_flux_const = 86.4e-3      ! Constant value of geothermal heat flux 
     33   !                                         !!* Namelist nambbc: bottom boundary condition * 
     34   INTEGER  ::   nn_geoflx     = 1            ! Geothermal flux (0:no flux, 1:constant flux, 2:read in file ) 
     35   REAL(wp) ::   rn_geoflx_cst = 86.4e-3      ! Constant value of geothermal heat flux 
    3736 
    3837   INTEGER , DIMENSION(jpi,jpj) ::   nbotlevt   ! ocean bottom level index at T-pt 
     
    4241#  include "domzgr_substitute.h90" 
    4342   !!---------------------------------------------------------------------- 
    44    !!  OPA 9.0 , LOCEAN-IPSL (2006)  
     43   !! NEMO/OPA 3.2 , LOCEAN-IPSL (2009)  
    4544   !! $Id$  
    4645   !! Software governed by the CeCILL licence (modipsl/doc/NEMO_CeCILL.txt) 
     
    5453      !! 
    5554      !! ** Purpose :   Compute the bottom boundary contition on temperature  
    56       !!      associated with geothermal heating and add it to the general 
    57       !!      trend of temperature equations. 
     55      !!              associated with geothermal heating and add it to the  
     56      !!              general trend of temperature equations. 
    5857      !! 
    5958      !! ** Method  :   The geothermal heat flux set to its constant value of  
    60       !!       86.4 mW/m2 (Stein and Stein 1992, Huang 1999). 
     59      !!              86.4 mW/m2 (Stein and Stein 1992, Huang 1999). 
    6160      !!       The temperature trend associated to this heat flux through the 
    6261      !!       ocean bottom can be computed once and is added to the temperature 
     
    6968      !! 
    7069      !! References : Stein, C. A., and S. Stein, 1992, Nature, 359, 123-129. 
     70      !!              Emile-Geay and Madec, 2009, Ocean Science. 
    7171      !!---------------------------------------------------------------------- 
    7272      USE oce, ONLY :   ztrdt => ua   ! use ua as 3D workspace    
     
    7575      INTEGER, INTENT( in ) ::   kt   ! ocean time-step index 
    7676      !! 
    77 #if defined key_vectopt_loop 
    78       INTEGER ::   ji       ! dummy loop indices 
    79 #else 
    80       INTEGER ::   ji, jj   ! dummy loop indices 
    81 #endif 
     77      INTEGER  ::   ji, jj    ! dummy loop indices 
    8278      REAL(wp) ::   zqgh_trd  ! geothermal heat flux trend 
    8379      !!---------------------------------------------------------------------- 
     
    9288      ! Add the geothermal heat flux trend on temperature 
    9389 
    94       SELECT CASE ( ngeo_flux ) 
     90      SELECT CASE ( nn_geoflx ) 
    9591      ! 
    9692      CASE ( 1:2 )                !  geothermal heat flux 
    9793#if defined key_vectopt_loop 
    98          DO ji = jpi+2, jpij-jpi-1   ! vector opt. (forced unrolling) 
    99             zqgh_trd = ro0cpr * qgh_trd0(ji,1) / fse3t(ji,1,nbotlevt(ji,1) ) 
    100             ta(ji,1,nbotlevt(ji,1)) = ta(ji,1,nbotlevt(ji,1)) + zqgh_trd 
    101          END DO 
     94         DO jj = 1, 1 
     95            DO ji = jpi+2, jpij-jpi-1   ! vector opt. (forced unrolling) 
    10296#else 
    10397         DO jj = 2, jpjm1 
    10498            DO ji = 2, jpim1 
     99#endif 
    105100               zqgh_trd = ro0cpr * qgh_trd0(ji,jj) / fse3t(ji,jj,nbotlevt(ji,jj)) 
    106101               ta(ji,jj,nbotlevt(ji,jj)) = ta(ji,jj,nbotlevt(ji,jj)) + zqgh_trd 
    107102            END DO 
    108103         END DO 
    109 #endif 
    110104      END SELECT 
    111105 
     
    115109      ENDIF 
    116110      ! 
    117       IF(ln_ctl)   CALL prt_ctl(tab3d_1=ta, clinfo1=' bbc  - Ta: ', mask1=tmask, clinfo3='tra-ta') 
     111      IF(ln_ctl)   CALL prt_ctl( tab3d_1=ta, clinfo1=' bbc  - Ta: ', mask1=tmask, clinfo3='tra-ta' ) 
    118112      ! 
    119113   END SUBROUTINE tra_bbc 
     
    124118      !!                  ***  ROUTINE tra_bbc_init  *** 
    125119      !! 
    126       !! ** Purpose :   Compute once for all the trend associated with geo- 
    127       !!      thermal heating that will be applied at each time step at the 
    128       !!      bottom ocean level 
     120      !! ** Purpose :   Compute once for all the trend associated with geothermal 
     121      !!              heating that will be applied at each time step at the 
     122      !!              last ocean level 
    129123      !! 
    130124      !! ** Method  :   Read the nambbc namelist and check the parameters. 
    131       !!      called at the first time step (nit000) 
    132125      !! 
    133126      !! ** Input   : - Namlist nambbc 
     
    141134      INTEGER  ::   ji, jj              ! dummy loop indices 
    142135      INTEGER  ::   inum                ! temporary logical unit 
    143  
    144       NAMELIST/nambbc/ngeo_flux, ngeo_flux_const  
     136      !! 
     137      NAMELIST/nambbc/nn_geoflx, rn_geoflx_cst  
    145138      !!---------------------------------------------------------------------- 
    146139 
     
    148141      READ   ( numnam, nambbc ) 
    149142 
    150       !                              ! Control print 
    151       IF(lwp) WRITE(numout,*) 
    152       IF(lwp) WRITE(numout,*) 'tra_bbc : tempearture Bottom Boundary Condition (bbc)' 
    153       IF(lwp) WRITE(numout,*) '~~~~~~~   Geothermal heatflux' 
    154       IF(lwp) WRITE(numout,*) '          Namelist nambbc : set bbc parameters' 
    155       IF(lwp) WRITE(numout,*) 
    156       IF(lwp) WRITE(numout,*) '             Geothermal flux           ngeo_flux       = ', ngeo_flux 
    157       IF(lwp) WRITE(numout,*) '             Constant geothermal flux  ngeo_flux_const = ', ngeo_flux_const 
    158       IF(lwp) WRITE(numout,*) 
     143      IF(lwp) THEN                   ! Control print 
     144        WRITE(numout,*) 
     145         WRITE(numout,*) 'tra_bbc : temperature Bottom Boundary Condition (bbc), Geothermal heatflux' 
     146         WRITE(numout,*) '~~~~~~~   ' 
     147         WRITE(numout,*) '   Namelist nambbc : set bbc parameters' 
     148         WRITE(numout,*) '      Geothermal flux            nn_geoflx     = ', nn_geoflx 
     149         WRITE(numout,*) '      Constant geothermal flux   rn_geoflx_cst = ', rn_geoflx_cst 
     150         WRITE(numout,*) 
     151      ENDIF 
    159152 
    160153      !                              ! level of the ocean bottom at T-point 
     
    165158      END DO 
    166159 
    167       SELECT CASE ( ngeo_flux )      ! initialization of geothermal heat flux 
     160      SELECT CASE ( nn_geoflx )      ! initialization of geothermal heat flux 
    168161      ! 
    169162      CASE ( 0 )                ! no geothermal heat flux 
    170          IF(lwp) WRITE(numout,*) 
    171          IF(lwp) WRITE(numout,*) '             *** no geothermal heat flux' 
     163         IF(lwp) WRITE(numout,*) '      *** no geothermal heat flux' 
    172164         ! 
    173165      CASE ( 1 )                ! constant flux 
    174          IF(lwp) WRITE(numout,*) '             *** constant heat flux  =   ', ngeo_flux_const 
    175          qgh_trd0(:,:) = ngeo_flux_const 
     166         IF(lwp) WRITE(numout,*) '      *** constant heat flux  =   ', rn_geoflx_cst 
    176167         ! 
    177       CASE ( 2 )                ! variable geothermal heat flux 
    178          ! read the geothermal fluxes in mW/m2 
     168         qgh_trd0(:,:) = rn_geoflx_cst 
    179169         ! 
    180          IF(lwp) WRITE(numout,*) '             *** variable geothermal heat flux' 
     170      CASE ( 2 )                ! variable geothermal heat flux : read the geothermal fluxes in mW/m2 
     171         IF(lwp) WRITE(numout,*) '      *** variable geothermal heat flux' 
    181172         CALL iom_open ( 'geothermal_heating.nc', inum ) 
    182          CALL iom_get ( inum, jpdom_data, 'heatflow', qgh_trd0 ) 
    183          CALL iom_close (inum) 
     173         CALL iom_get  ( inum, jpdom_data, 'heatflow', qgh_trd0 ) 
     174         CALL iom_close( inum ) 
    184175         ! 
    185176         qgh_trd0(:,:) = qgh_trd0(:,:) * 1.e-3 ! conversion in W/m2 
    186177         ! 
    187178      CASE DEFAULT 
    188          WRITE(ctmp1,*) '     bad flag value for ngeo_flux = ', ngeo_flux 
     179         WRITE(ctmp1,*) '     bad flag value for nn_geoflx = ', nn_geoflx 
    189180         CALL ctl_stop( ctmp1 ) 
    190181         ! 
    191182      END SELECT 
    192  
    193  
     183      ! 
    194184   END SUBROUTINE tra_bbc_init 
    195185 
Note: See TracChangeset for help on using the changeset viewer.