Changeset 3506 for trunk


Ignore:
Timestamp:
Nov 8, 2024, 10:57:27 AM (13 days ago)
Author:
afalco
Message:

Pluto: import write_output function from Mars.
xios specific outputs.
AF

Location:
trunk/LMDZ.PLUTO/libf/phypluto
Files:
1 added
4 edited

Legend:

Unmodified
Added
Removed
  • trunk/LMDZ.PLUTO/libf/phypluto/phyetat0_mod.F90

    r3504 r3506  
    22
    33implicit none
     4
     5real, save :: tab_cntrl_mod(100)
     6
     7!$OMP THREADPRIVATE(tab_cntrl_mod)
     8
    49
    510contains
     
    282287end subroutine phyetat0
    283288
     289
     290!======================================================================
     291subroutine ini_tab_controle_dyn_xios(idayref)
     292
     293use comcstfi_mod,        only: g, mugaz, omeg, rad, rcp
     294use time_phylmdz_mod,  only: daysec, dtphys
     295use mod_grid_phy_lmdz, only: nbp_lon, nbp_lat, nbp_lev
     296
     297implicit none
     298
     299integer*4, intent(in) :: idayref ! date (initial date for this run)
     300
     301integer :: length, l
     302parameter (length = 100)
     303real    :: tab_cntrl(length) ! run parameters are stored in this array
     304
     305do l = 1,length
     306    tab_cntrl(l) = 0.
     307enddo
     308tab_cntrl(1)  = real(nbp_lon)
     309tab_cntrl(2)  = real(nbp_lat-1)
     310tab_cntrl(3)  = real(nbp_lev)
     311tab_cntrl(4)  = real(idayref)
     312tab_cntrl(5)  = rad
     313tab_cntrl(6)  = omeg
     314tab_cntrl(7)  = g
     315tab_cntrl(8)  = mugaz
     316tab_cntrl(9)  = rcp
     317tab_cntrl(10) = daysec
     318tab_cntrl(11) = dtphys
     319
     320tab_cntrl_mod = tab_cntrl
     321
     322end subroutine ini_tab_controle_dyn_xios
     323
     324
    284325end module phyetat0_mod
  • trunk/LMDZ.PLUTO/libf/phypluto/physiq_mod.F90

    r3504 r3506  
    3737                          nesp, is_chim, is_condensable,constants_epsi_generic
    3838      use time_phylmdz_mod, only: ecritphy, iphysiq, nday
    39       use phyetat0_mod, only: phyetat0
     39      use phyetat0_mod, only: phyetat0,tab_cntrl_mod
    4040      use wstats_mod, only: callstats, wstats, mkstats
    4141      use phyredem, only: physdem0, physdem1
     
    7979      use datafile_mod, only: datadir
    8080#ifndef MESOSCALE
    81       use vertical_layers_mod, only: presnivs, pseudoalt
     81      USE vertical_layers_mod, ONLY: ap,bp,aps,bps,presnivs,pseudoalt
    8282      use mod_phys_lmdz_omp_data, ONLY: is_omp_master
    8383#else
     
    745745#ifdef CPP_XIOS
    746746
    747          write(*,*) "physiq: call initialize_xios_output"
    748          call initialize_xios_output(pday,ptime,ptimestep,daysec, &
    749                                      year_day,presnivs,pseudoalt,WNOI,WNOV)
     747         if (is_master) write(*,*) "physiq: call initialize_xios_output"
     748         call initialize_xios_output(pday,ptime,ptimestep,daysec,year_day, &
     749                                     presnivs,pseudoalt,mlayer,WNOI,WNOV)
    750750#endif
    751751
     
    26372637      ! Send fields to XIOS: (NB these fields must also be defined as
    26382638      ! <field id="..." /> in context_lmdz_physics.xml to be correctly used)
    2639       CALL send_xios_field("ls",zls)
    2640 
    2641       CALL send_xios_field("ps",ps)
    2642       CALL send_xios_field("area",cell_area)
    2643       CALL send_xios_field("p",pplay)
    2644       CALL send_xios_field("temperature",zt)
    2645       CALL send_xios_field("u",zu)
    2646       CALL send_xios_field("v",zv)
    2647       call send_xios_field("w",pw)
    2648 
    2649       CALL send_xios_field("ISR",fluxtop_dn)
    2650       CALL send_xios_field("OLR",fluxtop_lw)
    2651       CALL send_xios_field("ASR",fluxabs_sw)
    2652 
    2653       if (specOLR .and. corrk) then
    2654          call send_xios_field("OLR3D",OLR_nu)
    2655          call send_xios_field("IR_Bandwidth",DWNI)
    2656          call send_xios_field("VI_Bandwidth",DWNV)
    2657          call send_xios_field("OSR3D",OSR_nu)
    2658          call send_xios_field("GSR3D",GSR_nu)
    2659       endif
     2639      CALL send_xios_field("controle",tab_cntrl_mod,1)
     2640
     2641      CALL send_xios_field("ap",ap,1)
     2642      CALL send_xios_field("bp",bp,1)
     2643      CALL send_xios_field("aps",aps,1)
     2644      CALL send_xios_field("bps",bps,1)
    26602645
    26612646      if (lastcall.and.is_omp_master) then
  • trunk/LMDZ.PLUTO/libf/phypluto/writediagsoil.F90

    r3184 r3506  
     1module writediagsoil_mod
     2
     3implicit none
     4
     5contains
     6
    17subroutine writediagsoil(ngrid,name,title,units,dimpx,px)
    28
     
    8692    stop
    8793  endif
    88  
     94
    8995  ! Set output sample rate
    9096  isample=int(ecritphy) ! same as for diagfi outputs
    9197  ! Note ecritphy is known from control.h
    92  
     98
    9399  ! Create output NetCDF file
    94100  if (is_master) then
     
    129135    enddo
    130136   endif
    131    
     137
    132138   ! write "header" of file (longitudes, latitudes, geopotential, ...)
    133139   if (klon_glo>1) then ! general 3D case
     
    138144
    139145  endif ! of if (is_master)
    140  
     146
    141147  ! set zitau to -1 to be compatible with zitau incrementation step below
    142148  zitau=-1
    143  
     149
    144150else
    145151  ! If not an initialization call, simply open the NetCDF file
     
    164170    date=float(zitau+1)/float(day_step)
    165171    ! Note: day_step is known from control.h
    166    
     172
    167173    if (is_master) then
    168174     ! Get NetCDF ID for "time"
     
    176182     if (ierr.ne.NF_NOERR) then
    177183      write(*,*)"writediagsoil: Failed writing date to time variable"
    178       stop 
     184      stop
    179185     endif
    180186    endif ! of if (is_master)
     
    217223  endif
    218224#endif
    219  
     225
    220226  ! B. Write (append) the variable to the NetCDF file
    221227  if (is_master) then
     
    235241    call def_var(nid,name,title,units,4,id,varid,ierr)
    236242  endif ! of if (ierr.ne.NF_NOERR)
    237  
     243
    238244  ! B.2. Prepare things to be able to write/append the variable
    239245  corners(1)=1
     
    241247  corners(3)=1
    242248  corners(4)=ntime
    243  
     249
    244250  if (klon_glo==1) then
    245251    edges(1)=1
     
    250256  edges(3)=nsoilmx
    251257  edges(4)=1
    252  
     258
    253259  ! B.3. Write the slab of data
    254260!#ifdef NC_DOUBLE
     
    324330  corners(2)=1
    325331  corners(3)=ntime
    326  
     332
    327333  if (klon_glo==1) then
    328334    edges(1)=1
     
    332338  edges(2)=nbp_lat
    333339  edges(3)=1
    334  
     340
    335341  ! B.3. Write the slab of data
    336342!#ifdef NC_DOUBLE
     
    373379  ! B.2. Prepare things to be able to write/append the variable
    374380  corners(1)=ntime
    375  
     381
    376382  edges(1)=1
    377383
     
    396402
    397403end subroutine writediagsoil
     404
     405end module writediagsoil_mod
  • trunk/LMDZ.PLUTO/libf/phypluto/xios_output_mod.F90

    r3501 r3506  
    1111
    1212 INTERFACE send_xios_field
    13     MODULE PROCEDURE histwrite0d_xios,histwrite2d_xios,histwrite3d_xios!,histwrite1d_xios
     13    MODULE PROCEDURE histwrite0d_xios,histwrite1d_xios,histwrite2d_xios,histwrite3d_xios
    1414 END INTERFACE
    1515
     
    1717CONTAINS
    1818
    19   SUBROUTINE initialize_xios_output(day,timeofday,dtphys,daysec,&
    20                                     yearday,presnivs,pseudoalt,wnoi,wnov)
    21 !  USE mod_phys_lmdz_para, only: gather, bcast, &
    22 !                                jj_nb, jj_begin, jj_end, ii_begin, ii_end, &
    23 !                                mpi_size, mpi_rank, klon_mpi, &
    24 !                                is_sequential, is_south_pole_dyn
     19  SUBROUTINE initialize_xios_output(day,timeofday,dtphys,daysec,yearday,   &
     20                                    presnivs,pseudoalt,mlayer,wnoi,wnov)
    2521  USE mod_phys_lmdz_para, ONLY: jj_nb, jj_begin, jj_end, ii_begin, ii_end, &
    2622                                mpi_size, mpi_rank, klon_mpi, &
     
    4440  REAL,INTENT(IN) :: presnivs(:) ! vertical grid approximate pressure (Pa)
    4541  REAL,INTENT(IN) :: pseudoalt(:) ! vertical grid approximate altitude (km)
     42  REAL,INTENT(IN) :: mlayer(:) ! soil layer depth at intermediate level (m)
    4643  REAL,INTENT(IN) :: wnoi(:) ! Array of wavenumbers at the spectral interval centers for the infrared.
    4744  real,intent(in) :: wnov (:) !Array of wavenumbers at the spectral interval centers for the visible.
     45
    4846
    4947  INTEGER :: data_ibegin, data_iend
     
    6260    CALL xios_set_axis_attr("altitude", n_glo=size(pseudoalt), value=pseudoalt,&
    6361                            unit="km",positive="up")
     62    CALL xios_set_axis_attr("interlayer", n_glo=size(pseudoalt)+1,&
     63                            unit="km",positive="up")
     64    IF (prt_level>=10) WRITE(lunout,*) "initialize_xios_output: call xios_set_axis_attr for soil"
     65    CALL xios_set_axis_attr("soil_layers", n_glo=size(mlayer), value=mlayer,&
     66                            unit="m",positive="down")
    6467    if (prt_level >=10) write(lunout,*) "initialize_xios_output: call xios_set_axis_attr for IR_Wavenumber"
    6568    write(lunout,*) "writing IR_Wavenumber now in initialize_xios_output"
     
    139142    ! Now define the start time of this simulation
    140143    ! NB: we substract dtphys because we want to set the origin of the time axis
    141     start_date=time_origin+xios_duration(0,0,day,0,0,timeofday*daysec-dtphys)
     144    start_date=time_origin
    142145    call xios_set_start_date(start_date=start_date)
    143146    if (prt_level>=10) then
     
    148151    if (prt_level>=10) write(*,*) "initialize_xios_output: call wxios_closedef"
    149152    CALL wxios_closedef()
     153    if (prt_level>=10) write(*,*) "initialize_xios_output: after call wxios_closedef"
    150154
    151155!$OMP END MASTER
     
    211215
    212216  END SUBROUTINE histwrite0d_xios
     217
     218!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
     219
     220  SUBROUTINE histwrite1d_xios(field_name,field,dimens)
     221  USE xios, ONLY: xios_send_field
     222  USE print_control_mod, ONLY: prt_level, lunout
     223  IMPLICIT NONE
     224
     225    CHARACTER(LEN=*), INTENT(IN) :: field_name
     226    REAL, DIMENSION(:), INTENT(IN) :: field
     227    INTEGER, INTENT(IN) :: dimens
     228    IF (prt_level >= 10) WRITE(lunout,*)'Begin histrwrite1d_xios ',trim(field_name)
     229!$OMP MASTER
     230    CALL xios_send_field(field_name,field)
     231!$OMP END MASTER
     232
     233    IF (prt_level >= 10) WRITE(lunout,*)'End histrwrite1d_xios ',trim(field_name)
     234
     235  END SUBROUTINE histwrite1d_xios
    213236
    214237!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
     
    221244  USE print_control_mod, ONLY: prt_level, lunout
    222245  USE mod_grid_phy_lmdz, ONLY: nbp_lon
    223   USE radinc_h ,only: L_NSPECTI,L_NSPECTV
    224246  IMPLICIT NONE
    225247
     
    230252    REAL :: Field2d(nbp_lon,jj_nb)
    231253
     254    CHARACTER(len=128) :: msg
     255
    232256    IF (prt_level >= 10) WRITE(lunout,*)'Begin histrwrite2d_xios ',trim(field_name)
    233     if ((size(field) .eq. L_NSPECTI) .or. (size(field) .eq. L_NSPECTV)) then
    234 !$OMP MASTER
    235       ! only for spectral stuff: IR_Bandwidth and VI_Bandwidth
    236       call xios_send_field(field_name,field)
    237 !$OMP END MASTER
    238       return
    239     endif
    240     IF (SIZE(field)/=klon) CALL abort_physic('iophy::histwrite2d_xios','Field first DIMENSION not equal to klon',1)
    241 
     257    IF (SIZE(field)/=klon) THEN
     258      WRITE(msg,*) "Pb with field "//trim(field_name)//&
     259                   " : Field first DIMENSION not equal to klon"
     260      CALL abort_physic('iophy::histwrite2d_xios',trim(msg),1)
     261    ENDIF
    242262    CALL Gather_omp(field,buffer_omp)
    243263!$OMP MASTER
     
    269289    INTEGER :: ip, n, nlev
    270290
     291    CHARACTER(len=128) :: msg
     292
    271293  IF (prt_level >= 10) write(lunout,*)'Begin histrwrite3d_xios ',trim(field_name)
    272294
    273     !Et on.... écrit
    274     IF (SIZE(field,1)/=klon) CALL abort_physic('iophy::histwrite3d','Field first DIMENSION not equal to klon',1)
     295    !And we write...
     296    IF (SIZE(field,1)/=klon) THEN
     297      WRITE(msg,*) "Pb with field "//trim(field_name)//&
     298                   " : Field first DIMENSION not equal to klon"
     299      CALL abort_physic('iophy::histwrite3d',trim(msg),1)
     300    ENDIF
     301
    275302    nlev=SIZE(field,2)
    276303
     
    286313  END SUBROUTINE histwrite3d_xios
    287314
     315!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
     316
     317 FUNCTION xios_is_active_field(field_id)
     318 USE xios, only: xios_field_is_active
     319 USE mod_phys_lmdz_omp_transfert, only: bcast_omp
     320 IMPLICIT NONE
     321   LOGICAL ::  xios_is_active_field
     322   CHARACTER(LEN=*) :: field_id
     323
     324 ! check with XIOS if "field_id" is requested by the user
     325 ! to be in the output file(s)
     326
     327!$OMP BARRIER
     328!$OMP MASTER
     329   xios_is_active_field = xios_field_is_active(field_id)
     330!$OMP END MASTER
     331   CALL bcast_omp(xios_is_active_field)
     332 END FUNCTION xios_is_active_field
     333
    288334#endif
    289335
Note: See TracChangeset for help on using the changeset viewer.