Ignore:
Timestamp:
Jul 15, 2020, 10:14:36 PM (5 years ago)
Author:
adurocher
Message:

Remove useless zero-initializations

File:
1 edited

Legend:

Unmodified
Added
Removed
  • LMDZ6/branches/Optimisation_LMDZ/libf/phylmd/cv3a_driver.f90

    r3762 r3763  
    634634    else !compress
    635635      nloc = len
    636       ktop1 = 0
    637       precip1 = 0
    638       cbmf1 = 0
    639       plfc1 = 0
    640       wbeff1 = 0
    641       ptop21 = 0
    642       sigd1 = 0
    643       wd1 = 0
    644       cape1 = Cape_noconv
    645       cin1 = Cin_noconv
    646       Plim11 = 0
    647       plim21 = 0
    648       supmax01 = 0
    649       asupmaxmin1 = 0
    650       epmax_diag1 = 0
    651       ft1 = 0
    652       fq1 = 0
    653       fu1 = 0
    654       fv1 = 0
    655       ma1 = 0
    656       mip1 = 0
    657       upwd1 = 0
    658       dnwd1 = 0
    659       dnwd01 = 0
    660       qcondc1 = 0
    661       ftd1 = 0
    662       fqd1 = 0
    663       asupmax1 = 0
    664       da1 = 0
    665       mp1 = 0
    666       d1a1 = 0
    667       dam1 = 0
    668       qta1 = 0
    669       evap1 = 0
    670       ep1 = 0
    671       eplaMm1 = 0
    672       wdtrainA1 = 0
    673       wdtrainS1 = 0
    674       wdtrainM1 = 0
    675       qtc1 = 0
    676       sigt1 = 0
    677       vprecip1 = 0
    678       vprecipi1 = 0
    679       phi1 = 0
    680       phi21 = 0
    681       sigij1 = 0
    682       elij1 = 0
    683       epmlmMm1 = 0
    684636      coef_convective(:) = merge(1, 0, iflag1(:) == 0)
    685637      call cv3a_driver_compressed(nloc, nd, ntra, &
     
    810762
    811763      call driver_log('cv3_undilute2')
     764      qta(:,:) = 0
     765      ep(:,:) = 0
    812766      CALL cv3_undilute2(nloc, ncum, nd, iflag, icb, icbs, nk, &
    813767                         tnk, qnk, gznk, hnk, t, q, qs, gz, &
    814768                         p, ph, h, tv, lv, lf, pbase, buoybase, plcl, &
    815769                         inb, tp, tvp, clw, hp, ep, sigp, buoy, &
    816                          frac_a, frac_s, qpreca, qta)
    817 
     770                         frac_a, frac_s, qpreca, qta)     
     771     
    818772! epmax_cape
    819773! on recalcule ep et hp
    820774      call driver_log('cv3_epmax_cape')
     775      epmax_diag(:) = 0
    821776      call cv3_epmax_fn_cape(nloc, ncum, nd &
    822777                             , ep, hp, icb, inb, clw, nk, t, h, hnk, lv, lf, frac_s &
     
    828783! -------------------------------------------------------------------
    829784      call enter_profile("cv3p_mixing")
     785      elij(:,:,:) = 0
     786      supmax(:,:) = 0
    830787      IF (iflag_mix >= 1) THEN
    831         CALL zilch(supmax, nloc*nd)
    832788        call driver_log('cv3p_mixing')
    833789        CALL cv3p_mixing(nloc, ncum, nd, nd, ntra, icb, nk, inb, &
     
    836792                         ment, qent, hent, uent, vent, nent, &
    837793                         sigij, elij, supmax, ments, qents, traent)
    838       ELSE
    839         CALL zilch(supmax, nloc*nd)
    840794      END IF
    841795      call exit_profile("cv3p_mixing")
     
    845799! -------------------------------------------------------------------
    846800
     801      cape(:) = -1
     802      cin(:) = -100000.
    847803      ptop2(:) = 0
    848804      coef_clos(:) = 1.
     805      Plim1(:) = 0
     806      plim2(:) = 0
     807      supmax0(:) = 0
     808      asupmaxmin(:) = 0
     809      cbmf(:) = 0
     810      plfc(:) = 0
     811      wbeff(:) = 0
     812      asupmax(:,:) = 0
     813
     814      ok_inhib = (iflag_mix == 2)
     815     
    849816      IF (iflag_clos == 0) THEN
    850817        call driver_log('cv3_closure')
     
    852819                         pbase, p, ph, tv, buoy, &
    853820                         sig, w0, cape, m, iflag)
    854       END IF   ! iflag_clos==0
    855 
    856       ok_inhib = iflag_mix == 2
     821      END IF   ! iflag_clos==0     
    857822
    858823      IF (iflag_clos == 1) PRINT *, ' pas d appel cv3p_closure'
     
    958923      ENDIF
    959924
     925   
     926
    960927!^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^
    961928!--- passive tracers
     
    964931      call driver_log('cv3_tracer')
    965932      call enter_profile("cv3_tracer")
     933 
     934      sigij(:,:,:) = 0   
     935      vprecip(:,:) = 0
     936      ! GLITCHY : vprecip is unused in cv3_tracer and sigij is intent in
    966937      CALL cv3_tracer(nloc, -1, ncum, nd, nd, &
    967938                      ment, sigij, da, phi, phi2, d1a, dam, &
    968939                      ep, vprecip, elij, clw, epmlmMm, eplaMm, &
    969940                      icb, inb)
     941
     942      vprecipi = 0
    970943      call exit_profile("cv3_tracer")
    971944    END IF ! ncum>0
Note: See TracChangeset for help on using the changeset viewer.