Skip to content
Snippets Groups Projects
write_diachro.f90 82.4 KiB
Newer Older
  • Learn to ignore specific revisions
  • !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=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
    
    
    !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
    
    IF(YTYPE == 'CART' .AND. .NOT. tpbudiachro%licompress .AND. .NOT. tpbudiachro%ljcompress) THEN
    
                                  !for parallel execution, PVAR is distributed on several proc
    
    ENDIF
    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 ( tpbudiachro%ctype == 'TLES' ) THEN
      IKTRAJX = 1
      ITTRAJX = 1
      INTRAJX = IN
    
    IF ( PRESENT( tpflyer ) ) THEN
      IKTRAJY = 1
      ITTRAJY = SIZE( tpflyer%y )
      INTRAJY = 1
    ELSE IF ( tpbudiachro%ctype == 'TLES' ) THEN
      IKTRAJY = 1
      ITTRAJY = 1
      INTRAJY = IN
    
    IF ( PRESENT( tpflyer ) ) THEN
      IKTRAJZ = 1
      ITTRAJZ = SIZE( tpflyer%z )
      INTRAJZ = 1
    ELSE IF ( tpbudiachro%ctype == 'TLES' ) THEN
      IKTRAJZ = IK
      ITTRAJZ = 1
      INTRAJZ = IN
    
    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 )
        IF(YTYPE == 'MASK')THEN
    
    !     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
    
      IF(YTYPE == 'CART' .AND. .NOT. tpbudiachro%licompress .AND. .NOT. tpbudiachro%ljcompress) THEN
    
        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 ( tpbudiachro%ctype == 'TLES' ) 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 ( tpbudiachro%ctype == 'TLES' ) 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 ( tpbudiachro%ctype == 'TLES' ) 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 NETCDF,                only: NF90_DEF_DIM, NF90_DEF_GRP, NF90_DEF_VAR, NF90_INQ_NCID, NF90_PUT_ATT, NF90_PUT_VAR, &
                                     NF90_GLOBAL, NF90_NOERR, NF90_STRERROR
    
    use modd_aircraft_balloon, only: flyer
    
    use modd_budget,           only: nbutshift, nbusubwrite, tbudiachrometadata
    
    use modd_les,              only: cbl_height_def, cles_norm_type, nles_masks, xles_temp_sampling
    
    use modd_parameters,       only: jphext
    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
    
    
    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 :: ygroup
    character(len=:), allocatable :: ytype
    
    character(len=:), allocatable :: ystdnameprefix
    
    integer              :: idims
    integer              :: icount
    integer              :: icorr
    integer              :: ji
    integer              :: jp
    integer(kind=CDFINT) :: isavencid
    integer(kind=CDFINT) :: idimid
    integer(kind=CDFINT) :: igrpid
    integer(kind=CDFINT) :: istatus
    logical              :: gdistributed
    
    !Write only in netCDF files
    tzfile%cformat = 'NETCDF4'
    
    
    ygroup = tpbudiachro%cgroupname
    
    iil = tpbudiachro%nil
    iih = tpbudiachro%nih
    ijl = tpbudiachro%njl
    ijh = tpbudiachro%njh
    ikl = tpbudiachro%nkl
    ikh = tpbudiachro%nkh
    
    if ( trim ( ytype ) == 'CART' .or. trim ( ytype ) == 'MASK' .or. trim ( ytype ) == 'SPXY') then
        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_nc4', &
                          'nil, nih, njl, njh, nkl or nkh not set in tpbudiachro for variable ' // Trim( tpfields(1)%cmnhname ) )
        end if
    end if
    
    
    if ( Trim( ytype ) == 'CART' .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
    
      istatus = NF90_INQ_NCID( tzfile%nncid, trim( ygroup ), igrpid )
    
      if ( istatus == NF90_NOERR ) then
    
        ggroupdefined = .true.
        if ( .not. gsplit ) then
    
          call Print_msg( NVERB_WARNING, 'IO', 'Write_diachro_nc4', trim(tzfile%cname)//': group '//trim(ygroup)//' already defined' )
    
        istatus = NF90_DEF_GRP( tzfile%nncid, trim( ygroup ), igrpid )
    
        if ( istatus /= NF90_NOERR ) &
    
          call IO_Err_handle_nc4( istatus, 'Write_diachro_nc4', 'NF90_DEF_GRP', 'for '//trim(ygroup)//' group' )
    
      end if
    
      !Save id of the file root group ('/' group)
      isavencid = tzfile%nncid
      tzfile%nncid = igrpid
    
    
        call Att_write( ygroup, igrpid, 'name',    tpbudiachro%cname    )
        call Att_write( ygroup, igrpid, 'comment', tpbudiachro%ccomment )
        call Att_write( ygroup, igrpid, 'type',          ytype                 )
        call Att_write( ygroup, igrpid, 'category',      tpbudiachro%ccategory )
        call Att_write( ygroup, igrpid, 'shape',         tpbudiachro%cshape    )
        call Att_write( ygroup, igrpid, 'moving',        Merge( 'yes', 'no ', tpbudiachro%lmobile    ) )
        call Att_write( ygroup, igrpid, 'time averaged', Merge( 'yes', 'no ', tpbudiachro%ltcompress ) )
        call Att_write( ygroup, igrpid, 'normalized',    Merge( 'yes', 'no ', tpbudiachro%lnorm      ) )
    
        if ( tpbudiachro%ccategory == 'budget' .and. tpbudiachro%cshape == 'cartesian' ) then
          call Att_write( ygroup, igrpid, 'min I index in physical domain', iil )
          call Att_write( ygroup, igrpid, 'max I index in physical domain', iih )
          call Att_write( ygroup, igrpid, 'min J index in physical domain', ijl )
          call Att_write( ygroup, igrpid, 'max J index in physical domain', ijh )
          call Att_write( ygroup, igrpid, 'min K index in physical domain', ikl )
          call Att_write( ygroup, igrpid, 'max K index in physical domain', ikh )
    
          call Att_write( ygroup, igrpid, 'averaged in the I direction', Merge( 'yes', 'no ', tpbudiachro%licompress ) )
          call Att_write( ygroup, igrpid, 'averaged in the J direction', Merge( 'yes', 'no ', tpbudiachro%ljcompress ) )
          call Att_write( ygroup, igrpid, 'averaged in the K direction', Merge( 'yes', 'no ', tpbudiachro%lkcompress ) )
    
        else if ( tpbudiachro%ccategory == 'budget' .and. tpbudiachro%cshape == 'mask' ) then
          call Att_write( ygroup, igrpid, 'masks are stored in variable', 'MASKS' )
          call Att_write( ygroup, igrpid, 'averaged in the K direction', Merge( 1, 0, tpbudiachro%lkcompress ) )
    
        else if ( tpbudiachro%ccategory == 'LES' .and. tpbudiachro%cshape == 'cartesian' ) then
          call Att_write( ygroup, igrpid, 'min I index in physical domain', iil )
          call Att_write( ygroup, igrpid, 'max I index in physical domain', iih )
          call Att_write( ygroup, igrpid, 'min J index in physical domain', ijl )
          call Att_write( ygroup, igrpid, 'max J index in physical domain', ijh )
    
          call Att_write( ygroup, igrpid, 'averaged in the I direction', Merge( 'yes', 'no ', tpbudiachro%licompress ) )
          call Att_write( ygroup, igrpid, 'averaged in the J direction', Merge( 'yes', 'no ', tpbudiachro%ljcompress ) )
          call Att_write( ygroup, igrpid, 'averaged in the K direction', Merge( 'yes', 'no ', tpbudiachro%lkcompress ) )
    
          call Att_write( ygroup, igrpid, 'temporal sampling frequency', xles_temp_sampling )
    
          if ( tpbudiachro%lnorm ) then
            if ( cles_norm_type == 'NONE' ) then
              call Att_write( ygroup, igrpid, 'normalization', 'none' )
            else if ( cles_norm_type == 'CONV' ) then
              call Att_write( ygroup, igrpid, 'normalization', 'convective' )
              ! cbl_height_def determines how the boundary layer height is computed, which is used in this normalization
              call Att_write( ygroup, igrpid, 'definition of boundary layer height', cbl_height_def )
            else if ( cles_norm_type == 'EKMA' ) then
              call Att_write( ygroup, igrpid, 'normalization', 'Ekman' )
              ! cbl_height_def determines how the boundary layer height is computed, which is used in this normalization
              call Att_write( ygroup, igrpid, 'definition of boundary layer height', cbl_height_def )
            else if ( cles_norm_type == 'MOBU' ) then
              call Att_write( ygroup, igrpid, 'normalization', 'Monin-Obukhov' )
            else
              call Print_msg( NVERB_WARNING, 'IO', 'Write_diachro_nc4', Trim( tzfile%cname ) // &
                              ': group ' // Trim( ygroup ) // ': unknown normalization' )
              call Att_write( ygroup, igrpid, 'normalization', 'unknown' )
            end if
          else
            call Att_write( ygroup, igrpid, 'normalization', 'none' )
          end if
    
        else if ( tpbudiachro%ccategory == 'LES' .and. tpbudiachro%cshape == '2-point correlation' ) then
          call Att_write( ygroup, igrpid, 'direction of 2-point correlation', tpbudiachro%cdirection )
    
          call Att_write( ygroup, igrpid, 'min I index in physical domain', iil )
          call Att_write( ygroup, igrpid, 'max I index in physical domain', iih )
          call Att_write( ygroup, igrpid, 'min J index in physical domain', ijl )
          call Att_write( ygroup, igrpid, 'max J index in physical domain', ijh )
    
          call Att_write( ygroup, igrpid, 'temporal sampling frequency', xles_temp_sampling )
    
        else if ( tpbudiachro%ccategory == 'LES' .and. tpbudiachro%cshape == 'spectrum' ) then
          call Att_write( ygroup, igrpid, 'direction of spectrum', tpbudiachro%cdirection )
    
          call Att_write( ygroup, igrpid, 'min I index in physical domain', iil )
          call Att_write( ygroup, igrpid, 'max I index in physical domain', iih )
          call Att_write( ygroup, igrpid, 'min J index in physical domain', ijl )
          call Att_write( ygroup, igrpid, 'max J index in physical domain', ijh )
    
          call Att_write( ygroup, igrpid, 'temporal sampling frequency', xles_temp_sampling )
    
        else if ( (      tpbudiachro%ccategory == 'aircraft'                   &
                    .or. tpbudiachro%ccategory == 'radiosonde balloon'         &
                    .or. tpbudiachro%ccategory == 'iso-density balloon'        &
                    .or. tpbudiachro%ccategory ==  'constant volume balloon' ) &
                  .and.  tpbudiachro%cshape == 'point' ) then
    
        else if ( (      tpbudiachro%ccategory == 'aircraft'                   &
                    .or. tpbudiachro%ccategory == 'radiosonde balloon'         &
                    .or. tpbudiachro%ccategory == 'iso-density balloon'        &
                    .or. tpbudiachro%ccategory ==  'constant volume balloon' ) &
                  .and.  tpbudiachro%cshape == 'vertical profile' ) then
    
        else if ( tpbudiachro%ccategory == 'profiler' .and.  tpbudiachro%cshape == 'vertical profile' ) then
        else if ( tpbudiachro%ccategory == 'station' .and.  tpbudiachro%cshape == 'point' ) then
    
        else if ( tpbudiachro%cgroupname == 'TSERIES' ) then
          call Att_write( ygroup, igrpid, 'min I index in physical domain', iil )
          call Att_write( ygroup, igrpid, 'max I index in physical domain', iih )
          call Att_write( ygroup, igrpid, 'min J index in physical domain', ijl )
          call Att_write( ygroup, igrpid, 'max J index in physical domain', ijh )
          call Att_write( ygroup, igrpid, 'min K index in physical domain', ikl )
          call Att_write( ygroup, igrpid, 'max K index in physical domain', ikh )
    
          call Att_write( ygroup, igrpid, 'averaged in the I direction', Merge( 'yes', 'no ', tpbudiachro%licompress ) )
          call Att_write( ygroup, igrpid, 'averaged in the J direction', Merge( 'yes', 'no ', tpbudiachro%ljcompress ) )
          call Att_write( ygroup, igrpid, 'averaged in the K direction', Merge( 'yes', 'no ', tpbudiachro%lkcompress ) )
    
        else if ( tpbudiachro%cgroupname == 'ZTSERIES' ) then
          call Att_write( ygroup, igrpid, 'min I index in physical domain', iil )
          call Att_write( ygroup, igrpid, 'max I index in physical domain', iih )
          call Att_write( ygroup, igrpid, 'min J index in physical domain', ijl )
          call Att_write( ygroup, igrpid, 'max J index in physical domain', ijh )
          call Att_write( ygroup, igrpid, 'min K index in physical domain', ikl )
          call Att_write( ygroup, igrpid, 'max K index in physical domain', ikh )
    
          call Att_write( ygroup, igrpid, 'averaged in the I direction', Merge( 'yes', 'no ', tpbudiachro%licompress ) )
          call Att_write( ygroup, igrpid, 'averaged in the J direction', Merge( 'yes', 'no ', tpbudiachro%ljcompress ) )
          call Att_write( ygroup, igrpid, 'averaged in the K direction', Merge( 'yes', 'no ', tpbudiachro%lkcompress ) )
    
        else if ( tpbudiachro%cgroupname(1:8) == 'XTSERIES' ) then
          call Att_write( ygroup, igrpid, 'min I index in physical domain', iil )
          call Att_write( ygroup, igrpid, 'max I index in physical domain', iih )
          call Att_write( ygroup, igrpid, 'min J index in physical domain', ijl )
          call Att_write( ygroup, igrpid, 'max J index in physical domain', ijh )
          call Att_write( ygroup, igrpid, 'min K index in physical domain', ikl )
          call Att_write( ygroup, igrpid, 'max K index in physical domain', ikh )
    
          call Att_write( ygroup, igrpid, 'averaged in the I direction', Merge( 'yes', 'no ', tpbudiachro%licompress ) )
          call Att_write( ygroup, igrpid, 'averaged in the J direction', Merge( 'yes', 'no ', tpbudiachro%ljcompress ) )
          call Att_write( ygroup, igrpid, 'averaged in the K direction', Merge( 'yes', 'no ', tpbudiachro%lkcompress ) )
    
        else
          call Print_msg( NVERB_WARNING, 'IO', 'Write_diachro_nc4', &
                        'unknown group definition for ' // Trim( tpbudiachro%cname ) // ': using default behavior' )
    
          call Att_write( ygroup, igrpid, 'min I index in physical domain', iil )
          call Att_write( ygroup, igrpid, 'max I index in physical domain', iih )
          call Att_write( ygroup, igrpid, 'min J index in physical domain', ijl )
          call Att_write( ygroup, igrpid, 'max J index in physical domain', ijh )
          call Att_write( ygroup, igrpid, 'min K index in physical domain', ikl )
          call Att_write( ygroup, igrpid, 'max K index in physical domain', ikh )
    
          call Att_write( ygroup, igrpid, 'averaged in the I direction', Merge( 'yes', 'no ', tpbudiachro%licompress ) )
          call Att_write( ygroup, igrpid, 'averaged in the J direction', Merge( 'yes', 'no ', tpbudiachro%ljcompress ) )
          call Att_write( ygroup, igrpid, 'averaged in the K direction', Merge( 'yes', 'no ', tpbudiachro%lkcompress ) )
    
    !Determine the number of dimensions and do some verifications
    do jp = 1, Size( tpfields )
      if ( Any( tpfields(jp)%ndimlist(:) == NMNHDIM_UNKNOWN ) ) &
        call Print_msg( NVERB_ERROR, 'IO', 'Write_diachro_nc4', &
                        'some dimensions are unknown for variable '//trim(tpfields(jp)%cmnhname) )
    
      icount = Count( tpfields(jp)%ndimlist(:) /= NMNHDIM_UNUSED )
    
      if ( tpfields(jp)%ndims /= icount ) &
    
        call Print_msg( NVERB_ERROR, 'IO', 'Write_diachro_nc4', &
    
                        'ndims is not coherent with ndimlist for variable '//trim(tpfields(jp)%cmnhname) )
    
      if ( jp == 1 ) then
        idims = icount
      else
        if ( idims /= icount ) &
          call Print_msg( NVERB_ERROR, 'IO', 'Write_diachro_nc4', &
                          'number of dimensions not the same for all tpfields for variable '//trim(tpfields(jp)%cmnhname) )
    
    !The dimension list should be the same for all tpfields entries
    do jp = 2, Size( tpfields )
      do ji = 1, NMNHMAXDIMS
    
        if ( tpfields(jp)%ndimlist(ji) /= tpfields(1)%ndimlist(ji) ) then
    
          !For SERIES: it is possible to have NMNHDIM_NI and NMNHDIM_NI_U in the different tpfields
    
          !For SERIES: it is possible to have NMNHDIM_SERIES_LEVEL and NMNHDIM_SERIES_LEVEL_W in the different tpfields
    
          if ( tpfields(jp)%ndimlist(ji) /= NMNHDIM_NI           .and. tpfields(jp)%ndimlist(ji) /= NMNHDIM_NI_U .and.     &
               tpfields(jp)%ndimlist(ji) /= NMNHDIM_SERIES_LEVEL .and. tpfields(jp)%ndimlist(ji) /= NMNHDIM_SERIES_LEVEL_W ) then
    
            call Print_msg( NVERB_ERROR, 'IO', 'Write_diachro_nc4', &
                            'some dimensions are not the same for all tpfields entries for variable '//trim(tpfields(jp)%cmnhname) )
          end if
        end if
    
    !Check that if 'CART' and no horizontal compression, parameters are as expected
    
    if ( ytype == 'CART' .and. .not. tpbudiachro%licompress .and. .not. tpbudiachro%ljcompress ) then
      icorr = Merge( 1, 0, tpbudiachro%lkcompress )
    
      if ( ( idims + icorr ) /= 3 .and. ( idims + icorr ) /= 4 ) then
    
        call Print_msg( NVERB_ERROR, 'IO', 'Write_diachro_nc4',                                                 &
                        'unexpected number of dimensions for CART without horizontal compression for variable ' &
                        // Trim( tpfields(1)%cmnhname ) )
      end if
    
      if (      (       tpfields(1)%ndimlist(1) /= NMNHDIM_BUDGET_CART_NI              &
                  .and. tpfields(1)%ndimlist(1) /= NMNHDIM_BUDGET_CART_NI_U            &
                  .and. tpfields(1)%ndimlist(1) /= NMNHDIM_BUDGET_CART_NI_V          ) &
           .or. (       tpfields(1)%ndimlist(2) /= NMNHDIM_BUDGET_CART_NJ              &
                  .and. tpfields(1)%ndimlist(2) /= NMNHDIM_BUDGET_CART_NJ_U            &
                  .and. tpfields(1)%ndimlist(2) /= NMNHDIM_BUDGET_CART_NJ_V          ) &
    
                  .and. tpfields(1)%ndimlist(3) /= NMNHDIM_BUDGET_CART_LEVEL           &
    
                  .and. tpfields(1)%ndimlist(3) /= NMNHDIM_BUDGET_CART_LEVEL_W       ) &
           .or. ( idims == 4 .and. tpfields(1)%ndimlist(6) /= NMNHDIM_BUDGET_NGROUPS ) ) then
        call Print_msg( NVERB_ERROR, 'IO', 'Write_diachro_nc4',                                       &
                        'unexpected dimensions for CART without horizontal compression for variable ' &
                        // Trim( tpfields(1)%cmnhname ) )
      end if
    end if
    
    
         !Remark: [ integer:: ] is a constructor for a zero-size array of integers, [] is not allowed (type can not be determined)
    
          call Diachro_one_field_write_nc4( tzfile, tpfields(1), ytype, pvar, [ integer:: ], gsplit, gdistributed )
    
        if ( tpfields(1)%ndimlist(4) == NMNHDIM_BUDGET_LES_TIME .or. tpfields(1)%ndimlist(4) == NMNHDIM_BUDGET_LES_AVG_TIME ) then
    
          if ( Size( tpfields ) /= 1 ) call Print_msg( NVERB_FATAL, 'IO', 'Write_diachro_nc4', &
                                                       'wrong size of tpfields (variable '//trim(tpfields(1)%cmnhname)//')' )
    
    
          call Diachro_one_field_write_nc4( tzfile, tpfields(1), ytype, pvar, [ 4 ], gsplit, gdistributed )
    
        else if ( Any( tpfields(1)%ndimlist(1) == [ NMNHDIM_NI, NMNHDIM_NI_U, NMNHDIM_NI_V, NMNHDIM_BUDGET_CART_NI,     &
                                                    NMNHDIM_BUDGET_CART_NI_U, NMNHDIM_BUDGET_CART_NI_V              ] ) ) then
    
          if ( Size( tpfields ) /= 1 ) call Print_msg( NVERB_FATAL, 'IO', 'Write_diachro_nc4', &
                                                       'wrong size of tpfields (variable '//trim(tpfields(1)%cmnhname)//')' )
    
          call Diachro_one_field_write_nc4( tzfile, tpfields(1), ytype, pvar, [ 1 ], gsplit, gdistributed )