Changeset 3757 for LMDZ6


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

Create separate subroutines for cv3a_driver and cv4a_driver

Location:
LMDZ6/branches/Optimisation_LMDZ/libf/phylmd
Files:
1 edited
1 copied

Legend:

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

    r3755 r3757  
    1 
    2 ! $Id$
    3 
    4 SUBROUTINE cva_driver(len, nd, ndp1, ntra, nloc, k_upper, &
     1module cv3a_driver_mod
     2  contains
     3
     4SUBROUTINE cv3a_driver(len, nd, ndp1, ntra, nloc, k_upper, &
    55                      iflag_con, iflag_mix, iflag_ice_thermo, iflag_clos, ok_conserv_q, &
    66!!                      delt, t1, q1, qs1, t1_wake, q1_wake, qs1_wake, s1_wake, &  ! jyg
     
    13811381
    13821382  RETURN
    1383 END SUBROUTINE cva_driver
     1383END SUBROUTINE cv3a_driver
     1384
     1385END MODULE
  • LMDZ6/branches/Optimisation_LMDZ/libf/phylmd/cva_driver.F90

    r3709 r3757  
    1 
    2 ! $Id$
    3 
    41SUBROUTINE cva_driver(len, nd, ndp1, ntra, nloc, k_upper, &
     2  iflag_con, iflag_mix, iflag_ice_thermo, iflag_clos, ok_conserv_q, &
     3  delt, comp_threshold, &
     4  t1, q1, qs1, t1_wake, q1_wake, qs1_wake, s1_wake, &
     5  u1, v1, tra1, &
     6  p1, ph1, &
     7  Ale1, Alp1, omega1, &
     8  sig1feed1, sig2feed1, wght1, &
     9  iflag1, ft1, fq1, fu1, fv1, ftra1, &
     10  precip1, kbas1, ktop1, &
     11  cbmf1, plcl1, plfc1, wbeff1, &
     12  sig1, w01, &
     13  ptop21, sigd1, &
     14  ma1, mip1, Vprecip1, Vprecipi1, upwd1, dnwd1, dnwd01, &
     15  qcondc1, wd1, &
     16  cape1, cin1, tvp1, &
     17  ftd1, fqd1, &
     18  Plim11, Plim21, asupmax1, supmax01, asupmaxmin1, &
     19  lalim_conv1, &
     20  da1, phi1, mp1, phi21, d1a1, dam1, sigij1, wghti1, &
     21  qta1, clw1, elij1, evap1, ep1, epmlmMm1, eplaMm1, &
     22  wdtrainA1, wdtrainS1, wdtrainM1, qtc1, sigt1, tau_cld_cv, &
     23  coefw_cld_cv, &
     24  epmax_diag1)
     25  use cv3a_driver_mod
     26  IMPLICIT NONE
     27  INTEGER, INTENT (IN)                               :: len
     28  INTEGER, INTENT (IN)                               :: nd
     29  INTEGER, INTENT (IN)                               :: ndp1
     30  INTEGER, INTENT (IN)                               :: ntra
     31  INTEGER, INTENT(IN)                                :: nloc ! (nloc=len)  pour l'instant
     32  INTEGER, INTENT (IN)                               :: k_upper
     33  INTEGER, INTENT (IN)                               :: iflag_con
     34  INTEGER, INTENT (IN)                               :: iflag_mix
     35  INTEGER, INTENT (IN)                               :: iflag_ice_thermo
     36  INTEGER, INTENT (IN)                               :: iflag_clos
     37  LOGICAL, INTENT (IN)                               :: ok_conserv_q
     38  REAL, INTENT (IN)                                  :: tau_cld_cv
     39  REAL, INTENT (IN)                                  :: coefw_cld_cv
     40  REAL, INTENT (IN)                                  :: delt
     41  REAL, INTENT (IN)                                  :: comp_threshold
     42  REAL, DIMENSION (len, nd), INTENT (IN)             :: t1
     43  REAL, DIMENSION (len, nd), INTENT (IN)             :: q1
     44  REAL, DIMENSION (len, nd), INTENT (IN)             :: qs1
     45  REAL, DIMENSION (len, nd), INTENT (IN)             :: t1_wake
     46  REAL, DIMENSION (len, nd), INTENT (IN)             :: q1_wake
     47  REAL, DIMENSION (len, nd), INTENT (IN)             :: qs1_wake
     48  REAL, DIMENSION (len), INTENT (IN)                 :: s1_wake
     49  REAL, DIMENSION (len, nd), INTENT (IN)             :: u1
     50  REAL, DIMENSION (len, nd), INTENT (IN)             :: v1
     51  REAL, DIMENSION (len, nd, ntra), INTENT (IN)       :: tra1
     52  REAL, DIMENSION (len, nd), INTENT (IN)             :: p1
     53  REAL, DIMENSION (len, ndp1), INTENT (IN)           :: ph1
     54  REAL, DIMENSION (len), INTENT (IN)                 :: Ale1
     55  REAL, DIMENSION (len), INTENT (IN)                 :: Alp1
     56  REAL, DIMENSION (len, nd), INTENT (IN)             :: omega1
     57  REAL, INTENT (IN)                                  :: sig1feed1 ! pressure at lower bound of feeding layer
     58  REAL, INTENT (IN)                                  :: sig2feed1 ! pressure at upper bound of feeding layer
     59  REAL, DIMENSION (nd), INTENT (IN)                  :: wght1     ! weight density determining the feeding mixture
     60  INTEGER, DIMENSION (len), INTENT (IN)              :: lalim_conv1
     61
     62! Input/Output
     63  REAL, DIMENSION (len, nd), INTENT (INOUT)          :: sig1
     64  REAL, DIMENSION (len, nd), INTENT (INOUT)          :: w01
     65
     66! Output
     67  INTEGER, DIMENSION (len), INTENT (OUT)             :: iflag1
     68  REAL, DIMENSION (len, nd), INTENT (OUT)            :: ft1
     69  REAL, DIMENSION (len, nd), INTENT (OUT)            :: fq1
     70  REAL, DIMENSION (len, nd), INTENT (OUT)            :: fu1
     71  REAL, DIMENSION (len, nd), INTENT (OUT)            :: fv1
     72  REAL, DIMENSION (len, nd, ntra), INTENT (OUT)      :: ftra1
     73  REAL, DIMENSION (len), INTENT (OUT)                :: precip1
     74  INTEGER, DIMENSION (len), INTENT (OUT)             :: kbas1
     75  INTEGER, DIMENSION (len), INTENT (OUT)             :: ktop1
     76  REAL, DIMENSION (len), INTENT (OUT)                :: cbmf1
     77  REAL, DIMENSION (len), INTENT (OUT)                :: plcl1
     78  REAL, DIMENSION (len), INTENT (OUT)                :: plfc1
     79  REAL, DIMENSION (len), INTENT (OUT)                :: wbeff1
     80  REAL, DIMENSION (len), INTENT (OUT)                :: ptop21
     81  REAL, DIMENSION (len), INTENT (OUT)                :: sigd1
     82  REAL, DIMENSION (len, nd), INTENT (OUT)            :: ma1        ! adiab. asc. mass flux (staggered grid)
     83  REAL, DIMENSION (len, nd), INTENT (OUT)            :: mip1       ! mass flux shed from adiab. ascent (extensive)
     84  REAL, DIMENSION (len, ndp1), INTENT (OUT)          :: vprecip1   ! tot precipitation flux (staggered grid)
     85  REAL, DIMENSION (len, ndp1), INTENT (OUT)          :: vprecipi1  ! ice precipitation flux (staggered grid)
     86  REAL, DIMENSION (len, nd), INTENT (OUT)            :: upwd1      ! upwd sat. mass flux (staggered grid)
     87  REAL, DIMENSION (len, nd), INTENT (OUT)            :: dnwd1      ! dnwd sat. mass flux (staggered grid)
     88  REAL, DIMENSION (len, nd), INTENT (OUT)            :: dnwd01     ! unsat. mass flux (staggered grid)
     89  REAL, DIMENSION (len, nd), INTENT (OUT)            :: qcondc1    ! max cloud condensate (intensive)  ! cld
     90  REAL, DIMENSION (len), INTENT (OUT)                :: wd1             ! gust
     91  REAL, DIMENSION (len), INTENT (OUT)                :: cape1
     92  REAL, DIMENSION (len), INTENT (OUT)                :: cin1
     93  REAL, DIMENSION (len, nd), INTENT (OUT)            :: tvp1       ! Virt. temp. in the adiab. ascent
     94  REAL, DIMENSION (len, nd), INTENT (OUT)            :: ftd1       ! Temp. tendency due to the sole unsat. drafts
     95  REAL, DIMENSION (len, nd), INTENT (OUT)            :: fqd1       ! Moist. tendency due to the sole unsat. drafts
     96  REAL, DIMENSION (len), INTENT (OUT)                :: Plim11
     97  REAL, DIMENSION (len), INTENT (OUT)                :: Plim21
     98  REAL, DIMENSION (len, nd), INTENT (OUT)            :: asupmax1   ! Highest mixing fraction of mixed updraughts
     99  REAL, DIMENSION (len), INTENT (OUT)                :: supmax01
     100  REAL, DIMENSION (len), INTENT (OUT)                :: asupmaxmin1
     101  REAL, DIMENSION (len, nd), INTENT (OUT)            :: qtc1    ! in cloud water content (intensive)   ! cld
     102  REAL, DIMENSION (len, nd), INTENT (OUT)            :: sigt1   ! fract. cloud area (intensive)        ! cld
     103
     104! RomP >>>
     105  REAL, DIMENSION (len, nd), INTENT (OUT)            :: wdtrainA1, wdtrainS1, wdtrainM1 ! precipitation sources (extensive)
     106  REAL, DIMENSION (len, nd), INTENT (OUT)            :: mp1  ! unsat. mass flux (staggered grid)
     107  REAL, DIMENSION (len, nd), INTENT (OUT)            :: da1  ! detrained mass flux of adiab. asc. air (extensive)
     108  REAL, DIMENSION (len, nd, nd), INTENT (OUT)        :: phi1 ! mass flux of envt. air in mixed draughts (extensive)
     109  REAL, DIMENSION (len, nd, nd), INTENT (OUT)        :: epmlmMm1  ! (extensive)
     110  REAL, DIMENSION (len, nd), INTENT (OUT)            :: eplaMm1   ! (extensive)
     111  REAL, DIMENSION (len, nd), INTENT (OUT)            :: evap1 ! evaporation rate in precip. downdraft. (intensive)
     112  REAL, DIMENSION (len, nd), INTENT (OUT)            :: ep1
     113  REAL, DIMENSION (len, nd, nd), INTENT (OUT)        :: sigij1 ! mass fraction of env. air in mixed draughts (intensive)
     114  REAL, DIMENSION (len, nd, nd), INTENT (OUT)        :: elij1! cond. water per unit mass of mixed draughts (intensive)
     115  REAL, DIMENSION (len, nd), INTENT (OUT)            :: qta1 ! total water per unit mass of the adiab. asc. (intensive)
     116  REAL, DIMENSION (len, nd), INTENT (OUT)            :: clw1 ! cond. water per unit mass of the adiab. asc. (intensive)
     117!JYG,RL
     118  REAL, DIMENSION (len, nd), INTENT (OUT)            :: wghti1   ! final weight of the feeding layers (extensive)
     119!JYG,RL
     120  REAL, DIMENSION (len, nd, nd), INTENT (OUT)        :: phi21    ! (extensive)
     121  REAL, DIMENSION (len, nd), INTENT (OUT)            :: d1a1     ! (extensive)
     122  REAL, DIMENSION (len, nd), INTENT (OUT)            :: dam1     ! (extensive)
     123! RomP <<<
     124  REAL, DIMENSION (len ), INTENT (OUT)               :: epmax_diag1
     125
     126  if(iflag_con == 3) then
     127    call cv3a_driver(len, nd, ndp1, ntra, nloc, k_upper, &
     128                iflag_con, iflag_mix, iflag_ice_thermo, iflag_clos, ok_conserv_q, &
     129                delt, comp_threshold, &
     130                t1, q1, qs1, t1_wake, q1_wake, qs1_wake, s1_wake, &
     131                u1, v1, tra1, &
     132                p1, ph1, &
     133                Ale1, Alp1, omega1, &
     134                sig1feed1, sig2feed1, wght1, &
     135                iflag1, ft1, fq1, fu1, fv1, ftra1, &
     136                precip1, kbas1, ktop1, &
     137                cbmf1, plcl1, plfc1, wbeff1, &
     138                sig1, w01, &
     139                ptop21, sigd1, &
     140                ma1, mip1, Vprecip1, Vprecipi1, upwd1, dnwd1, dnwd01, &
     141                qcondc1, wd1, &
     142                cape1, cin1, tvp1, &
     143                ftd1, fqd1, &
     144                Plim11, Plim21, asupmax1, supmax01, asupmaxmin1, &
     145                lalim_conv1, &
     146                da1, phi1, mp1, phi21, d1a1, dam1, sigij1, wghti1, &
     147                qta1, clw1, elij1, evap1, ep1, epmlmMm1, eplaMm1, &
     148                wdtrainA1, wdtrainS1, wdtrainM1, qtc1, sigt1, tau_cld_cv, &
     149                coefw_cld_cv, &
     150                epmax_diag1)
     151  elseif(iflag_con == 4) then
     152    call cv4a_driver(len, nd, ndp1, ntra, nloc, k_upper, &
     153                iflag_con, iflag_mix, iflag_ice_thermo, iflag_clos, ok_conserv_q, &
     154                delt, comp_threshold, &
     155                t1, q1, qs1, t1_wake, q1_wake, qs1_wake, s1_wake, &
     156                u1, v1, tra1, &
     157                p1, ph1, &
     158                Ale1, Alp1, omega1, &
     159                sig1feed1, sig2feed1, wght1, &
     160                iflag1, ft1, fq1, fu1, fv1, ftra1, &
     161                precip1, kbas1, ktop1, &
     162                cbmf1, plcl1, plfc1, wbeff1, &
     163                sig1, w01, &
     164                ptop21, sigd1, &
     165                ma1, mip1, Vprecip1, Vprecipi1, upwd1, dnwd1, dnwd01, &
     166                qcondc1, wd1, &
     167                cape1, cin1, tvp1, &
     168                ftd1, fqd1, &
     169                Plim11, Plim21, asupmax1, supmax01, asupmaxmin1, &
     170                lalim_conv1, &
     171                da1, phi1, mp1, phi21, d1a1, dam1, sigij1, wghti1, &
     172                qta1, clw1, elij1, evap1, ep1, epmlmMm1, eplaMm1, &
     173                wdtrainA1, wdtrainS1, wdtrainM1, qtc1, sigt1, tau_cld_cv, &
     174                coefw_cld_cv, &
     175                epmax_diag1)
     176  else
     177    call abort_physic("cva_driver", "iflag_con is not compatible", 1)
     178  endif
     179
     180END SUBROUTINE
     181
     182SUBROUTINE cv4a_driver(len, nd, ndp1, ntra, nloc, k_upper, &
    5183                      iflag_con, iflag_mix, iflag_ice_thermo, iflag_clos, ok_conserv_q, &
    6184!!                      delt, t1, q1, qs1, t1_wake, q1_wake, qs1_wake, s1_wake, &  ! jyg
     
    13811559
    13821560  RETURN
    1383 END SUBROUTINE cva_driver
     1561END SUBROUTINE cv4a_driver
Note: See TracChangeset for help on using the changeset viewer.