Skip to content
Snippets Groups Projects
write_diachro.f90 101 KiB
Newer Older
      tzfield%ndimlist(2:) = NMNHDIM_UNUSED

      allocate( zdata1d( size(pvar,3) ) )

      zdata1d(:) = pvar(1, 1, :, 1, 1, 1)

      TZFIELD%CMNHNAME   = tpfields(1)%cmnhname
      TZFIELD%CSTDNAME   = tpfields(1)%cstdname
      TZFIELD%CLONGNAME  = tpfields(1)%clongname
      TZFIELD%CUNITS     = tpfields(1)%cunits
      TZFIELD%CDIR       = '--'
      TZFIELD%CCOMMENT   = tpfields(1)%ccomment
      TZFIELD%NGRID      = tpfields(1)%ngrid
      TZFIELD%NTYPE      = tpfields(1)%ntype
      TZFIELD%NDIMS      = 1
      TZFIELD%LTIMEDEP   = .FALSE.

      if ( gsplit ) then
        if ( htype /= 'CART' ) call Print_msg( NVERB_ERROR, 'IO', 'Write_diachro_nc4', Trim( tzfile%cname ) // &
                    ': group ' // Trim( hgroup ) //': gsplit=T not implemented for these dimensions and htype/=CART' )

        !Add budget time dimension
        tzfield%ndims = 2
        tzfield%ndimlist(2) = NMNHDIM_BUDGET_TIME

        !Create the metadata of the field (has to be done only once)
        if ( nbutshift == 1 ) call IO_Field_create( tzfile, tzfield )

        call IO_Field_write( tzfile, tzfield, Reshape( zdata1d, [ Size(zdata1d,1), 1 ] ), &
                             koffset= [ 0, ( nbutshift - 1 ) * nbusubwrite ] )
      else
        call IO_Field_write( tzfile, tzfield, zdata1d )
      end if

    else if ( tpfields(1)%ndimlist(6) == NMNHDIM_BUDGET_NGROUPS ) then
      tzfield%ndimlist(:) = NMNHDIM_UNUSED

      do ji = 1, Size( pvar, 6 )
        zdata0d = pvar(1, 1, 1, 1, 1, ji)

        tzfield%cmnhname   = tpfields(ji)%cmnhname
        tzfield%cstdname   = tpfields(ji)%cstdname
        tzfield%clongname  = tpfields(ji)%clongname
        tzfield%cunits     = tpfields(ji)%cunits
        tzfield%cdir       = '--'
        tzfield%ccomment   = tpfields(ji)%ccomment
        tzfield%ngrid      = tpfields(ji)%ngrid
        tzfield%ntype      = tpfields(ji)%ntype
        tzfield%ndims      = 2
        tzfield%ltimedep   = .false.

        if ( gsplit ) then
          !Add budget time dimension
          tzfield%ndims = 1
          tzfield%ndimlist(1) = NMNHDIM_BUDGET_TIME

          !Create the metadata of the field (has to be done only once)
          if ( nbutshift == 1 ) call IO_Field_create( tzfile, tzfield )

          call IO_Field_write( tzfile, tzfield, [ zdata0d ], koffset= [ ( nbutshift - 1 ) * nbusubwrite ] )
        else
          call IO_Field_write( tzfile, tzfield, zdata0d )
        end if
      end do

    else
      call Print_msg( NVERB_FATAL, 'IO', 'Write_diachro_nc4', &
                      'case not yet implemented (variable '//trim(tpfields(1)%cmnhname)//')' )

      if ( gsplit ) then
        call Print_msg( NVERB_ERROR, 'IO', 'Write_diachro_nc4', Trim( tzfile%cname ) // &
                        ': group ' // Trim( hgroup ) //' gsplit=T not implemented' )
      end if

    if (       ( tpfields(1)%ndimlist(1) == NMNHDIM_NI .or. tpfields(1)%ndimlist(1) == NMNHDIM_NI_U .or. &
                 tpfields(1)%ndimlist(1) == NMNHDIM_NI_V .or. tpfields(1)%ndimlist(1) == NMNHDIM_BUDGET_CART_NI &
                 .or. tpfields(1)%ndimlist(1) == NMNHDIM_BUDGET_CART_NI_U &
                 .or. tpfields(1)%ndimlist(1) == NMNHDIM_BUDGET_CART_NI_V )     &
         .and. ( tpfields(1)%ndimlist(2) == NMNHDIM_NJ .or. tpfields(1)%ndimlist(2) == NMNHDIM_NJ_U .or. &
                  tpfields(1)%ndimlist(2) == NMNHDIM_NJ_V .or. tpfields(1)%ndimlist(2) == NMNHDIM_BUDGET_CART_NJ .or. &
                  tpfields(1)%ndimlist(2) == NMNHDIM_BUDGET_CART_NJ_U &
                 .or. tpfields(1)%ndimlist(2) == NMNHDIM_BUDGET_CART_NJ_V ) ) then
      if ( Size( tpfields ) /= 1 ) call Print_msg( NVERB_FATAL, 'IO', 'Write_diachro_nc4', &
                                                   'wrong size of tpfields (variable '//trim(tpfields(1)%cmnhname)//')' )

      tzfield%ndimlist(1)  = tpfields(1)%ndimlist(1)
      tzfield%ndimlist(2)  = tpfields(1)%ndimlist(2)
      tzfield%ndimlist(3:) = NMNHDIM_UNUSED

      allocate( zdata2d( size(pvar,1), size(pvar,2) ) )

      zdata2d(:,:) = pvar(:, :, 1, 1, 1, 1)

      TZFIELD%CMNHNAME   = tpfields(1)%cmnhname
      TZFIELD%CSTDNAME   = tpfields(1)%cstdname
      TZFIELD%CLONGNAME  = tpfields(1)%clongname
      TZFIELD%CUNITS     = tpfields(1)%cunits
      TZFIELD%CDIR       = '--'
      TZFIELD%CCOMMENT   = tpfields(1)%ccomment
      TZFIELD%NGRID      = tpfields(1)%ngrid
      TZFIELD%NTYPE      = tpfields(1)%ntype
      TZFIELD%NDIMS      = 2
      TZFIELD%LTIMEDEP   = .FALSE.

      if ( gsplit ) then
        if ( htype /= 'CART' ) call Print_msg( NVERB_ERROR, 'IO', 'Write_diachro_nc4', Trim( tzfile%cname ) // &
                    ': group ' // Trim( hgroup ) //': gsplit=T not implemented for these dimensions and htype/=CART' )

        !Add budget time dimension
        tzfield%ndims = 3
        tzfield%ndimlist(3) = NMNHDIM_BUDGET_TIME

        !Create the metadata of the field (has to be done only once)
        if ( nbutshift == 1 ) call IO_Field_create( tzfile, tzfield )

        call IO_Field_write( tzfile, tzfield, Reshape( zdata2d, [ Size(zdata2d,1), Size(zdata2d,2), 1 ] ), &
                             koffset= [ 0, 0, ( nbutshift - 1 ) * nbusubwrite ] )
      else
        call IO_Field_write( tzfile, tzfield, zdata2d )
      end if

      deallocate( zdata2d )

    else if (       ( tpfields(1)%ndimlist(1) == NMNHDIM_NI .or. tpfields(1)%ndimlist(1) == NMNHDIM_NI_U &
                      .or. tpfields(1)%ndimlist(1) == NMNHDIM_NI_V .or. tpfields(1)%ndimlist(1) == NMNHDIM_BUDGET_CART_NI &
                      .or. tpfields(1)%ndimlist(1) == NMNHDIM_BUDGET_CART_NI_U &
                 .or. tpfields(1)%ndimlist(1) == NMNHDIM_BUDGET_CART_NI_V )     &
       .and.  ( tpfields(1)%ndimlist(3) == NMNHDIM_LEVEL .or. tpfields(1)%ndimlist(3) == NMNHDIM_LEVEL_W &
           .or. tpfields(1)%ndimlist(3) == NMNHDIM_BUDGET_CART_LEVEL &
           .or. tpfields(1)%ndimlist(3) == NMNHDIM_BUDGET_CART_LEVEL_W ) ) then
      if ( Size( tpfields ) /= 1 ) call Print_msg( NVERB_FATAL, 'IO', 'Write_diachro_nc4', &
                                                   'wrong size of tpfields (variable '//trim(tpfields(1)%cmnhname)//')' )

      tzfield%ndimlist(1)  = tpfields(1)%ndimlist(1)
      tzfield%ndimlist(2)  = tpfields(1)%ndimlist(3)
      tzfield%ndimlist(3:) = NMNHDIM_UNUSED

      allocate( zdata2d( size(pvar,1), size(pvar,3) ) )

      zdata2d(:,:) = pvar(:, 1, :, 1, 1, 1)

      TZFIELD%CMNHNAME   = tpfields(1)%cmnhname
      TZFIELD%CSTDNAME   = tpfields(1)%cstdname
      TZFIELD%CLONGNAME  = tpfields(1)%clongname
      TZFIELD%CUNITS     = tpfields(1)%cunits
      TZFIELD%CDIR       = '--'
      TZFIELD%CCOMMENT   = tpfields(1)%ccomment
      TZFIELD%NGRID      = tpfields(1)%ngrid
      TZFIELD%NTYPE      = tpfields(1)%ntype
      TZFIELD%NDIMS      = 2
      TZFIELD%LTIMEDEP   = .FALSE.

      if ( gsplit ) then
        if ( htype /= 'CART' ) call Print_msg( NVERB_ERROR, 'IO', 'Write_diachro_nc4', Trim( tzfile%cname ) // &
                    ': group ' // Trim( hgroup ) //': gsplit=T not implemented for these dimensions and htype/=CART' )

        !Add budget time dimension
        tzfield%ndims = 3
        tzfield%ndimlist(3) = NMNHDIM_BUDGET_TIME

        !Create the metadata of the field (has to be done only once)
        if ( nbutshift == 1 ) call IO_Field_create( tzfile, tzfield )

        call IO_Field_write( tzfile, tzfield, Reshape( zdata2d, [ Size(zdata2d,1), Size(zdata2d,2), 1 ] ), &
                             koffset= [ 0, 0, ( nbutshift - 1 ) * nbusubwrite ] )
      else
        call IO_Field_write( tzfile, tzfield, zdata2d )
      end if

      deallocate( zdata2d )

    else if (       ( tpfields(1)%ndimlist(2) == NMNHDIM_NJ .or. tpfields(1)%ndimlist(2) == NMNHDIM_NJ_U &
                     .or. tpfields(1)%ndimlist(2) == NMNHDIM_NJ_V .or. tpfields(1)%ndimlist(2) == NMNHDIM_BUDGET_CART_NJ &
                     .or. tpfields(1)%ndimlist(2) == NMNHDIM_BUDGET_CART_NJ_U &
                 .or. tpfields(1)%ndimlist(2) == NMNHDIM_BUDGET_CART_NJ_V )     &
       .and.  ( tpfields(1)%ndimlist(3) == NMNHDIM_LEVEL .or. tpfields(1)%ndimlist(3) == NMNHDIM_LEVEL_W &
           .or. tpfields(1)%ndimlist(3) == NMNHDIM_BUDGET_CART_LEVEL &
           .or. tpfields(1)%ndimlist(3) == NMNHDIM_BUDGET_CART_LEVEL_W ) ) then
      if ( Size( tpfields ) /= 1 ) call Print_msg( NVERB_FATAL, 'IO', 'Write_diachro_nc4', &
                                                   'wrong size of tpfields (variable '//trim(tpfields(1)%cmnhname)//')' )

      tzfield%ndimlist(1)  = tpfields(1)%ndimlist(2)
      tzfield%ndimlist(2)  = tpfields(1)%ndimlist(3)
      tzfield%ndimlist(3:) = NMNHDIM_UNUSED

      allocate( zdata2d( size(pvar,2), size(pvar,3) ) )

      zdata2d(:,:) = pvar(1, :, :, 1, 1, 1)

      TZFIELD%CMNHNAME   = tpfields(1)%cmnhname
      TZFIELD%CSTDNAME   = tpfields(1)%cstdname
      TZFIELD%CLONGNAME  = tpfields(1)%clongname
      TZFIELD%CUNITS     = tpfields(1)%cunits
      TZFIELD%CDIR       = '--'
      TZFIELD%CCOMMENT   = tpfields(1)%ccomment
      TZFIELD%NGRID      = tpfields(1)%ngrid
      TZFIELD%NTYPE      = tpfields(1)%ntype
      TZFIELD%NDIMS      = 2
      TZFIELD%LTIMEDEP   = .FALSE.

      if ( gsplit ) then
        if ( htype /= 'CART' ) call Print_msg( NVERB_ERROR, 'IO', 'Write_diachro_nc4', Trim( tzfile%cname ) // &
                    ': group ' // Trim( hgroup ) //': gsplit=T not implemented for these dimensions and htype/=CART' )

        !Add budget time dimension
        tzfield%ndims = 3
        tzfield%ndimlist(3) = NMNHDIM_BUDGET_TIME

        !Create the metadata of the field (has to be done only once)
        if ( nbutshift == 1 ) call IO_Field_create( tzfile, tzfield )

        call IO_Field_write( tzfile, tzfield, Reshape( zdata2d, [ Size(zdata2d,1), Size(zdata2d,2), 1 ] ), &
                             koffset= [ 0, 0, ( nbutshift - 1 ) * nbusubwrite ] )
      else
        call IO_Field_write( tzfile, tzfield, zdata2d )
      end if
    else if (  Any( tpfields(1)%ndimlist(1) == [ NMNHDIM_BUDGET_CART_NI, NMNHDIM_BUDGET_CART_NI_U, NMNHDIM_BUDGET_CART_NI_V ] ) &
              .and. tpfields(1)%ndimlist(6) == NMNHDIM_BUDGET_NGROUPS ) then
      tzfield%ndimlist(1)  = tpfields(1)%ndimlist(1)
      tzfield%ndimlist(2:) = NMNHDIM_UNUSED

      Allocate( zdata1d(Size( pvar, 1 )) )

      do ji = 1, Size( pvar, 6 )
        zdata1d(:) = pvar(:, 1, 1, 1, 1, ji)

        tzfield%cmnhname   = tpfields(ji)%cmnhname
        tzfield%cstdname   = tpfields(ji)%cstdname
        tzfield%clongname  = tpfields(ji)%clongname
        tzfield%cunits     = tpfields(ji)%cunits
        tzfield%cdir       = '--'
        tzfield%ccomment   = tpfields(ji)%ccomment
        tzfield%ngrid      = tpfields(ji)%ngrid
        tzfield%ntype      = tpfields(ji)%ntype
        tzfield%ndims      = 2
        tzfield%ltimedep   = .false.

        if ( gsplit ) then
          !Add budget time dimension
          tzfield%ndims = 2
          tzfield%ndimlist(2) = NMNHDIM_BUDGET_TIME

          !Create the metadata of the field (has to be done only once)
          if ( nbutshift == 1 ) call IO_Field_create( tzfile, tzfield )

          call IO_Field_write( tzfile, tzfield, Reshape( zdata1d, [ Size(zdata1d,1), 1 ] ), &
                               koffset= [ 0, ( nbutshift - 1 ) * nbusubwrite ] )
        else
          call IO_Field_write( tzfile, tzfield, zdata1d )
        end if
      end do

      Deallocate( zdata1d )

    else if (  Any( tpfields(1)%ndimlist(2) == [ NMNHDIM_BUDGET_CART_NJ, NMNHDIM_BUDGET_CART_NJ_U, NMNHDIM_BUDGET_CART_NJ_V ] ) &
              .and. tpfields(1)%ndimlist(6) == NMNHDIM_BUDGET_NGROUPS ) then
      tzfield%ndimlist(1)  = tpfields(1)%ndimlist(2)
      tzfield%ndimlist(2:) = NMNHDIM_UNUSED

      Allocate( zdata1d(Size( pvar, 2 )) )

      do ji = 1, Size( pvar, 6 )
        zdata1d(:) = pvar(1, :, 1, 1, 1, ji)

        tzfield%cmnhname   = tpfields(ji)%cmnhname
        tzfield%cstdname   = tpfields(ji)%cstdname
        tzfield%clongname  = tpfields(ji)%clongname
        tzfield%cunits     = tpfields(ji)%cunits
        tzfield%cdir       = '--'
        tzfield%ccomment   = tpfields(ji)%ccomment
        tzfield%ngrid      = tpfields(ji)%ngrid
        tzfield%ntype      = tpfields(ji)%ntype
        tzfield%ndims      = 2
        tzfield%ltimedep   = .false.

        if ( gsplit ) then
          !Add budget time dimension
          tzfield%ndims = 2
          tzfield%ndimlist(2) = NMNHDIM_BUDGET_TIME

          !Create the metadata of the field (has to be done only once)
          if ( nbutshift == 1 ) call IO_Field_create( tzfile, tzfield )

          call IO_Field_write( tzfile, tzfield, Reshape( zdata1d, [ Size(zdata1d,1), 1 ] ), &
                               koffset= [ 0, ( nbutshift - 1 ) * nbusubwrite ] )
        else
          call IO_Field_write( tzfile, tzfield, zdata1d )
        end if
      end do

      Deallocate( zdata1d )

    else if (       tpfields(1)%ndimlist(3) == NMNHDIM_BUDGET_LES_LEVEL     &
       .and. (      tpfields(1)%ndimlist(4) == NMNHDIM_BUDGET_LES_TIME &
               .or. tpfields(1)%ndimlist(4) == NMNHDIM_BUDGET_LES_AVG_TIME ) ) then
      if ( gsplit ) then
          call Print_msg( NVERB_ERROR, 'IO', 'Write_diachro_nc4', Trim( tzfile%cname ) // &
                          ': group ' // Trim( hgroup ) //' gsplit=T not implemented' )
      end if

      if ( Size( tpfields ) /= 1 ) call Print_msg( NVERB_FATAL, 'IO', 'Write_diachro_nc4', &
                                                   'wrong size of tpfields (variable '//trim(tpfields(1)%cmnhname)//')' )

      tzfield%ndimlist(1)  = tpfields(1)%ndimlist(3)
      tzfield%ndimlist(2)  = tpfields(1)%ndimlist(4)
      tzfield%ndimlist(3:) = NMNHDIM_UNUSED

      allocate( zdata2d( size(pvar,3), size(pvar,4) ) )

      zdata2d(:,:) = pvar(1, 1, :, :, 1, 1)

      TZFIELD%CMNHNAME   = tpfields(1)%cmnhname
      TZFIELD%CSTDNAME   = tpfields(1)%cstdname
      TZFIELD%CLONGNAME  = tpfields(1)%clongname
      TZFIELD%CUNITS     = tpfields(1)%cunits
      TZFIELD%CDIR       = '--'
      TZFIELD%CCOMMENT   = tpfields(1)%ccomment
      TZFIELD%NGRID      = tpfields(1)%ngrid
      TZFIELD%NTYPE      = tpfields(1)%ntype
      TZFIELD%NDIMS      = 2
      TZFIELD%LTIMEDEP   = .FALSE.
      CALL IO_Field_write( tzfile, tzfield, zdata2d )

      deallocate( zdata2d )

    else if ( Any( tpfields(1)%ndimlist(3) == [ NMNHDIM_BUDGET_CART_LEVEL, NMNHDIM_BUDGET_CART_LEVEL_W ] ) &
              .and. tpfields(1)%ndimlist(6) == NMNHDIM_BUDGET_NGROUPS ) then
      tzfield%ndimlist(1)  = tpfields(1)%ndimlist(3)
      tzfield%ndimlist(2:) = NMNHDIM_UNUSED

      allocate( zdata1d( size(pvar,3) ) )

      ! Loop on the processes (1 written variable per process)
      do ji = 1, Size( pvar, 6 )
        zdata1d(:) = pvar(1, 1, :, 1, 1, ji)

        tzfield%cmnhname   = tpfields(ji)%cmnhname
        tzfield%cstdname   = tpfields(ji)%cstdname
        tzfield%clongname  = tpfields(ji)%clongname
        tzfield%cunits     = tpfields(ji)%cunits
        tzfield%cdir       = '--'
        tzfield%ccomment   = tpfields(ji)%ccomment
        tzfield%ngrid      = tpfields(ji)%ngrid
        tzfield%ntype      = tpfields(ji)%ntype
        tzfield%ndims      = 1
        tzfield%ltimedep   = .FALSE.

        if ( gsplit ) then
          !Add budget time dimension
          tzfield%ndims = 2
          tzfield%ndimlist(2) = NMNHDIM_BUDGET_TIME

          !Create the metadata of the field (has to be done only once)
          if ( nbutshift == 1 ) call IO_Field_create( tzfile, tzfield )

          call IO_Field_write( tzfile, tzfield, Reshape( zdata1d, [ Size(zdata1d,1), 1 ] ), &
                               koffset= [ 0, ( nbutshift - 1 ) * nbusubwrite ] )
        else
          call IO_Field_write( tzfile, tzfield, zdata1d )
        end if
      end do

      deallocate( zdata1d )

    else if (  tpfields(1)%ndimlist(4) == NMNHDIM_BUDGET_TIME .and. tpfields(1)%ndimlist(5) == NMNHDIM_BUDGET_MASK_NBUMASK ) then
      if ( Size( tpfields ) /= 1 ) call Print_msg( NVERB_FATAL, 'IO', 'Write_diachro_nc4', &
                                                   'wrong size of tpfields (variable '//trim(tpfields(1)%cmnhname)//')' )

      tzfield%ndimlist(1)  = tpfields(1)%ndimlist(4)
      tzfield%ndimlist(2)  = tpfields(1)%ndimlist(5)
      tzfield%ndimlist(3:) = NMNHDIM_UNUSED

      Allocate( zdata2d(Size( pvar, 4 ), Size( pvar, 5 )) )

      zdata2d(:,:) = pvar(1, 1, 1, :, :, 1)

      tzfield%cmnhname   = tpfields(1)%cmnhname
      tzfield%cstdname   = tpfields(1)%cstdname
      tzfield%clongname  = tpfields(1)%clongname
      tzfield%cunits     = tpfields(1)%cunits
      tzfield%cdir       = '--'
      tzfield%ccomment   = tpfields(1)%ccomment
      tzfield%ngrid      = tpfields(1)%ngrid
      tzfield%ntype      = tpfields(1)%ntype
      tzfield%ndims      = 2
      tzfield%ltimedep   = .false.

      if ( gsplit ) then
        !Create the metadata of the field (has to be done only once)
        if ( nbutshift == 1 ) call IO_Field_create( tzfile, tzfield )

        call IO_Field_write( tzfile, tzfield, zdata2d, koffset= [ ( nbutshift - 1 ) * nbusubwrite, 0 ] )
      else
        call IO_Field_write( tzfile, tzfield, zdata2d )
      end if

      Deallocate( zdata2d )

    else if (  (      tpfields(1)%ndimlist(4) == NMNHDIM_BUDGET_LES_TIME &
               .or. tpfields(1)%ndimlist(4) == NMNHDIM_BUDGET_LES_AVG_TIME ) &
         .and. tpfields(1)%ndimlist(5) == NMNHDIM_BUDGET_LES_SV       ) then
      if ( gsplit ) then
          call Print_msg( NVERB_ERROR, 'IO', 'Write_diachro_nc4', Trim( tzfile%cname ) // &
                          ': group ' // Trim( hgroup ) //' gsplit=T not implemented' )
      end if

      if ( Size( tpfields ) /= 1 ) call Print_msg( NVERB_FATAL, 'IO', 'Write_diachro_nc4', &
                                                   'wrong size of tpfields (variable '//trim(tpfields(1)%cmnhname)//')' )

      tzfield%ndimlist(1)  = tpfields(1)%ndimlist(4)
      tzfield%ndimlist(2)  = tpfields(1)%ndimlist(5)
      tzfield%ndimlist(3:) = NMNHDIM_UNUSED

      allocate( zdata2d( size(pvar,4), size(pvar,5) ) )

      zdata2d(:,:) = pvar(1, 1, 1, :, :, 1)

      TZFIELD%CMNHNAME   = tpfields(1)%cmnhname
      TZFIELD%CSTDNAME   = tpfields(1)%cstdname
      TZFIELD%CLONGNAME  = tpfields(1)%clongname
      TZFIELD%CUNITS     = tpfields(1)%cunits
      TZFIELD%CDIR       = '--'
      TZFIELD%CCOMMENT   = tpfields(1)%ccomment
      TZFIELD%NGRID      = tpfields(1)%ngrid
      TZFIELD%NTYPE      = tpfields(1)%ntype
      TZFIELD%NDIMS      = 2
      TZFIELD%LTIMEDEP   = .FALSE.
      CALL IO_Field_write( tzfile, tzfield, zdata2d )

      deallocate( zdata2d )
    else if (  tpfields(1)%ndimlist(4) == NMNHDIM_FLYER_TIME &
         .and. tpfields(1)%ndimlist(6) == NMNHDIM_FLYER_PROC ) then
      !Correspond to FLYER_DIACHRO
      if ( gsplit ) then
          call Print_msg( NVERB_ERROR, 'IO', 'Write_diachro_nc4', Trim( tzfile%cname ) // &
                          ': group ' // Trim( hgroup ) //' gsplit=T not implemented' )
      end if

      !Create local time dimension
      if ( isp == tzfile%nmaster_rank) then
        istatus = NF90_DEF_DIM( igrpid, 'time_flyer', Size( pvar, 4), idimid )
        if ( istatus /= NF90_NOERR ) &
          call IO_Err_handle_nc4( istatus, 'Write_diachro_nc4', 'NF90_DEF_DIM', Trim( tpfields(1)%cmnhname ) )
      end if

      tzfield%ndimlist(1)  = tpfields(1)%ndimlist(4)
      tzfield%ndimlist(2:) = NMNHDIM_UNUSED

      allocate( zdata1d( size(pvar,4) ) )

      ! Loop on the processes (1 written variable per process)
      do ji = 1, size(pvar,6)
        zdata1d(:) = pvar(1, 1, 1, :, 1, ji)

        TZFIELD%CMNHNAME   = tpfields(ji)%cmnhname
        TZFIELD%CSTDNAME   = tpfields(ji)%cstdname
        TZFIELD%CLONGNAME  = tpfields(ji)%clongname
        TZFIELD%CUNITS     = tpfields(ji)%cunits
        TZFIELD%CDIR       = '--'
        TZFIELD%CCOMMENT   = tpfields(ji)%ccomment
        TZFIELD%NGRID      = tpfields(ji)%ngrid
        TZFIELD%NTYPE      = tpfields(ji)%ntype
        TZFIELD%NDIMS      = 1
        TZFIELD%LTIMEDEP   = .FALSE.
        CALL IO_Field_write( tzfile, tzfield, zdata1d )
      end do

      deallocate( zdata1d )
    else if (  tpfields(1)%ndimlist(4) == NMNHDIM_STATION_TIME &
         .and. tpfields(1)%ndimlist(6) == NMNHDIM_STATION_PROC ) then
      !Correspond to STATION_DIACHRO_n
      if ( gsplit ) then
          call Print_msg( NVERB_ERROR, 'IO', 'Write_diachro_nc4', Trim( tzfile%cname ) // &
                          ': group ' // Trim( hgroup ) //' gsplit=T not implemented' )
      end if

      tzfield%ndimlist(1)  = tpfields(1)%ndimlist(4)
      tzfield%ndimlist(2:) = NMNHDIM_UNUSED

      allocate( zdata1d( size(pvar,4) ) )

      ! Loop on the processes (1 written variable per process)
      do ji = 1, size(pvar,6)
        zdata1d(:) = pvar(1, 1, 1, :, 1, ji)

        TZFIELD%CMNHNAME   = tpfields(ji)%cmnhname
        TZFIELD%CSTDNAME   = tpfields(ji)%cstdname
        TZFIELD%CLONGNAME  = tpfields(ji)%clongname
        TZFIELD%CUNITS     = tpfields(ji)%cunits
        TZFIELD%CDIR       = '--'
        TZFIELD%CCOMMENT   = tpfields(ji)%ccomment
        TZFIELD%NGRID      = tpfields(ji)%ngrid
        TZFIELD%NTYPE      = tpfields(ji)%ntype
        TZFIELD%NDIMS      = 1
        TZFIELD%LTIMEDEP   = .FALSE.
        CALL IO_Field_write( tzfile, tzfield, zdata1d )
      end do

      deallocate( zdata1d )
    else if (  tpfields(1)%ndimlist(4) == NMNHDIM_SERIES_TIME &
         .and. tpfields(1)%ndimlist(6) == NMNHDIM_SERIES_PROC ) then
      !Correspond to WRITE_SERIES_n
      if ( gsplit ) then
          call Print_msg( NVERB_ERROR, 'IO', 'Write_diachro_nc4', Trim( tzfile%cname ) // &
                          ': group ' // Trim( hgroup ) //' gsplit=T not implemented' )
      end if

      tzfield%ndimlist(1)  = tpfields(1)%ndimlist(4)
      tzfield%ndimlist(2:) = NMNHDIM_UNUSED

      allocate( zdata1d( size(pvar,4) ) )

      ! Loop on the processes (1 written variable per process)
      do ji = 1, size(pvar,6)
        zdata1d(:) = pvar(1, 1, 1, :, 1, ji)

        TZFIELD%CMNHNAME   = tpfields(ji)%cmnhname
        TZFIELD%CSTDNAME   = tpfields(ji)%cstdname
        TZFIELD%CLONGNAME  = tpfields(ji)%clongname
        TZFIELD%CUNITS     = tpfields(ji)%cunits
        TZFIELD%CDIR       = '--'
        TZFIELD%CCOMMENT   = tpfields(ji)%ccomment
        TZFIELD%NGRID      = tpfields(ji)%ngrid
        TZFIELD%NTYPE      = tpfields(ji)%ntype
        TZFIELD%NDIMS      = 1
        TZFIELD%LTIMEDEP   = .FALSE.
        CALL IO_Field_write( tzfile, tzfield, zdata1d )
      end do

      deallocate( zdata1d )
    else
      call Print_msg( NVERB_FATAL, 'IO', 'Write_diachro_nc4', &
                      'case not yet implemented (variable '//trim(tpfields(1)%cmnhname)//')' )

      if ( gsplit ) then
          call Print_msg( NVERB_ERROR, 'IO', 'Write_diachro_nc4', Trim( tzfile%cname ) // &
                          ': group ' // Trim( hgroup ) //' gsplit=T not implemented' )
      end if

    end if


  case (3)
    if (       ( tpfields(1)%ndimlist(1) == NMNHDIM_NI .or. tpfields(1)%ndimlist(1) == NMNHDIM_NI_U .or. &
                 tpfields(1)%ndimlist(1) == NMNHDIM_NI_V .or. tpfields(1)%ndimlist(1) == NMNHDIM_BUDGET_CART_NI &
                 .or. tpfields(1)%ndimlist(1) == NMNHDIM_BUDGET_CART_NI_U &
                 .or. tpfields(1)%ndimlist(1) == NMNHDIM_BUDGET_CART_NI_V )     &
         .and. ( tpfields(1)%ndimlist(2) == NMNHDIM_NJ .or. tpfields(1)%ndimlist(2) == NMNHDIM_NJ_U .or. &
                  tpfields(1)%ndimlist(2) == NMNHDIM_NJ_V .or. tpfields(1)%ndimlist(2) == NMNHDIM_BUDGET_CART_NJ .or. &
                  tpfields(1)%ndimlist(2) == NMNHDIM_BUDGET_CART_NJ_U &
                 .or. tpfields(1)%ndimlist(2) == NMNHDIM_BUDGET_CART_NJ_V ) &
       .and.  ( tpfields(1)%ndimlist(3) == NMNHDIM_LEVEL .or. tpfields(1)%ndimlist(3) == NMNHDIM_LEVEL_W &
           .or. tpfields(1)%ndimlist(3) == NMNHDIM_BUDGET_CART_LEVEL &
           .or. tpfields(1)%ndimlist(3) == NMNHDIM_BUDGET_CART_LEVEL_W ) ) then
      if ( Size( tpfields ) /= 1 ) call Print_msg( NVERB_FATAL, 'IO', 'Write_diachro_nc4', &
                                                   'wrong size of tpfields (variable '//trim(tpfields(1)%cmnhname)//')' )

      tzfield%ndimlist(1)  = tpfields(1)%ndimlist(1)
      tzfield%ndimlist(2)  = tpfields(1)%ndimlist(2)
      tzfield%ndimlist(3)  = tpfields(1)%ndimlist(3)
      tzfield%ndimlist(4:) = NMNHDIM_UNUSED

      allocate( zdata3d( size(pvar,1), size(pvar,2), size(pvar,3) ) )

      zdata3d(:,:,:) = pvar(:, :, :, 1, 1, 1)

      TZFIELD%CMNHNAME   = tpfields(1)%cmnhname
      TZFIELD%CSTDNAME   = tpfields(1)%cstdname
      TZFIELD%CLONGNAME  = tpfields(1)%clongname
      TZFIELD%CUNITS     = tpfields(1)%cunits
      TZFIELD%CCOMMENT   = tpfields(1)%ccomment
      TZFIELD%NGRID      = tpfields(1)%ngrid
      TZFIELD%NTYPE      = tpfields(1)%ntype
      TZFIELD%NDIMS      = 3
      TZFIELD%LTIMEDEP   = .FALSE.

      if ( gsplit ) then
        if ( htype /= 'CART' ) call Print_msg( NVERB_ERROR, 'IO', 'Write_diachro_nc4', Trim( tzfile%cname ) // &
                    ': group ' // Trim( hgroup ) //': gsplit=T not implemented for these dimensions and htype/=CART' )

        if ( htype == 'CART' .and. .not. oicp .and. .not. ojcp ) then
          !Data is distributed between all the processes
          tzfield%cdir = 'XY'

          !Add budget time dimension
          tzfield%ndims = 4
          tzfield%ndimlist(4) = NMNHDIM_BUDGET_TIME

          !Create the metadata of the field (has to be done only once)
          if ( nbutshift == 1 ) call IO_Field_create( tzfile, tzfield )

          call IO_Field_write_box( tzfile, tzfield, 'BUDGET',                                                     &
                                   Reshape( zdata3d, [ Size(zdata3d,1), Size(zdata3d,2), Size(zdata3d,3), 1 ] ) , &
                                   kil + jphext, kih + jphext, kjl + jphext, kjh + jphext,                        &
                                   koffset= [ 0, 0, 0, ( nbutshift - 1 ) * nbusubwrite ]                          )
        else
          call Print_msg( NVERB_ERROR, 'IO', 'Write_diachro_nc4', Trim( tzfile%cname ) // &
                          ': group ' // Trim( hgroup ) //' gsplit=T not implemented' )
        end if
        if ( htype == 'CART' .and. .not. oicp .and. .not. ojcp ) then
          !Data is distributed between all the processes
          tzfield%cdir = 'XY'
          call IO_Field_write_box( tzfile, tzfield, 'BUDGET', zdata3d, &
                                  kil + jphext, kih + jphext, kjl + jphext, kjh + jphext )
        else
          !Data is already collected on the master process
          tzfield%cdir = '--'
          call IO_Field_write( tzfile, tzfield, zdata3d )
        end if

    else if (       Any(tpfields(1)%ndimlist(1) == [ NMNHDIM_BUDGET_CART_NI, NMNHDIM_BUDGET_CART_NI_U, NMNHDIM_BUDGET_CART_NI_V ]) &
              .and. Any(tpfields(1)%ndimlist(2) == [ NMNHDIM_BUDGET_CART_NJ, NMNHDIM_BUDGET_CART_NJ_U, NMNHDIM_BUDGET_CART_NJ_V ]) &
              .and. tpfields(1)%ndimlist(6) == NMNHDIM_BUDGET_NGROUPS    ) then
      tzfield%ndimlist(1)  = tpfields(1)%ndimlist(1)
      tzfield%ndimlist(2)  = tpfields(1)%ndimlist(2)
      tzfield%ndimlist(3:) = NMNHDIM_UNUSED

      Allocate( zdata2d(Size( pvar, 1 ), Size( pvar, 2 )) )

      ! Loop on the processes
      do ji = 1, Size( pvar, 6 )
        zdata2d(:, :) = pvar(:, :, 1, 1, 1, ji)

        tzfield%cmnhname   = tpfields(ji)%cmnhname
        tzfield%cstdname   = tpfields(ji)%cstdname
        tzfield%clongname  = tpfields(ji)%clongname
        tzfield%cunits     = tpfields(ji)%cunits
        tzfield%cdir       = '--'
        tzfield%ccomment   = tpfields(ji)%ccomment
        tzfield%ngrid      = tpfields(ji)%ngrid
        tzfield%ntype      = tpfields(ji)%ntype
        tzfield%ndims      = 2
        tzfield%ltimedep   = .false.

        if ( gsplit ) then
          !Add budget time dimension
          tzfield%ndims = 3
          tzfield%ndimlist(3) = NMNHDIM_BUDGET_TIME

          !Create the metadata of the field (has to be done only once)
          if ( nbutshift == 1 ) call IO_Field_create( tzfile, tzfield )

          call IO_Field_write( tzfile, tzfield,                                             &
                               Reshape( zdata2d, [ Size(zdata2d,1), Size(zdata2d,2), 1 ] ), &
                               koffset= [ 0, 0, ( nbutshift - 1 ) * nbusubwrite ]           )
        else
          call IO_Field_write( tzfile, tzfield, zdata2d )
        end if
      end do

      Deallocate( zdata2d )

    else if ( Any ( tpfields(1)%ndimlist(1) == [ NMNHDIM_BUDGET_CART_NI, NMNHDIM_BUDGET_CART_NI_U, NMNHDIM_BUDGET_CART_NI_V ] ) &
              .and. tpfields(1)%ndimlist(3) == NMNHDIM_BUDGET_CART_LEVEL &
              .and. tpfields(1)%ndimlist(6) == NMNHDIM_BUDGET_NGROUPS    ) then
      tzfield%ndimlist(1)  = tpfields(1)%ndimlist(1)
      tzfield%ndimlist(2)  = tpfields(1)%ndimlist(3)
      tzfield%ndimlist(3:) = NMNHDIM_UNUSED

      Allocate( zdata2d(Size( pvar, 1 ), Size( pvar, 3 )) )

      ! Loop on the processes
      do ji = 1, Size( pvar, 6 )
        zdata2d(:, :) = pvar(:, 1, :, 1, 1, ji)

        tzfield%cmnhname   = tpfields(ji)%cmnhname
        tzfield%cstdname   = tpfields(ji)%cstdname
        tzfield%clongname  = tpfields(ji)%clongname
        tzfield%cunits     = tpfields(ji)%cunits
        tzfield%cdir       = '--'
        tzfield%ccomment   = tpfields(ji)%ccomment
        tzfield%ngrid      = tpfields(ji)%ngrid
        tzfield%ntype      = tpfields(ji)%ntype
        tzfield%ndims      = 2
        tzfield%ltimedep   = .false.
        if ( gsplit ) then
          !Add budget time dimension
          tzfield%ndims = 3
          tzfield%ndimlist(3) = NMNHDIM_BUDGET_TIME

          !Create the metadata of the field (has to be done only once)
          if ( nbutshift == 1 ) call IO_Field_create( tzfile, tzfield )

          call IO_Field_write( tzfile, tzfield,                                             &
                               Reshape( zdata2d, [ Size(zdata2d,1), Size(zdata2d,2), 1 ] ), &
                               koffset= [ 0, 0, ( nbutshift - 1 ) * nbusubwrite ]           )
        else
          call IO_Field_write( tzfile, tzfield, zdata2d )
        end if
      end do

      Deallocate( zdata2d )
    else if ( Any ( tpfields(1)%ndimlist(2) == [ NMNHDIM_BUDGET_CART_NJ, NMNHDIM_BUDGET_CART_NJ_U, NMNHDIM_BUDGET_CART_NJ_V ] ) &
              .and. tpfields(1)%ndimlist(3) == NMNHDIM_BUDGET_CART_LEVEL &
              .and. tpfields(1)%ndimlist(6) == NMNHDIM_BUDGET_NGROUPS    ) then
      tzfield%ndimlist(1)  = tpfields(1)%ndimlist(2)
      tzfield%ndimlist(2)  = tpfields(1)%ndimlist(3)
      tzfield%ndimlist(3:) = NMNHDIM_UNUSED

      Allocate( zdata2d(Size( pvar, 2 ), Size( pvar, 3 )) )

      ! Loop on the processes
      do ji = 1, Size( pvar, 6 )
        zdata2d(:, :) = pvar(1, :, :, 1, 1, ji)

        tzfield%cmnhname   = tpfields(ji)%cmnhname
        tzfield%cstdname   = tpfields(ji)%cstdname
        tzfield%clongname  = tpfields(ji)%clongname
        tzfield%cunits     = tpfields(ji)%cunits
        tzfield%cdir       = '--'
        tzfield%ccomment   = tpfields(ji)%ccomment
        tzfield%ngrid      = tpfields(ji)%ngrid
        tzfield%ntype      = tpfields(ji)%ntype
        tzfield%ndims      = 2
        tzfield%ltimedep   = .false.
        if ( gsplit ) then
          !Add budget time dimension
          tzfield%ndims = 3
          tzfield%ndimlist(3) = NMNHDIM_BUDGET_TIME

          !Create the metadata of the field (has to be done only once)
          if ( nbutshift == 1 ) call IO_Field_create( tzfile, tzfield )

          call IO_Field_write( tzfile, tzfield,                                             &
                               Reshape( zdata2d, [ Size(zdata2d,1), Size(zdata2d,2), 1 ] ), &
                               koffset= [ 0, 0, ( nbutshift - 1 ) * nbusubwrite ]           )
        else
          call IO_Field_write( tzfile, tzfield, zdata2d )
        end if
      end do

      Deallocate( zdata2d )
    else if (  ( tpfields(1)%ndimlist(3) == NMNHDIM_BUDGET_MASK_LEVEL &
                  .or. tpfields(1)%ndimlist(3) == NMNHDIM_BUDGET_MASK_LEVEL_W ) &
       .and.    tpfields(1)%ndimlist(4) == NMNHDIM_BUDGET_TIME &
       .and. tpfields(1)%ndimlist(5) == NMNHDIM_BUDGET_MASK_NBUMASK      ) then
      !Correspond to Store_one_budget_rho (MASK)
      if ( Size( tpfields ) /= 1 ) call Print_msg( NVERB_FATAL, 'IO', 'Write_diachro_nc4', &
                                                   'wrong size of tpfields (variable '//trim(tpfields(1)%cmnhname)//')' )

      tzfield%ndimlist(1)  = tpfields(1)%ndimlist(3)
      tzfield%ndimlist(2)  = tpfields(1)%ndimlist(4)
      tzfield%ndimlist(3)  = tpfields(1)%ndimlist(5)
      tzfield%ndimlist(4:) = NMNHDIM_UNUSED

      allocate( zdata3d( size(pvar,3), size(pvar,4), size(pvar,5) ) )

      zdata3d(:,:,:) = pvar(1, 1, :, :, :, 1)

      TZFIELD%CMNHNAME   = tpfields(1)%cmnhname
      TZFIELD%CSTDNAME   = tpfields(1)%cstdname
      TZFIELD%CLONGNAME  = tpfields(1)%clongname
      TZFIELD%CUNITS     = tpfields(1)%cunits
      TZFIELD%CDIR       = '--'
      TZFIELD%CCOMMENT   = tpfields(1)%ccomment
      TZFIELD%NGRID      = tpfields(1)%ngrid
      TZFIELD%NTYPE      = tpfields(1)%ntype
      TZFIELD%NDIMS      = 3
      TZFIELD%LTIMEDEP   = .FALSE.
      if ( gsplit ) then
        !Create the metadata of the field (has to be done only once)
        if ( nbutshift == 1 ) call IO_Field_create( tzfile, tzfield )
        call IO_Field_write( tzfile, tzfield, zdata3d(:,:,:), koffset= [ 0, ( nbutshift - 1 ) * nbusubwrite, 0 ] )
      else
        call IO_Field_write( tzfile, tzfield, zdata3d )
      end if

      deallocate( zdata3d )
    else if (       tpfields(1)%ndimlist(3) == NMNHDIM_BUDGET_LES_LEVEL     &
       .and. (      tpfields(1)%ndimlist(4) == NMNHDIM_BUDGET_LES_TIME &
               .or. tpfields(1)%ndimlist(4) == NMNHDIM_BUDGET_LES_AVG_TIME ) &
       .and. tpfields(1)%ndimlist(6) == NMNHDIM_BUDGET_LES_MASK      ) then
      if ( gsplit ) then
          call Print_msg( NVERB_ERROR, 'IO', 'Write_diachro_nc4', Trim( tzfile%cname ) // &
                          ': group ' // Trim( hgroup ) //' gsplit=T not implemented' )
      end if

      if ( nles_masks /= Size( pvar, 6 ) ) &
        call Print_msg( NVERB_FATAL, 'IO', 'Write_diachro_nc4',                             &
                        'last dimension size of pvar is not equal to nles_masks (variable ' &
                        // Trim( tpfields(1)%cmnhname ) // ')' )

      tzfield%ndimlist(1)  = tpfields(1)%ndimlist(3)
      tzfield%ndimlist(2)  = tpfields(1)%ndimlist(4)
      tzfield%ndimlist(3:) = NMNHDIM_UNUSED

      allocate( zdata2d( size(pvar,3), size(pvar,4) ) )

      ! Loop on the masks (1 written variable per mask)
      do ji = 1, size(pvar,6)
        zdata2d(:,:) = pvar(1, 1, :, :, 1, ji)

        TZFIELD%CMNHNAME   = tpfields(ji)%cmnhname
        TZFIELD%CSTDNAME   = tpfields(ji)%cstdname
        TZFIELD%CLONGNAME  = tpfields(ji)%clongname
        TZFIELD%CUNITS     = tpfields(ji)%cunits
        TZFIELD%CDIR       = '--'
        TZFIELD%CCOMMENT   = tpfields(ji)%ccomment
        TZFIELD%NGRID      = tpfields(ji)%ngrid
        TZFIELD%NTYPE      = tpfields(ji)%ntype
        TZFIELD%NDIMS      = 2
        TZFIELD%LTIMEDEP   = .FALSE.
        CALL IO_Field_write( tzfile, tzfield, zdata2d )
      end do

      deallocate( zdata2d )
    else if (       tpfields(1)%ndimlist(3) == NMNHDIM_BUDGET_LES_LEVEL     &
       .and. (      tpfields(1)%ndimlist(4) == NMNHDIM_BUDGET_LES_TIME &
               .or. tpfields(1)%ndimlist(4) == NMNHDIM_BUDGET_LES_AVG_TIME ) &
       .and. tpfields(1)%ndimlist(6) == NMNHDIM_BUDGET_TERM      ) then
      if ( gsplit ) then
          call Print_msg( NVERB_ERROR, 'IO', 'Write_diachro_nc4', Trim( tzfile%cname ) // &
                          ': group ' // Trim( hgroup ) //' gsplit=T not implemented' )
      end if

      tzfield%ndimlist(1)  = tpfields(1)%ndimlist(3)
      tzfield%ndimlist(2)  = tpfields(1)%ndimlist(4)
      tzfield%ndimlist(3:) = NMNHDIM_UNUSED

      allocate( zdata2d( size(pvar,3), size(pvar,4) ) )

      ! Loop on the masks (1 written variable per mask)
      do ji = 1, size(pvar,6)
        zdata2d(:,:) = pvar(1, 1, :, :, 1, ji)

        TZFIELD%CMNHNAME   = tpfields(ji)%cmnhname
        TZFIELD%CSTDNAME   = tpfields(ji)%cstdname
        TZFIELD%CLONGNAME  = tpfields(ji)%clongname
        TZFIELD%CUNITS     = tpfields(ji)%cunits
        TZFIELD%CDIR       = '--'
        TZFIELD%CCOMMENT   = tpfields(ji)%ccomment
        TZFIELD%NGRID      = tpfields(ji)%ngrid
        TZFIELD%NTYPE      = tpfields(ji)%ntype
        TZFIELD%NDIMS      = 2
        TZFIELD%LTIMEDEP   = .FALSE.
        CALL IO_Field_write( tzfile, tzfield, zdata2d )
      end do

      deallocate( zdata2d )
    else if (       tpfields(1)%ndimlist(3) == NMNHDIM_BUDGET_LES_LEVEL     &
       .and. (      tpfields(1)%ndimlist(4) == NMNHDIM_BUDGET_LES_TIME &
               .or. tpfields(1)%ndimlist(4) == NMNHDIM_BUDGET_LES_AVG_TIME ) &
       .and. tpfields(1)%ndimlist(5) == NMNHDIM_BUDGET_LES_SV      ) then
      if ( gsplit ) then
          call Print_msg( NVERB_ERROR, 'IO', 'Write_diachro_nc4', Trim( tzfile%cname ) // &
                          ': group ' // Trim( hgroup ) //' gsplit=T not implemented' )
      end if

      if ( Size( tpfields ) /= 1 ) call Print_msg( NVERB_FATAL, 'IO', 'Write_diachro_nc4', &
                                                   'wrong size of tpfields (variable '//trim(tpfields(1)%cmnhname)//')' )

      !Correspond to Les_diachro_sv_new
      tzfield%ndimlist(1)  = tpfields(1)%ndimlist(3)
      tzfield%ndimlist(2)  = tpfields(1)%ndimlist(4)
      tzfield%ndimlist(3)  = tpfields(1)%ndimlist(5)
      tzfield%ndimlist(4:) = NMNHDIM_UNUSED

      allocate( zdata3d( size(pvar,3), size(pvar,4), size(pvar,5) ) )

      zdata3d(:,:,:) = pvar(1, 1, :, :, :, 1)

      TZFIELD%CMNHNAME   = tpfields(1)%cmnhname
      TZFIELD%CSTDNAME   = tpfields(1)%cstdname
      TZFIELD%CLONGNAME  = tpfields(1)%clongname
      TZFIELD%CUNITS     = tpfields(1)%cunits
      TZFIELD%CDIR       = '--'
      TZFIELD%CCOMMENT   = tpfields(1)%ccomment
      TZFIELD%NGRID      = tpfields(1)%ngrid
      TZFIELD%NTYPE      = tpfields(1)%ntype
      TZFIELD%NDIMS      = 3
      TZFIELD%LTIMEDEP   = .FALSE.
      CALL IO_Field_write( tzfile, tzfield, zdata3d )

      deallocate( zdata3d )
    else if (       tpfields(1)%ndimlist(1) == NMNHDIM_SPECTRA_2PTS_NI                   &
              .and. tpfields(1)%ndimlist(3) == NMNHDIM_SPECTRA_LEVEL                &
              .and. (      tpfields(1)%ndimlist(4) == NMNHDIM_BUDGET_LES_TIME       &
                      .or. tpfields(1)%ndimlist(4) == NMNHDIM_BUDGET_LES_AVG_TIME ) ) then
      if ( gsplit ) then
          call Print_msg( NVERB_ERROR, 'IO', 'Write_diachro_nc4', Trim( tzfile%cname ) // &
                          ': group ' // Trim( hgroup ) //' gsplit=T not implemented' )
      end if

      if ( Size( tpfields ) /= 1 ) call Print_msg( NVERB_FATAL, 'IO', 'Write_diachro_nc4', &
                                                   'wrong size of tpfields (variable '//trim(tpfields(1)%cmnhname)//')' )

      tzfield%ndimlist(1)  = tpfields(1)%ndimlist(1)
      tzfield%ndimlist(2)  = tpfields(1)%ndimlist(3)
      tzfield%ndimlist(3)  = tpfields(1)%ndimlist(4)
      tzfield%ndimlist(4:) = NMNHDIM_UNUSED

      allocate( zdata3d( size(pvar,1), size(pvar,3), size(pvar,4) ) )

      zdata3d(:,:,:) = pvar(:, 1, :, :, 1, 1)

      TZFIELD%CMNHNAME   = tpfields(1)%cmnhname
      TZFIELD%CSTDNAME   = tpfields(1)%cstdname
      TZFIELD%CLONGNAME  = tpfields(1)%clongname
      TZFIELD%CUNITS     = tpfields(1)%cunits
      TZFIELD%CDIR       = '--'
      TZFIELD%CCOMMENT   = tpfields(1)%ccomment
      TZFIELD%NGRID      = tpfields(1)%ngrid
      TZFIELD%NTYPE      = tpfields(1)%ntype
      TZFIELD%NDIMS      = 3
      TZFIELD%LTIMEDEP   = .FALSE.
      CALL IO_Field_write( tzfile, tzfield, zdata3d )

      deallocate( zdata3d )
    else if (       tpfields(1)%ndimlist(2) == NMNHDIM_SPECTRA_2PTS_NJ                   &
              .and. tpfields(1)%ndimlist(3) == NMNHDIM_SPECTRA_LEVEL                &
              .and. (      tpfields(1)%ndimlist(4) == NMNHDIM_BUDGET_LES_TIME       &
                      .or. tpfields(1)%ndimlist(4) == NMNHDIM_BUDGET_LES_AVG_TIME ) ) then
      if ( gsplit ) then
          call Print_msg( NVERB_ERROR, 'IO', 'Write_diachro_nc4', Trim( tzfile%cname ) // &
                          ': group ' // Trim( hgroup ) //' gsplit=T not implemented' )
      end if

      if ( Size( tpfields ) /= 1 ) call Print_msg( NVERB_FATAL, 'IO', 'Write_diachro_nc4', &
                                                   'wrong size of tpfields (variable '//trim(tpfields(1)%cmnhname)//')' )

      tzfield%ndimlist(1)  = tpfields(1)%ndimlist(2)
      tzfield%ndimlist(2)  = tpfields(1)%ndimlist(3)
      tzfield%ndimlist(3)  = tpfields(1)%ndimlist(4)
      tzfield%ndimlist(4:) = NMNHDIM_UNUSED

      allocate( zdata3d( size(pvar,2), size(pvar,3), size(pvar,4) ) )

      zdata3d(:,:,:) = pvar(1, :, :, :, 1, 1)

      TZFIELD%CMNHNAME   = tpfields(1)%cmnhname
      TZFIELD%CSTDNAME   = tpfields(1)%cstdname
      TZFIELD%CLONGNAME  = tpfields(1)%clongname
      TZFIELD%CUNITS     = tpfields(1)%cunits
      TZFIELD%CDIR       = '--'
      TZFIELD%CCOMMENT   = tpfields(1)%ccomment
      TZFIELD%NGRID      = tpfields(1)%ngrid
      TZFIELD%NTYPE      = tpfields(1)%ntype
      TZFIELD%NDIMS      = 3
      TZFIELD%LTIMEDEP   = .FALSE.
      CALL IO_Field_write( tzfile, tzfield, zdata3d )

      deallocate( zdata3d )
    else if (  tpfields(1)%ndimlist(3) == NMNHDIM_LEVEL      &
         .and. tpfields(1)%ndimlist(4) == NMNHDIM_FLYER_TIME &
         .and. tpfields(1)%ndimlist(6) == NMNHDIM_FLYER_PROC ) then
      !Correspond to FLYER_DIACHRO
      if ( gsplit ) then
          call Print_msg( NVERB_ERROR, 'IO', 'Write_diachro_nc4', Trim( tzfile%cname ) // &
                          ': group ' // Trim( hgroup ) //' gsplit=T not implemented' )
      end if

      !Create local time dimension
      if ( isp == tzfile%nmaster_rank) then
        istatus = NF90_DEF_DIM( igrpid, 'time_flyer', Size( pvar, 4), idimid )
        if ( istatus /= NF90_NOERR ) &
          call IO_Err_handle_nc4( istatus, 'Write_diachro_nc4', 'NF90_DEF_DIM', Trim( tpfields(1)%cmnhname ) )
      end if

      tzfield%ndimlist(1)  = tpfields(1)%ndimlist(3)
      tzfield%ndimlist(2)  = tpfields(1)%ndimlist(4)
      tzfield%ndimlist(3:) = NMNHDIM_UNUSED

      allocate( zdata2d( size(pvar,3), size(pvar,4) ) )

      ! Loop on the processes (1 written variable per process)
      do ji = 1, size(pvar,6)
        zdata2d(:, :) = pvar(1, 1, :, :, 1, ji)

        TZFIELD%CMNHNAME   = tpfields(ji)%cmnhname
        TZFIELD%CSTDNAME   = tpfields(ji)%cstdname
        TZFIELD%CLONGNAME  = tpfields(ji)%clongname
        TZFIELD%CUNITS     = tpfields(ji)%cunits
        TZFIELD%CDIR       = '--'
        TZFIELD%CCOMMENT   = tpfields(ji)%ccomment
        TZFIELD%NGRID      = tpfields(ji)%ngrid
        TZFIELD%NTYPE      = tpfields(ji)%ntype
        TZFIELD%NDIMS      = 2
        TZFIELD%LTIMEDEP   = .FALSE.
        CALL IO_Field_write( tzfile, tzfield, zdata2d )
      end do

      deallocate( zdata2d )
    else if (  tpfields(1)%ndimlist(3) == NMNHDIM_LEVEL      &
         .and. tpfields(1)%ndimlist(4) == NMNHDIM_PROFILER_TIME &