Ignore:
Timestamp:
Jun 11, 2014, 3:46:46 PM (10 years ago)
Author:
Laurent Fairhead
Message:

Merged trunk changes r1997:2055 into testing branch

Location:
LMDZ5/branches/testing
Files:
2 edited

Legend:

Unmodified
Added
Removed
  • LMDZ5/branches/testing

  • LMDZ5/branches/testing/libf/phylmd/cva_driver.F90

    r1999 r2056  
    22! $Id$
    33
    4 SUBROUTINE cva_driver(len, nd, ndp1, ntra, nloc, iflag_con, iflag_mix, &
    5     iflag_ice_thermo, iflag_clos, delt, t1, q1, qs1, t1_wake, q1_wake, &
    6     qs1_wake, s1_wake, u1, v1, tra1, p1, ph1, ale1, alp1, sig1feed1, &
    7     sig2feed1, wght1, iflag1, ft1, fq1, fu1, fv1, ftra1, precip1, kbas1, &
    8     ktop1, cbmf1, plcl1, plfc1, wbeff1, sig1, w01, & !input/output
    9     ptop21, sigd1, ma1, mip1, vprecip1, upwd1, dnwd1, dnwd01, qcondc1, wd1, &
    10     cape1, cin1, tvp1, ftd1, fqd1, plim11, plim21, asupmax1, supmax01, &
    11     asupmaxmin1, lalim_conv, da1, phi1, mp1, phi21, d1a1, dam1, sigij1, clw1, & ! RomP
    12     elij1, evap1, ep1, epmlmmm1, eplamm1, & ! RomP
    13     wdtraina1, wdtrainm1) ! RomP
    14   ! **************************************************************
    15   ! *
    16   ! CV_DRIVER                                                   *
    17   ! *
    18   ! *
    19   ! written by   : Sandrine Bony-Lena , 17/05/2003, 11.19.41    *
    20   ! modified by :                                               *
    21   ! **************************************************************
    22   ! **************************************************************
     4SUBROUTINE cva_driver(len, nd, ndp1, ntra, nloc, &
     5                      iflag_con, iflag_mix, iflag_ice_thermo, iflag_clos, ok_conserv_q, &
     6                      delt, t1, q1, qs1, t1_wake, q1_wake, qs1_wake, s1_wake, &
     7                      u1, v1, tra1, &
     8                      p1, ph1, &
     9                      Ale1, Alp1, &
     10                      sig1feed1, sig2feed1, wght1, &
     11                      iflag1, ft1, fq1, fu1, fv1, ftra1, &
     12                      precip1, kbas1, ktop1, &
     13                      cbmf1, plcl1, plfc1, wbeff1, &
     14                      sig1, w01, & !input/output
     15                      ptop21, sigd1, &
     16                      ma1, mip1, Vprecip1, upwd1, dnwd1, dnwd01, &
     17                      qcondc1, wd1, &
     18                      cape1, cin1, tvp1, &
     19                      ftd1, fqd1, &
     20                      Plim11, Plim21, asupmax1, supmax01, asupmaxmin1, &
     21                      lalim_conv, &
     22!!                      da1,phi1,mp1,phi21,d1a1,dam1,sigij1,clw1, &        ! RomP
     23!!                      elij1,evap1,ep1,epmlmMm1,eplaMm1, &                ! RomP
     24                      da1, phi1, mp1, phi21, d1a1, dam1, sigij1, wghti1, & ! RomP, RL
     25                      clw1, elij1, evap1, ep1, epmlmMm1, eplaMm1, &        ! RomP, RL
     26                      wdtrainA1, wdtrainM1)                                ! RomP
     27! **************************************************************
     28! *
     29! CV_DRIVER                                                   *
     30! *
     31! *
     32! written by   : Sandrine Bony-Lena , 17/05/2003, 11.19.41    *
     33! modified by :                                               *
     34! **************************************************************
     35! **************************************************************
    2336
    2437  USE dimphy
    2538  IMPLICIT NONE
    2639
    27   ! .............................START PROLOGUE............................
    28 
    29 
    30   ! All argument names (except len,nd,ntra,nloc,delt and the flags) have a
    31   ! "1" appended.
    32   ! The "1" is removed for the corresponding compressed variables.
    33   ! PARAMETERS:
    34   ! Name            Type         Usage            Description
    35   ! ----------      ----------     -------  ----------------------------
    36 
    37   ! len           Integer        Input        first (i) dimension
    38   ! nd            Integer        Input        vertical (k) dimension
    39   ! ndp1          Integer        Input        nd + 1
    40   ! ntra          Integer        Input        number of tracors
    41   ! iflag_con     Integer        Input        version of convect (3/4)
    42   ! iflag_mix     Integer        Input        version of mixing  (0/1/2)
    43   ! iflag_ice_thermo Integer        Input        accounting for ice
    44   ! thermodynamics (0/1)
    45   ! iflag_clos    Integer        Input        version of closure (0/1)
    46   ! delt          Real           Input        time step
    47   ! t1            Real           Input        temperature (sat draught envt)
    48   ! q1            Real           Input        specific hum (sat draught envt)
    49   ! qs1           Real           Input        sat specific hum (sat draught
    50   ! envt)
    51   ! t1_wake       Real           Input        temperature (unsat draught
    52   ! envt)
    53   ! q1_wake       Real           Input        specific hum(unsat draught
    54   ! envt)
    55   ! qs1_wake      Real           Input        sat specific hum(unsat draughts
    56   ! envt)
    57   ! s1_wake       Real           Input        fractionnal area covered by
    58   ! wakes
    59   ! u1            Real           Input        u-wind
    60   ! v1            Real           Input        v-wind
    61   ! tra1          Real           Input        tracors
    62   ! p1            Real           Input        full level pressure
    63   ! ph1           Real           Input        half level pressure
    64   ! ALE1          Real           Input        Available lifting Energy
    65   ! ALP1          Real           Input        Available lifting Power
    66   ! sig1feed1     Real           Input        sigma coord at lower bound of
    67   ! feeding layer
    68   ! sig2feed1     Real           Input        sigma coord at upper bound of
    69   ! feeding layer
    70   ! wght1         Real           Input        weight density determining the
    71   ! feeding mixture
    72   ! iflag1        Integer        Output       flag for Emanuel conditions
    73   ! ft1           Real           Output       temp tend
    74   ! fq1           Real           Output       spec hum tend
    75   ! fu1           Real           Output       u-wind tend
    76   ! fv1           Real           Output       v-wind tend
    77   ! ftra1         Real           Output       tracor tend
    78   ! precip1       Real           Output       precipitation
    79   ! kbas1         Integer        Output       cloud base level
    80   ! ktop1         Integer        Output       cloud top level
    81   ! cbmf1         Real           Output       cloud base mass flux
    82   ! sig1          Real           In/Out       section adiabatic updraft
    83   ! w01           Real           In/Out       vertical velocity within adiab
    84   ! updraft
    85   ! ptop21        Real           In/Out       top of entraining zone
    86   ! Ma1           Real           Output       mass flux adiabatic updraft
    87   ! mip1          Real           Output       mass flux shed by the adiabatic
    88   ! updraft
    89   ! Vprecip1      Real           Output       vertical profile of
    90   ! precipitations
    91   ! upwd1         Real           Output       total upward mass flux
    92   ! (adiab+mixed)
    93   ! dnwd1         Real           Output       saturated downward mass flux
    94   ! (mixed)
    95   ! dnwd01        Real           Output       unsaturated downward mass flux
    96   ! qcondc1       Real           Output       in-cld mixing ratio of
    97   ! condensed water
    98   ! wd1           Real           Output       downdraft velocity scale for
    99   ! sfc fluxes
    100   ! cape1         Real           Output       CAPE
    101   ! cin1          Real           Output       CIN
    102   ! tvp1          Real           Output       adiab lifted parcell virt temp
    103   ! ftd1          Real           Output       precip temp tend
    104   ! fqt1          Real           Output       precip spec hum tend
    105   ! Plim11        Real           Output
    106   ! Plim21        Real           Output
    107   ! asupmax1      Real           Output
    108   ! supmax01      Real           Output
    109   ! asupmaxmin1   Real           Output
    110 
    111   ! ftd1          Real           Output  Array of temperature tendency due to
    112   ! precipitations (K/s) of dimension ND,
    113   ! defined at same grid levels as T, Q, QS and P.
    114 
    115   ! fqd1          Real           Output  Array of specific humidity
    116   ! tendencies due to precipitations ((gm/gm)/s)
    117   ! of dimension ND, defined at same grid levels as T, Q, QS and P.
    118 
    119   ! wdtrainA1     Real           Output   precipitation detrained from
    120   ! adiabatic draught;
    121   ! used in tracer transport (cvltr)
    122   ! wdtrainM1     Real           Output   precipitation detrained from mixed
    123   ! draughts;
    124   ! used in tracer transport (cvltr)
    125   ! da1           Real           Output   used in tracer transport (cvltr)
    126   ! phi1          Real           Output   used in tracer transport (cvltr)
    127   ! mp1           Real           Output   used in tracer transport (cvltr)
    128 
    129   ! phi21         Real           Output   used in tracer transport (cvltr)
    130 
    131   ! d1a1          Real           Output   used in tracer transport (cvltr)
    132   ! dam1          Real           Output   used in tracer transport (cvltr)
    133 
    134   ! epmlmMm1      Real           Output   used in tracer transport (cvltr)
    135   ! eplaMm1       Real           Output   used in tracer transport (cvltr)
    136 
    137   ! evap1         Real           Output
    138   ! ep1           Real           Output
    139   ! sigij1        Real           Output
    140   ! elij1         Real           Output
    141 
    142 
    143   ! S. Bony, Mar 2002:
    144   ! * Several modules corresponding to different physical processes
    145   ! * Several versions of convect may be used:
    146   ! - iflag_con=3: version lmd  (previously named convect3)
    147   ! - iflag_con=4: version 4.3b (vect. version, previously convect1/2)
    148   ! + tard:     - iflag_con=5: version lmd with ice (previously named convectg)
    149   ! S. Bony, Oct 2002:
    150   ! * Vectorization of convect3 (ie version lmd)
    151 
    152   ! ..............................END PROLOGUE.............................
     40! .............................START PROLOGUE............................
     41
     42
     43! All argument names (except len,nd,ntra,nloc,delt and the flags) have a "1" appended.
     44! The "1" is removed for the corresponding compressed variables.
     45! PARAMETERS:
     46! Name            Type         Usage            Description
     47! ----------      ----------     -------  ----------------------------
     48
     49! len           Integer        Input        first (i) dimension
     50! nd            Integer        Input        vertical (k) dimension
     51! ndp1          Integer        Input        nd + 1
     52! ntra          Integer        Input        number of tracors
     53! iflag_con     Integer        Input        version of convect (3/4)
     54! iflag_mix     Integer        Input        version of mixing  (0/1/2)
     55! iflag_ice_thermo Integer        Input        accounting for ice thermodynamics (0/1)
     56! iflag_clos    Integer        Input        version of closure (0/1)
     57! ok_conserv_q  Logical        Input        when true corrections for water conservation are swtiched on
     58! delt          Real           Input        time step
     59! t1            Real           Input        temperature (sat draught envt)
     60! q1            Real           Input        specific hum (sat draught envt)
     61! qs1           Real           Input        sat specific hum (sat draught envt)
     62! t1_wake       Real           Input        temperature (unsat draught envt)
     63! q1_wake       Real           Input        specific hum(unsat draught envt)
     64! qs1_wake      Real           Input        sat specific hum(unsat draughts envt)
     65! s1_wake       Real           Input        fractionnal area covered by wakes
     66! u1            Real           Input        u-wind
     67! v1            Real           Input        v-wind
     68! tra1          Real           Input        tracors
     69! p1            Real           Input        full level pressure
     70! ph1           Real           Input        half level pressure
     71! ALE1          Real           Input        Available lifting Energy
     72! ALP1          Real           Input        Available lifting Power
     73! sig1feed1     Real           Input        sigma coord at lower bound of feeding layer
     74! sig2feed1     Real           Input        sigma coord at upper bound of feeding layer
     75! wght1         Real           Input        weight density determining the feeding mixture
     76! iflag1        Integer        Output       flag for Emanuel conditions
     77! ft1           Real           Output       temp tend
     78! fq1           Real           Output       spec hum tend
     79! fu1           Real           Output       u-wind tend
     80! fv1           Real           Output       v-wind tend
     81! ftra1         Real           Output       tracor tend
     82! precip1       Real           Output       precipitation
     83! kbas1         Integer        Output       cloud base level
     84! ktop1         Integer        Output       cloud top level
     85! cbmf1         Real           Output       cloud base mass flux
     86! sig1          Real           In/Out       section adiabatic updraft
     87! w01           Real           In/Out       vertical velocity within adiab updraft
     88! ptop21        Real           In/Out       top of entraining zone
     89! Ma1           Real           Output       mass flux adiabatic updraft
     90! mip1          Real           Output       mass flux shed by the adiabatic updraft
     91! Vprecip1      Real           Output       vertical profile of precipitations
     92! upwd1         Real           Output       total upward mass flux (adiab+mixed)
     93! dnwd1         Real           Output       saturated downward mass flux (mixed)
     94! dnwd01        Real           Output       unsaturated downward mass flux
     95! qcondc1       Real           Output       in-cld mixing ratio of condensed water
     96! wd1           Real           Output       downdraft velocity scale for sfc fluxes
     97! cape1         Real           Output       CAPE
     98! cin1          Real           Output       CIN
     99! tvp1          Real           Output       adiab lifted parcell virt temp
     100! ftd1          Real           Output       precip temp tend
     101! fqt1          Real           Output       precip spec hum tend
     102! Plim11        Real           Output
     103! Plim21        Real           Output
     104! asupmax1      Real           Output
     105! supmax01      Real           Output
     106! asupmaxmin1   Real           Output
     107
     108! ftd1          Real           Output  Array of temperature tendency due to precipitations (K/s) of dimension ND,
     109!                                      defined at same grid levels as T, Q, QS and P.
     110
     111! fqd1          Real           Output  Array of specific humidity tendencies due to precipitations ((gm/gm)/s)
     112!                                      of dimension ND, defined at same grid levels as T, Q, QS and P.
     113
     114! wdtrainA1     Real           Output   precipitation detrained from adiabatic draught;
     115!                                         used in tracer transport (cvltr)
     116! wdtrainM1     Real           Output   precipitation detrained from mixed draughts;
     117!                                         used in tracer transport (cvltr)
     118! da1           Real           Output     used in tracer transport (cvltr)
     119! phi1          Real           Output     used in tracer transport (cvltr)
     120! mp1           Real           Output     used in tracer transport (cvltr)
     121                                         
     122! phi21         Real           Output     used in tracer transport (cvltr)
     123                                         
     124! d1a1          Real           Output     used in tracer transport (cvltr)
     125! dam1          Real           Output     used in tracer transport (cvltr)
     126                                         
     127! epmlmMm1      Real           Output     used in tracer transport (cvltr)
     128! eplaMm1       Real           Output     used in tracer transport (cvltr)
     129                                         
     130! evap1         Real           Output   
     131! ep1           Real           Output   
     132! sigij1        Real           Output     used in tracer transport (cvltr)
     133! elij1         Real           Output
     134! wghti1        Real           Output   final weight of the feeding layers,
     135!                                         used in tracer transport (cvltr)
     136
     137
     138! S. Bony, Mar 2002:
     139! * Several modules corresponding to different physical processes
     140! * Several versions of convect may be used:
     141!         - iflag_con=3: version lmd  (previously named convect3)
     142!         - iflag_con=4: version 4.3b (vect. version, previously convect1/2)
     143! + tard: - iflag_con=5: version lmd with ice (previously named convectg)
     144! S. Bony, Oct 2002:
     145! * Vectorization of convect3 (ie version lmd)
     146
     147! ..............................END PROLOGUE.............................
    153148
    154149
    155150  include "dimensions.h"
    156   ! cccc#include "dimphy.h"
     151!!!!!#include "dimphy.h"
    157152  include 'iniprint.h'
    158153
    159154
    160   ! Input
     155! Input
    161156  INTEGER len
    162157  INTEGER nd
     
    167162  INTEGER iflag_ice_thermo
    168163  INTEGER iflag_clos
     164  LOGICAL ok_conserv_q
    169165  REAL delt
    170166  REAL t1(len, nd)
     
    180176  REAL p1(len, nd)
    181177  REAL ph1(len, ndp1)
    182   REAL ale1(len)
    183   REAL alp1(len)
     178  REAL Ale1(len)
     179  REAL Alp1(len)
    184180  REAL sig1feed1 ! pressure at lower bound of feeding layer
    185181  REAL sig2feed1 ! pressure at upper bound of feeding layer
    186182  REAL wght1(nd) ! weight density determining the feeding mixture
    187183
    188   ! Output
     184! Output
    189185  INTEGER iflag1(len)
    190186  REAL ft1(len, nd)
     
    206202  REAL ma1(len, nd)
    207203  REAL mip1(len, nd)
    208   ! real Vprecip1(len,nd)
     204! real Vprecip1(len,nd)
    209205  REAL vprecip1(len, nd+1)
    210206  REAL upwd1(len, nd)
     
    217213  REAL tvp1(len, nd)
    218214
    219   ! AC!
    220   ! !      real da1(len,nd),phi1(len,nd,nd)
    221   ! !      real da(len,nd),phi(len,nd,nd)
    222   ! AC!
     215!AC!
     216!!      real da1(len,nd),phi1(len,nd,nd)
     217!!      real da(len,nd),phi(len,nd,nd)
     218!AC!
    223219  REAL ftd1(len, nd)
    224220  REAL fqd1(len, nd)
    225   REAL plim11(len)
    226   REAL plim21(len)
     221  REAL Plim11(len)
     222  REAL Plim21(len)
    227223  REAL asupmax1(len, nd)
    228224  REAL supmax01(len)
    229225  REAL asupmaxmin1(len)
    230226  INTEGER lalim_conv(len)
    231   ! RomP >>>
    232   REAL wdtraina1(len, nd), wdtrainm1(len, nd)
     227! RomP >>>
     228  REAL wdtrainA1(len, nd), wdtrainM1(len, nd)
    233229  REAL da1(len, nd), phi1(len, nd, nd), mp1(len, nd)
    234   REAL epmlmmm1(len, nd, nd), eplamm1(len, nd)
     230  REAL epmlmMm1(len, nd, nd), eplaMm1(len, nd)
    235231  REAL evap1(len, nd), ep1(len, nd)
    236232  REAL sigij1(len, nd, nd), elij1(len, nd, nd)
     233!JYG,RL
     234  REAL wghti1(len, nd) ! final weight of the feeding layers
     235!JYG,RL
    237236  REAL phi21(len, nd, nd)
    238237  REAL d1a1(len, nd), dam1(len, nd)
    239   ! RomP <<<
    240 
    241   ! -------------------------------------------------------------------
    242   ! Prolog by Kerry Emanuel.
    243   ! -------------------------------------------------------------------
    244   ! --- ARGUMENTS
    245   ! -------------------------------------------------------------------
    246   ! --- On input:
    247 
    248   ! t:   Array of absolute temperature (K) of dimension ND, with first
    249   ! index corresponding to lowest model level. Note that this array
    250   ! will be altered by the subroutine if dry convective adjustment
    251   ! occurs and if IPBL is not equal to 0.
    252 
    253   ! q:   Array of specific humidity (gm/gm) of dimension ND, with first
    254   ! index corresponding to lowest model level. Must be defined
    255   ! at same grid levels as T. Note that this array will be altered
    256   ! if dry convective adjustment occurs and if IPBL is not equal to 0.
    257 
    258   ! qs:  Array of saturation specific humidity of dimension ND, with first
    259   ! index corresponding to lowest model level. Must be defined
    260   ! at same grid levels as T. Note that this array will be altered
    261   ! if dry convective adjustment occurs and if IPBL is not equal to 0.
    262 
    263   ! t_wake: Array of absolute temperature (K), seen by unsaturated draughts,
    264   ! of dimension ND, with first index corresponding to lowest model level.
    265 
    266   ! q_wake: Array of specific humidity (gm/gm), seen by unsaturated draughts,
    267   ! of dimension ND, with first index corresponding to lowest model level.
    268   ! Must be defined at same grid levels as T.
    269 
    270   ! qs_wake: Array of saturation specific humidity, seen by unsaturated
    271   ! draughts,
    272   ! of dimension ND, with first index corresponding to lowest model level.
    273   ! Must be defined at same grid levels as T.
    274 
    275   ! s_wake: Array of fractionnal area occupied by the wakes.
    276 
    277   ! u:   Array of zonal wind velocity (m/s) of dimension ND, witth first
    278   ! index corresponding with the lowest model level. Defined at
    279   ! same levels as T. Note that this array will be altered if
    280   ! dry convective adjustment occurs and if IPBL is not equal to 0.
    281 
    282   ! v:   Same as u but for meridional velocity.
    283 
    284   ! tra: Array of passive tracer mixing ratio, of dimensions (ND,NTRA),
    285   ! where NTRA is the number of different tracers. If no
    286   ! convective tracer transport is needed, define a dummy
    287   ! input array of dimension (ND,1). Tracers are defined at
    288   ! same vertical levels as T. Note that this array will be altered
    289   ! if dry convective adjustment occurs and if IPBL is not equal to 0.
    290 
    291   ! p:   Array of pressure (mb) of dimension ND, with first
    292   ! index corresponding to lowest model level. Must be defined
    293   ! at same grid levels as T.
    294 
    295   ! ph:  Array of pressure (mb) of dimension ND+1, with first index
    296   ! corresponding to lowest level. These pressures are defined at
    297   ! levels intermediate between those of P, T, Q and QS. The first
    298   ! value of PH should be greater than (i.e. at a lower level than)
    299   ! the first value of the array P.
    300 
    301   ! ALE:  Available lifting Energy
    302 
    303   ! ALP:  Available lifting Power
    304 
    305   ! nl:  The maximum number of levels to which convection can penetrate, plus
    306   ! 1.
    307   ! NL MUST be less than or equal to ND-1.
    308 
    309   ! delt: The model time step (sec) between calls to CONVECT
    310 
    311   ! ----------------------------------------------------------------------------
    312   ! ---   On Output:
    313 
    314   ! iflag: An output integer whose value denotes the following:
    315   ! VALUE   INTERPRETATION
    316   ! -----   --------------
    317   ! 0     Moist convection occurs.
    318   ! 1     Moist convection occurs, but a CFL condition
    319   ! on the subsidence warming is violated. This
    320   ! does not cause the scheme to terminate.
    321   ! 2     Moist convection, but no precip because ep(inb) lt 0.0001
    322   ! 3     No moist convection because new cbmf is 0 and old cbmf is 0.
    323   ! 4     No moist convection; atmosphere is not
    324   ! unstable
    325   ! 6     No moist convection because ihmin le minorig.
    326   ! 7     No moist convection because unreasonable
    327   ! parcel level temperature or specific humidity.
    328   ! 8     No moist convection: lifted condensation
    329   ! level is above the 200 mb level.
    330   ! 9     No moist convection: cloud base is higher
    331   ! then the level NL-1.
    332 
    333   ! ft:   Array of temperature tendency (K/s) of dimension ND, defined at
    334   ! same
    335   ! grid levels as T, Q, QS and P.
    336 
    337   ! fq:   Array of specific humidity tendencies ((gm/gm)/s) of dimension ND,
    338   ! defined at same grid levels as T, Q, QS and P.
    339 
    340   ! fu:   Array of forcing of zonal velocity (m/s^2) of dimension ND,
    341   ! defined at same grid levels as T.
    342 
    343   ! fv:   Same as FU, but for forcing of meridional velocity.
    344 
    345   ! ftra: Array of forcing of tracer content, in tracer mixing ratio per
    346   ! second, defined at same levels as T. Dimensioned (ND,NTRA).
    347 
    348   ! precip: Scalar convective precipitation rate (mm/day).
    349 
    350   ! wd:   A convective downdraft velocity scale. For use in surface
    351   ! flux parameterizations. See convect.ps file for details.
    352 
    353   ! tprime: A convective downdraft temperature perturbation scale (K).
    354   ! For use in surface flux parameterizations. See convect.ps
    355   ! file for details.
    356 
    357   ! qprime: A convective downdraft specific humidity
    358   ! perturbation scale (gm/gm).
    359   ! For use in surface flux parameterizations. See convect.ps
    360   ! file for details.
    361 
    362   ! cbmf: The cloud base mass flux ((kg/m**2)/s). THIS SCALAR VALUE MUST
    363   ! BE STORED BY THE CALLING PROGRAM AND RETURNED TO CONVECT AT
    364   ! ITS NEXT CALL. That is, the value of CBMF must be "remembered"
    365   ! by the calling program between calls to CONVECT.
    366 
    367   ! det:   Array of detrainment mass flux of dimension ND.
    368   ! -------------------------------------------------------------------
    369 
    370   ! Local arrays
     238! RomP <<<
     239
     240! -------------------------------------------------------------------
     241! Prolog by Kerry Emanuel.
     242! -------------------------------------------------------------------
     243! --- ARGUMENTS
     244! -------------------------------------------------------------------
     245! --- On input:
     246
     247! t:   Array of absolute temperature (K) of dimension ND, with first
     248! index corresponding to lowest model level. Note that this array
     249! will be altered by the subroutine if dry convective adjustment
     250! occurs and if IPBL is not equal to 0.
     251
     252! q:   Array of specific humidity (gm/gm) of dimension ND, with first
     253! index corresponding to lowest model level. Must be defined
     254! at same grid levels as T. Note that this array will be altered
     255! if dry convective adjustment occurs and if IPBL is not equal to 0.
     256
     257! qs:  Array of saturation specific humidity of dimension ND, with first
     258! index corresponding to lowest model level. Must be defined
     259! at same grid levels as T. Note that this array will be altered
     260! if dry convective adjustment occurs and if IPBL is not equal to 0.
     261
     262! t_wake: Array of absolute temperature (K), seen by unsaturated draughts,
     263! of dimension ND, with first index corresponding to lowest model level.
     264
     265! q_wake: Array of specific humidity (gm/gm), seen by unsaturated draughts,
     266! of dimension ND, with first index corresponding to lowest model level.
     267! Must be defined at same grid levels as T.
     268
     269! qs_wake: Array of saturation specific humidity, seen by unsaturated draughts,
     270! of dimension ND, with first index corresponding to lowest model level.
     271! Must be defined at same grid levels as T.
     272
     273! s_wake: Array of fractionnal area occupied by the wakes.
     274
     275! u:   Array of zonal wind velocity (m/s) of dimension ND, witth first
     276! index corresponding with the lowest model level. Defined at
     277! same levels as T. Note that this array will be altered if
     278! dry convective adjustment occurs and if IPBL is not equal to 0.
     279
     280! v:   Same as u but for meridional velocity.
     281
     282! tra: Array of passive tracer mixing ratio, of dimensions (ND,NTRA),
     283! where NTRA is the number of different tracers. If no
     284! convective tracer transport is needed, define a dummy
     285! input array of dimension (ND,1). Tracers are defined at
     286! same vertical levels as T. Note that this array will be altered
     287! if dry convective adjustment occurs and if IPBL is not equal to 0.
     288
     289! p:   Array of pressure (mb) of dimension ND, with first
     290! index corresponding to lowest model level. Must be defined
     291! at same grid levels as T.
     292
     293! ph:  Array of pressure (mb) of dimension ND+1, with first index
     294! corresponding to lowest level. These pressures are defined at
     295! levels intermediate between those of P, T, Q and QS. The first
     296! value of PH should be greater than (i.e. at a lower level than)
     297! the first value of the array P.
     298
     299! ALE:  Available lifting Energy
     300
     301! ALP:  Available lifting Power
     302
     303! nl:  The maximum number of levels to which convection can penetrate, plus 1.
     304!       NL MUST be less than or equal to ND-1.
     305
     306! delt: The model time step (sec) between calls to CONVECT
     307
     308! ----------------------------------------------------------------------------
     309! ---   On Output:
     310
     311! iflag: An output integer whose value denotes the following:
     312!       VALUE   INTERPRETATION
     313!       -----   --------------
     314!         0     Moist convection occurs.
     315!         1     Moist convection occurs, but a CFL condition
     316!               on the subsidence warming is violated. This
     317!               does not cause the scheme to terminate.
     318!         2     Moist convection, but no precip because ep(inb) lt 0.0001
     319!         3     No moist convection because new cbmf is 0 and old cbmf is 0.
     320!         4     No moist convection; atmosphere is not
     321!               unstable
     322!         6     No moist convection because ihmin le minorig.
     323!         7     No moist convection because unreasonable
     324!               parcel level temperature or specific humidity.
     325!         8     No moist convection: lifted condensation
     326!               level is above the 200 mb level.
     327!         9     No moist convection: cloud base is higher
     328!               then the level NL-1.
     329
     330! ft:   Array of temperature tendency (K/s) of dimension ND, defined at same
     331!       grid levels as T, Q, QS and P.
     332
     333! fq:   Array of specific humidity tendencies ((gm/gm)/s) of dimension ND,
     334!       defined at same grid levels as T, Q, QS and P.
     335
     336! fu:   Array of forcing of zonal velocity (m/s^2) of dimension ND,
     337!      defined at same grid levels as T.
     338
     339! fv:   Same as FU, but for forcing of meridional velocity.
     340
     341! ftra: Array of forcing of tracer content, in tracer mixing ratio per
     342!       second, defined at same levels as T. Dimensioned (ND,NTRA).
     343
     344! precip: Scalar convective precipitation rate (mm/day).
     345
     346! wd:   A convective downdraft velocity scale. For use in surface
     347!       flux parameterizations. See convect.ps file for details.
     348
     349! tprime: A convective downdraft temperature perturbation scale (K).
     350!         For use in surface flux parameterizations. See convect.ps
     351!         file for details.
     352
     353! qprime: A convective downdraft specific humidity
     354!         perturbation scale (gm/gm).
     355!         For use in surface flux parameterizations. See convect.ps
     356!         file for details.
     357
     358! cbmf: The cloud base mass flux ((kg/m**2)/s). THIS SCALAR VALUE MUST
     359!       BE STORED BY THE CALLING PROGRAM AND RETURNED TO CONVECT AT
     360!       ITS NEXT CALL. That is, the value of CBMF must be "remembered"
     361!       by the calling program between calls to CONVECT.
     362
     363! det:   Array of detrainment mass flux of dimension ND.
     364! -------------------------------------------------------------------
     365
     366! Local (non compressed) arrays
    371367
    372368
     
    380376  LOGICAL ok_inhib ! True => possible inhibition of convection by dryness
    381377  LOGICAL, SAVE :: debut = .TRUE.
    382   !$OMP THREADPRIVATE(debut)
     378!$OMP THREADPRIVATE(debut)
    383379
    384380  REAL tnk1(klon)
     
    414410  REAL p1feed1(len) ! pressure at lower bound of feeding layer
    415411  REAL p2feed1(len) ! pressure at upper bound of feeding layer
    416   REAL wghti1(len, nd) ! weights of the feeding layers
    417 
    418   ! (local) compressed fields:
     412!JYG,RL
     413!!      real wghti1(len,nd) ! weights of the feeding layers
     414!JYG,RL
     415
     416! (local) compressed fields:
    419417
    420418  INTEGER nloc
    421   ! parameter (nloc=klon) ! pour l'instant
     419! parameter (nloc=klon) ! pour l'instant
    422420
    423421  INTEGER idcum(nloc)
     
    456454  REAL elij(nloc, klev, klev)
    457455  REAL supmax(nloc, klev)
    458   REAL ale(nloc), alp(nloc), coef_clos(nloc)
     456  REAL Ale(nloc), Alp(nloc), coef_clos(nloc)
    459457  REAL sigd(nloc)
    460   ! real mp(nloc,klev), qp(nloc,klev), up(nloc,klev), vp(nloc,klev)
    461   ! real wt(nloc,klev), water(nloc,klev), evap(nloc,klev), ice(nloc,klev)
    462   ! real b(nloc,klev), sigd(nloc)
    463   ! save mp,qp,up,vp,wt,water,evap,b
     458! real mp(nloc,klev), qp(nloc,klev), up(nloc,klev), vp(nloc,klev)
     459! real wt(nloc,klev), water(nloc,klev), evap(nloc,klev), ice(nloc,klev)
     460! real b(nloc,klev), sigd(nloc)
     461! save mp,qp,up,vp,wt,water,evap,b
    464462  REAL, SAVE, ALLOCATABLE :: mp(:, :), qp(:, :), up(:, :), vp(:, :)
    465463  REAL, SAVE, ALLOCATABLE :: wt(:, :), water(:, :), evap(:, :)
    466464  REAL, SAVE, ALLOCATABLE :: ice(:, :), fondue(:, :), b(:, :)
    467465  REAL, SAVE, ALLOCATABLE :: frac(:, :), faci(:, :)
    468   !$OMP THREADPRIVATE(mp,qp,up,vp,wt,water,evap,ice,fondue,b,frac,faci)
     466!$OMP THREADPRIVATE(mp,qp,up,vp,wt,water,evap,ice,fondue,b,frac,faci)
    469467  REAL ft(nloc, klev), fq(nloc, klev)
    470468  REAL ftd(nloc, klev), fqd(nloc, klev)
     
    474472  REAL tps(nloc, klev), qprime(nloc), tprime(nloc)
    475473  REAL precip(nloc)
    476   ! real Vprecip(nloc,klev)
     474! real Vprecip(nloc,klev)
    477475  REAL vprecip(nloc, klev+1)
    478476  REAL tra(nloc, klev, ntra), trap(nloc, klev, ntra)
    479477  REAL ftra(nloc, klev, ntra), traent(nloc, klev, klev, ntra)
    480   REAL qcondc(nloc, klev) ! cld
    481   REAL wd(nloc) ! gust
    482   REAL plim1(nloc), plim2(nloc)
     478  REAL qcondc(nloc, klev)      ! cld
     479  REAL wd(nloc)                ! gust
     480  REAL Plim1(nloc), plim2(nloc)
    483481  REAL asupmax(nloc, klev)
    484482  REAL supmax0(nloc)
     
    489487  REAL hnk(nloc), unk(nloc), vnk(nloc)
    490488
    491   ! RomP >>>
    492   REAL wdtraina(nloc, klev), wdtrainm(nloc, klev)
     489! RomP >>>
     490  REAL wdtrainA(nloc, klev), wdtrainM(nloc, klev)
    493491  REAL da(len, nd), phi(len, nd, nd)
    494   REAL epmlmmm(nloc, klev, klev), eplamm(nloc, klev)
     492  REAL epmlmMm(nloc, klev, klev), eplaMm(nloc, klev)
    495493  REAL phi2(len, nd, nd)
    496494  REAL d1a(len, nd), dam(len, nd)
    497   ! RomP <<<
     495! RomP <<<
    498496
    499497  LOGICAL, SAVE :: first = .TRUE.
    500   !$OMP THREADPRIVATE(first)
     498!$OMP THREADPRIVATE(first)
    501499  CHARACTER (LEN=20) :: modname = 'cva_driver'
    502500  CHARACTER (LEN=80) :: abort_message
    503501
    504502
    505   ! print *, 't1, t1_wake ',(k,t1(1,k),t1_wake(1,k),k=1,klev)
    506   ! print *, 'q1, q1_wake ',(k,q1(1,k),q1_wake(1,k),k=1,klev)
    507 
    508   ! -------------------------------------------------------------------
    509   ! --- SET CONSTANTS AND PARAMETERS
    510   ! -------------------------------------------------------------------
     503! print *, 't1, t1_wake ',(k,t1(1,k),t1_wake(1,k),k=1,klev)
     504! print *, 'q1, q1_wake ',(k,q1(1,k),q1_wake(1,k),k=1,klev)
     505
     506! -------------------------------------------------------------------
     507! --- SET CONSTANTS AND PARAMETERS
     508! -------------------------------------------------------------------
    511509
    512510  IF (first) THEN
     
    518516    first = .FALSE.
    519517  END IF
    520   ! -- set simulation flags:
    521   ! (common cvflag)
     518! -- set simulation flags:
     519! (common cvflag)
    522520
    523521  CALL cv_flag(iflag_ice_thermo)
    524522
    525   ! -- set thermodynamical constants:
    526   ! (common cvthermo)
     523! -- set thermodynamical constants:
     524! (common cvthermo)
    527525
    528526  CALL cv_thermo(iflag_con)
    529527
    530   ! -- set convect parameters
    531 
    532   ! includes microphysical parameters and parameters that
    533   ! control the rate of approach to quasi-equilibrium)
    534   ! (common cvparam)
     528! -- set convect parameters
     529
     530! includes microphysical parameters and parameters that
     531! control the rate of approach to quasi-equilibrium)
     532! (common cvparam)
    535533
    536534  IF (iflag_con==3) THEN
     
    543541  END IF
    544542
    545   ! ---------------------------------------------------------------------
    546   ! --- INITIALIZE OUTPUT ARRAYS AND PARAMETERS
    547   ! ---------------------------------------------------------------------
     543! ---------------------------------------------------------------------
     544! --- INITIALIZE OUTPUT ARRAYS AND PARAMETERS
     545! ---------------------------------------------------------------------
    548546  nword1 = len
    549547  nword2 = len*nd
     
    576574  ftd1(:, :) = 0.
    577575  fqd1(:, :) = 0.
    578   plim11(:) = 0.
    579   plim21(:) = 0.
     576  Plim11(:) = 0.
     577  Plim21(:) = 0.
    580578  asupmax1(:, :) = 0.
    581579  supmax01(:) = 0.
     
    594592  END IF
    595593
    596   ! RomP >>>
    597   wdtraina1(:, :) = 0.
    598   wdtrainm1(:, :) = 0.
     594! RomP >>>
     595  wdtrainA1(:, :) = 0.
     596  wdtrainM1(:, :) = 0.
    599597  da1(:, :) = 0.
    600598  phi1(:, :, :) = 0.
    601   epmlmmm1(:, :, :) = 0.
    602   eplamm1(:, :) = 0.
     599  epmlmMm1(:, :, :) = 0.
     600  eplaMm1(:, :) = 0.
    603601  mp1(:, :) = 0.
    604602  evap1(:, :) = 0.
     
    609607  d1a1(:, :) = 0.
    610608  dam1(:, :) = 0.
    611   ! RomP <<<
    612   ! ---------------------------------------------------------------------
    613   ! --- INITIALIZE LOCAL ARRAYS AND PARAMETERS
    614   ! ---------------------------------------------------------------------
     609! RomP <<<
     610! ---------------------------------------------------------------------
     611! --- INITIALIZE LOCAL ARRAYS AND PARAMETERS
     612! ---------------------------------------------------------------------
    615613
    616614  DO il = 1, nloc
     
    618616  END DO
    619617
    620   ! --------------------------------------------------------------------
    621   ! --- CALCULATE ARRAYS OF GEOPOTENTIAL, HEAT CAPACITY & STATIC ENERGY
    622   ! --------------------------------------------------------------------
     618! --------------------------------------------------------------------
     619! --- CALCULATE ARRAYS OF GEOPOTENTIAL, HEAT CAPACITY & STATIC ENERGY
     620! --------------------------------------------------------------------
    623621
    624622  IF (iflag_con==3) THEN
     
    627625      PRINT *, 'Emanuel version 3 nouvelle'
    628626    END IF
    629     ! print*,'t1, q1 ',t1,q1
    630     CALL cv3_prelim(len, nd, ndp1, t1, q1, p1, ph1 & ! nd->na
    631       , lv1, lf1, cpn1, tv1, gz1, h1, hm1, th1)
    632 
    633 
    634     CALL cv3_prelim(len, nd, ndp1, t1_wake, q1_wake, p1, ph1 & !
    635                                                                ! nd->na
    636       , lv1_wake, lf1_wake, cpn1_wake, tv1_wake, gz1_wake, h1_wake, bid, &
    637       th1_wake)
     627! print*,'t1, q1 ',t1,q1
     628    CALL cv3_prelim(len, nd, ndp1, t1, q1, p1, ph1, &           ! nd->na
     629                    lv1, lf1, cpn1, tv1, gz1, h1, hm1, th1)
     630
     631
     632    CALL cv3_prelim(len, nd, ndp1, t1_wake, q1_wake, p1, ph1, & ! nd->na
     633                    lv1_wake, lf1_wake, cpn1_wake, tv1_wake, gz1_wake, &
     634                    h1_wake, bid, th1_wake)
    638635
    639636  END IF
     
    641638  IF (iflag_con==4) THEN
    642639    PRINT *, 'Emanuel version 4 '
    643     CALL cv_prelim(len, nd, ndp1, t1, q1, p1, ph1, lv1, cpn1, tv1, gz1, h1, &
    644       hm1)
    645   END IF
    646 
    647   ! --------------------------------------------------------------------
    648   ! --- CONVECTIVE FEED
    649   ! --------------------------------------------------------------------
    650 
    651   ! compute feeding layer potential temperature and mixing ratio :
    652 
    653   ! get bounds of feeding layer
    654 
    655   ! test niveaux couche alimentation KE
     640    CALL cv_prelim(len, nd, ndp1, t1, q1, p1, ph1, &
     641                   lv1, cpn1, tv1, gz1, h1, hm1)
     642  END IF
     643
     644! --------------------------------------------------------------------
     645! --- CONVECTIVE FEED
     646! --------------------------------------------------------------------
     647
     648! compute feeding layer potential temperature and mixing ratio :
     649
     650! get bounds of feeding layer
     651
     652! test niveaux couche alimentation KE
    656653  IF (sig1feed1==sig2feed1) THEN
    657654    WRITE (lunout, *) 'impossible de choisir sig1feed=sig2feed'
     
    664661    p1feed1(i) = sig1feed1*ph1(i, 1)
    665662    p2feed1(i) = sig2feed1*ph1(i, 1)
    666     ! test maf
    667     ! p1feed1(i)=ph1(i,1)
    668     ! p2feed1(i)=ph1(i,2)
    669     ! p2feed1(i)=ph1(i,3)
    670     ! testCR: on prend la couche alim des thermiques
    671     ! p2feed1(i)=ph1(i,lalim_conv(i)+1)
    672     ! print*,'lentr=',lentr(i),ph1(i,lentr(i)+1),ph1(i,2)
     663!test maf
     664 p1feed1(i)=ph1(i,1)
     665 p2feed1(i)=ph1(i,2)
     666 p2feed1(i)=ph1(i,3)
     667!testCR: on prend la couche alim des thermiques
     668 p2feed1(i)=ph1(i,lalim_conv(i)+1)
     669 print*,'lentr=',lentr(i),ph1(i,lentr(i)+1),ph1(i,2)
    673670  END DO
    674671
     
    676673  END IF
    677674  DO i = 1, len
    678     ! print*,'avant cv3_feed plim',p1feed1(i),p2feed1(i)
     675! print*,'avant cv3_feed Plim',p1feed1(i),p2feed1(i)
    679676  END DO
    680677  IF (iflag_con==3) THEN
    681678
    682     ! print*, 'IFLAG1 avant cv3_feed'
    683     ! print*,'len,nd',len,nd
    684     ! write(*,'(64i1)') iflag1(2:klon-1)
    685 
    686     CALL cv3_feed(len, nd, t1, q1, u1, v1, p1, ph1, hm1, gz1 & !
    687                                                                ! nd->na
    688       , p1feed1, p2feed1, wght1, wghti1, tnk1, thnk1, qnk1, qsnk1, unk1, &
    689       vnk1, cpnk1, hnk1, nk1, icb1, icbmax, iflag1, gznk1, plcl1)
    690   END IF
    691 
    692   ! print*, 'IFLAG1 apres cv3_feed'
    693   ! print*,'len,nd',len,nd
    694   ! write(*,'(64i1)') iflag1(2:klon-1)
     679! print*, 'IFLAG1 avant cv3_feed'
     680! print*,'len,nd',len,nd
     681! write(*,'(64i1)') iflag1(2:klon-1)
     682
     683    CALL cv3_feed(len, nd, ok_conserv_q, &                 ! nd->na
     684                  t1, q1, u1, v1, p1, ph1, hm1, gz1, &
     685                  p1feed1, p2feed1, wght1, &
     686                  wghti1, tnk1, thnk1, qnk1, qsnk1, unk1, vnk1, &
     687                  cpnk1, hnk1, nk1, icb1, icbmax, iflag1, gznk1, plcl1)
     688  END IF
     689
     690! print*, 'IFLAG1 apres cv3_feed'
     691! print*,'len,nd',len,nd
     692! write(*,'(64i1)') iflag1(2:klon-1)
    695693
    696694  IF (iflag_con==4) THEN
    697     CALL cv_feed(len, nd, t1, q1, qs1, p1, hm1, gz1, nk1, icb1, icbmax, &
    698       iflag1, tnk1, qnk1, gznk1, plcl1)
    699   END IF
    700 
    701   ! print *, 'cv3_feed-> iflag1, plcl1 ',iflag1(1),plcl1(1)
    702 
    703   ! --------------------------------------------------------------------
    704   ! --- UNDILUTE (ADIABATIC) UPDRAFT / 1st part
    705   ! (up through ICB for convect4, up through ICB+1 for convect3)
    706   ! Calculates the lifted parcel virtual temperature at nk, the
    707   ! actual temperature, and the adiabatic liquid water content.
    708   ! --------------------------------------------------------------------
     695    CALL cv_feed(len, nd, t1, q1, qs1, p1, hm1, gz1, &
     696                 nk1, icb1, icbmax, iflag1, tnk1, qnk1, gznk1, plcl1)
     697  END IF
     698
     699! print *, 'cv3_feed-> iflag1, plcl1 ',iflag1(1),plcl1(1)
     700
     701! --------------------------------------------------------------------
     702! --- UNDILUTE (ADIABATIC) UPDRAFT / 1st part
     703! (up through ICB for convect4, up through ICB+1 for convect3)
     704! Calculates the lifted parcel virtual temperature at nk, the
     705! actual temperature, and the adiabatic liquid water content.
     706! --------------------------------------------------------------------
    709707
    710708  IF (iflag_con==3) THEN
    711709
    712     CALL cv3_undilute1(len, nd, t1, qs1, gz1, plcl1, p1, icb1, tnk1, qnk1 & ! nd->na
    713       , gznk1, tp1, tvp1, clw1, icbs1)
     710    CALL cv3_undilute1(len, nd, t1, qs1, gz1, plcl1, p1, icb1, tnk1, qnk1, & ! nd->na
     711                      gznk1, tp1, tvp1, clw1, icbs1)
    714712  END IF
    715713
    716714
    717715  IF (iflag_con==4) THEN
    718     CALL cv_undilute1(len, nd, t1, q1, qs1, gz1, p1, nk1, icb1, icbmax, tp1, &
    719       tvp1, clw1)
    720   END IF
    721 
    722   ! -------------------------------------------------------------------
    723   ! --- TRIGGERING
    724   ! -------------------------------------------------------------------
    725 
    726   ! print *,' avant triggering, iflag_con ',iflag_con
     716    CALL cv_undilute1(len, nd, t1, q1, qs1, gz1, p1, nk1, icb1, icbmax, &
     717                      tp1, tvp1, clw1)
     718  END IF
     719
     720! -------------------------------------------------------------------
     721! --- TRIGGERING
     722! -------------------------------------------------------------------
     723
     724! print *,' avant triggering, iflag_con ',iflag_con
    727725
    728726  IF (iflag_con==3) THEN
    729727
    730     CALL cv3_trigger(len, nd, icb1, plcl1, p1, th1, tv1, tvp1, thnk1 & !
    731                                                                        ! nd->na
    732       , pbase1, buoybase1, iflag1, sig1, w01)
    733 
    734 
    735     ! print*, 'IFLAG1 apres cv3_triger'
    736     ! print*,'len,nd',len,nd
    737     ! write(*,'(64i1)') iflag1(2:klon-1)
    738 
    739     ! call dump2d(iim,jjm-1,sig1(2)
     728    CALL cv3_trigger(len, nd, icb1, plcl1, p1, th1, tv1, tvp1, thnk1, & ! nd->na
     729                      pbase1, buoybase1, iflag1, sig1, w01)
     730
     731
     732! print*, 'IFLAG1 apres cv3_triger'
     733! print*,'len,nd',len,nd
     734! write(*,'(64i1)') iflag1(2:klon-1)
     735
     736! call dump2d(iim,jjm-1,sig1(2)
    740737  END IF
    741738
     
    745742
    746743
    747   ! =====================================================================
    748   ! --- IF THIS POINT IS REACHED, MOIST CONVECTIVE ADJUSTMENT IS NECESSARY
    749   ! =====================================================================
     744! =====================================================================
     745! --- IF THIS POINT IS REACHED, MOIST CONVECTIVE ADJUSTMENT IS NECESSARY
     746! =====================================================================
    750747
    751748  ncum = 0
     
    757754  END DO
    758755
    759   ! print*,'klon, ncum = ',len,ncum
     756! print*,'klon, ncum = ',len,ncum
    760757
    761758  IF (ncum>0) THEN
    762759
    763     ! ^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^
    764     ! --- COMPRESS THE FIELDS
    765     ! (-> vectorization over convective gridpoints)
    766     ! ^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^
     760! ^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^
     761! --- COMPRESS THE FIELDS
     762!      (-> vectorization over convective gridpoints)
     763! ^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^
    767764
    768765    IF (iflag_con==3) THEN
    769       ! print*,'ncum tv1 ',ncum,tv1
    770       ! print*,'tvp1 ',tvp1
    771       CALL cv3a_compress(len, nloc, ncum, nd, ntra, iflag1, nk1, icb1, icbs1, &
    772         plcl1, tnk1, qnk1, gznk1, hnk1, unk1, vnk1, wghti1, pbase1, &
    773         buoybase1, t1, q1, qs1, t1_wake, q1_wake, qs1_wake, s1_wake, u1, v1, &
    774         gz1, th1, th1_wake, tra1, h1, lv1, lf1, cpn1, p1, ph1, tv1, tp1, &
    775         tvp1, clw1, h1_wake, lv1_wake, lf1_wake, cpn1_wake, tv1_wake, sig1, &
    776         w01, ptop21, ale1, alp1, iflag, nk, icb, icbs, plcl, tnk, qnk, gznk, &
    777         hnk, unk, vnk, wghti, pbase, buoybase, t, q, qs, t_wake, q_wake, &
    778         qs_wake, s_wake, u, v, gz, th, th_wake, tra, h, lv, lf, cpn, p, ph, &
    779         tv, tp, tvp, clw, h_wake, lv_wake, lf_wake, cpn_wake, tv_wake, sig, &
    780         w0, ptop2, ale, alp)
    781 
    782       ! print*,'tv ',tv
    783       ! print*,'tvp ',tvp
     766! print*,'ncum tv1 ',ncum,tv1
     767! print*,'tvp1 ',tvp1
     768      CALL cv3a_compress(len, nloc, ncum, nd, ntra, &
     769                         iflag1, nk1, icb1, icbs1, &
     770                         plcl1, tnk1, qnk1, gznk1, hnk1, unk1, vnk1, &
     771                         wghti1, pbase1, buoybase1, &
     772                         t1, q1, qs1, t1_wake, q1_wake, qs1_wake, s1_wake, &
     773                         u1, v1, gz1, th1, th1_wake, &
     774                         tra1, &
     775                         h1, lv1, lf1, cpn1, p1, ph1, tv1, tp1, tvp1, clw1, &
     776                         h1_wake, lv1_wake, lf1_wake, cpn1_wake, tv1_wake, &
     777                         sig1, w01, ptop21, &
     778                         Ale1, Alp1, &
     779                         iflag, nk, icb, icbs, &
     780                         plcl, tnk, qnk, gznk, hnk, unk, vnk, &
     781                         wghti, pbase, buoybase, &
     782                         t, q, qs, t_wake, q_wake, qs_wake, s_wake, &
     783                         u, v, gz, th, th_wake, &
     784                         tra, &
     785                         h, lv, lf, cpn, p, ph, tv, tp, tvp, clw, &
     786                         h_wake, lv_wake, lf_wake, cpn_wake, tv_wake, &
     787                         sig, w0, ptop2, &
     788                         Ale, Alp)
     789
     790! print*,'tv ',tv
     791! print*,'tvp ',tvp
    784792
    785793    END IF
    786794
    787795    IF (iflag_con==4) THEN
    788       CALL cv_compress(len, nloc, ncum, nd, iflag1, nk1, icb1, cbmf1, plcl1, &
    789         tnk1, qnk1, gznk1, t1, q1, qs1, u1, v1, gz1, h1, lv1, cpn1, p1, ph1, &
    790         tv1, tp1, tvp1, clw1, iflag, nk, icb, cbmf, plcl, tnk, qnk, gznk, t, &
    791         q, qs, u, v, gz, h, lv, cpn, p, ph, tv, tp, tvp, clw, dph)
    792     END IF
    793 
    794     ! -------------------------------------------------------------------
    795     ! --- UNDILUTE (ADIABATIC) UPDRAFT / second part :
    796     ! ---   FIND THE REST OF THE LIFTED PARCEL TEMPERATURES
    797     ! ---   &
    798     ! ---   COMPUTE THE PRECIPITATION EFFICIENCIES AND THE
    799     ! ---   FRACTION OF PRECIPITATION FALLING OUTSIDE OF CLOUD
    800     ! ---   &
    801     ! ---   FIND THE LEVEL OF NEUTRAL BUOYANCY
    802     ! -------------------------------------------------------------------
     796      CALL cv_compress(len, nloc, ncum, nd, &
     797                       iflag1, nk1, icb1, &
     798                       cbmf1, plcl1, tnk1, qnk1, gznk1, &
     799                       t1, q1, qs1, u1, v1, gz1, &
     800                       h1, lv1, cpn1, p1, ph1, tv1, tp1, tvp1, clw1, &
     801                       iflag, nk, icb, &
     802                       cbmf, plcl, tnk, qnk, gznk, &
     803                       t, q, qs, u, v, gz, h, lv, cpn, p, ph, tv, tp, tvp, clw, &
     804                       dph)
     805    END IF
     806
     807! -------------------------------------------------------------------
     808! --- UNDILUTE (ADIABATIC) UPDRAFT / second part :
     809! ---   FIND THE REST OF THE LIFTED PARCEL TEMPERATURES
     810! ---   &
     811! ---   COMPUTE THE PRECIPITATION EFFICIENCIES AND THE
     812! ---   FRACTION OF PRECIPITATION FALLING OUTSIDE OF CLOUD
     813! ---   &
     814! ---   FIND THE LEVEL OF NEUTRAL BUOYANCY
     815! -------------------------------------------------------------------
    803816
    804817    IF (iflag_con==3) THEN
    805       CALL cv3_undilute2(nloc, ncum, nd, icb, icbs, nk & !na->nd
    806         , tnk, qnk, gznk, hnk, t, q, qs, gz, p, h, tv, lv, lf, pbase, &
    807         buoybase, plcl, inb, tp, tvp, clw, hp, ep, sigp, buoy, frac)
     818      CALL cv3_undilute2(nloc, ncum, nd, icb, icbs, nk, &              !na->nd
     819                         tnk, qnk, gznk, hnk, t, q, qs, gz, &
     820                         p, h, tv, lv, lf, pbase, buoybase, plcl, &
     821                         inb, tp, tvp, clw, hp, ep, sigp, buoy, &
     822                         frac)
    808823
    809824    END IF
    810825
    811826    IF (iflag_con==4) THEN
    812       CALL cv_undilute2(nloc, ncum, nd, icb, nk, tnk, qnk, gznk, t, q, qs, &
    813         gz, p, dph, h, tv, lv, inb, inbis, tp, tvp, clw, hp, ep, sigp, frac)
    814     END IF
    815 
    816     ! -------------------------------------------------------------------
    817     ! --- MIXING(1)   (if iflag_mix .ge. 1)
    818     ! -------------------------------------------------------------------
     827      CALL cv_undilute2(nloc, ncum, nd, icb, nk, &
     828                        tnk, qnk, gznk, t, q, qs, gz, &
     829                        p, dph, h, tv, lv, &
     830                        inb, inbis, tp, tvp, clw, hp, ep, sigp, frac)
     831    END IF
     832
     833! -------------------------------------------------------------------
     834! --- MIXING(1)   (if iflag_mix .ge. 1)
     835! -------------------------------------------------------------------
    819836    IF (iflag_con==3) THEN
    820837      IF ((iflag_ice_thermo==1) .AND. (iflag_mix/=0)) THEN
    821         WRITE (*, *) ' iflag_ice_thermo==1 requires iflag_mix==0', &
    822           ' but iflag_mix=', iflag_mix, '. Might as well stop here.'
     838        WRITE (*, *) ' iflag_ice_thermo==1 requires iflag_mix==0', ' but iflag_mix=', iflag_mix, &
     839          '. Might as well stop here.'
    823840        STOP
    824841      END IF
    825842      IF (iflag_mix>=1) THEN
    826843        CALL zilch(supmax, nloc*klev)
    827         CALL cv3p_mixing(nloc, ncum, nd, nd, ntra, icb, nk, inb & !
    828                                                                   ! na->nd
    829           , ph, t, q, qs, u, v, tra, h, lv, qnk, unk, vnk, hp, tv, tvp, ep, &
    830           clw, sig, ment, qent, hent, uent, vent, nent, sigij, elij, supmax, &
    831           ments, qents, traent)
    832         ! print*, 'cv3p_mixing-> supmax ', (supmax(1,k), k=1,nd)
     844        CALL cv3p_mixing(nloc, ncum, nd, nd, ntra, icb, nk, inb, &           ! na->nd
     845                         ph, t, q, qs, u, v, tra, h, lv, qnk, &
     846                         unk, vnk, hp, tv, tvp, ep, clw, sig, &
     847                         ment, qent, hent, uent, vent, nent, &
     848                         sigij, elij, supmax, ments, qents, traent)
     849! print*, 'cv3p_mixing-> supmax ', (supmax(1,k), k=1,nd)
    833850
    834851      ELSE
     
    836853      END IF
    837854    END IF
    838     ! -------------------------------------------------------------------
    839     ! --- CLOSURE
    840     ! -------------------------------------------------------------------
     855! -------------------------------------------------------------------
     856! --- CLOSURE
     857! -------------------------------------------------------------------
    841858
    842859
    843860    IF (iflag_con==3) THEN
    844861      IF (iflag_clos==0) THEN
    845         CALL cv3_closure(nloc, ncum, nd, icb, inb & ! na->nd
    846           , pbase, p, ph, tv, buoy, sig, w0, cape, m, iflag)
     862        CALL cv3_closure(nloc, ncum, nd, icb, inb, &           ! na->nd
     863                         pbase, p, ph, tv, buoy, &
     864                         sig, w0, cape, m, iflag)
    847865      END IF
    848866
     
    851869      IF (iflag_clos==1) THEN
    852870        PRINT *, ' pas d appel cv3p_closure'
    853         ! c        CALL cv3p_closure(nloc,ncum,nd,icb,inb              !
    854         ! na->nd
    855         ! c    :                       ,pbase,plcl,p,ph,tv,tvp,buoy
    856         ! c    :                       ,supmax
    857         ! c    o                       ,sig,w0,ptop2,cape,cin,m)
     871! c        CALL cv3p_closure(nloc,ncum,nd,icb,inb              ! na->nd
     872! c    :                       ,pbase,plcl,p,ph,tv,tvp,buoy
     873! c    :                       ,supmax
     874! c    o                       ,sig,w0,ptop2,cape,cin,m)
    858875      END IF
    859876      IF (iflag_clos==2) THEN
    860         CALL cv3p1_closure(nloc, ncum, nd, icb, inb & ! na->nd
    861           , pbase, plcl, p, ph, tv, tvp, buoy, supmax, ok_inhib, ale, alp, &
    862           sig, w0, ptop2, cape, cin, m, iflag, coef_clos, plim1, plim2, &
    863           asupmax, supmax0, asupmaxmin, cbmf, plfc, wbeff)
     877        CALL cv3p1_closure(nloc, ncum, nd, icb, inb, &         ! na->nd
     878                           pbase, plcl, p, ph, tv, tvp, buoy, &
     879                           supmax, ok_inhib, Ale, Alp, &
     880                           sig, w0, ptop2, cape, cin, m, iflag, coef_clos, &
     881                           Plim1, plim2, asupmax, supmax0, &
     882                           asupmaxmin, cbmf, plfc, wbeff)
    864883
    865884        PRINT *, 'cv3p1_closure-> plfc,wbeff ', plfc(1), wbeff(1)
     
    868887
    869888    IF (iflag_con==4) THEN
    870       CALL cv_closure(nloc, ncum, nd, nk, icb, tv, tvp, p, ph, dph, plcl, &
    871         cpn, iflag, cbmf)
    872     END IF
    873 
    874     ! print *,'cv_closure-> cape ',cape(1)
    875 
    876     ! -------------------------------------------------------------------
    877     ! --- MIXING(2)
    878     ! -------------------------------------------------------------------
     889      CALL cv_closure(nloc, ncum, nd, nk, icb, &
     890                         tv, tvp, p, ph, dph, plcl, cpn, &
     891                         iflag, cbmf)
     892    END IF
     893
     894! print *,'cv_closure-> cape ',cape(1)
     895
     896! -------------------------------------------------------------------
     897! --- MIXING(2)
     898! -------------------------------------------------------------------
    879899
    880900    IF (iflag_con==3) THEN
    881901      IF (iflag_mix==0) THEN
    882         CALL cv3_mixing(nloc, ncum, nd, nd, ntra, icb, nk, inb & !
    883                                                                  ! na->nd
    884           , ph, t, q, qs, u, v, tra, h, lv, lf, frac, qnk, unk, vnk, hp, tv, &
    885           tvp, ep, clw, m, sig, ment, qent, uent, vent, nent, sigij, elij, &
    886           ments, qents, traent)
     902        CALL cv3_mixing(nloc, ncum, nd, nd, ntra, icb, nk, inb, &             ! na->nd
     903                        ph, t, q, qs, u, v, tra, h, lv, lf, frac, qnk, &
     904                        unk, vnk, hp, tv, tvp, ep, clw, m, sig, &
     905                        ment, qent, uent, vent, nent, sigij, elij, ments, qents, traent)
    887906        CALL zilch(hent, nloc*klev*klev)
    888907      ELSE
     
    895914
    896915    IF (iflag_con==4) THEN
    897       CALL cv_mixing(nloc, ncum, nd, icb, nk, inb, inbis, ph, t, q, qs, u, v, &
    898         h, lv, qnk, hp, tv, tvp, ep, clw, cbmf, m, ment, qent, uent, vent, &
    899         nent, sigij, elij)
    900     END IF
     916      CALL cv_mixing(nloc, ncum, nd, icb, nk, inb, inbis, &
     917                     ph, t, q, qs, u, v, h, lv, qnk, &
     918                     hp, tv, tvp, ep, clw, cbmf, &
     919                     m, ment, qent, uent, vent, nent, sigij, elij)
     920    END IF                                                                                         
    901921
    902922    IF (debut) THEN
    903923      PRINT *, ' cv_mixing ->'
    904924    END IF !(debut) THEN
    905     ! do i = 1,klev
    906     ! print*,'cv_mixing-> i,ment ',i,(ment(1,i,j),j=1,klev)
    907     ! enddo
    908 
    909     ! -------------------------------------------------------------------
    910     ! --- UNSATURATED (PRECIPITATING) DOWNDRAFTS
    911     ! -------------------------------------------------------------------
     925! do i = 1,klev
     926! print*,'cv_mixing-> i,ment ',i,(ment(1,i,j),j=1,klev)
     927! enddo
     928
     929! -------------------------------------------------------------------
     930! --- UNSATURATED (PRECIPITATING) DOWNDRAFTS
     931! -------------------------------------------------------------------
    912932    IF (iflag_con==3) THEN
    913933      IF (debut) THEN
     
    915935      END IF !(debut) THEN
    916936
    917       CALL cv3_unsat(nloc, ncum, nd, nd, ntra, icb, inb, iflag & !
    918                                                                  ! na->nd
    919         , t_wake, q_wake, qs_wake, gz, u, v, tra, p, ph, th_wake, tv_wake, &
    920         lv_wake, lf_wake, cpn_wake, ep, sigp, clw, m, ment, elij, delt, plcl, &
    921         coef_clos, mp, qp, up, vp, trap, wt, water, evap, fondue, ice, faci, &
    922         b, sigd, wdtraina, wdtrainm) ! RomP
     937      CALL cv3_unsat(nloc, ncum, nd, nd, ntra, icb, inb, iflag, &              ! na->nd
     938                     t_wake, q_wake, qs_wake, gz, u, v, tra, p, ph, &
     939                     th_wake, tv_wake, lv_wake, lf_wake, cpn_wake, &
     940                     ep, sigp, clw, &
     941                     m, ment, elij, delt, plcl, coef_clos, &
     942                     mp, qp, up, vp, trap, wt, water, evap, fondue, ice, &
     943                     faci, b, sigd, &
     944                     wdtrainA, wdtrainM)                                       ! RomP
    923945    END IF
    924946
    925947    IF (iflag_con==4) THEN
    926       CALL cv_unsat(nloc, ncum, nd, inb, t, q, qs, gz, u, v, p, ph, h, lv, &
    927         ep, sigp, clw, m, ment, elij, iflag, mp, qp, up, vp, wt, water, evap)
     948      CALL cv_unsat(nloc, ncum, nd, inb, t, q, qs, gz, u, v, p, ph, &
     949                     h, lv, ep, sigp, clw, m, ment, elij, &
     950                     iflag, mp, qp, up, vp, wt, water, evap)
    928951    END IF
    929952
     
    932955    END IF !(debut) THEN
    933956
    934     ! print *,'cv_unsat-> mp ',mp
    935     ! print *,'cv_unsat-> water ',water
    936     ! -------------------------------------------------------------------
    937     ! --- YIELD
    938     ! (tendencies, precipitation, variables of interface with other
    939     ! processes, etc)
    940     ! -------------------------------------------------------------------
     957! print *,'cv_unsat-> mp ',mp
     958! print *,'cv_unsat-> water ',water
     959! -------------------------------------------------------------------
     960! --- YIELD
     961! (tendencies, precipitation, variables of interface with other
     962! processes, etc)
     963! -------------------------------------------------------------------
    941964
    942965    IF (iflag_con==3) THEN
    943966
    944       CALL cv3_yield(nloc, ncum, nd, nd, ntra & ! na->nd
    945         , icb, inb, delt, t, q, t_wake, q_wake, s_wake, u, v, tra, gz, p, ph, &
    946         h, hp, lv, lf, cpn, th, th_wake, ep, clw, m, tp, mp, qp, up, vp, &
    947         trap, wt, water, ice, evap, fondue, faci, b, sigd, ment, qent, hent, &
    948         iflag_mix, uent, vent, nent, elij, traent, sig, tv, tvp, wghti, &
    949         iflag, precip, vprecip, ft, fq, fu, fv, ftra, cbmf, upwd, dnwd, &
    950         dnwd0, ma, mip, tls, tps, qcondc, wd, ftd, fqd)
     967      CALL cv3_yield(nloc, ncum, nd, nd, ntra, ok_conserv_q, &                      ! na->nd
     968                     icb, inb, delt, &
     969                     t, q, t_wake, q_wake, s_wake, u, v, tra, &
     970                     gz, p, ph, h, hp, lv, lf, cpn, th, th_wake, &
     971                     ep, clw, m, tp, mp, qp, up, vp, trap, &
     972                     wt, water, ice, evap, fondue, faci, b, sigd, &
     973                     ment, qent, hent, iflag_mix, uent, vent, &
     974                     nent, elij, traent, sig, &
     975                     tv, tvp, wghti, &
     976                     iflag, precip, vprecip, ft, fq, fu, fv, ftra, &
     977                     cbmf, upwd, dnwd, dnwd0, ma, mip, &
     978                     tls, tps, qcondc, wd, &
     979                     ftd, fqd)
    951980    END IF
    952981
     
    956985
    957986    IF (iflag_con==4) THEN
    958       CALL cv_yield(nloc, ncum, nd, nk, icb, inb, delt, t, q, u, v, gz, p, &
    959         ph, h, hp, lv, cpn, ep, clw, frac, m, mp, qp, up, vp, wt, water, &
    960         evap, ment, qent, uent, vent, nent, elij, tv, tvp, iflag, wd, qprime, &
    961         tprime, precip, cbmf, ft, fq, fu, fv, ma, qcondc)
    962     END IF
    963 
    964     ! AC!
    965     ! ^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^
    966     ! --- passive tracers
    967     ! ^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^
     987      CALL cv_yield(nloc, ncum, nd, nk, icb, inb, delt, &
     988                     t, q, u, v, &
     989                     gz, p, ph, h, hp, lv, cpn, &
     990                     ep, clw, frac, m, mp, qp, up, vp, &
     991                     wt, water, evap, &
     992                     ment, qent, uent, vent, nent, elij, &
     993                     tv, tvp, &
     994                     iflag, wd, qprime, tprime, &
     995                     precip, cbmf, ft, fq, fu, fv, ma, qcondc)
     996    END IF
     997
     998!AC!
     999!^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^
     1000!--- passive tracers
     1001!^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^
    9681002
    9691003    IF (iflag_con==3) THEN
    970       ! RomP >>>
    971       CALL cv3_tracer(nloc, len, ncum, nd, nd, ment, sigij, da, phi, phi2, &
    972         d1a, dam, ep, vprecip, elij, clw, epmlmmm, eplamm, icb, inb)
    973       ! RomP <<<
    974     END IF
    975 
    976     ! AC!
    977 
    978     ! ^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^
    979     ! --- UNCOMPRESS THE FIELDS
    980     ! ^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^
     1004!RomP >>>
     1005      CALL cv3_tracer(nloc, len, ncum, nd, nd, &
     1006                     ment, sigij, da, phi, phi2, d1a, dam, &
     1007                     ep, vprecip, elij, clw, epmlmMm, eplaMm, &
     1008                     icb, inb)
     1009!RomP <<<
     1010    END IF
     1011
     1012!AC!
     1013
     1014! ^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^
     1015! --- UNCOMPRESS THE FIELDS
     1016! ^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^
    9811017
    9821018
    9831019    IF (iflag_con==3) THEN
    984       CALL cv3a_uncompress(nloc, len, ncum, nd, ntra, idcum, iflag, icb, inb, &
    985         precip, cbmf, plcl, plfc, wbeff, sig, w0, ptop2, ft, fq, fu, fv, &
    986         ftra, sigd, ma, mip, vprecip, upwd, dnwd, dnwd0, qcondc, wd, cape, &
    987         cin, tvp, ftd, fqd, plim1, plim2, asupmax, supmax0, asupmaxmin, da, &
    988         phi, mp, phi2, d1a, dam, sigij & ! RomP
    989         , clw, elij, evap, ep, epmlmmm, eplamm & ! RomP
    990         , wdtraina, wdtrainm &     ! RomP
    991         , iflag1, kbas1, ktop1, precip1, cbmf1, plcl1, plfc1, wbeff1, sig1, &
    992         w01, ptop21, ft1, fq1, fu1, fv1, ftra1, sigd1, ma1, mip1, vprecip1, &
    993         upwd1, dnwd1, dnwd01, qcondc1, wd1, cape1, cin1, tvp1, ftd1, fqd1, &
    994         plim11, plim21, asupmax1, supmax01, asupmaxmin1, da1, phi1, mp1, &
    995         phi21, d1a1, dam1, sigij1 & ! RomP
    996         , clw1, elij1, evap1, ep1, epmlmmm1, eplamm1 & ! RomP
    997         , wdtraina1, wdtrainm1) ! RomP
     1020      CALL cv3a_uncompress(nloc, len, ncum, nd, ntra, idcum, &
     1021                           iflag, icb, inb, &
     1022                           precip, cbmf, plcl, plfc, wbeff, sig, w0, ptop2, &
     1023                           ft, fq, fu, fv, ftra, &
     1024                           sigd, ma, mip, vprecip, upwd, dnwd, dnwd0, &
     1025                           qcondc, wd, cape, cin, &
     1026                           tvp, &
     1027                           ftd, fqd, &
     1028                           Plim1, plim2, asupmax, supmax0, &
     1029                           asupmaxmin, &
     1030                           da, phi, mp, phi2, d1a, dam, sigij, &         ! RomP
     1031                           clw, elij, evap, ep, epmlmMm, eplaMm, &       ! RomP
     1032                           wdtrainA, wdtrainM, &                         ! RomP
     1033                           iflag1, kbas1, ktop1, &
     1034                           precip1, cbmf1, plcl1, plfc1, wbeff1, sig1, w01, ptop21, &
     1035                           ft1, fq1, fu1, fv1, ftra1, &
     1036                           sigd1, ma1, mip1, vprecip1, upwd1, dnwd1, dnwd01, &
     1037                           qcondc1, wd1, cape1, cin1, &
     1038                           tvp1, &
     1039                           ftd1, fqd1, &
     1040                           Plim11, plim21, asupmax1, supmax01, &
     1041                           asupmaxmin1, &
     1042                           da1, phi1, mp1, phi21, d1a1, dam1, sigij1,  & ! RomP
     1043                           clw1, elij1, evap1, ep1, epmlmMm1, eplaMm1, & ! RomP
     1044                           wdtrainA1, wdtrainM1)                         ! RomP
    9981045    END IF
    9991046
    10001047    IF (iflag_con==4) THEN
    1001       CALL cv_uncompress(nloc, len, ncum, nd, idcum, iflag, precip, cbmf, ft, &
    1002         fq, fu, fv, ma, qcondc, iflag1, precip1, cbmf1, ft1, fq1, fu1, fv1, &
    1003         ma1, qcondc1)
     1048      CALL cv_uncompress(nloc, len, ncum, nd, idcum, &
     1049                           iflag, &
     1050                           precip, cbmf, &
     1051                           ft, fq, fu, fv, &
     1052                           ma, qcondc, &
     1053                           iflag1, &
     1054                           precip1,cbmf1, &
     1055                           ft1, fq1, fu1, fv1, &
     1056                           ma1, qcondc1)
    10041057    END IF
    10051058
     
    10091062    PRINT *, ' cv_compress -> '
    10101063    debut = .FALSE.
    1011   END IF !(debut) THEN
     1064  END IF  !(debut) THEN
     1065
    10121066
    10131067  RETURN
Note: See TracChangeset for help on using the changeset viewer.