Ignore:
Timestamp:
Mar 12, 2018, 2:42:42 PM (7 years ago)
Author:
Laurent Fairhead
Message:

Integration of transport diagnostics for the CMIP6 data request

Location:
LMDZ6/branches/IPSLCM6.0.15/libf/phylmd
Files:
5 edited

Legend:

Unmodified
Added
Removed
  • LMDZ6/branches/IPSLCM6.0.15/libf/phylmd/phys_local_var_mod.F90

    r3148 r3250  
    319319      REAL,ALLOCATABLE,SAVE,DIMENSION(:) :: slab_wfbils
    320320!$OMP THREADPRIVATE(slab_wfbils)
    321       REAL,ALLOCATABLE,SAVE,DIMENSION(:) :: tpot, tpote, ue, uq, ve, vq, zxffonte
    322 !$OMP THREADPRIVATE(tpot, tpote, ue, uq, ve, vq, zxffonte)
     321      REAL,ALLOCATABLE,SAVE,DIMENSION(:) :: tpot, tpote, ue, uq, uwat, ve, vq, vwat, zxffonte
     322!$OMP THREADPRIVATE(tpot, tpote, ue, uq, uwat, ve, vq, vwat, zxffonte)
    323323      REAL,ALLOCATABLE,SAVE,DIMENSION(:) :: zxfqcalving
    324324!$OMP THREADPRIVATE(zxfqcalving)
     
    712712      ALLOCATE(slab_wfbils(klon), tpot(klon), tpote(klon), ue(klon))
    713713      ALLOCATE(uq(klon), ve(klon), vq(klon), zxffonte(klon))
     714      ALLOCATE(uwat(klon), vwat(klon))
    714715      ALLOCATE(zxfqcalving(klon), zxfluxlat(klon))
    715716      ALLOCATE(zxtsol(klon), snow_lsc(klon), zxfqfonte(klon), zxqsurf(klon))
     
    10041005      DEALLOCATE(slab_wfbils, tpot, tpote, ue)
    10051006      DEALLOCATE(uq, ve, vq, zxffonte)
     1007      DEALLOCATE(uwat, vwat)
    10061008      DEALLOCATE(zxfqcalving, zxfluxlat)
    10071009      DEALLOCATE(zxrunofflic)
  • LMDZ6/branches/IPSLCM6.0.15/libf/phylmd/phys_output_ctrlout_mod.F90

    r3218 r3250  
    679679    'iwp', 'Cloud ice water path', 'kg/m2', (/ ('', i=1, 10) /))
    680680  TYPE(ctrl_out), SAVE :: o_ue = ctrl_out((/ 1, 10, 10, 10, 10, 10, 11, 11, 11, 11/), &
    681     'ue', 'Zonal energy transport', '-', (/ ('', i=1, 10) /))
     681    'ue', 'Zonal dry static energy transport', '-', (/ ('', i=1, 10) /))
    682682  TYPE(ctrl_out), SAVE :: o_ve = ctrl_out((/ 1, 10, 10, 10, 10, 10, 11, 11, 11, 11/), &
    683     've', 'Merid energy transport', '-', (/ ('', i=1, 10) /))
     683    've', 'Merid dry static energy transport', '-', (/ ('', i=1, 10) /))
    684684  TYPE(ctrl_out), SAVE :: o_uq = ctrl_out((/ 1, 10, 10, 10, 10, 10, 11, 11, 11, 11/), &
    685685    'uq', 'Zonal humidity transport', '-', (/ ('', i=1, 10) /))
    686686  TYPE(ctrl_out), SAVE :: o_vq = ctrl_out((/ 1, 10, 10, 10, 10, 10, 11, 11, 11, 11/), &
    687687    'vq', 'Merid humidity transport', '-', (/ ('', i=1, 10) /))
     688  TYPE(ctrl_out), SAVE :: o_uwat = ctrl_out((/ 1, 10, 10, 10, 10, 10, 11, 11, 11, 11/), &
     689    'uwat', 'Zonal total water transport', '-', (/ ('', i=1, 10) /))
     690  TYPE(ctrl_out), SAVE :: o_vwat = ctrl_out((/ 1, 10, 10, 10, 10, 10, 11, 11, 11, 11/), &
     691    'vwat', 'Merid total water transport', '-', (/ ('', i=1, 10) /))
    688692  TYPE(ctrl_out), SAVE :: o_cape = ctrl_out((/ 1, 10, 10, 10, 10, 10, 11, 11, 11, 11/), &
    689693    'cape', 'Conv avlbl pot ener', 'J/kg', (/ ('', i=1, 10) /))
  • LMDZ6/branches/IPSLCM6.0.15/libf/phylmd/phys_output_write_mod.F90

    r3235 r3250  
    7070         o_cldhjn, o_cldtjn, o_cldq, o_lwp, o_iwp, &
    7171         o_ue, o_ve, o_uq, o_vq, o_cape, o_pbase, &
     72         o_uwat, o_vwat, &
    7273         o_ptop, o_fbase, o_plcl, o_plfc, &
    7374         o_wbeff, o_convoccur, o_cape_max, o_upwd, o_ep,o_epmax_diag, o_Ma, &
     
    254255         cldh, cldt, JrNt, cldljn, cldmjn, cldhjn, &
    255256         cldtjn, cldq, flwp, fiwp, ue, ve, uq, vq, &
     257         uwat, vwat, &
    256258         plcl, plfc, wbeff, convoccur, upwd, dnwd, dnwd0, prw, prlw, prsw, &
    257259         s_pblh, s_pblt, s_lcl, s_therm, uwriteSTD, &
     
    960962       CALL histwrite_phy(o_uq, uq)
    961963       CALL histwrite_phy(o_vq, vq)
     964       CALL histwrite_phy(o_uwat, uwat)
     965       CALL histwrite_phy(o_vwat, vwat)
    962966       IF (iflag_con.GE.3) THEN ! sb
    963967          CALL histwrite_phy(o_cape, cape)
  • LMDZ6/branches/IPSLCM6.0.15/libf/phylmd/physiq_mod.F90

    r3240 r3250  
    127127       slab_wfbils, tpot, tpote,               &
    128128       ue, uq, ve, vq, zxffonte,               &
     129       uwat, vwat,                             &
    129130       zxfqcalving, zxfluxlat,                 &
    130131       zxrunofflic,                            &
     
    45034504    !
    45044505    CALL transp (paprs,zxtsol, &
    4505          t_seri, q_seri, u_seri, v_seri, zphi, &
    4506          ve, vq, ue, uq)
     4506         t_seri, q_seri, ql_seri, qs_seri, u_seri, v_seri, zphi, &
     4507         ve, vq, ue, uq, vwat, uwat)
    45074508    !
    45084509    !IM global posePB BEG
  • LMDZ6/branches/IPSLCM6.0.15/libf/phylmd/transp.F90

    r2346 r3250  
    11
    2 ! $Header$
     2! $Id$
    33
    4 SUBROUTINE transp(paprs, tsol, t, q, u, v, geom, vtran_e, vtran_q, utran_e, &
    5     utran_q)
     4SUBROUTINE transp(paprs, tsol, t, q, ql, qs, u, v, geom, vtran_e, vtran_q, utran_e, &
     5    utran_q, vtran_w, utran_w)
    66
    77  USE dimphy
     
    1616
    1717  REAL paprs(klon, klev+1), tsol(klon)
    18   REAL t(klon, klev), q(klon, klev), u(klon, klev), v(klon, klev)
     18  REAL t(klon, klev), q(klon, klev), ql(klon, klev), qs(klon, klev)
     19  REAL u(klon, klev), v(klon, klev)
    1920  REAL utran_e(klon), utran_q(klon), vtran_e(klon), vtran_q(klon)
     21  REAL utran_w(klon), vtran_w(klon)
    2022
    2123  INTEGER i, l
     
    2830    vtran_e(i) = 0.0
    2931    vtran_q(i) = 0.0
     32    utran_w(i) = 0.0
     33    vtran_w(i) = 0.0
    3034  END DO
    3135
    3236  DO l = 1, klev
    3337    DO i = 1, klon
    34       e = rcpd*t(i, l) + rlvtt*q(i, l) + geom(i, l)
     38!      e = rcpd*t(i, l) + rlvtt*q(i, l) + geom(i, l)
     39      e = rcpd*t(i, l) + geom(i, l)
    3540      utran_e(i) = utran_e(i) + u(i, l)*e*(paprs(i,l)-paprs(i,l+1))/rg
    3641      utran_q(i) = utran_q(i) + u(i, l)*q(i, l)*(paprs(i,l)-paprs(i,l+1))/rg
     42      utran_w(i) = utran_w(i) + u(i, l)*(q(i, l)+ql(i, l)+qs(i, l))           &
     43                                       *(paprs(i,l)-paprs(i,l+1))/rg
    3744      vtran_e(i) = vtran_e(i) + v(i, l)*e*(paprs(i,l)-paprs(i,l+1))/rg
    3845      vtran_q(i) = vtran_q(i) + v(i, l)*q(i, l)*(paprs(i,l)-paprs(i,l+1))/rg
     46      vtran_w(i) = vtran_w(i) + v(i, l)*(q(i, l)+ql(i, l)+qs(i, l))           &
     47                                       *(paprs(i,l)-paprs(i,l+1))/rg
    3948    END DO
    4049  END DO
Note: See TracChangeset for help on using the changeset viewer.