Skip to content
Snippets Groups Projects
write_diachro.f90 93.6 KiB
Newer Older
!MNH_LIC Copyright 1996-2021 CNRS, Meteo-France and Universite Paul Sabatier
!MNH_LIC This is part of the Meso-NH software governed by the CeCILL-C licence
!MNH_LIC version 1. See LICENSE, CeCILL-C_V1-en.txt and CeCILL-C_V1-fr.txt
!MNH_LIC for details. version 1.
!-----------------------------------------------------------------
interface Att_write
   procedure Att_write_c0, Att_write_i0, Att_write_x0
end interface
! #################################################################
subroutine Write_diachro( tpdiafile, tpbudiachro, tpfields,       &
! #################################################################
!
!!****  *WRITE_DIACHRO* - Ecriture d'un enregistrement dans un fichier
!!                        diachronique (de nom de base HGROUP)
!!
!!    PURPOSE
!!    -------
!
!!**  METHOD
!!    ------
!!      En fait pour un groupe donne HGROUP, on ecrit systematiquement
!       plusieurs enregistrements :
!       - 1: HGROUP.TYPE          (type d'informations a enregistrer)
!       - 2: HGROUP.DIM           (dimensions de toutes les matrices a
!                                  enregistrer)
!       - 3: HGROUP.TITRE         (Nom des processus)
!       - 4: HGROUP.UNITE         (Unites pour chaque processus)
!       - 5: HGROUP.COMMENT       (Champ commentaire pour chaque processus)
!       - 6: HGROUP.TRAJT         (Temps)
!       - 7: HGROUP.PROCx         (Champ traite . 1 enr./ 1 processus)
!       - 8: HGROUP.DATIM         (Les differentes dates du modele)
!       et pour certains types d'informations on enregistre egalement
!       des coordonnees (HGROUP.TRAJX, HGROUP.TRAJY, HGROUP.TRAJZ)
!!
!!    EXTERNAL
!!    --------
!!      None
!!
!!    IMPLICIT ARGUMENTS
!!    ------------------
!!      Module
!!
!!    REFERENCE
!!    ---------
!!
!!
!!    AUTHOR
!!    ------
!!      J. Duron    * Laboratoire d'Aerologie *
!!
!!
!!    MODIFICATIONS
!!    -------------
!!      Original       08/01/96
!!      Updated   PM
!!      Modification (N. Asencio) 18/06/99  : the two first dimensions of PMASK
!!                   are linked to the horizontal grid, FMWRIT is called with 'XY' argument.
!!                   In standard configuration of the budgets, the mask is written once
!!                   outside this routine with FMWRIT call. Its record name is 'MASK_nnnn.MASK'
!!                   So optional PMASK is not used .
!!      Modification (J. Duron)   24/06/99  : add logical GPACK to disable the pack option,
!!                                            add the initialization of the dimensions of
!!                                          MASK array in MASK case with write outside the
!!                                          routine.
!!      J.Escobar       02/10/2015 modif for JPHEXT(JPVEXT) variable
!!      D.Gazen+ G.Delautier 06/2016 modif for ncl files
!!      P. Wautelet     09/06/2017: name of the variable added to the name of the written field
!!                                  and better comment (true comment + units)
!!  Philippe Wautelet: 05/2016-04/2018: new data structures and calls for I/O
!  P. Wautelet 13/09/2019: budget: simplify and modernize date/time management
!  P. Wautelet 13/09/2019: remove never used PMASK optional dummy-argument
!  P. Wautelet 28/08/2020: remove TPLUOUTDIA dummy argument
!  P. Wautelet 09/10/2020: use new data type tpfields
!  P. Wautelet 08/12/2020: merge budgets terms with different nbutshift in same group variables
!  P. Wautelet 03/03/2021: add tbudiachrometadata type (useful to pass more information to Write_diachro)
!  P. Wautelet 11/03/2021: remove ptrajx/y/z optional dummy arguments of Write_diachro
!                          + get the trajectory data for LFI files differently
!-------------------------------------------------------------------------------
!
!*       0.    DECLARATIONS
!              ------------
!
use modd_aircraft_balloon, only: flyer
use modd_conf,             only: lpack
use modd_field,            only: tfield_metadata_base
use modd_io,               only: tfiledata
use modd_type_date,        only: date_time
IMPLICIT NONE
!
!*       0.1   Dummy arguments
!              ---------------
TYPE(TFILEDATA),                                     INTENT(IN)           :: TPDIAFILE    ! file to write
type(tbudiachrometadata),                            intent(in)           :: tpbudiachro
class(tfield_metadata_base), dimension(:),           intent(in)           :: tpfields
type(date_time),             dimension(:),           intent(in)           :: tpdates  !Used only for LFI files
REAL,                        DIMENSION(:,:,:,:,:,:), INTENT(IN)           :: PVAR
type(flyer),                                         intent(in), optional :: tpflyer
!
!*       0.1   Local variables
!              ---------------
logical :: gpack
!------------------------------------------------------------------------------

call Print_msg( NVERB_DEBUG, 'BUD', 'Write_diachro', 'called' )

gpack = lpack
lpack = .false.

if ( tpdiafile%cformat == 'LFI' .or. tpdiafile%cformat == 'LFICDF4' ) &
  call Write_diachro_lfi( tpdiafile, tpbudiachro, tpfields, tpdates, pvar,         tpflyer )

#ifdef MNH_IOCDF4
if ( tpdiafile%cformat == 'NETCDF4' .or. tpdiafile%cformat == 'LFICDF4' ) &
  call Write_diachro_nc4( tpdiafile, tpbudiachro, tpfields,          pvar, osplit, tpflyer )
!-----------------------------------------------------------------------------
subroutine Write_diachro_lfi( tpdiafile, tpbudiachro, tpfields, tpdates, pvar, tpflyer )
use modd_budget,         only: nbumask, nbutshift, nbusubwrite, tbudiachrometadata
use modd_field,          only: NMNHDIM_ONE, NMNHDIM_UNKNOWN, NMNHDIM_FLYER_TIME, NMNHDIM_NOTLISTED, NMNHDIM_UNUSED, &
                               TYPECHAR, TYPEINT, TYPEREAL,                                                         &
                               tfield_metadata_base, tfielddata
use modd_io,             only: tfiledata
use modd_les,            only: nles_current_iinf, nles_current_isup, nles_current_jinf, nles_current_jsup, &
                               nles_k, xles_current_z
use modd_parameters,     only: jphext
use modd_time,           only: tdtexp, tdtseg
use modd_time_n,         only: tdtmod
use modd_type_date,      only: date_time

use mode_datetime,       only: Datetime_distance
use mode_io_field_write, only: IO_Field_write, IO_Field_write_box
use mode_tools_ll,       only: Get_globaldims_ll


type(tfiledata),                                     intent(in)           :: tpdiafile        ! File to write
type(tbudiachrometadata),                            intent(in)           :: tpbudiachro
class(tfield_metadata_base), dimension(:),           intent(in)           :: tpfields
type(date_time),             dimension(:),           intent(in)           :: tpdates
real,                        dimension(:,:,:,:,:,:), intent(in)           :: pvar
integer, parameter :: LFITITLELGT = 100
integer, parameter :: LFIUNITLGT = 100
integer, parameter :: LFICOMMENTLGT = 100

character(len=:), allocatable :: ycategory
character(len=:), allocatable :: yshape
CHARACTER(LEN=20) :: YCOMMENT
CHARACTER(LEN=3)  :: YJ
character(len=LFITITLELGT),   dimension(:), allocatable :: ytitles   !Used to respect LFI fileformat
character(len=LFIUNITLGT),    dimension(:), allocatable :: yunits    !Used to respect LFI fileformat
character(len=LFICOMMENTLGT), dimension(:), allocatable :: ycomments !Used to respect LFI fileformat
INTEGER   ::   INTRAJT, IKTRAJX, IKTRAJY, IKTRAJZ
INTEGER   ::   ITTRAJX, ITTRAJY, ITTRAJZ
INTEGER   ::   INTRAJX, INTRAJY, INTRAJZ
INTEGER   ::   IIMASK, IJMASK, IKMASK, ITMASK, INMASK, IPMASK
INTEGER   ::   IIMAX_ll, IJMAX_ll ! size of the physical global domain
INTEGER,DIMENSION(:),ALLOCATABLE :: ITABCHAR
real, dimension(:,:), allocatable :: ztimes
real, dimension(:,:), allocatable :: zdatime
TYPE(TFIELDDATA) :: TZFIELD
type(tfiledata)  :: tzfile
call Print_msg( NVERB_DEBUG, 'BUD', 'Write_diachro_lfi', 'called' )
iil = tpbudiachro%nil
iih = tpbudiachro%nih
ijl = tpbudiachro%njl
ijh = tpbudiachro%njh
ikl = tpbudiachro%nkl
ikh = tpbudiachro%nkh

ycategory = Trim( tpbudiachro%ccategory )
yshape    = Trim( tpbudiachro%cshape    )

!For backward compatibility of LFI files
if ( tpbudiachro%cdirection == 'I' ) then
  ijl = 1
  ijh = 1
else if ( tpbudiachro%cdirection == 'J' ) then
  iil = 1
  iih = 1
end if

!Write only in LFI files
tzfile%cformat = 'LFI'
YCOMMENT='NOTHING'
!Set ygroup to preserve backward compatibility of LFI files
if (      Any( tpbudiachro%cgroupname == [ 'RJS', 'RJX', 'RJY', 'RJZ'] )                                              &
     .or. Any( tpbudiachro%cgroupname == [ 'UU', 'VV', 'WW', 'TH', 'TK', 'RV', 'RC', 'RR', 'RI', 'RS', 'RG', 'RH' ] ) &
     .or.    ( tpbudiachro%cgroupname(1:2) == 'SV' .and. Len_trim( tpbudiachro%cgroupname ) == 5 )                    ) then
  ygroup(:) = Trim( tpbudiachro%cgroupname )
  do ji = Len_trim( tpbudiachro%cgroupname ) + 1, 5
    ygroup(ji : ji) = '_'
  end do
  Write( ygroup(6:9), '( i4.4 )' ) nbutshift
else if ( tpbudiachro%nsv > 0 ) then
  Allocate( character(len=9) :: ygroup )
  Write( ygroup, '( "SV", i3.3, i4.4 )' ) tpbudiachro%nsv, nbutshift
!Recompute old TYPE for backward compatibility
if ( ycategory == 'budget' ) then
  if ( yshape == 'cartesian' ) then
    ytype = 'CART'
  else
    ytype = 'MASK'
  end if
else if ( ycategory == 'LES' ) then
  if ( yshape == 'cartesian' ) then
    ytype = 'SSOL'
  else
    ytype = 'SPXY'
  end if
else if (      ycategory == 'aircraft'                 &
          .or. ycategory == 'radiosonde balloon'       &
          .or. ycategory == 'iso-density balloon'      &
          .or. ycategory ==  'constant volume balloon' ) then
  if ( yshape == 'point' ) then
    ytype = 'RSPL'
  else
    ytype = 'CART'
  end if
else if ( ycategory == 'profiler' .or. ycategory == 'station' ) then
  ytype = 'CART'
else if ( ycategory == 'time series'  ) then
  if ( tpbudiachro%licompress ) then
    ytype = 'CART'
  else
    ytype = 'SSOL'
  end if
else
  call Print_msg( NVERB_ERROR, 'IO', 'Write_diachro_lfi', &
                  'unknown classification for type of variable '//trim(tpfields(1)%cmnhname) )
  ytype = 'UNKN'
end if
if ( ycategory == 'budget' .and. tpbudiachro%cshape == 'cartesian' &
     .and. .not. tpbudiachro%licompress .and. .not. tpbudiachro%ljcompress     ) then
  gdistributed = .true.
else
  !By default data is already collected on the write process for budgets
  gdistributed = .false.
end if
IK = SIZE(PVAR,3)
IT = SIZE(PVAR,4)
IN = SIZE(PVAR,5)
IP = SIZE(PVAR,6)


IKTRAJX=0; IKTRAJY=0; IKTRAJZ=0
ITTRAJX=0; ITTRAJY=0; ITTRAJZ=0
INTRAJX=0; INTRAJY=0; INTRAJZ=0
IF ( PRESENT( tpflyer ) ) THEN
  IKTRAJX = 1
  ITTRAJX = SIZE( tpflyer%x )
  INTRAJX = 1
ELSE IF ( ycategory == 'LES' .and.  tpbudiachro%cshape == 'cartesian' ) THEN
IF ( PRESENT( tpflyer ) ) THEN
  IKTRAJY = 1
  ITTRAJY = SIZE( tpflyer%y )
  INTRAJY = 1
ELSE IF ( ycategory == 'LES' .and.  tpbudiachro%cshape == 'cartesian' ) THEN
IF ( PRESENT( tpflyer ) ) THEN
  IKTRAJZ = 1
  ITTRAJZ = SIZE( tpflyer%z )
  INTRAJZ = 1
ELSE IF ( ycategory == 'LES' .and.  tpbudiachro%cshape == 'cartesian' ) THEN
ENDIF

IIMASK=0; IJMASK=0; IKMASK=0; ITMASK=0; INMASK=0; IPMASK=0
!     MASK is written outside this routine but the dimensions must be initialized
!     the mask is defined on the extended domain
  CALL GET_GLOBALDIMS_ll (IIMAX_ll,IJMAX_ll)
  IIMASK=IIMAX_ll + 2 * JPHEXT
  IJMASK=IJMAX_ll + 2 * JPHEXT
ILENTITRE   = LFITITLELGT
ILENUNITE   = LFIUNITLGT
ILENCOMMENT = LFICOMMENTLGT
!
! 1er enregistrement TYPE
!
TZFIELD%CUNITS     = ''
TZFIELD%CDIR       = '--'
TZFIELD%CCOMMENT   = TRIM(YCOMMENT)
TZFIELD%NTYPE      = TYPECHAR
TZFIELD%NDIMS      = 0
!
! 2eme  enregistrement DIMENSIONS des MATRICES et LONGUEUR des TABLEAUX de CARACTERES et FLAGS de COMPRESSION sur les DIFFERENTS AXES
!
TZFIELD%CUNITS     = ''
TZFIELD%CDIR       = '--'
TZFIELD%CCOMMENT   = TRIM(YCOMMENT)
TZFIELD%NTYPE      = TYPEINT
TZFIELD%NDIMS      = 1
  CASE('CART','MASK','SPXY')
    if ( iil < 0 .or. iih < 0 .or. ijl < 0 .or. ijh < 0 .or. ikl < 0 .or. ikh < 0 ) then
      call Print_msg( NVERB_FATAL, 'IO', 'Write_diachro_lfi', &
                      'nil, nih, njl, njh, nkl or nkh not set in tpbudiachro for variable ' // Trim( tpfields(1)%cmnhname ) )
    ILENG = 34
    ALLOCATE(ITABCHAR(ILENG))
    ITABCHAR(1)=ILENTITRE; ITABCHAR(2)=ILENUNITE
    ITABCHAR(3)=ILENCOMMENT; ITABCHAR(4)=II
    ITABCHAR(5)=IJ; ITABCHAR(6)=IK
    ITABCHAR(7)=IT; ITABCHAR(8)=IN
    ITABCHAR(9)=IP; ITABCHAR(10)=iil
    ITABCHAR(11)=ijl; ITABCHAR(12)=ikl
    ITABCHAR(13)=iih; ITABCHAR(14)=ijh
    ITABCHAR(15)=ikh
    ITABCHAR(16)=Merge( 1, 0, tpbudiachro%licompress )
    ITABCHAR(17)=Merge( 1, 0, tpbudiachro%ljcompress )
    ITABCHAR(18)=Merge( 1, 0, tpbudiachro%lkcompress )
!     ITABCHAR(10)=1; ITABCHAR(11)=1
!     ITABCHAR(13)=1; ITABCHAR(14)=1
      ITABCHAR(16)=1; ITABCHAR(17)=1
    ENDIF
    ITABCHAR(19)=INTRAJT; ITABCHAR(20)=IKTRAJX
    ITABCHAR(21)=IKTRAJY; ITABCHAR(22)=IKTRAJZ
    ITABCHAR(23)=ITTRAJX; ITABCHAR(24)=ITTRAJY
    ITABCHAR(25)=ITTRAJZ; ITABCHAR(26)=INTRAJX
    ITABCHAR(27)=INTRAJY; ITABCHAR(28)=INTRAJZ
    ITABCHAR(29)=IIMASK; ITABCHAR(30)=IJMASK
    ITABCHAR(31)=IKMASK; ITABCHAR(32)=ITMASK
    ITABCHAR(33)=INMASK; ITABCHAR(34)=IPMASK
    CALL IO_Field_write(tzfile,TZFIELD,ITABCHAR)
    DEALLOCATE(ITABCHAR)
  CASE DEFAULT
    ALLOCATE(ITABCHAR(ILENG))
    ITABCHAR(1)=ILENTITRE; ITABCHAR(2)=ILENUNITE
    ITABCHAR(3)=ILENCOMMENT; ITABCHAR(4)=II
    ITABCHAR(5)=IJ; ITABCHAR(6)=IK
    ITABCHAR(7)=IT; ITABCHAR(8)=IN
    ITABCHAR(9)=IP
    ITABCHAR(10)=INTRAJT; ITABCHAR(11)=IKTRAJX
    ITABCHAR(12)=IKTRAJY; ITABCHAR(13)=IKTRAJZ
    ITABCHAR(14)=ITTRAJX; ITABCHAR(15)=ITTRAJY
    ITABCHAR(16)=ITTRAJZ; ITABCHAR(17)=INTRAJX
    ITABCHAR(18)=INTRAJY; ITABCHAR(19)=INTRAJZ
    ITABCHAR(20)=IIMASK; ITABCHAR(21)=IJMASK
    ITABCHAR(22)=IKMASK; ITABCHAR(23)=ITMASK
    ITABCHAR(24)=INMASK; ITABCHAR(25)=IPMASK
    CALL IO_Field_write(tzfile,TZFIELD,ITABCHAR)
    DEALLOCATE(ITABCHAR)
END SELECT
!
! 3eme enregistrement TITRE
!
TZFIELD%CUNITS     = ''
TZFIELD%CDIR       = '--'
TZFIELD%CCOMMENT   = TRIM(YCOMMENT)
TZFIELD%NTYPE      = TYPECHAR
TZFIELD%NDIMS      = 1
allocate( ytitles( ip ) )
ytitles(:) = tpfields(1 : ip)%cmnhname
CALL IO_Field_write(tzfile,TZFIELD,ytitles(:))
!
! 4eme enregistrement UNITE
!
TZFIELD%CUNITS     = ''
TZFIELD%CDIR       = '--'
TZFIELD%CCOMMENT   = TRIM(YCOMMENT)
TZFIELD%NTYPE      = TYPECHAR
TZFIELD%NDIMS      = 1
allocate( yunits( ip ) )
yunits(:) = tpfields(1 : ip)%cunits
CALL IO_Field_write(tzfile,TZFIELD,yunits(:))
!
! 5eme enregistrement COMMENT
!
TZFIELD%CLONGNAME  = TRIM(ygroup)//'.COMMENT'
TZFIELD%CUNITS     = ''
TZFIELD%CDIR       = '--'
TZFIELD%CCOMMENT   = TRIM(YCOMMENT)
TZFIELD%NTYPE      = TYPECHAR
TZFIELD%NDIMS      = 1
allocate( ycomments( ip ) )
ycomments(:) = tpfields(1 : ip)%ccomment
CALL IO_Field_write(tzfile,TZFIELD,ycomments(:))
!
! 6eme enregistrement PVAR
!
! Dans la mesure ou cette matrice risque d'etre tres volumineuse, on ecrira un
! enregistrement par processus
DO J = 1,IP
  if ( All( tpfields(1)%ndimlist(:) /= NMNHDIM_UNKNOWN ) ) then
    tzfield%ndimlist(1:5) = tpfields(j)%ndimlist(1:5)
    do jj = 1, 5
      if ( tzfield%ndimlist(jj) == NMNHDIM_UNUSED ) then
        tzfield%ndimlist(jj) = NMNHDIM_ONE
      end if
    end do
    if ( tzfield%ndimlist(4) == NMNHDIM_FLYER_TIME ) tzfield%ndimlist(4) = NMNHDIM_NOTLISTED
    tzfield%ndimlist(6:)   = NMNHDIM_UNUSED
  else
    call Print_msg( NVERB_ERROR, 'IO', 'Write_diachro_lfi', &
                    'some dimensions are unknown for variable '//trim(tpfields(1)%cmnhname) )
  YJ = '   '
  IF(J < 10)WRITE(YJ,'(I1)')J ; YJ = ADJUSTL(YJ)
          WRITE(YJ,'(I2)')J ; YJ = ADJUSTL(YJ)
  ELSE IF(J >= 100 .AND. J < 1000) THEN
          WRITE(YJ,'(I3)')J
  ENDIF
    TZFIELD%CMNHNAME   = TRIM(ygroup)//'.PROC'//YJ
    TZFIELD%CLONGNAME  = TRIM(TZFIELD%CMNHNAME)
    TZFIELD%CUNITS     = tpfields(j)%cunits
    TZFIELD%CCOMMENT   = TRIM(tpfields(j)%cmnhname)//' - '//TRIM(tpfields(j)%ccomment)//' ('// Trim( tpfields(j)%cunits ) //')'
    TZFIELD%NGRID      = tpfields(j)%ngrid
    CALL IO_Field_write_BOX(tzfile,TZFIELD,'BUDGET',PVAR(:,:,:,:,:,J), &
                            iil+JPHEXT,iih+JPHEXT,ijl+JPHEXT,ijh+JPHEXT)
    TZFIELD%CMNHNAME   = TRIM(ygroup)//'.PROC'//YJ
    TZFIELD%CLONGNAME  = TRIM(TZFIELD%CMNHNAME)
    TZFIELD%CUNITS     = tpfields(j)%cunits
    TZFIELD%CCOMMENT   = TRIM(tpfields(j)%cmnhname)//' - '//TRIM(tpfields(j)%ccomment)//' ('// Trim( tpfields(j)%cunits ) //')'
    TZFIELD%NGRID      = tpfields(j)%ngrid
    TZFIELD%NTYPE      = TYPEREAL
    TZFIELD%NDIMS      = 5
    CALL IO_Field_write(tzfile,TZFIELD,PVAR(:,:,:,:,:,J))
  tzfield%ndimlist(:)   = NMNHDIM_UNKNOWN
ENDDO
!
! 7eme enregistrement TRAJT
!
TZFIELD%CUNITS     = ''
TZFIELD%CDIR       = '--'
TZFIELD%CCOMMENT   = TRIM(YCOMMENT)
TZFIELD%NTYPE      = TYPEREAL
TZFIELD%NDIMS      = 2
!NMNHDIM_FLYER_TIME excluded because created only in netCDF/HDF groups (local to each flyer)
if ( tpfields(1)%ndimlist(4) /= NMNHDIM_UNKNOWN .and. tpfields(1)%ndimlist(4) /= NMNHDIM_UNUSED &
     .and. tpfields(1)%ndimlist(4) /= NMNHDIM_FLYER_TIME ) then
  tzfield%ndimlist(1)  = tpfields(1)%ndimlist(4)
  tzfield%ndimlist(2)  = NMNHDIM_ONE
  tzfield%ndimlist(3:) = NMNHDIM_UNUSED
end if

!Reconstitute old diachro format
allocate( ztimes( size( tpdates ), 1 ) )

do ji=1,size(tpdates)
  call Datetime_distance( tdtexp, tpdates(ji ), ztimes(ji, 1 ) )
end do

call IO_Field_write( tzfile, tzfield, ztimes )
!Reset ndimlist
tzfield%ndimlist(:) = NMNHDIM_UNKNOWN

!
! Dans certains cas
!
!
! 8eme enregistrement TRAJX
!
  TZFIELD%CUNITS     = ''
  TZFIELD%CDIR       = '--'
  TZFIELD%CCOMMENT   = TRIM(YCOMMENT)
  TZFIELD%NTYPE      = TYPEREAL
  TZFIELD%NDIMS      = 3
  CALL IO_Field_write(tzfile,TZFIELD, Reshape( tpflyer%x, [1, Size( tpflyer%x), 1] ) )
ELSE IF ( ycategory == 'LES' .and.  tpbudiachro%cshape == 'cartesian' ) THEN
  TZFIELD%CMNHNAME   = TRIM(ygroup)//'.TRAJX'
  TZFIELD%CSTDNAME   = ''
  TZFIELD%CLONGNAME  = TRIM(ygroup)//'.TRAJX'
  TZFIELD%CUNITS     = ''
  TZFIELD%CDIR       = '--'
  TZFIELD%CCOMMENT   = TRIM(YCOMMENT)
  TZFIELD%NGRID      = tpfields(1)%ngrid
  TZFIELD%NTYPE      = TYPEREAL
  TZFIELD%NDIMS      = 3
  TZFIELD%LTIMEDEP   = .FALSE.
  !TRAJX is given in extended domain coordinates (=> +jphext) for backward compatibility
                       Spread( source = ( nles_current_iinf + nles_current_isup) / 2 + jphext, dim = 1, ncopies = IN ), &
ENDIF
!
! 9eme enregistrement TRAJY
!
IF(PRESENT(tpflyer))THEN
  TZFIELD%CMNHNAME   = TRIM(ygroup)//'.TRAJY'
  TZFIELD%CSTDNAME   = ''
  TZFIELD%CLONGNAME  = TRIM(ygroup)//'.TRAJY'
  TZFIELD%CUNITS     = ''
  TZFIELD%CDIR       = '--'
  TZFIELD%CCOMMENT   = TRIM(YCOMMENT)
  TZFIELD%NGRID      = tpfields(1)%ngrid
  TZFIELD%NTYPE      = TYPEREAL
  TZFIELD%NDIMS      = 3
  TZFIELD%LTIMEDEP   = .FALSE.
  CALL IO_Field_write(tzfile,TZFIELD, Reshape( tpflyer%y, [1, Size( tpflyer%y), 1] ) )
ELSE IF ( ycategory == 'LES' .and.  tpbudiachro%cshape == 'cartesian' ) THEN
  TZFIELD%CUNITS     = ''
  TZFIELD%CDIR       = '--'
  TZFIELD%CCOMMENT   = TRIM(YCOMMENT)
  TZFIELD%NTYPE      = TYPEREAL
  TZFIELD%NDIMS      = 3
  !TRAJY is given in extended domain coordinates (=> +jphext) for backward compatibility
                       Spread( source = ( nles_current_jinf + nles_current_jsup) / 2 + jphext, dim = 1, ncopies = IN ), &
ENDIF
!
! 10eme enregistrement TRAJZ
!
  TZFIELD%CUNITS     = ''
  TZFIELD%CDIR       = '--'
  TZFIELD%CCOMMENT   = TRIM(YCOMMENT)
  TZFIELD%NTYPE      = TYPEREAL
  TZFIELD%NDIMS      = 3
  CALL IO_Field_write(tzfile,TZFIELD, Reshape( tpflyer%z, [1, Size( tpflyer%z), 1] ) )
ELSE IF ( ycategory == 'LES' .and.  tpbudiachro%cshape == 'cartesian' ) THEN
  TZFIELD%CMNHNAME   = TRIM(ygroup)//'.TRAJZ'
  TZFIELD%CSTDNAME   = ''
  TZFIELD%CLONGNAME  = TRIM(ygroup)//'.TRAJZ'
  TZFIELD%CUNITS     = ''
  TZFIELD%CDIR       = '--'
  TZFIELD%CCOMMENT   = TRIM(YCOMMENT)
  TZFIELD%NGRID      = tpfields(1)%ngrid
  TZFIELD%NTYPE      = TYPEREAL
  TZFIELD%NDIMS      = 3
  TZFIELD%LTIMEDEP   = .FALSE.

  Allocate( ztrajz(IK, 1, IN) )
  do jj = 1, IK
    ztrajz(jj, :, :) = xles_current_z(jj)
  end do
  CALL IO_Field_write(tzfile,TZFIELD,ztrajz)
  Deallocate( ztrajz )
ENDIF
!
! 11eme enregistrement PDATIME
!
TZFIELD%CUNITS     = ''
TZFIELD%CDIR       = '--'
TZFIELD%CCOMMENT   = TRIM(YCOMMENT)
TZFIELD%NTYPE      = TYPEREAL
TZFIELD%NDIMS      = 2

!Reconstitute old diachro format
allocate( zdatime( 16, size(tpdates) ) )

zdatime(1,  : ) = tdtexp%nyear
zdatime(2,  : ) = tdtexp%nmonth
zdatime(3,  : ) = tdtexp%nday
zdatime(4,  : ) = tdtexp%xtime
zdatime(5,  : ) = tdtseg%nyear
zdatime(6,  : ) = tdtseg%nmonth
zdatime(7,  : ) = tdtseg%nday
zdatime(8,  : ) = tdtseg%xtime
zdatime(9,  : ) = tdtmod%nyear
zdatime(10, : ) = tdtmod%nmonth
zdatime(11, : ) = tdtmod%nday
zdatime(12, : ) = tdtmod%xtime
zdatime(13, : ) = tpdates(:)%nyear
zdatime(14, : ) = tpdates(:)%nmonth
zdatime(15, : ) = tpdates(:)%nday
zdatime(16, : ) = tpdates(:)%xtime
call IO_Field_write( tzfile, tzfield, zdatime )
end subroutine Write_diachro_lfi
!-----------------------------------------------------------------------------
subroutine Write_diachro_nc4( tpdiafile, tpbudiachro, tpfields, pvar, osplit, tpflyer )
use modd_aircraft_balloon, only: flyer
use modd_budget,           only: CNOTSET, nbutshift, nbusubwrite, tbudiachrometadata
use modd_les,              only: cbl_height_def, cles_norm_type, nles_masks, xles_temp_sampling
use modd_parameters,       only: jphext, NBUNAMELGTMAX, NCOMMENTLGTMAX
use modd_precision,        only: CDFINT, MNHREAL_NF90
use modd_type_date,        only: date_time
use mode_io_field_write,   only: IO_Field_create, IO_Field_write, IO_Field_write_box
use mode_io_tools_nc4,     only: IO_Err_handle_nc4
integer, parameter :: NMAXLEVELS       = 7
integer, parameter :: NLVL_ROOT        = 0
integer, parameter :: NLVL_CATEGORY    = 1
integer, parameter :: NLVL_SUBCATEGORY = 2
integer, parameter :: NLVL_GROUP       = 3
integer, parameter :: NLVL_SHAPE       = 4
integer, parameter :: NLVL_TIMEAVG     = 5
integer, parameter :: NLVL_NORM        = 6
integer, parameter :: NLVL_MASK        = 7
character(len=*), dimension(NMAXLEVELS), parameter :: CNCGROUPNAMES = [ &
                                         'category   ', &  !Name of the different type of groups/levels in the netCDF file
                                         'subcategory', &
                                         'group      ', &
                                         'shape      ', &
                                         'timeavg    ', &
                                         'norm       ', &
                                         'mask       '  ]

type(tfiledata),                                     intent(in)           :: tpdiafile        ! File to write
type(tbudiachrometadata),                            intent(in)           :: tpbudiachro
class(tfield_metadata_base), dimension(:),           intent(in)           :: tpfields
real,                        dimension(:,:,:,:,:,:), intent(in)           :: pvar
type(flyer),                                         intent(in), optional :: tpflyer
character(len=:), allocatable :: ylevelname
character(len=:), allocatable :: ylevels
character(len=:), allocatable :: ystdnameprefix
character(len=NBUNAMELGTMAX),  dimension(NMAXLEVELS) :: ylevelnames !Name of the different groups/levels in the netCDF file
character(len=NCOMMENTLGTMAX), dimension(NMAXLEVELS) :: ylevelcomments !Comments for the different groups/levels in the netCDF file
integer                                       :: iil, iih, ijl, ijh, ikl, ikh
integer                                       :: idims
integer                                       :: icount
integer                                       :: icorr
integer                                       :: ji
integer                                       :: jl
integer                                       :: jp
integer(kind=CDFINT)                          :: idimid
integer(kind=CDFINT)                          :: istatus
integer(kind=CDFINT)                          :: ilevelid
integer(kind=CDFINT), dimension(0:NMAXLEVELS) :: ilevelids ! ids of the different groups/levels in the netCDF file
logical                                       :: gdistributed
logical                                       :: gsplit
logical(kind=CDFINT), dimension(NMAXLEVELS)   :: gleveluse ! Are the different groups/levels in the netCDF file used?
logical(kind=CDFINT), dimension(0:NMAXLEVELS) :: gleveldefined ! Are the different groups/levels already defined in the netCDF file
type(tfielddata)                              :: tzfield
type(tfiledata)                               :: tzfile

call Print_msg( NVERB_DEBUG, 'BUD', 'Write_diachro_nc4', 'called' )
!Write only in netCDF files
tzfile%cformat = 'NETCDF4'

ycategory = Trim( tpbudiachro%ccategory  )
yshape    = Trim( tpbudiachro%cshape     )
ygroup    = Trim( tpbudiachro%cgroupname )

iil = tpbudiachro%nil
iih = tpbudiachro%nih
ijl = tpbudiachro%njl
ijh = tpbudiachro%njh
ikl = tpbudiachro%nkl
ikh = tpbudiachro%nkh
if ( ycategory == 'budget' .and. yshape == 'cartesian' &
     .and. .not. tpbudiachro%licompress .and. .not. tpbudiachro%ljcompress     ) then
  gdistributed = .true.
else
  !By default data is already collected on the write process for budgets
  gdistributed = .false.
end if

MASTER: if ( isp == tzfile%nmaster_rank) then
  ilevelids(NLVL_ROOT) = tzfile%nncid

  gleveldefined(NLVL_ROOT) = .false.

  gleveldefined(NLVL_CATEGORY) = .false.
  gleveldefined(NLVL_SUBCATEGORY) = .false.
  gleveldefined(NLVL_GROUP)    = .false.
  gleveldefined(NLVL_SHAPE)    = .false.
  gleveldefined(NLVL_TIMEAVG)  = .false.
  gleveldefined(NLVL_NORM)     = .false.
  gleveldefined(NLVL_MASK)     = .false.

  ylevelnames(:)    = ''
  ylevelcomments(:) = ''
      gleveluse(NLVL_CATEGORY)  = .true.
      ylevelnames(NLVL_CATEGORY) = 'Budgets'
      ylevelcomments(NLVL_CATEGORY) = 'Group for the different budgets'

      gleveluse(NLVL_SUBCATEGORY) = .false.

      gleveluse(NLVL_GROUP)    = .true.
      ylevelnames(NLVL_GROUP)   = Trim( tpbudiachro%cgroupname )

      gleveluse(NLVL_SHAPE)    = .false.
      ylevelnames(NLVL_SHAPE)   = Trim( tpbudiachro%cshape )

      gleveluse(NLVL_TIMEAVG)  = .false.
      if ( tpbudiachro%ltcompress ) then
        ylevelnames(NLVL_TIMEAVG) = 'time averaged'
      else
        ylevelnames(NLVL_TIMEAVG) = 'not time averaged'
      end if

      gleveluse(NLVL_NORM)     = .false.
      if ( tpbudiachro%lnorm ) then
        ylevelnames(NLVL_NORM) = 'normalized'
      else
        ylevelnames(NLVL_NORM) = 'not normalized'
      end if

      gleveluse(NLVL_MASK)     = .false.
      ylevelnames(NLVL_MASK)    = tpbudiachro%cmask
      gleveluse(NLVL_CATEGORY)  = .true.
      ylevelnames(NLVL_CATEGORY) = 'LES budgets'
      ylevelcomments(NLVL_CATEGORY) = 'Group for the different LES budgets'

      gleveluse(NLVL_SUBCATEGORY) = .false.
      gleveluse(NLVL_GROUP)    = .false.

      gleveluse(NLVL_SHAPE)    = .true.
      ylevelnames(NLVL_SHAPE)   = Trim( tpbudiachro%cshape )

      gleveluse(NLVL_TIMEAVG)   = .true.
      if ( tpbudiachro%ltcompress ) then
        ylevelnames(NLVL_TIMEAVG) = 'time averaged'
      else
        ylevelnames(NLVL_TIMEAVG) = 'not time averaged'
      end if

      gleveluse(NLVL_NORM)     = .true.
      if ( tpbudiachro%lnorm ) then
        ylevelnames(NLVL_NORM) = 'normalized'
      else
        ylevelnames(NLVL_NORM) = 'not normalized'
      end if

      if ( tpbudiachro%cshape == 'cartesian' ) then
       if ( tpbudiachro%cmask == CNOTSET ) then
          call Print_msg( NVERB_WARNING, 'IO', 'Write_diachro_nc4', 'mask not set for ' // ygroup  )
          gleveluse(NLVL_MASK) = .false.
        else
          gleveluse(NLVL_MASK)  = .true.
          ylevelnames(NLVL_MASK) = tpbudiachro%cmask
        end if
      else
        gleveluse(NLVL_MASK)     = .false.
      end if
      gleveluse(NLVL_CATEGORY)  = .true.
      ylevelnames(NLVL_CATEGORY) = 'Profilers'
      ylevelcomments(NLVL_CATEGORY) = 'Group for the different vertical profilers'

      gleveluse(NLVL_SUBCATEGORY) = .false.

      gleveluse(NLVL_GROUP)    = .true.
      ylevelnames(NLVL_GROUP)   = Trim( tpbudiachro%cgroupname )

      gleveluse(NLVL_SHAPE)    = .false.
      ylevelnames(NLVL_SHAPE)   = Trim( tpbudiachro%cshape )

      gleveluse(NLVL_TIMEAVG)  = .false.
      gleveluse(NLVL_NORM)     = .false.
      gleveluse(NLVL_MASK)     = .false.
      gleveluse(NLVL_CATEGORY)  = .true.
      ylevelnames(NLVL_CATEGORY) = 'Stations'
      ylevelcomments(NLVL_CATEGORY) = 'Group for the different stations'

      gleveluse(NLVL_SUBCATEGORY) = .false.

      gleveluse(NLVL_GROUP)    = .true.
      ylevelnames(NLVL_GROUP)   = Trim( tpbudiachro%cgroupname )

      gleveluse(NLVL_SHAPE)    = .false.
      ylevelnames(NLVL_SHAPE)   = Trim( tpbudiachro%cshape )

      gleveluse(NLVL_TIMEAVG)  = .false.
      gleveluse(NLVL_NORM)     = .false.
      gleveluse(NLVL_MASK)     = .false.

    case( 'aircraft', 'radiosonde balloon', 'iso-density balloon', 'constant volume balloon' )
      gleveluse(NLVL_CATEGORY)  = .true.
      ylevelnames(NLVL_CATEGORY) = 'Flyers'
      ylevelcomments(NLVL_CATEGORY) = 'Group for the different flyers (aircrafts and balloons)'

      gleveluse(NLVL_SUBCATEGORY) = .true.
      ylevelnames(NLVL_SUBCATEGORY) = ycategory
      ylevelcomments(NLVL_SUBCATEGORY) = 'Group for the different ' // Trim( ycategory ) // 's'

      gleveluse(NLVL_GROUP)    = .true.
      ylevelnames(NLVL_GROUP)   = Trim( tpbudiachro%cgroupname )

      gleveluse(NLVL_SHAPE)    = .true.
      ylevelnames(NLVL_SHAPE) = Trim( tpbudiachro%cshape )

      gleveluse(NLVL_TIMEAVG)  = .false.

      gleveluse(NLVL_NORM)     = .false.

      gleveluse(NLVL_MASK)     = .false.
      gleveluse(NLVL_CATEGORY)  = .true.
      ylevelnames(NLVL_CATEGORY) = 'Time series'
      ylevelcomments(NLVL_CATEGORY) = 'Group for the different time series'

      gleveluse(NLVL_SUBCATEGORY) = .false.

      gleveluse(NLVL_GROUP)    = .true.
      ylevelnames(NLVL_GROUP)   = Trim( tpbudiachro%cgroupname )

      gleveluse(NLVL_SHAPE)    = .false.
      ylevelnames(NLVL_SHAPE)   = Trim( tpbudiachro%cshape )

      gleveluse(NLVL_TIMEAVG)  = .false.
      gleveluse(NLVL_NORM)     = .false.

      if ( Trim( tpbudiachro%cgroupname ) == 'TSERIES' .or. Trim( tpbudiachro%cgroupname ) == 'ZTSERIES' ) then
        gleveluse(NLVL_MASK)   = .true.
        ylevelnames(NLVL_MASK)  = tpbudiachro%cmask
      else
        gleveluse(NLVL_MASK)     = .false.
      end if

    case default
      call Print_msg( NVERB_ERROR, 'IO', 'Write_diachro_nc4', 'unknown category ' // ycategory // ' for group ' // ygroup )
      return
  end select

  do jl = 1, NMAXLEVELS
    call Move_to_next_level( ilevelids(jl-1), gleveldefined(jl-1), gleveluse(jl), &
                           ylevelnames(jl), gleveldefined(jl), ilevelids(jl) )
  end do
  tzfile%nncid = ilevelids(NLVL_MASK)

  ylevels = ''

  do jl = NMAXLEVELS, 1, -1
    ylevels = Trim( CNCGROUPNAMES(jl) ) // ' ' // ylevels
    if ( gleveluse(jl) ) then
      call Att_write( ylevelnames(jl), ilevelids(jl), 'levels', Trim( ylevels ) )
      ylevels = ''
  end do

  if ( .not. gleveldefined(NLVL_CATEGORY) ) then
    ylevelname = ylevelnames(NLVL_CATEGORY)
    ilevelid   = ilevelids  (NLVL_CATEGORY)