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 3294 for trunk/NEMOGCM/NEMO/OPA_SRC/ZDF/zdfbfr.F90 – NEMO

Ignore:
Timestamp:
2012-01-28T17:44:18+01:00 (12 years ago)
Author:
rblod
Message:

Merge of 3.4beta into the trunk

File:
1 edited

Legend:

Unmodified
Added
Removed
  • trunk/NEMOGCM/NEMO/OPA_SRC/ZDF/zdfbfr.F90

    r2715 r3294  
    2222   USE lib_mpp         ! distributed memory computing 
    2323   USE prtctl          ! Print control 
     24   USE timing          ! Timing 
    2425 
    2526   IMPLICIT NONE 
     
    3637   REAL(wp) ::   rn_bfrien = 30._wp      ! local factor to enhance coefficient bfri 
    3738   LOGICAL  ::   ln_bfr2d  = .false.     ! logical switch for 2D enhancement 
    38     
    39    REAL(wp), ALLOCATABLE, SAVE, DIMENSION(:,:) ::  bfrcoef2d   ! 2D bottom drag coefficient 
     39   LOGICAL , PUBLIC                            ::  ln_bfrimp = .false.  ! logical switch for implicit bottom friction 
     40   REAL(wp), ALLOCATABLE, SAVE, DIMENSION(:,:) ::  bfrcoef2d            ! 2D bottom drag coefficient 
    4041 
    4142   !! * Substitutions 
     
    8283      REAL(wp) ::   zvu, zuv, zecu, zecv   ! temporary scalars 
    8384      !!---------------------------------------------------------------------- 
    84  
     85      ! 
     86      IF( nn_timing == 1 )  CALL timing_start('zdf_bfr') 
     87      ! 
    8588      IF( nn_bfr == 2 ) THEN                 ! quadratic botton friction 
    8689         ! Calculate and store the quadratic bottom friction coefficient bfrua and bfrva 
     
    120123            &                       tab2d_2=bfrva, clinfo2=       ' v: ', mask2=vmask,ovlap=1 ) 
    121124      ENDIF 
     125 
     126      ! 
     127      IF( nn_timing == 1 )  CALL timing_stop('zdf_bfr') 
    122128      ! 
    123129   END SUBROUTINE zdf_bfr 
     
    142148      REAL(wp) ::  zfru, zfrv         !    -         - 
    143149      !! 
    144       NAMELIST/nambfr/ nn_bfr, rn_bfri1, rn_bfri2, rn_bfeb2, ln_bfr2d, rn_bfrien 
    145       !!---------------------------------------------------------------------- 
    146  
     150      NAMELIST/nambfr/ nn_bfr, rn_bfri1, rn_bfri2, rn_bfeb2, ln_bfr2d, rn_bfrien, ln_bfrimp 
     151      !!---------------------------------------------------------------------- 
     152      ! 
     153      IF( nn_timing == 1 )  CALL timing_start('zdf_bfr_init') 
     154      ! 
    147155      REWIND ( numnam )               !* Read Namelist nam_bfr : bottom momentum boundary condition 
    148156      READ   ( numnam, nambfr ) 
     
    156164      !                              ! allocate zdfbfr arrays 
    157165      IF( zdf_bfr_alloc() /= 0 )   CALL ctl_stop( 'STOP', 'zdf_bfr_init : unable to allocate arrays' ) 
     166 
     167      !                              ! Make sure ln_zdfexp=.false. when use implicit bfr 
     168      IF( ln_bfrimp .AND. ln_zdfexp ) THEN 
     169         IF(lwp) THEN 
     170            WRITE(numout,*) 
     171            WRITE(numout,*) 'Implicit bottom friction can only be used when ln_zdfexp=.false.' 
     172            WRITE(numout,*) '         but you set: ln_bfrimp=.true. and ln_zdfexp=.true.!!!!' 
     173            WRITE(ctmp1,*)  '         set either ln_zdfexp = .false or ln_bfrimp = .false.' 
     174            CALL ctl_stop( ctmp1 ) 
     175         END IF 
     176      END IF 
    158177 
    159178      SELECT CASE (nn_bfr) 
     
    207226         ! 
    208227      END SELECT 
     228      IF(lwp) WRITE(numout,*) '      implicit bottom friction switch                ln_bfrimp  = ', ln_bfrimp 
    209229      ! 
    210230      ! Basic stability check on bottom friction coefficient 
     
    253273         CALL mpp_max( zmaxbfr ) 
    254274      ENDIF 
     275      IF( .NOT.ln_bfrimp) THEN 
    255276      IF( lwp .AND. ictu + ictv > 0 ) THEN 
    256277         WRITE(numout,*) ' Bottom friction stability check failed at ', ictu, ' U-points ' 
     
    259280         WRITE(numout,*) ' Bottom friction coefficient will be reduced where necessary' 
    260281      ENDIF 
     282      ENDIF 
     283      ! 
     284      IF( nn_timing == 1 )  CALL timing_stop('zdf_bfr_init') 
    261285      ! 
    262286   END SUBROUTINE zdf_bfr_init 
Note: See TracChangeset for help on using the changeset viewer.