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 1526 – NEMO

Changeset 1526


Ignore:
Timestamp:
2009-07-22T15:51:02+02:00 (15 years ago)
Author:
ctlod
Message:

style changes only, see ticket: #439

File:
1 edited

Legend:

Unmodified
Added
Removed
  • trunk/NEMO/LIM_SRC_3/limsbc.F90

    r1525 r1526  
    4040   REAL(wp)  ::   rone   = 1.e0 
    4141 
    42    REAL(wp), DIMENSION(jpi,jpj) ::   utau_oce, vtau_oce   !: air-ocean surface i- & j-stress            [N/m2] 
     42   REAL(wp), DIMENSION(jpi,jpj) ::   utau_oce, vtau_oce   !: air-ocean surface i- & j-stress              [N/m2] 
    4343   REAL(wp), DIMENSION(jpi,jpj) ::   tmod_io              !: modulus of the ice-ocean relative velocity   [m/s] 
    44    REAL(wp), DIMENSION(jpi,jpj) ::   ssu_mb  , ssv_mb     !: before mean ocean surface currents          [m/s] 
     44   REAL(wp), DIMENSION(jpi,jpj) ::   ssu_mb  , ssv_mb     !: before mean ocean surface currents           [m/s] 
     45 
    4546   !! * Substitutions 
    4647#  include "vectopt_loop_substitute.h90" 
    4748   !!---------------------------------------------------------------------- 
    48    !! NEMO/LIM  3.0 ,  UCL-LOCEAN-IPSL (2008)  
     49   !! NEMO/LIM  3.2 ,  UCL-LOCEAN-IPSL (2009)  
    4950   !! $Id$ 
    5051   !! Software governed by the CeCILL licence (modipsl/doc/NEMO_CeCILL.txt) 
     
    7778      !                   !                               =2  combination of 0 and 1 cases 
    7879      !! 
    79       INTEGER  ::   ji, jj           ! dummy loop indices 
    80       REAL(wp) ::   zfrldu, zfrldv   ! lead fraction at U- & V-points 
    81       REAL(wp) ::   zat_u, zu_ico, zutaui, zu_u 
    82       REAL(wp) ::   zat_v, zv_ico, zvtaui, zv_v, zsang 
    83       REAL(wp) ::   zu_ij, zu_im1j, zv_ij, zv_ijm1 
    84  
     80      INTEGER  ::   ji, jj   ! dummy loop indices 
     81      REAL(wp) ::   zfrldu, zat_u, zu_ico, zutaui, zu_u, zu_ij, zu_im1j   ! temporary scalar 
     82      REAL(wp) ::   zfrldv, zat_v, zv_ico, zvtaui, zv_v, zv_ij, zv_ijm1   !    -         - 
     83      REAL(wp) ::   zsang                                                 !    -         - 
     84      REAL(wp), DIMENSION(jpi,jpj) ::   ztio_u, ztio_v   ! ocean stress below sea-ice 
    8585#if defined key_coupled     
    8686      REAL(wp), DIMENSION(jpi,jpj,jpl) ::   zalb     ! albedo of ice under overcast sky 
    8787      REAL(wp), DIMENSION(jpi,jpj,jpl) ::   zalbp    ! albedo of ice under clear sky 
    8888#endif 
    89       REAL(wp), DIMENSION(jpi,jpj) ::   ztio_u, ztio_v   ! ocean stress below sea-ice 
    90       !!--------------------------------------------------------------------- 
     89     !!--------------------------------------------------------------------- 
    9190 
    9291      IF( kt == nit000 ) THEN 
     
    10099      CASE( 0 )                                   !  LIM 3 old stress computation  !  (at ice timestep only) 
    101100         !                                        !--------------------------------!  
    102          DO jj = 2, jpjm1                      ! ... modulus of the ice-ocean velocity 
     101         DO jj = 2, jpjm1                             !* modulus of the ice-ocean velocity 
    103102            DO ji = fs_2, fs_jpim1 
    104103               zu_ij   = u_ice(ji  ,jj) - ssu_m(ji  ,jj)               ! (i  ,j) 
     
    110109            END DO 
    111110         END DO 
    112          CALL lbc_lnk( tmod_io, 'T', 1. ) 
    113          ! ... ice stress over ocean with a ice-ocean rotation angle 
     111         CALL lbc_lnk( tmod_io, 'T', 1. )   ! lateral boundary condition 
     112         ! 
     113         !                                             !* ice stress over ocean with a ice-ocean rotation angle 
    114114         DO jj = 1, jpjm1 
    115             ! ... change the sinus angle sign in the south hemisphere 
    116             zsang  = SIGN(1.e0, gphif(1,jj) ) * sangvg 
     115            zsang  = SIGN( 1.e0, gphif(1,jj) ) * sangvg         ! change the sinus angle sign in the south hemisphere 
    117116            DO ji = 1, fs_jpim1 
    118                ! ... ice velocity relative to the ocean 
    119                zu_u = u_ice(ji,jj) - u_oce(ji,jj) 
     117               zu_u = u_ice(ji,jj) - u_oce(ji,jj)               ! ice velocity relative to the ocean 
    120118               zv_v = v_ice(ji,jj) - v_oce(ji,jj) 
    121                ! quadratic drag formulation 
     119               !                                                ! quadratic drag formulation with rotation 
    122120!!gm still an error in the rotation, but usually the angle is zero (zsang=0, cangvg=1) 
    123121               zutaui   = 0.5 * ( tmod_io(ji,jj) + tmod_io(ji+1,jj) ) * rhoco * ( cangvg * zu_u - zsang * zv_v )  
    124122               zvtaui   = 0.5 * ( tmod_io(ji,jj) + tmod_io(ji,jj+1) ) * rhoco * ( cangvg * zv_v + zsang * zu_u )  
    125                ! IMPORTANT 
    126                ! these lines are bound to prevent numerical oscillations 
    127                ! in the ice-ocean stress 
    128                ! They are physically ill-based. There is a cleaner solution 
    129                ! to try (remember discussion in Paris Gurvan) 
    130                ztio_u(ji,jj) = zutaui * exp( - ( tmod_io(ji,jj) + tmod_io(ji+1,jj) )  ) 
    131                ztio_v(ji,jj) = zvtaui * exp( - ( tmod_io(ji,jj) + tmod_io(ji,jj+1) )  )  
    132                ! 
    133             END DO 
    134          END DO 
    135  
    136          DO jj = 2, jpjm1 
     123               !                                                ! bound for too large stress values 
     124               ! IMPORTANT: the exponential below prevents numerical oscillations in the ice-ocean stress 
     125               ! This is not physically based. A cleaner solution is offer in CASE kcpl=2 
     126               ztio_u(ji,jj) = zutaui * EXP( - ( tmod_io(ji,jj) + tmod_io(ji+1,jj) )  ) 
     127               ztio_v(ji,jj) = zvtaui * EXP( - ( tmod_io(ji,jj) + tmod_io(ji,jj+1) )  )  
     128            END DO 
     129         END DO 
     130         DO jj = 2, jpjm1                                       ! stress at the surface of the ocean 
    137131            DO ji = fs_2, fs_jpim1   ! vertor opt. 
    138                ! ... open-ocean (lead) fraction at U- & V-points (from T-point values) 
    139                zfrldu = 0.5 * ( ato_i(ji,jj) + ato_i(ji+1,jj  ) ) 
     132               zfrldu = 0.5 * ( ato_i(ji,jj) + ato_i(ji+1,jj  ) )   ! open-ocean fraction at U- & V-points (from T-point values) 
    140133               zfrldv = 0.5 * ( ato_i(ji,jj) + ato_i(ji  ,jj+1) ) 
    141                ! update surface ocean stress 
     134               !                                                    ! update surface ocean stress 
    142135               utau(ji,jj) = zfrldu * utau(ji,jj) + ( 1. - zfrldu ) * ztio_u(ji,jj) 
    143136               vtau(ji,jj) = zfrldv * vtau(ji,jj) + ( 1. - zfrldv ) * ztio_v(ji,jj) 
    144                ! 
    145             END DO 
    146          END DO 
    147  
    148          ! boundary condition on the stress (utau,vtau) 
    149          CALL lbc_lnk( utau, 'U', -1. )   ;   CALL lbc_lnk( vtau, 'V', -1. ) 
     137            END DO 
     138         END DO 
     139         CALL lbc_lnk( utau, 'U', -1. )   ;   CALL lbc_lnk( vtau, 'V', -1. )   ! lateral boundary condition 
     140 
    150141         ! 
    151142         !                                        !--------------------------------! 
     
    153144         !                                        !--------------------------------!  
    154145         IF( MOD( kt-1, nn_fsbc ) == 0 ) THEN 
    155             utau_oce(:,:) = utau(:,:)             ! ... save the air-ocean stresses at ice time-step 
     146            utau_oce(:,:) = utau(:,:)                 !* save the air-ocean stresses at ice time-step 
    156147            vtau_oce(:,:) = vtau(:,:) 
    157             DO jj = 2, jpjm1                      ! ... modulus of the ice-ocean velocity 
     148            DO jj = 2, jpjm1                          !* modulus of the ice-ocean velocity 
    158149               DO ji = fs_2, fs_jpim1 
    159150                  zu_ij   = u_ice(ji  ,jj) - ssu_m(ji  ,jj)               ! (i  ,j) 
     
    165156               END DO 
    166157            END DO 
    167          CALL lbc_lnk( tmod_io, 'T', 1. ) 
     158            CALL lbc_lnk( tmod_io, 'T', 1. )          ! lateral boundary condition 
    168159         ENDIF 
    169          ! ... ice stress over ocean with a ice-ocean rotation angle 
    170          DO jj = 2, jpjm1 
    171             zsang  = SIGN(1.e0, gphif(1,jj-1) ) * sangvg 
     160         ! 
     161        DO jj = 2, jpjm1                              !* ice stress over ocean with a ice-ocean rotation angle 
     162            zsang  = SIGN(1.e0, gphif(1,jj-1) ) * sangvg        ! change the sinus angle sign in the south hemisphere 
    172163            DO ji = fs_2, fs_jpim1 
    173                ! computation of wind stress over ocean in X and Y direction 
    174                zat_u  = ( at_i(ji,jj) + at_i(ji+1,jj) ) * 0.5      ! ice area at u and V-points 
     164               zat_u  = ( at_i(ji,jj) + at_i(ji+1,jj) ) * 0.5   ! ice area at u and V-points 
    175165               zat_v  = ( at_i(ji,jj) + at_i(ji,jj+1) ) * 0.5 
    176  
    177                zu_u   = u_ice(ji,jj) - ub(ji,jj,1)                  ! u ice-ocean velocity at U-point 
    178                zv_v   = v_ice(ji,jj) - vb(ji,jj,1)                  ! v ice-ocean velocity at V-point 
    179                ! 
     166               !                                                ! (u,v) ice-ocean velocity at (U,V)-point, resp. 
     167               zu_u   = u_ice(ji,jj) - ub(ji,jj,1) 
     168               zv_v   = v_ice(ji,jj) - vb(ji,jj,1) 
     169               !                                                ! quadratic drag formulation with rotation 
    180170!!gm still an error in the rotation, but usually the angle is zero (zsang=0, cangvg=1) 
    181171               zutaui   = 0.5 * ( tmod_io(ji,jj) + tmod_io(ji+1,jj) ) * rhoco * ( cangvg * zu_u - zsang * zv_v )  
    182172               zvtaui   = 0.5 * ( tmod_io(ji,jj) + tmod_io(ji,jj+1) ) * rhoco * ( cangvg * zv_v + zsang * zu_u )  
    183  
    184                utau(ji,jj) = ( 1.- zat_u ) * utau_oce(ji,jj) + zat_u * zutaui    ! stress at the ocean surface 
     173               !                                                   ! stress at the ocean surface 
     174               utau(ji,jj) = ( 1.- zat_u ) * utau_oce(ji,jj) + zat_u * zutaui 
    185175               vtau(ji,jj) = ( 1.- zat_v ) * vtau_oce(ji,jj) + zat_v * zvtaui 
    186                !                                                    ! u ice-ocean velocity at V-point 
    187             END DO 
    188          END DO 
    189          ! boundary condition on the stress (utau,vtau) 
    190          CALL lbc_lnk( utau, 'U', -1. )   ;   CALL lbc_lnk( vtau, 'V', -1. ) 
     176            END DO 
     177         END DO 
     178         CALL lbc_lnk( utau, 'U', -1. )   ;   CALL lbc_lnk( vtau, 'V', -1. )   ! lateral boundary condition 
     179 
    191180         ! 
    192181         !                                        !--------------------------------! 
     
    194183         !                                        !--------------------------------!  
    195184         IF( MOD( kt-1, nn_fsbc ) == 0 ) THEN 
    196             utau_oce(:,:) = utau (:,:)            ! ... save the air-ocean stresses at ice time-step 
     185            utau_oce(:,:) = utau (:,:)               !* save the air-ocean stresses at ice time-step 
    197186            vtau_oce(:,:) = vtau (:,:) 
    198             ssu_mb  (:,:) = ssu_m(:,:)            ! ... save the ice-ocean velocity at ice time-step 
     187            ssu_mb  (:,:) = ssu_m(:,:)               !* save the ice-ocean velocity at ice time-step 
    199188            ssv_mb  (:,:) = ssv_m(:,:) 
    200             DO jj = 2, jpjm1                      ! ... modulus of the ice-ocean velocity 
     189            DO jj = 2, jpjm1                         !* modulus of the ice-ocean velocity 
    201190               DO ji = fs_2, fs_jpim1 
    202191                  zu_ij   = u_ice(ji  ,jj) - ssu_m(ji  ,jj)               ! (i  ,j) 
     
    208197               END DO 
    209198            END DO 
    210          CALL lbc_lnk( tmod_io, 'T', 1. ) 
     199            CALL lbc_lnk( tmod_io, 'T', 1. ) 
    211200         ENDIF 
    212          ! ... ice stress over ocean with a ice-ocean rotation angle 
    213          DO jj = 2, jpjm1 
     201         DO jj = 2, jpjm1                            !* ice stress over ocean with a ice-ocean rotation angle 
    214202            zsang  = SIGN(1.e0, gphif(1,jj-1) ) * sangvg 
    215203            DO ji = fs_2, fs_jpim1 
    216                ! computation of wind stress over ocean in X and Y direction 
    217204               zat_u = ( at_i(ji,jj) + at_i(ji+1,jj) ) * 0.5     ! ice area at u and V-points 
    218205               zat_v = ( at_i(ji,jj) + at_i(ji,jj+1) ) * 0.5  
    219  
    220                !!gm bug mixing U and V points value below     ====>>> to be corrected 
    221                zu_ico = u_ice(ji,jj) - 0.5 * ( ub(ji,jj,1) - ssu_mb(ji,jj) )   ! ice-oce velocity using un and ssu_mb 
     206               ! 
     207               zu_ico = u_ice(ji,jj) - 0.5 * ( ub(ji,jj,1) - ssu_mb(ji,jj) )   ! ice-oce velocity using ub and ssu_mb 
    222208               zv_ico = v_ice(ji,jj) - 0.5 * ( vb(ji,jj,1) - ssv_mb(ji,jj) ) 
    223209               !                                        ! quadratic drag formulation with rotation 
     
    230216            END DO 
    231217         END DO 
    232          ! boundary condition on the stress (utau,vtau) 
    233          CALL lbc_lnk( utau, 'U', -1. )   ;   CALL lbc_lnk( vtau, 'V', -1. ) 
     218         CALL lbc_lnk( utau, 'U', -1. )   ;   CALL lbc_lnk( vtau, 'V', -1. )   ! lateral boundary condition 
    234219         ! 
    235220      END SELECT 
     221 
    236222      IF(ln_ctl)   CALL prt_ctl( tab2d_1=utau, clinfo1=' lim_sbc: utau   : ', mask1=umask,   & 
    237223         &                       tab2d_2=vtau, clinfo2=' vtau    : '        , mask2=vmask ) 
     
    389375      !------------------------------------------! 
    390376 
    391       !!gm   optimisation: this loop have to be merged with the previous one 
     377!!gm   optimisation: this loop have to be merged with the previous one 
    392378      DO jj = 1, jpj 
    393379         DO ji = 1, jpi 
     
    475461   END SUBROUTINE lim_sbc_flx 
    476462 
    477  
    478463#else 
    479464   !!---------------------------------------------------------------------- 
Note: See TracChangeset for help on using the changeset viewer.