Skip to content

Commit

Permalink
working version of nf_def_decomp
Browse files Browse the repository at this point in the history
  • Loading branch information
edhartnett committed Jul 19, 2019
1 parent fc4d65e commit fcf2f7d
Show file tree
Hide file tree
Showing 4 changed files with 50 additions and 42 deletions.
78 changes: 42 additions & 36 deletions src/flib/ncint_mod.F90
Original file line number Diff line number Diff line change
Expand Up @@ -15,12 +15,10 @@
module ncint_mod
use iso_c_binding
use pio_kinds
use pio_types, only : file_desc_t, iosystem_desc_t, var_desc_t, io_desc_t, &
pio_iotype_netcdf, pio_iotype_pnetcdf, pio_iotype_netcdf4p, pio_iotype_netcdf4c, &
pio_noerr, pio_rearr_subset, pio_rearr_opt_t
use pio_types
use pio_support, only : piodie, debug, debugio, debugasync, checkmpireturn
use pio_nf, only : pio_set_log_level
use piolib_mod, only : pio_init, pio_finalize
use piolib_mod, only : pio_init, pio_finalize, pio_initdecomp

#ifndef NO_MPIMOD
use mpi ! _EXTERNAL
Expand All @@ -31,7 +29,7 @@ module ncint_mod
include 'mpif.h' ! _EXTERNAL
#endif

public :: nf_def_iosystem, nf_free_iosystem, nf_free_decomp
public :: nf_def_iosystem, nf_free_iosystem, nf_def_decomp, nf_free_decomp

contains

Expand Down Expand Up @@ -150,36 +148,44 @@ end function nc_free_decomp
status = ierr
end function nf_free_decomp

! !>
! !! @public
! !! @ingroup ncint
! !! Implements the block-cyclic decomposition for PIO_initdecomp.
! !! This provides the ability to describe a computational
! !! decomposition in PIO that has a block-cyclic form. That is
! !! something that can be described using start and count arrays.
! !! Optional parameters for this subroutine allows for the
! !! specification of io decomposition using iostart and iocount
! !! arrays. If iostart and iocount arrays are not specified by the
! !! user, and rearrangement is turned on then PIO will calculate a
! !! suitable IO decomposition
! !!
! !! @param iosystem @copydoc iosystem_desc_t
! !! @param basepiotype @copydoc use_PIO_kinds
! !! @param dims An array of the global length of each dimesion of the
! !! variable(s)
! !! @param compstart The start index into the block-cyclic
! !! computational decomposition
! !! @param compcount The count for the block-cyclic computational
! !! decomposition
! !! @param iodesc @copydoc iodesc_generate
! !! @author Jim Edwards
! !<
! function nf_init_decomp(iosystem,basepiotype,dims,compstart,compcount,iodesc)
! type (iosystem_desc_t), intent(inout) :: iosystem
! integer(i4), intent(in) :: basepiotype
! integer(i4), intent(in) :: dims(:)
! integer (kind=PIO_OFFSET_KIND) :: compstart(:)
! integer (kind=PIO_OFFSET_KIND) :: compcount(:)
! type (IO_desc_t), intent(out) :: iodesc
!>
!! @public
!! @ingroup ncint
!! Implements the block-cyclic decomposition for PIO_initdecomp.
!! This provides the ability to describe a computational
!! decomposition in PIO that has a block-cyclic form. That is
!! something that can be described using start and count arrays.
!! Optional parameters for this subroutine allows for the
!! specification of io decomposition using iostart and iocount
!! arrays. If iostart and iocount arrays are not specified by the
!! user, and rearrangement is turned on then PIO will calculate a
!! suitable IO decomposition
!!
!! @param iosystem @copydoc iosystem_desc_t
!! @param basepiotype @copydoc use_PIO_kinds
!! @param dims An array of the global length of each dimesion of the
!! variable(s)
!! @param compstart The start index into the block-cyclic
!! computational decomposition
!! @param compcount The count for the block-cyclic computational
!! decomposition
!! @param iodesc @copydoc iodesc_generate
!! @author Jim Edwards
!<
function nf_def_decomp(iosystem, basepiotype, dims, compdof, &
iodesc, rearr, iostart, iocount) result(status)
type (iosystem_desc_t), intent(in) :: iosystem
integer(i4), intent(in) :: basepiotype
integer(i4), intent(in) :: dims(:)
integer (PIO_OFFSET_KIND), intent(in) :: compdof(:)
integer, optional, target :: rearr
integer (PIO_OFFSET_KIND), optional :: iostart(:), iocount(:)
type (io_desc_t), intent(inout) :: iodesc
integer :: status

call PIO_initdecomp(iosystem, basepiotype, dims, compdof, &
iodesc, rearr, iostart, iocount)
status = 0
end function nf_def_decomp

end module ncint_mod
3 changes: 2 additions & 1 deletion src/flib/pio.F90
Original file line number Diff line number Diff line change
Expand Up @@ -25,7 +25,8 @@ module pio
pio_set_rearr_opts

#ifdef NETCDF_INTEGRATION
use ncint_mod, only: nf_def_iosystem, nf_free_iosystem, nf_free_decomp
use ncint_mod, only: nf_def_iosystem, nf_free_iosystem, &
nf_def_decomp, nf_free_decomp
#endif

use pio_types, only : io_desc_t, file_desc_t, var_desc_t, iosystem_desc_t, &
Expand Down
6 changes: 4 additions & 2 deletions src/flib/piolib_mod.F90
Original file line number Diff line number Diff line change
Expand Up @@ -879,7 +879,8 @@ end subroutine PIO_initdecomp_internal
!! @ingroup PIO_initdecomp
!! I8 version of PIO_initdecomp_dof_i4.
!! @author Jim Edwards
subroutine PIO_initdecomp_dof_i8(iosystem,basepiotype,dims,compdof, iodesc, rearr, iostart, iocount)
subroutine PIO_initdecomp_dof_i8(iosystem, basepiotype, dims, compdof, &
iodesc, rearr, iostart, iocount)
type (iosystem_desc_t), intent(in) :: iosystem
integer(i4), intent(in) :: basepiotype
integer(i4), intent(in) :: dims(:)
Expand All @@ -895,7 +896,8 @@ subroutine PIO_initdecomp_dof_i8(iosystem,basepiotype,dims,compdof, iodesc, rear

maplen = size(compdof)

call PIO_initdecomp_internal(iosystem, basepiotype, dims, maplen, compdof, iodesc, rearr, iostart,iocount)
call PIO_initdecomp_internal(iosystem, basepiotype, dims, maplen, &
compdof, iodesc, rearr, iostart, iocount)

#ifdef TIMING
call t_stopf("PIO:initdecomp_dof")
Expand Down
5 changes: 2 additions & 3 deletions tests/fncint/ftst_pio.f90
Original file line number Diff line number Diff line change
Expand Up @@ -13,7 +13,7 @@ program ftst_pio
integer :: ncid
character*(*) FILE_NAME
parameter (FILE_NAME='ftst_pio.nc')
integer, dimension(3) :: data_buffer, compdof
integer(kind=PIO_OFFSET_KIND), dimension(3) :: data_buffer, compdof
integer, dimension(1) :: dims
type(io_desc_t) :: iodesc
integer :: decompid
Expand All @@ -35,7 +35,7 @@ program ftst_pio
! Define a decomposition.
dims(1) = 3 * ntasks
compdof = 3 * myRank + (/1, 2, 3/) ! Where in the global array each task writes
call PIO_initdecomp(ioSystem, PIO_int, dims, compdof, iodesc)
ierr = nf_def_decomp(ioSystem, PIO_int, dims, compdof, iodesc)
decompid = iodesc%ioid

! Create a file.
Expand All @@ -48,7 +48,6 @@ program ftst_pio

! Free resources.
ierr = nf_free_decomp(decompid)
! call PIO_freedecomp(ioSystem, iodesc_nCells)
ierr = nf_free_iosystem()

! We're done!
Expand Down

0 comments on commit fcf2f7d

Please sign in to comment.