Changeset 4547


Ignore:
Timestamp:
May 27, 2023, 12:08:31 PM (12 months ago)
Author:
fhourdin
Message:

Details pour travail sur PHHYEX

Location:
LMDZ6/trunk/libf/phylmd
Files:
2 edited

Legend:

Unmodified
Added
Removed
  • LMDZ6/trunk/libf/phylmd/output_physiqex_mod.F90

    r4540 r4547  
    55CONTAINS
    66
    7 SUBROUTINE output_physiqex(debut,zjulian,pdtphys,presnivs,paprs,u,v,t)
     7SUBROUTINE output_physiqex(debut,zjulian,pdtphys,presnivs,paprs,u,v,t,qx,cf,zqr,zqs,zqg,ptke,theta)
    88
    99      USE dimphy, only : klon,klev
     
    1515      USE iophy, ONLY : init_iophy_new
    1616      USE geometry_mod, ONLY: latitude_deg, longitude_deg
     17      USE infotrac_phy, only : nqtot
    1718
    1819
     
    2526real,intent(in) :: v(klon,klev) ! northward meridional wind (m/s)
    2627real,intent(in) :: t(klon,klev) ! temperature (K)
     28real,intent(in) :: theta(klon,klev) ! temperature (K)
    2729real,intent(in) :: paprs(klon,klev+1) ! interlayer pressure (Pa)
     30real,intent(in) :: qx(klon,klev,nqtot) !tracers
     31real,intent(in) :: cf(klon,klev) !cloud fraction
     32real,intent(in) :: zqr(klon,klev) !rain specifiq content
     33real,intent(in) :: zqs(klon,klev) !snow specifiq content
     34real,intent(in) :: zqg(klon,klev) !graupel specifiq content
     35real,intent(in) :: ptke(klon,klev) !tke
    2836
    2937real :: t_ops ! frequency of the IOIPSL operations (eg average over...)
     
    4856
    4957   call getin_p("iwrite_phys",iwrite_phys)
    50    call getin_p("ioex",ioex)
    51 
    52    if ( ioex == 1 ) then
    53       CALL iophys_ini(pdtphys)
    54    else if ( ioex == 2 ) then
    55 
    56       CALL init_iophy_new(latitude_deg,longitude_deg)
    57       dtime=pdtphys
    58       itau=0
    59       call histbeg_phy("histins.nc",itau,zjulian,dtime,nhori,nid_hist)
    60       print*,'NNNNNNN ',nid_hist,debut
    61       print*,'NNNNNNN OK0'
    62       t_ops=pdtphys*iwrite_phys ! frequency of the IOIPSL operation
    63       t_wrt=pdtphys*iwrite_phys ! frequency of the outputs in the file
    64       print*,'NNNNNNN OK1'
    6558
    6659   !$OMP MASTER
    67 
    68 #ifndef CPP_IOIPSL_NO_OUTPUT
    69        ! IOIPSL
    70        ! define vertical coordinate
    71        call histvert(nid_hist,"presnivs","Vertical levels","Pa",klev, &
    72                      presnivs,zvertid,'down')
    73        ! define variables which will be written in "histins.nc" file
    74        call histdef(nid_hist,'Temp','Atmospheric temperature','K', &
    75                     nbp_lon,jj_nb,nhori,klev,1,klev,zvertid,32, &
    76                     'inst(X)',t_ops,t_wrt)
    77        print*,'NNNNNNN OK2a',nid_hist,t_ops,t_wrt
    78        call histdef(nid_hist,'u','Eastward Zonal Wind','m/s', &
    79                     nbp_lon,jj_nb,nhori,klev,1,klev,zvertid,32, &
    80                     'inst(X)',t_ops,t_wrt)
    81        print*,'NNNNNNN OK2b',nid_hist,t_ops,t_wrt
    82        call histdef(nid_hist,'v','Northward Meridional Wind','m/s', &
    83                     nbp_lon,jj_nb,nhori,klev,1,klev,zvertid,32, &
    84                     'inst(X)',t_ops,t_wrt)
    85        print*,'NNNNNNN OK2c',nid_hist,t_ops,t_wrt
    86        call histdef(nid_hist,'ps','Surface Pressure','Pa', &
    87                     nbp_lon,jj_nb,nhori,1,1,1,zvertid,32, &
    88                     'inst(X)',t_ops,t_wrt)
    89        ! end definition sequence
    90        print*,'NNNNNNN OK2',nid_hist,t_ops,t_wrt
    91        call histend(nid_hist)
    92        print*,'NNNNNNN OK3'
    93 #endif
    94 
    95 #ifdef CPP_XIOS
    96       !XIOS
    97           ! Declare available vertical axes to be used in output files:   
    98           CALL wxios_add_vaxis("presnivs", klev, presnivs)
    99      
    100           ! Declare calendar and time step
    101           CALL wxios_set_cal(dtime,"earth_360d",1,1,1,0.0,1,1,1,0.0)
    102          
    103           !Finalize the context:
    104           CALL wxios_closedef()
    105 #endif
    106 
    107       !$OMP END MASTER
    108       !$OMP BARRIER
    109    endif
     60   CALL iophys_ini(pdtphys)
     61   !$OMP END MASTER
     62   !$OMP BARRIER
    11063
    11164endif
     
    11467itau=itau+1
    11568
    116 ! write some outputs:
    117 ! IOIPSL
    118 #ifndef CPP_IOIPSL_NO_OUTPUT
    11969if (modulo(itau,iwrite_phys)==0) then
    120   if ( ioex == 1 ) then
    12170     call iophys_ecrit('temp',klev,'Temperature','K',t)
    122      call iophys_ecrit('u',klev,'zonal wind','m/s',t)
    123      call iophys_ecrit('v',klev,'meridinal wind','m/s',t)
     71     call iophys_ecrit('u',klev,'zonal wind','m/s',u)
     72     call iophys_ecrit('v',klev,'meridinal wind','m/s',v)
    12473     call iophys_ecrit('ps',1,'Surface pressure','Pa',paprs(:,1))
    125   else if ( ioex == 2 ) then
    126      call histwrite_phy(nid_hist,.false.,"Temp",itau,t)
    127      call histwrite_phy(nid_hist,.false.,"u",itau,u)
    128      call histwrite_phy(nid_hist,.false.,"v",itau,v)
    129      call histwrite_phy(nid_hist,.false.,"ps",itau,paprs(:,1))
    130      !$OMP MASTER
    131      CALL histsync(nid_hist)
    132      !$OMP END MASTER
    133   endif
     74     call iophys_ecrit('qv',klev,'Water vapor specifiq content', 'kg/kg', qx(:,:,1))
     75     call iophys_ecrit('qc',klev,'Cloud liquid water specifiq content', 'kg/kg', qx(:,:,2))
     76     call iophys_ecrit('qi',klev,'Cloud solid water specifiq content', 'kg/kg', qx(:,:,3))
     77     call iophys_ecrit('CF',klev,'Cloud fraction', '0-1', cf)
     78     call iophys_ecrit('qr',klev,'Rain specifiq content', 'kg/kg', zqr)
     79     call iophys_ecrit('qs',klev,'Snow specifiq content', 'kg/kg', zqs)
     80     call iophys_ecrit('qg',klev,'Graupel specifiq content', 'kg/kg', zqg)
     81     call iophys_ecrit('TKE',klev,'TKE', 'm2/s2', ptke)
     82     call iophys_ecrit('theta',klev,'Temperature potentielle', 'K', theta)
    13483endif
    135 #endif
    136 
    137 !XIOS
    138 #ifdef CPP_XIOS
    139    !$OMP MASTER
    140        !Increment XIOS time
    141        CALL xios_update_calendar(itau)
    142    !$OMP END MASTER
    143    !$OMP BARRIER
    144    
    145        !Send fields to XIOS: (NB these fields must also be defined as
    146        ! <field id="..." /> in iodef.xml to be correctly used
    147        CALL histwrite_phy("Temp",t)
    148        CALL histwrite_phy("temp_newton",temp_newton)
    149        CALL histwrite_phy("u",u)
    150        CALL histwrite_phy("v",v)
    151        CALL histwrite_phy("ps",paprs(:,1))
    152 #endif
    15384
    15485
  • LMDZ6/trunk/libf/phylmd/physiq_mod.F90

    r4537 r4547  
    324324       zxsnow,snowhgt,qsnow,to_ice,sissnow,runoff,albsol3_lic
    325325       !
     326      USE output_physiqex_mod, ONLY: output_physiqex
     327
    326328
    327329    IMPLICIT NONE
     
    12371239    !======================================================================!
    12381240    if (debut) then                                                        !
    1239        iflag_physiq=1                                                      !
     1241       iflag_physiq=0
    12401242       call getin_p('iflag_physiq', iflag_physiq)                          !
    12411243    endif                                                                  !
     
    54845486
    54855487#endif
     5488    ! Petit appelle de sorties pour accompagner le travail sur phyex
     5489    if ( iflag_physiq == 1 ) then
     5490        call output_physiqex(debut,jD_eq,pdtphys,presnivs,paprs,u,v,t,qx,cldfra,0.*t,0.*t,0.*t,pbl_tke,theta)
     5491    endif
    54865492
    54875493    !====================================================================
     
    55045510    ! Disabling calls to the prt_alerte function
    55055511    alert_first_call = .FALSE.
     5512
    55065513   
    55075514    IF (lafin) THEN
Note: See TracChangeset for help on using the changeset viewer.