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 921 for trunk/NEMO/LIM_SRC_3/limsbc.F90 – NEMO

Ignore:
Timestamp:
2008-05-13T10:28:52+02:00 (16 years ago)
Author:
rblod
Message:

Correct indentation and print for debug in LIM3, see ticket #134, step I

File:
1 edited

Legend:

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

    r918 r921  
    8383      REAL(wp) ::   zat_u, zu_ico, zutaui, zu_u, zv_u, zmodu, zmod 
    8484      REAL(wp) ::   zat_v, zv_ico, zvtaui, zu_v, zv_v, zmodv, zsang 
    85        
     85 
    8686#if defined key_coupled     
    8787      REAL(wp), DIMENSION(jpi,jpj,jpl) ::   zalb     ! albedo of ice under overcast sky 
    8888      REAL(wp), DIMENSION(jpi,jpj,jpl) ::   zalbp    ! albedo of ice under clear sky 
    8989#endif 
    90      REAL(wp), DIMENSION(jpi,jpj) ::   ztio_u, ztio_v   ! ocean stress below sea-ice 
     90      REAL(wp), DIMENSION(jpi,jpj) ::   ztio_u, ztio_v   ! ocean stress below sea-ice 
    9191      !!--------------------------------------------------------------------- 
    92       
     92 
    9393      IF( kt == nit000 ) THEN 
    9494         IF(lwp) WRITE(numout,*) 
     
    9898 
    9999      SELECT CASE( kcpl ) 
    100       !                                           !--------------------------------! 
     100         !                                           !--------------------------------! 
    101101      CASE( 0 )                                   !  LIM 3 old stress computation  !  (at ice timestep only) 
    102102         !                                        !--------------------------------!  
     
    191191               zat_v = at_i(ji,jj) + at_i(ji,jj+1) * 0.5  
    192192 
    193 !!gm bug mixing U and V points value below     ====>>> to be corrected 
     193               !!gm bug mixing U and V points value below     ====>>> to be corrected 
    194194               zu_ico   = u_ice(ji,jj) - 0.5 * ( un(ji,jj,1) - ssu_m(ji,jj) )   ! ice-oce velocity using un and ssu_m 
    195195               zv_ico   = v_ice(ji,jj) - 0.5 * ( vn(ji,jj,1) - ssu_m(ji,jj) ) 
     
    199199               zutaui   = rhoco * zmod * ( cangvg * zu_ico - zsang * zv_ico ) 
    200200               zvtaui   = rhoco * zmod * ( cangvg * zv_ico + zsang * zu_ico ) 
    201 ! 
     201               ! 
    202202               utau(ji,jj) = ( 1.-zat_u ) * utau_oce(ji,jj) + zat_u * zutaui    ! stress at the ocean surface 
    203203               vtau(ji,jj) = ( 1.-zat_v ) * vtau_oce(ji,jj) + zat_v * zvtaui 
     
    247247#endif 
    248248      !!--------------------------------------------------------------------- 
    249       
     249 
    250250      IF( kt == nit000 ) THEN 
    251251         IF(lwp) WRITE(numout,*) 
     
    259259      ! pfrld is the lead fraction at the previous time step (actually between TRP and THD) 
    260260      ! changed to old_frld and old ht_i 
    261         
     261 
    262262      DO jj = 1, jpj 
    263263         DO ji = 1, jpi 
     
    286286            !   computation the solar flux at ocean surface 
    287287            zfcm1(ji,jj)   = pfrld(ji,jj) * qsr(ji,jj)  + ( 1. - pfrld(ji,jj) ) * fstric(ji,jj) 
    288                 ! fstric     Solar flux transmitted trough the ice 
    289                 ! qsr        Net short wave heat flux on free ocean 
    290 ! new line 
     288            ! fstric     Solar flux transmitted trough the ice 
     289            ! qsr        Net short wave heat flux on free ocean 
     290            ! new line 
    291291            fscmbq(ji,jj) = ( 1.0 - pfrld(ji,jj) ) * fstric(ji,jj) 
    292292 
     
    294294            zfcm2(ji,jj) = - zfcm1(ji,jj)                  & 
    295295               &           + iflt    * ( fscmbq(ji,jj) )   & ! total abl -> fscmbq is given to the ocean 
    296 ! fscmbq and ffltbif are obsolete 
    297 !              &           + iflt * ffltbif(ji,jj) !!! only if one category is used 
     296               ! fscmbq and ffltbif are obsolete 
     297               !              &           + iflt * ffltbif(ji,jj) !!! only if one category is used 
    298298               &           + ifral   * ( ial * qcmif(ji,jj) + (1 - ial) * qldif(ji,jj) ) / rdt_ice   & 
    299299               &           + ifrdv   * ( qfvbq(ji,jj) + qdtcn(ji,jj) ) / rdt_ice                     & 
     
    301301               &           + fheat_rpo(ji,jj) & ! contribution from ridge formation 
    302302               &           + fheat_res(ji,jj) 
    303                 ! fscmbq  Part of the solar radiation transmitted through the ice and going to the ocean 
    304                 !         computed in limthd_zdf.F90 
    305                 ! ffltbif Total heat content of the ice (brine pockets+ice) / delta_t 
    306                 ! qcmif   Energy needed to bring the ocean surface layer until its freezing (ok) 
    307                 ! qldif   heat balance of the lead (or of the open ocean) 
    308                 ! qfvbq   i think this is wrong! 
    309                 ! ---> Array used to store energy in case of total lateral ablation 
    310                 ! qfvbq latent heat uptake/release after accretion/ablation 
    311                 ! qdtcn Energy from the turbulent oceanic heat flux heat flux coming in the lead 
     303            ! fscmbq  Part of the solar radiation transmitted through the ice and going to the ocean 
     304            !         computed in limthd_zdf.F90 
     305            ! ffltbif Total heat content of the ice (brine pockets+ice) / delta_t 
     306            ! qcmif   Energy needed to bring the ocean surface layer until its freezing (ok) 
     307            ! qldif   heat balance of the lead (or of the open ocean) 
     308            ! qfvbq   i think this is wrong! 
     309            ! ---> Array used to store energy in case of total lateral ablation 
     310            ! qfvbq latent heat uptake/release after accretion/ablation 
     311            ! qdtcn Energy from the turbulent oceanic heat flux heat flux coming in the lead 
    312312 
    313313            IF ( num_sal .EQ. 2 ) zfcm2(ji,jj) = zfcm2(ji,jj) + & 
    314                                   fhbri(ji,jj) ! new contribution due to brine drainage  
     314               fhbri(ji,jj) ! new contribution due to brine drainage  
    315315 
    316316            ! bottom radiative component is sent to the computation of the 
     
    321321            qsr(ji,jj) = zfcm1(ji,jj)                                       ! solar heat flux  
    322322            qns(ji,jj) = zfcm2(ji,jj) - fdtcn(ji,jj)                        ! non solar heat flux 
    323 !                           ! fdtcn : turbulent oceanic heat flux 
    324  
    325 !!gm   this IF prevents the vertorisation of the whole loop 
     323            !                           ! fdtcn : turbulent oceanic heat flux 
     324 
     325            !!gm   this IF prevents the vertorisation of the whole loop 
    326326            IF ( ( ji .EQ. jiindx ) .AND. ( jj .EQ. jjindx) ) THEN 
    327327               WRITE(numout,*) ' lim_sbc : heat fluxes ' 
     
    352352               WRITE(numout,*) ' fheat_res : ', fheat_res(jiindx,jjindx) 
    353353            ENDIF 
    354 !!gm   end 
     354            !!gm   end 
    355355         END DO 
    356356      END DO 
    357         
     357 
    358358      !------------------------------------------! 
    359359      !      mass flux at the ocean surface      ! 
    360360      !------------------------------------------! 
    361361 
    362 !!gm   optimisation: this loop have to be merged with the previous one 
     362      !!gm   optimisation: this loop have to be merged with the previous one 
    363363      DO jj = 1, jpj 
    364364         DO ji = 1, jpi 
     
    375375            zpme = - emp(ji,jj)     * ( 1.0 - at_i(ji,jj) )  &   !  evaporation over oceanic fraction 
    376376               &   + tprecip(ji,jj) *         at_i(ji,jj)    &   !  total precipitation 
    377 ! old fashioned way                
    378 !              &   - sprecip(ji,jj) * ( 1. - pfrld(ji,jj) )  &   !  remov. snow precip over ice 
     377               ! old fashioned way                
     378               !              &   - sprecip(ji,jj) * ( 1. - pfrld(ji,jj) )  &   !  remov. snow precip over ice 
    379379               &   - sprecip(ji,jj) * ( 1. - (pfrld(ji,jj)**betas) )  &   !  remov. snow precip over ice 
    380380               &   - rdmsnif(ji,jj) / rdt_ice                &   !  freshwaterflux due to snow melting  
    381 ! new contribution from snow falling when ridging 
     381               ! new contribution from snow falling when ridging 
    382382               &   + fmmec(ji,jj) 
    383              
     383 
    384384            !  computing salt exchanges at the ice/ocean interface 
    385385            !  sice should be the same as computed with the ice model 
    386386            zfons =  ( soce - sice ) * ( rdmicif(ji,jj) / rdt_ice )  
    387 ! SOCE 
     387            ! SOCE 
    388388            zfons =  ( sss_m(ji,jj) - sice ) * ( rdmicif(ji,jj) / rdt_ice )  
    389              
    390 !CT useless            !  salt flux for constant salinity 
    391 !CT useless            fsalt(ji,jj)      =  zfons / ( sss_m(ji,jj) + epsi16 ) + fsalt_res(ji,jj) 
     389 
     390            !CT useless            !  salt flux for constant salinity 
     391            !CT useless            fsalt(ji,jj)      =  zfons / ( sss_m(ji,jj) + epsi16 ) + fsalt_res(ji,jj) 
    392392            !  salt flux for variable salinity 
    393393            zinda             = 1.0 - MAX( rzero , SIGN( rone , - ( 1.0 - pfrld(ji,jj) ) ) ) 
     
    415415         emps(:,:) =              fseqv(:,:) + fsalt_res(:,:) + fsalt_rpo(:,:) + emp(:,:) 
    416416      ENDIF 
    417        
     417 
    418418      IF( lk_dynspg_rl )    emp (:,:) = emps(:,:)      ! rigid-lid formulation : emp = emps 
    419419 
     
    442442         CALL prt_ctl( tab2d_1=freeze, clinfo1=' lim_sbc: freeze : ' ) 
    443443         CALL prt_ctl( tab3d_1=tn_ice, clinfo1=' lim_sbc: tn_ice : ', kdim=jpl ) 
    444       ENDIF  
     444      ENDIF 
    445445      !  
    446446   END SUBROUTINE lim_sbc_flx 
Note: See TracChangeset for help on using the changeset viewer.