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 811 for branches/dev_001_SBC/NEMO/OPA_SRC/LDF/ldfeiv.F90 – NEMO

Ignore:
Timestamp:
2008-02-07T17:00:12+01:00 (16 years ago)
Author:
ctlod
Message:

dev_001_SBC: merge with the trunk last changesets: #780, 782, 783, 784, 785, 788, 789, 793, 794

File:
1 edited

Legend:

Unmodified
Added
Removed
  • branches/dev_001_SBC/NEMO/OPA_SRC/LDF/ldfeiv.F90

    r717 r811  
    1010   !!---------------------------------------------------------------------- 
    1111   !!   ldf_eiv      : compute the eddy induced velocity coefficients 
    12    !!                  Same results but not same routine if 'key_mpp_omp' 
    13    !!                  is defined or not 
    1412   !!---------------------------------------------------------------------- 
    1513   !! * Modules used 
     
    4139 
    4240CONTAINS 
    43  
    44 # if defined key_mpp_omp 
    45    !!---------------------------------------------------------------------- 
    46    !!   'key_mpp_omp' :                  OpenMP /  NEC autotasking (j-slab) 
    47    !!---------------------------------------------------------------------- 
    48  
    49    SUBROUTINE ldf_eiv( kt ) 
    50       !!---------------------------------------------------------------------- 
    51       !!                  ***  ROUTINE ldf_eiv  *** 
    52       !! 
    53       !! ** Purpose :   Compute the eddy induced velocity coefficient from the 
    54       !!      growth rate of baroclinic instability. 
    55       !! 
    56       !! ** Method : 
    57       !! 
    58       !! ** Action :   uslp(),   : i- and j-slopes of neutral surfaces 
    59       !!               vslp()      at u- and v-points, resp. 
    60       !!               wslpi(),  : i- and j-slopes of neutral surfaces 
    61       !!               wslpj()     at w-points.  
    62       !! 
    63       !! History : 
    64       !!   8.1  !  99-03  (G. Madec, A. Jouzeau)  Original code 
    65       !!   8.5  !  02-06  (G. Madec)  Free form, F90 
    66       !!---------------------------------------------------------------------- 
    67       !! * Arguments 
    68       INTEGER, INTENT( in ) ::   kt     ! ocean time-step inedx 
    69        
    70       !! * Local declarations 
    71       INTEGER ::   ji, jj, jk           ! dummy loop indices 
    72       REAL(wp) ::   & 
    73          zfw, ze3w, zn2, zf20,       &  ! temporary scalars 
    74          zaht, zaht_min 
    75       REAL(wp), DIMENSION(jpi,jpj) ::   & 
    76          zn, zah, zhw, zross            ! workspace 
    77       !!---------------------------------------------------------------------- 
    78  
    79       IF( kt == nit000 ) THEN 
    80          IF(lwp) WRITE(numout,*) 
    81          IF(lwp) WRITE(numout,*) 'ldf_eiv : eddy induced velocity coefficients' 
    82          IF(lwp) WRITE(numout,*) '~~~~~~~   NEC autotasking / OpenMP : j-slab' 
    83       ENDIF 
    84        
    85       !                                                ! =============== 
    86       DO jj = 2, jpjm1                                 !  Vertical slab 
    87          !                                             ! =============== 
    88           
    89          ! 0. Local initialization 
    90          ! ----------------------- 
    91          zn   (:,jj) = 0.e0 
    92          zhw  (:,jj) = 5.e0 
    93          zah  (:,jj) = 0.e0 
    94          zross(:,jj) = 0.e0 
    95           
    96          ! 1. Compute lateral diffusive coefficient  
    97          ! ---------------------------------------- 
    98  
    99 !CDIR NOVERRCHK  
    100          DO jk = 1, jpk 
    101 !CDIR NOVERRCHK  
    102             DO ji = 2, jpim1 
    103                ! Take the max of N^2 and zero then take the vertical sum  
    104                ! of the square root of the resulting N^2 ( required to compute  
    105                ! internal Rossby radius Ro = .5 * sum_jpk(N) / f  
    106                zn2 = MAX( rn2(ji,jj,jk), 0.e0 ) 
    107                ze3w = fse3w(ji,jj,jk) * tmask(ji,jj,jk) 
    108                zn(ji,jj) = zn(ji,jj) + SQRT( zn2 ) * fse3w(ji,jj,jk) 
    109                ! Compute elements required for the inverse time scale of baroclinic 
    110                ! eddies using the isopycnal slopes calculated in ldfslp.F :  
    111                ! T^-1 = sqrt(m_jpk(N^2*(r1^2+r2^2)*e3w)) 
    112                zah(ji,jj) = zah(ji,jj) + zn2   & 
    113                               * ( wslpi(ji,jj,jk) * wslpi(ji,jj,jk)    & 
    114                                 + wslpj(ji,jj,jk) * wslpj(ji,jj,jk) )   & 
    115                               * ze3w 
    116                zhw(ji,jj) = zhw(ji,jj) + ze3w 
    117             END DO  
    118          END DO  
    119   
    120 !CDIR NOVERRCHK  
    121          DO ji = 2, jpim1 
    122             zfw = MAX( ABS( 2. * omega * SIN( rad * gphit(ji,jj) ) ) , 1.e-10 ) 
    123             ! Rossby radius at w-point taken < 40km and  > 2km 
    124             zross(ji,jj) = MAX( MIN( .4 * zn(ji,jj) / zfw, 40.e3 ), 2.e3 ) 
    125             ! Compute aeiw by multiplying Ro^2 and T^-1 
    126             aeiw(ji,jj) = zross(ji,jj) * zross(ji,jj) * SQRT( zah(ji,jj) / zhw(ji,jj) ) * tmask(ji,jj,1) 
    127             IF( cp_cfg == "orca" .AND. jp_cfg == 2 ) THEN   ! ORCA R02 
    128                ! Take the minimum between aeiw and aeiv0 for depth levels 
    129                ! lower than 20 (21 in w- point) 
    130                IF( mbathy(ji,jj) <= 21. ) aeiw(ji,jj) = MIN( aeiw(ji,jj), 1000. ) 
    131             ENDIF 
    132          END DO 
    133  
    134          ! Decrease the coefficient in the tropics (20N-20S)  
    135          zf20 = 2. * omega * sin( rad * 20. ) 
    136          DO ji = 2, jpim1 
    137             aeiw(ji,jj) = MIN( 1., ABS( ff(ji,jj) / zf20 ) ) * aeiw(ji,jj) 
    138          END DO 
    139    
    140          ! ORCA R05: Take the minimum between aeiw and aeiv0 
    141          IF( cp_cfg == "orca" .AND. jp_cfg == 05 ) THEN   ! ORCA R05 
    142             DO ji = 2, jpim1 
    143                aeiw(ji,jj) = MIN( aeiw(ji,jj), aeiv0 ) 
    144             END DO 
    145          ENDIF 
    146          !                                             ! =============== 
    147       END DO                                           !   End of slab 
    148       !                                                ! =============== 
    149  
    150       !,,,,,,,,,,,,,,,,,,,,,,,,,,,,,synchro,,,,,,,,,,,,,,,,,,,,,,,,,,,,,,,,,, 
    151  
    152       ! lateral boundary condition on aeiw  
    153       CALL lbc_lnk( aeiw, 'W', 1. ) 
    154  
    155       ! Average the diffusive coefficient at u- v- points  
    156       DO jj = 2, jpjm1 
    157          DO ji = fs_2, fs_jpim1   ! vector opt. 
    158             aeiu(ji,jj) = .5 * (aeiw(ji,jj) + aeiw(ji+1,jj  )) 
    159             aeiv(ji,jj) = .5 * (aeiw(ji,jj) + aeiw(ji  ,jj+1)) 
    160          END DO  
    161       END DO  
    162       !,,,,,,,,,,,,,,,,,,,,,,,,,,,,,synchro,,,,,,,,,,,,,,,,,,,,,,,,,,,,,,,,,, 
    163  
    164       ! lateral boundary condition on aeiu, aeiv  
    165       CALL lbc_lnk( aeiu, 'U', 1. ) 
    166       CALL lbc_lnk( aeiv, 'V', 1. ) 
    167  
    168       IF(ln_ctl)   THEN 
    169          CALL prt_ctl(tab2d_1=aeiu, clinfo1=' eiv  - u: ', ovlap=1) 
    170          CALL prt_ctl(tab2d_1=aeiv, clinfo1=' eiv  - v: ', ovlap=1) 
    171       ENDIF 
    172        
    173       ! ORCA R05: add a space variation on aht (=aeiv except at the equator and river mouth) 
    174       IF( cp_cfg == "orca" .AND. jp_cfg == 05 ) THEN 
    175          zf20     = 2. * omega * SIN( rad * 20. ) 
    176          zaht_min = 100.                              ! minimum value for aht 
    177          DO jj = 1, jpj 
    178             DO ji = 1, jpi 
    179                zaht      = ( 1. -  MIN( 1., ABS( ff(ji,jj) / zf20 ) ) ) * ( aht0 - zaht_min )  & 
    180                   &      + aht0 * rnfmsk(ji,jj)                          ! enhanced near river mouths 
    181                ahtu(ji,jj) = MAX( MAX( zaht_min, aeiu(ji,jj) ) + zaht, aht0 ) 
    182                ahtv(ji,jj) = MAX( MAX( zaht_min, aeiv(ji,jj) ) + zaht, aht0 ) 
    183                ahtw(ji,jj) = MAX( MAX( zaht_min, aeiw(ji,jj) ) + zaht, aht0 ) 
    184             END DO 
    185          END DO 
    186          IF(ln_ctl) THEN 
    187             CALL prt_ctl(tab2d_1=ahtu, clinfo1=' aht  - u: ', ovlap=1) 
    188             CALL prt_ctl(tab2d_1=ahtv, clinfo1=' aht  - v: ', ovlap=1) 
    189             CALL prt_ctl(tab2d_1=ahtw, clinfo1=' aht  - w: ', ovlap=1) 
    190          ENDIF 
    191       ENDIF 
    192  
    193       IF( aeiv0 == 0.e0 ) THEN 
    194          aeiu(:,:) = 0.e0 
    195          aeiv(:,:) = 0.e0 
    196          aeiw(:,:) = 0.e0 
    197       ENDIF 
    198  
    199    END SUBROUTINE ldf_eiv 
    200  
    201 # else 
    202    !!---------------------------------------------------------------------- 
    203    !!   Default key                                             k-j-i loops 
    204    !!---------------------------------------------------------------------- 
    20541 
    20642   SUBROUTINE ldf_eiv( kt ) 
     
    25288 
    25389      DO jk = 1, jpk 
    254 #  if defined key_vectopt_loop  &&  ! defined key_mpp_omp 
     90#  if defined key_vectopt_loop   
    25591!CDIR NOVERRCHK  
    25692         DO ji = 1, jpij   ! vector opt. 
     
    374210   END SUBROUTINE ldf_eiv 
    375211 
    376 # endif 
    377  
    378212#else 
    379213   !!---------------------------------------------------------------------- 
Note: See TracChangeset for help on using the changeset viewer.