Ignore:
Timestamp:
Mar 30, 2015, 11:08:45 AM (10 years ago)
Author:
jyg
Message:

1/ Introduction of two variables in the ".def" files: (i) cvl_sig2feed is
the top of the convective feeding layer in sigma coordinates (D=0.97);
(ii) cvl_comp_threshold is the threshold fraction of convective points
below which compression occurs (D=1.).
2/ Corrections of various bugs revealed by the changes in compression:

  • correct bugs in cv3a_uncompress.F90 for 3 fields used for convective

scavenging.

  • add a reset to zero of "sig" and "w0" for non-convective points

(cva_driver.F90).

  • in cv3_routines.F90, correct bounds of a few loops in cv3_undilute2,

correct the reset of the no-convection counter in cv3_yield.

  • in phys_output_write_mod.F90, correct output of wdtrainA and wdtrainM.

3/ Improve declarations in various subroutines.

Modified files:

conema3.h
cv3param.h
cv3p1_closure.F90
conf_phys_m.F90
cv3a_compress.F90
phys_output_write_mod.F90
cv3_routines.F90
concvl.F90
cva_driver.F90
cv3a_uncompress.F90

File:
1 edited

Legend:

Unmodified
Added
Removed
  • LMDZ5/trunk/libf/phylmd/cv3a_compress.F90

    r2201 r2253  
    1 SUBROUTINE cv3a_compress(len, nloc, ncum, nd, ntra, iflag1, nk1, icb1, icbs1, &
    2     plcl1, tnk1, qnk1, gznk1, hnk1, unk1, vnk1, wghti1, pbase1, buoybase1, &
    3     t1, q1, qs1, t1_wake, q1_wake, qs1_wake, s1_wake, u1, v1, gz1, th1, &
    4     th1_wake, tra1, h1, lv1, lf1, cpn1, p1, ph1, tv1, tp1, tvp1, clw1, &
    5     h1_wake, lv1_wake, lf1_wake, cpn1_wake, tv1_wake, sig1, w01, ptop21, &
    6     ale1, alp1, omega1, iflag, nk, icb, icbs, plcl, tnk, qnk, gznk, hnk, unk, vnk, &
    7     wghti, pbase, buoybase, t, q, qs, t_wake, q_wake, qs_wake, s_wake, u, v, &
    8     gz, th, th_wake, tra, h, lv, lf, cpn, p, ph, tv, tp, tvp, clw, h_wake, &
    9     lv_wake, lf_wake, cpn_wake, tv_wake, sig, w0, ptop2, ale, alp, omega)
     1SUBROUTINE cv3a_compress(len, nloc, ncum, nd, ntra, compress, &
     2                         iflag1, nk1, icb1, icbs1, &
     3                         plcl1, tnk1, qnk1, gznk1, hnk1, unk1, vnk1, &
     4                         wghti1, pbase1, buoybase1, &
     5                         t1, q1, qs1, t1_wake, q1_wake, qs1_wake, s1_wake, &
     6                         u1, v1, gz1, th1, th1_wake, &
     7                         tra1, &
     8                         h1, lv1, lf1, cpn1, p1, ph1, tv1, tp1, tvp1, clw1, &
     9                         h1_wake, lv1_wake, lf1_wake, cpn1_wake, tv1_wake, &
     10                         sig1, w01, ptop21, &
     11                         Ale1, Alp1, omega1, &
     12                         iflag, nk, icb, icbs, &
     13                         plcl, tnk, qnk, gznk, hnk, unk, vnk, &
     14                         wghti, pbase, buoybase, &
     15                         t, q, qs, t_wake, q_wake, qs_wake, s_wake, &
     16                         u, v, gz, th, th_wake, &
     17                         tra, &
     18                         h, lv, lf, cpn, p, ph, tv, tp, tvp, clw, &
     19                         h_wake, lv_wake, lf_wake, cpn_wake, tv_wake, &
     20                         sig, w0, ptop2, &
     21                         Ale, Alp, omega)
    1022  ! **************************************************************
    1123  ! *
     
    2234
    2335  ! inputs:
    24   INTEGER len, nloc, ncum, nd, ntra
    25   INTEGER iflag1(len), nk1(len), icb1(len), icbs1(len)
    26   REAL plcl1(len), tnk1(len), qnk1(len), gznk1(len)
    27   REAL hnk1(len), unk1(len), vnk1(len)
    28   REAL wghti1(len, nd), pbase1(len), buoybase1(len)
    29   REAL t1(len, nd), q1(len, nd), qs1(len, nd)
    30   REAL t1_wake(len, nd), q1_wake(len, nd), qs1_wake(len, nd)
    31   REAL s1_wake(len)
    32   REAL u1(len, nd), v1(len, nd)
    33   REAL gz1(len, nd), th1(len, nd), th1_wake(len, nd)
    34   REAL tra1(len, nd, ntra)
    35   REAL h1(len, nd), lv1(len, nd), lf1(len, nd), cpn1(len, nd)
    36   REAL p1(len, nd), ph1(len, nd+1), tv1(len, nd), tp1(len, nd)
    37   REAL tvp1(len, nd), clw1(len, nd)
    38   REAL h1_wake(len, nd), lv1_wake(len, nd), cpn1_wake(len, nd)
    39   REAL tv1_wake(len, nd), lf1_wake(len, nd)
    40   REAL sig1(len, nd), w01(len, nd), ptop21(len)
    41   REAL ale1(len), alp1(len)
    42   REAL omega1(len,nd)
    43 
     36  INTEGER, INTENT (IN)                               :: len, nloc, nd, ntra
     37!jyg<
     38  LOGICAL, INTENT (IN)                               :: compress  ! compression is performed if compress is true
     39!>jyg
     40  INTEGER, DIMENSION (len), INTENT (IN)              :: iflag1, nk1, icb1, icbs1
     41  REAL, DIMENSION (len), INTENT (IN)                 :: plcl1, tnk1, qnk1, gznk1
     42  REAL, DIMENSION (len), INTENT (IN)                 :: hnk1, unk1, vnk1
     43  REAL, DIMENSION (len, nd), INTENT (IN)             :: wghti1(len, nd)
     44  REAL, DIMENSION (len), INTENT (IN)                 :: pbase1, buoybase1
     45  REAL, DIMENSION (len, nd), INTENT (IN)             :: t1, q1, qs1
     46  REAL, DIMENSION (len, nd), INTENT (IN)             :: t1_wake, q1_wake, qs1_wake
     47  REAL, DIMENSION (len), INTENT (IN)                 :: s1_wake
     48  REAL, DIMENSION (len, nd), INTENT (IN)             :: u1, v1
     49  REAL, DIMENSION (len, nd), INTENT (IN)             :: gz1, th1, th1_wake
     50  REAL, DIMENSION (len, nd,ntra), INTENT (IN)        :: tra1
     51  REAL, DIMENSION (len, nd), INTENT (IN)             :: h1, lv1, lf1, cpn1
     52  REAL, DIMENSION (len, nd), INTENT (IN)             :: p1
     53  REAL, DIMENSION (len, nd+1), INTENT (IN)           :: ph1(len, nd+1)
     54  REAL, DIMENSION (len, nd), INTENT (IN)             :: tv1, tp1
     55  REAL, DIMENSION (len, nd), INTENT (IN)             :: tvp1, clw1
     56  REAL, DIMENSION (len, nd), INTENT (IN)             :: h1_wake, lv1_wake, cpn1_wake
     57  REAL, DIMENSION (len, nd), INTENT (IN)             :: tv1_wake, lf1_wake
     58  REAL, DIMENSION (len, nd), INTENT (IN)             :: sig1, w01
     59  REAL, DIMENSION (len), INTENT (IN)                 :: ptop21
     60  REAL, DIMENSION (len), INTENT (IN)                 :: Ale1, Alp1
     61  REAL, DIMENSION (len, nd), INTENT (IN)             :: omega1
     62!
     63  ! in/out
     64  INTEGER, INTENT (INOUT)                            :: ncum
     65!
    4466  ! outputs:
    4567  ! en fait, on a nloc=len pour l'instant (cf cv_driver)
    46   INTEGER iflag(len), nk(len), icb(len), icbs(len)
    47   REAL plcl(len), tnk(len), qnk(len), gznk(len)
    48   REAL hnk(len), unk(len), vnk(len)
    49   REAL wghti(len, nd), pbase(len), buoybase(len)
    50   REAL t(len, nd), q(len, nd), qs(len, nd)
    51   REAL t_wake(len, nd), q_wake(len, nd), qs_wake(len, nd)
    52   REAL s_wake(len)
    53   REAL u(len, nd), v(len, nd)
    54   REAL gz(len, nd), th(len, nd), th_wake(len, nd)
    55   REAL tra(len, nd, ntra)
    56   REAL h(len, nd), lv(len, nd), lf(len, nd), cpn(len, nd)
    57   REAL p(len, nd), ph(len, nd+1), tv(len, nd), tp(len, nd)
    58   REAL tvp(len, nd), clw(len, nd)
    59   REAL h_wake(len, nd), lv_wake(len, nd), cpn_wake(len, nd)
    60   REAL tv_wake(len, nd), lf_wake(len, nd)
    61   REAL sig(len, nd), w0(len, nd), ptop2(len)
    62   REAL ale(len), alp(len)
    63   REAL omega(len,nd)
     68  INTEGER, DIMENSION (nloc), INTENT (OUT)            ::  iflag, nk, icb, icbs
     69  REAL, DIMENSION (nloc), INTENT (OUT)               ::  plcl, tnk, qnk, gznk
     70  REAL, DIMENSION (nloc), INTENT (OUT)               ::  hnk, unk, vnk
     71  REAL, DIMENSION (nloc, nd), INTENT (OUT)           ::  wghti
     72  REAL, DIMENSION (nloc), INTENT (OUT)               ::  pbase, buoybase
     73  REAL, DIMENSION (nloc, nd), INTENT (OUT)           ::  t, q, qs
     74  REAL, DIMENSION (nloc, nd), INTENT (OUT)           ::  t_wake, q_wake, qs_wake
     75  REAL, DIMENSION (nloc), INTENT (OUT)               ::  s_wake
     76  REAL, DIMENSION (nloc, nd), INTENT (OUT)           ::  u, v
     77  REAL, DIMENSION (nloc, nd), INTENT (OUT)           ::  gz, th, th_wake
     78  REAL, DIMENSION (nloc, nd,ntra), INTENT (OUT)      ::  tra
     79  REAL, DIMENSION (nloc, nd), INTENT (OUT)           ::  h, lv, lf, cpn
     80  REAL, DIMENSION (nloc, nd), INTENT (OUT)           ::  p
     81  REAL, DIMENSION (nloc, nd+1), INTENT (OUT)         ::  ph
     82  REAL, DIMENSION (nloc, nd), INTENT (OUT)           ::  tv, tp
     83  REAL, DIMENSION (nloc, nd), INTENT (OUT)           ::  tvp, clw
     84  REAL, DIMENSION (nloc, nd), INTENT (OUT)           ::  h_wake, lv_wake, cpn_wake
     85  REAL, DIMENSION (nloc, nd), INTENT (OUT)           ::  tv_wake, lf_wake
     86  REAL, DIMENSION (nloc, nd), INTENT (OUT)           ::  sig, w0
     87  REAL, DIMENSION (nloc), INTENT (OUT)               ::  ptop2
     88  REAL, DIMENSION (nloc), INTENT (OUT)               ::  Ale, Alp
     89  REAL, DIMENSION (nloc, nd), INTENT (OUT)           ::  omega
    6490
    6591  ! local variables:
     
    6995  CHARACTER (LEN=80) :: abort_message
    7096
     97!jyg<
     98  IF (compress) THEN
     99!>jyg
    71100
    72101  DO k = 1, nl + 1
     
    108137    END DO
    109138  END DO
    110 
     139!
    111140  ! AC!      do 121 j=1,ntra
    112141  ! AC!ccccc      do 111 k=1,nl+1
     
    147176      buoybase(nn) = buoybase1(i)
    148177      ptop2(nn) = ptop2(i)
    149       ale(nn) = ale1(i)
    150       alp(nn) = alp1(i)
     178      Ale(nn) = Ale1(i)
     179      Alp(nn) = Alp1(i)
    151180    END IF
    152181  END DO
     
    157186    CALL abort_gcm(modname, abort_message, 1)
    158187  END IF
     188!
     189!jyg<
     190  ELSE  !(compress)
     191!
     192      ncum = len
     193!
     194      wghti(:,:) = wghti1(:,:)
     195      t(:,:) = t1(:,:)
     196      q(:,:) = q1(:,:)
     197      qs(:,:) = qs1(:,:)
     198      t_wake(:,:) = t1_wake(:,:)
     199      q_wake(:,:) = q1_wake(:,:)
     200      qs_wake(:,:) = qs1_wake(:,:)
     201      u(:,:) = u1(:,:)
     202      v(:,:) = v1(:,:)
     203      gz(:,:) = gz1(:,:)
     204      th(:,:) = th1(:,:)
     205      th_wake(:,:) = th1_wake(:,:)
     206      h(:,:) = h1(:,:)
     207      lv(:,:) = lv1(:,:)
     208      lf(:,:) = lf1(:,:)
     209      cpn(:,:) = cpn1(:,:)
     210      p(:,:) = p1(:,:)
     211      ph(:,:) = ph1(:,:)
     212      tv(:,:) = tv1(:,:)
     213      tp(:,:) = tp1(:,:)
     214      tvp(:,:) = tvp1(:,:)
     215      clw(:,:) = clw1(:,:)
     216      h_wake(:,:) = h1_wake(:,:)
     217      lv_wake(:,:) = lv1_wake(:,:)
     218      lf_wake(:,:) = lf1_wake(:,:)
     219      cpn_wake(:,:) = cpn1_wake(:,:)
     220      tv_wake(:,:) = tv1_wake(:,:)
     221      sig(:,:) = sig1(:,:)
     222      w0(:,:) = w01(:,:)
     223      omega(:,:) = omega1(:,:)
     224!
     225      s_wake(:) = s1_wake(:)
     226      iflag(:) = iflag1(:)
     227      nk(:) = nk1(:)
     228      icb(:) = icb1(:)
     229      icbs(:) = icbs1(:)
     230      plcl(:) = plcl1(:)
     231      tnk(:) = tnk1(:)
     232      qnk(:) = qnk1(:)
     233      gznk(:) = gznk1(:)
     234      hnk(:) = hnk1(:)
     235      unk(:) = unk1(:)
     236      vnk(:) = vnk1(:)
     237      pbase(:) = pbase1(:)
     238      buoybase(:) = buoybase1(:)
     239      ptop2(:) = ptop2(:)
     240      Ale(:) = Ale1(:)
     241      Alp(:) = Alp1(:)
     242!
     243  ENDIF !(compress)
     244!>jyg
    159245
    160246  RETURN
Note: See TracChangeset for help on using the changeset viewer.