Skip to content
Snippets Groups Projects
write_diachro.f90 72.1 KiB
Newer Older
      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.
      CALL IO_Field_write( tzfile, tzfield, zdata2d )

      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 ) ) 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(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 (  (      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 ( 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

      !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

      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

      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)//')' )
    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 ( 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

      deallocate( zdata3d )
    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.
      CALL IO_Field_write( tzfile, tzfield, zdata3d )

      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 ( 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
      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 ( 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 ( 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 ( 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

      !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 &
         .and. tpfields(1)%ndimlist(6) == NMNHDIM_PROFILER_PROC ) then
      !Correspond to PROFILER_DIACHRO_n

      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_SERIES_LEVEL .or. tpfields(1)%ndimlist(3) == NMNHDIM_SERIES_LEVEL_W )      &
         .and. tpfields(1)%ndimlist(4) == NMNHDIM_SERIES_TIME &
         .and. tpfields(1)%ndimlist(6) == NMNHDIM_SERIES_PROC ) then
      !Correspond to PROFILER_DIACHRO_n

      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(1) == NMNHDIM_NI .or. tpfields(1)%ndimlist(1) == NMNHDIM_NI_U )      &
         .and. tpfields(1)%ndimlist(4) == NMNHDIM_SERIES_TIME &
         .and. tpfields(1)%ndimlist(6) == NMNHDIM_SERIES_PROC ) then
      !Correspond to PROFILER_DIACHRO_n

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

      allocate( zdata2d( size(pvar,1), 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
      call Print_msg( NVERB_FATAL, 'IO', 'Write_diachro_nc4', &
                      'case not yet implemented (variable '//trim(tpfields(1)%cmnhname)//')' )
    end if

  case (4)
    if (       ( 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_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_BUDGET_CART_LEVEL &
                  .or. tpfields(1)%ndimlist(3) == NMNHDIM_BUDGET_CART_LEVEL_W ) &
       .and. tpfields(1)%ndimlist(6) == NMNHDIM_BUDGET_NGROUPS      ) then
      !Correspond to Store_one_budget (CART)
      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) ) )

      ! Loop on the processes
      do ji = 1, size(pvar,6)
        zdata3d(:,:,:) = pvar(:, :, :, 1, 1, ji)

        TZFIELD%CMNHNAME   = tpfields(ji)%cmnhname
        TZFIELD%CSTDNAME   = tpfields(ji)%cstdname
        TZFIELD%CLONGNAME  = tpfields(ji)%clongname
        TZFIELD%CUNITS     = tpfields(ji)%cunits
        TZFIELD%CCOMMENT   = tpfields(ji)%ccomment
        TZFIELD%NGRID      = tpfields(ji)%ngrid
        TZFIELD%NTYPE      = tpfields(ji)%ntype
        TZFIELD%NDIMS      = 3
        TZFIELD%LTIMEDEP   = .FALSE.
        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
      end do

      deallocate( zdata3d )

    elseif (  ( 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 &
       .and. tpfields(1)%ndimlist(6) == NMNHDIM_BUDGET_NGROUPS      ) then
      !Correspond to Store_one_budget (MASK)
      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) ) )

      ! Loop on the processes
      do ji = 1, size(pvar,6)
        zdata3d(:,:,:) = pvar(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      = 3
        TZFIELD%LTIMEDEP   = .FALSE.
        CALL IO_Field_write( tzfile, tzfield, zdata3d )
      end do

      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(5) == NMNHDIM_BUDGET_LES_SV      &
       .and. tpfields(1)%ndimlist(6) == NMNHDIM_BUDGET_LES_MASK      ) then
      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)  = tpfields(1)%ndimlist(5)
      tzfield%ndimlist(4:) = NMNHDIM_UNUSED

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

      ! Loop on the masks (1 written variable per mask)
      do ji = 1, size(pvar,6)
        zdata3d(:,:,:) = pvar(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      = 3
        TZFIELD%LTIMEDEP   = .FALSE.
        CALL IO_Field_write( tzfile, tzfield, zdata3d )
      end do

      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(5) == NMNHDIM_BUDGET_LES_SV      &
       .and. tpfields(1)%ndimlist(6) == NMNHDIM_BUDGET_TERM      ) then
      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) ) )

      ! Loop on the masks (1 written variable per mask)
      do ji = 1, size(pvar,6)
        zdata3d(:,:,:) = pvar(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      = 3
        TZFIELD%LTIMEDEP   = .FALSE.
        CALL IO_Field_write( tzfile, tzfield, zdata3d )
      end do

      deallocate( zdata3d )
    else if (       tpfields(1)%ndimlist(1) == NMNHDIM_SPECTRA_SPEC_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 ) &
       .and. tpfields(1)%ndimlist(5) == NMNHDIM_COMPLEX      ) then
      !Correspond to LES_DIACHRO_SPEC
      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)  = tpfields(1)%ndimlist(5)
      tzfield%ndimlist(5:) = NMNHDIM_UNUSED

      allocate( zdata4d( size(pvar,1), size(pvar,3), size(pvar,4), size(pvar,5) ) )

      zdata4d(:,:,:,:) = pvar(:, 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      = 4
      TZFIELD%LTIMEDEP   = .FALSE.
      CALL IO_Field_write( tzfile, tzfield, zdata4d )

      deallocate( zdata4d )
    else if (       tpfields(1)%ndimlist(2) == NMNHDIM_SPECTRA_SPEC_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 ) &
       .and. tpfields(1)%ndimlist(5) == NMNHDIM_COMPLEX      ) then
      !Correspond to LES_DIACHRO_SPEC
      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)  = tpfields(1)%ndimlist(5)
      tzfield%ndimlist(5:) = NMNHDIM_UNUSED

      allocate( zdata4d( size(pvar,2), size(pvar,3), size(pvar,4), size(pvar,5) ) )

      zdata4d(:,:,:,:) = pvar(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      = 4
      TZFIELD%LTIMEDEP   = .FALSE.
      CALL IO_Field_write( tzfile, tzfield, zdata4d )

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

!   case (5)

!   case (6)

  case default
    if ( All( tpfields(1)%ndimlist(:) /= NMNHDIM_UNKNOWN ) ) then
      tzfield%ndimlist(1)  = tpfields(1)%ndimlist(1)
      tzfield%ndimlist(2)  = tpfields(1)%ndimlist(2)
      tzfield%ndimlist(3)  = tpfields(1)%ndimlist(3)
      tzfield%ndimlist(4)  = tpfields(1)%ndimlist(4)
      tzfield%ndimlist(5)  = tpfields(1)%ndimlist(5)
      tzfield%ndimlist(6:) = NMNHDIM_UNUSED
    end if

    do ji = 1, Size( pvar, 6 )
      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      = 5
      TZFIELD%LTIMEDEP   = .FALSE.
      CALL IO_Field_write( tzfile, tzfield, pvar(:, :, :, :, :, ji ) )
    end do
end select

!Reset ndimlist (to prevent problems later)
tzfield%ndimlist(:) = NMNHDIM_UNKNOWN

TZFIELD%CMNHNAME   = 'dates'
TZFIELD%CSTDNAME   = ''
TZFIELD%CLONGNAME  = 'dates'
TZFIELD%CUNITS     = 'seconds since YYYY-MM-DD HH:MM:SS.S'
TZFIELD%CDIR       = '--'
TZFIELD%CCOMMENT   = 'Dates at the middle of the budget timesteps'
TZFIELD%NGRID      = 0
TZFIELD%NTYPE      = TYPEDATE
TZFIELD%NDIMS      = 1
TZFIELD%LTIMEDEP   = .FALSE.

if ( tpfields(1)%ndimlist(4) /= NMNHDIM_UNKNOWN .and. tpfields(1)%ndimlist(4) /= NMNHDIM_UNUSED) then
  tzfield%ndimlist(1) = tpfields(1)%ndimlist(4)
  tzfield%ndimlist(2:) = NMNHDIM_UNUSED
end if

CALL IO_Field_write( tzfile, tzfield, tpdates(:) )

!Reset ndimlist
tzfield%ndimlist(:) = NMNHDIM_UNKNOWN


!Restore id of the file root group ('/' group)
tzfile%nncid = isavencid

end  subroutine Write_diachro_nc4
#endif