Reputation: 69
I'm trying to modify a Fortran 90 code which writes a 2D array to the output in a NetCDF classic format. I would like the variable to have an extra dimension for time (i.e., it will be a 3D variable), printing it every corresponding time step during integration time of the model.
I'm not sure how it is being done; I appreciate any suggestion for doing it as efficiently as possible (also in a minimum file size).
subroutine writenetcdffile(array,argtitle)
use netcdf
implicit none
real, intent(IN), dimension(:,:) :: array
character*(*),intent(IN) :: argtitle
integer :: file_id, xdim_id, ydim_id
integer :: array_id
integer, dimension(2) :: arrdims
! character(len=*) :: argtitle = Flag_in
integer :: i, j
integer :: ierr
i = size(array,1)
j = size(array,2)
! create the file
ierr = nf90_create(path='test.nc', cmode=NF90_CLOBBER, ncid=file_id)
! define the dimensions
ierr = nf90_def_dim(file_id, 'X', i, xdim_id)
ierr = nf90_def_dim(file_id, 'Y', j, ydim_id)
! now that the dimensions are defined, we can define variables on them,...
arrdims = (/ xdim_id, ydim_id /)
ierr = nf90_def_var(file_id, 'Array', NF90_REAL, arrdims, array_id)
! ...and assign units to them as an attribute
ierr = nf90_put_att(file_id, array_id, "title", argtitle)
! done defining
ierr = nf90_enddef(file_id)
! Write out the values
ierr = nf90_put_var(file_id, array_id, array)
! close; done
ierr = nf90_close(file_id)
return
end subroutine writenetcdffile
MODULE Module_NetCDF
use netcdf
IMPLICIT NONE
integer :: file_id, xdim_id, ydim_id, tdim_id
integer :: array_id(5)
integer, dimension(3) :: arrdims
integer :: i, j
integer :: ierr
CONTAINS
SUBROUTINE NetCDF_Init(ICase)
IMPLICIT NONE
INTEGER :: ICase
SELECT CASE(ICase)
Case(1)
! create the file
ierr = nf90_create(path='test.nc', cmode = NF90_CLOBBER, ncid = file_id)
Case(2)
! Reopen the file for writing
ierr = nf90_open(path = "test.nc", mode = nf90_write, ncid = file_id)
if (ierr /= nf90_noerr) call check(ierr)
Case(3)
! close; done
ierr = nf90_close(file_id)
END SELECT
RETURN
END SUBROUTINE NetCDF_Init
SUBROUTINE NetCDF_Def(Array,ArrayTitle,ArrayUnits)
IMPLICIT NONE
real, intent(IN), dimension(:,:) :: Array
character(*),intent(IN) :: ArrayTitle(5)
character(*),intent(IN) :: ArrayUnits(5)
! Locals
integer :: k
i = size(Array,1)
j = size(Array,2)
! CALL NetCDF_Init(1)
! define the dimensions
ierr = nf90_def_dim(file_id, 'X', i, xdim_id)
ierr = nf90_def_dim(file_id, 'Y', j, ydim_id)
ierr = nf90_def_dim(file_id, 'Time', nf90_unlimited, tdim_id)
! now that the dimensions are defined, we can define variables on them,...
arrdims = (/ xdim_id, ydim_id, tdim_id /)
do k = 1,size(ArrayTitle)
ierr = nf90_def_var(file_id, ArrayTitle(k), NF90_REAL, arrdims, array_id(k))
! ...and assign units to them as an attribute
ierr = nf90_put_att(file_id, array_id(k), "Units", ArrayUnits(k))
enddo
! done defining
ierr = nf90_enddef(file_id)
RETURN
END SUBROUTINE NetCDF_Def
SUBROUTINE NetCDF_Write(Array,FlagTitle,NTime)
IMPLICIT NONE
real, intent(IN), dimension(:,:) :: Array
integer,intent(IN) :: NTime
character(*),intent(in) :: FlagTitle
! Locals
integer :: J_id
IF(FlagTitle.EQ.'ONECOND')THEN
J_id = 1
ELSEIF(FlagTitle.EQ.'MELTING')THEN
J_id = 2
ELSEIF(FlagTitle.EQ.'FREEZ_NEW')THEN
J_id = 3
ELSEIF(FlagTitle.EQ.'TFREEZ')THEN
J_id = 4
ELSEIF(FlagTitle.EQ.'DFREEZ')THEN
J_id = 5
ENDIF
CALL NetCDF_Init(2)
ierr = nf90_put_var(file_id, array_id(j_id), Array, start=[1,1,ntime], count=[i,j,1])
CALL NetCDF_Init(3)
RETURN
END SUBROUTINE
SUBROUTINE check(status)
IMPLICIT NONE
integer, intent ( in) :: status
IF(status /= nf90_noerr) THEN
PRINT *, trim(nf90_strerror(status))
STOP 2
ENDIF
END SUBROUTINE check
END MODULE Module_NetCDF
Upvotes: 1
Views: 1425
Reputation: 6241
What you need to do is define the time dimension of nf90_unlimited
length. This will allow you to write a 2-d array one slice at a time into a 3-d array, and makes the length of this array unspecified. Use start
and count
optional dummy arguments to a nf90_put_var
call to specify where to write the 2-d slice.
! create the file
ierr = nf90_create(path='test.nc', cmode=NF90_CLOBBER, ncid=file_id)
! define the dimensions
ierr = nf90_def_dim(file_id, 'X', i, xdim_id)
ierr = nf90_def_dim(file_id, 'Y', j, ydim_id)
ierr = nf90_def_dim(file_id, 'Time', nf90_unlimited, tdim_id)
! now that the dimensions are defined, we can define variables on them,...
arrdims = (/ xdim_id, ydim_id, tdim_id /)
ierr = nf90_def_var(file_id, 'Array', NF90_REAL, arrdims, array_id)
! done defining
ierr = nf90_enddef(file_id)
! Time loop
do n = 1,nm
! Calculations go here
! Write out the values
ierr = nf90_put_var(file_id, array_id, array, start=[1,1,n], count=[i,j,1])
enddo
What I do in most of my programs is create the file and define dimensions and variables at the beginning, and write the fields in a loop afterward. If your simulations take a long time and you want to be able to look at the output during the simulation in progress, do the open/write/close steps inside of the model solver do-loop.
Upvotes: 3