Hi, there,
I am trying to create a NetCDF4 file with parallel-enabled using the subroutine 
attached below,
and got the error message:
Start: file:test_netcdf4_write.F90  line:    34
Create parallel netcdf4 file: <test_par_necdf4.nc> successfully.
ncid:  65536
Problem to enddef ncid:  65536
Error status: NetCDF: HDF error
file: <test_netcdf4_write.F90>, line:   84
FORTRAN STOP
The problem is with line:
   status = nf90_enddef(ncid)
Anyone knows why?
Thanks,
Wei
huangwei@xxxxxxxx
VETS/CISL
National Center for Atmospheric Research
P.O. Box 3000 (1850 Table Mesa Dr.)
Boulder, CO 80307-3000 USA
(303) 497-8924
----------
SUBROUTINE test_netcdf4_write(nyds, nyde, nxds, nxde, nzds, nzde, &
                              nyms, nyme, nxms, nxme, nzms, nzme, &
                              nyts, nyte, nxts, nxte, nzts, nzte)
   use dmp_util_module
   use netcdf
   implicit none
   integer,intent(in) :: nyds, nyde, nxds, nxde, nzds, nzde, &
                         nyms, nyme, nxms, nxme, nzms, nzme, &
                         nyts, nyte, nxts, nxte, nzts, nzte
   integer :: it, ncid, status, nc_mode
   real, dimension(nyms:nyme, nxms:nxme, nzms:nzme) :: v3d
   character(len=128) :: output_flnm
   integer, dimension(6) :: dimids
   integer :: dimid_nx, dimid_ny, dimid_nz, dimid_nt
   real, parameter :: missing_real = -999.0
   write(unit=0, fmt='(2a,2x,a,i6)') &
        'Start: file:', __FILE__, 'line:', __LINE__
   output_flnm = "test_par_necdf4.nc"
 ! Create the file.
   status = nf90_create(output_flnm, NF90_NETCDF4, ncid, &
                        comm = MPI_COMM_WORLD, &
                        info = MPI_INFO_NULL)
   if(status /= nf90_noerr) then
      write(unit=0, fmt='(3a)') "Problem to create: <", trim(output_flnm), ">."
      write(unit=0, fmt='(2a)') "Error status: ", trim(nf90_strerror(status))
      write(unit=0, fmt='(3a, i4)') &
           "Stop in file: <", __FILE__, ">, line: ", __LINE__
      stop
   else
      write(unit=0, fmt='(3a)') &
           "Create parallel netcdf4 file: <", trim(output_flnm), "> 
successfully."
      write(unit=0, fmt='(a, i6)') &
           "ncid: ", ncid
   endif
 ! Define the dimensions. The record dimension is defined to have
 ! unlimited length - it can grow as needed. In this example it is
 ! the time dimension.
   call nc_write_dimInfo(ncid, "NX", nxde - nxds + 1, dimid_nx)
   call nc_write_dimInfo(ncid, "NY", nyde - nyds + 1, dimid_ny)
   call nc_write_dimInfo(ncid, "NZ", nzde - nzds + 1, dimid_nz)
   call nc_write_dimInfo(ncid, "NT", nf90_unlimited,  dimid_nt)
   call nc_putGlobalIntAttr(ncid, "NX", nxde - nxds + 1)
   call nc_putGlobalIntAttr(ncid, "NY", nyde - nyds + 1)
   call nc_putGlobalIntAttr(ncid, "NZ", nzde - nzds + 1)
 ! call nc_putGlobalIntAttr(ncid, "NT", nf90_unlimited)
   dimids(1) = dimid_nx
   dimids(2) = dimid_ny
   dimids(3) = dimid_nz
   dimids(4) = dimid_nt
   it = 3
   call nc_putAttr(ncid, it, dimids, &
                   "V3D", &
                   "LONG_NAME", &
                   "UNIT", &
                   missing_real)
!--End define mode.
   status = nf90_enddef(ncid)
   if(status /= nf90_noerr) then
      write(unit=0, fmt='(a,i6)') "Problem to enddef ncid: ", ncid
      write(unit=0, fmt='(2a)') "Error status: ", trim(nf90_strerror(status))
      write(unit=0, fmt='(3a, i4)') "file: <", __FILE__, ">, line: ", __LINE__
      stop
   end if
   it = 1
   write(unit=0, fmt='(a,i6)') &
     'write it:', it
   call gen_3d_float(v3d, it, &
                     nyms, nyme, nxms, nxme, nzms, nzme, &
                     nyts, nyte, nxts, nxte, nzts, nzte)
   call write_3d_field(ncid, "V3D", v3d, it, &
                       nyds, nyde, nxds, nxde, nzds, nzde, &
                       nyms, nyme, nxms, nxme, nzms, nzme, &
                       nyts, nyte, nxts, nxte, nzts, nzte)
   !--Close the file. This frees up any internal netCDF resources
   !--associated with the file.
   status =  nf90_close(ncid)
   if(status /= nf90_noerr) then
      write(unit=0, fmt='(a,i6)') "Problem to close ncid: ", ncid
      write(unit=0, fmt='(2a)') "Error status: ", trim(nf90_strerror(status))
      write(unit=0, fmt='(3a, i4)') "file: <", __FILE__, ">, line: ", __LINE__
      stop
   end if
   write(unit=0, fmt='(2a)') "End of: ", __FILE__
END SUBROUTINE test_netcdf4_write