Skip to content

Commit

Permalink
Review comments and no-1d chunking
Browse files Browse the repository at this point in the history
  • Loading branch information
anton-seaice committed Jan 31, 2024
1 parent c66a119 commit 4829247
Show file tree
Hide file tree
Showing 7 changed files with 262 additions and 223 deletions.
8 changes: 3 additions & 5 deletions cicecore/cicedyn/analysis/ice_history_shared.F90
Original file line number Diff line number Diff line change
Expand Up @@ -62,11 +62,9 @@ module ice_history_shared
integer (kind=int_kind), public :: &
history_iotasks , & ! iotasks, root, stride defines io pes for pio
history_root , & ! iotasks, root, stride defines io pes for pio
history_stride ! iotasks, root, stride defines io pes for pio

integer (kind=int_kind), public :: history_deflate ! compression level for netcdf4

integer (kind=int_kind), dimension(2), public :: history_chunksize ! chunksize for netcdf4
history_stride , & ! iotasks, root, stride defines io pes for pio
history_deflate , & ! compression level for hdf5/netcdf4
history_chunksize(2) ! chunksize for hdf5/netcdf4

!---------------------------------------------------------------
! Instructions for adding a field: (search for 'example')
Expand Down
47 changes: 19 additions & 28 deletions cicecore/cicedyn/general/ice_init.F90
Original file line number Diff line number Diff line change
Expand Up @@ -350,7 +350,7 @@ subroutine input_data
history_file = 'iceh' ! history file name prefix
history_precision = 4 ! precision of history files
history_deflate = 0 ! compression level for netcdf4
history_chunksize = (/0,0/) ! chunksize for netcdf4
history_chunksize(:) = 0 ! chunksize for netcdf4
write_ic = .false. ! write out initial condition
cpl_bgc = .false. ! couple bgc thru driver
incond_dir = history_dir ! write to history dir for default
Expand All @@ -372,7 +372,7 @@ subroutine input_data
restart_iotasks = -99 ! restart iotasks, root, stride sets pes for pio
restart_rearranger = 'default' ! restart rearranger for pio
restart_deflate = 0 ! compression level for netcdf4
restart_chunksize = (/0,0/) ! chunksize for netcdf4
restart_chunksize(:) = 0 ! chunksize for netcdf4
lcdf64 = .false. ! 64 bit offset for netCDF
ice_ic = 'default' ! latitude and sst-dependent
grid_format = 'bin' ! file format ('bin'=binary or 'nc'=netcdf)
Expand Down Expand Up @@ -953,8 +953,7 @@ subroutine input_data
call broadcast_scalar(history_rearranger, master_task)
call broadcast_scalar(hist_time_axis, master_task)
call broadcast_scalar(history_deflate, master_task)
call broadcast_scalar(history_chunksize(1), master_task)
call broadcast_scalar(history_chunksize(2), master_task)
call broadcast_array(history_chunksize, master_task)
call broadcast_scalar(write_ic, master_task)
call broadcast_scalar(cpl_bgc, master_task)
call broadcast_scalar(incond_dir, master_task)
Expand All @@ -972,8 +971,7 @@ subroutine input_data
call broadcast_scalar(restart_stride, master_task)
call broadcast_scalar(restart_rearranger, master_task)
call broadcast_scalar(restart_deflate, master_task)
call broadcast_scalar(restart_chunksize(1), master_task)
call broadcast_scalar(restart_chunksize(2), master_task)
call broadcast_array(restart_chunksize, master_task)
call broadcast_scalar(lcdf64, master_task)
call broadcast_scalar(pointer_file, master_task)
call broadcast_scalar(ice_ic, master_task)
Expand Down Expand Up @@ -1769,34 +1767,17 @@ subroutine input_data
if (history_deflate/=0 .or. restart_deflate/=0 &
.or. history_chunksize(1)/=0 .or. history_chunksize(2)/=0 &
.or. restart_chunksize(1)/=0 .or. restart_chunksize(2)/=0) then
if (my_task == master_task) then
write (nu_diag,*) subname//' WARNING: _deflate and _chunksize not compatible with PIO1, will be ignored'
endif
#else
if(history_deflate<0 .or. history_deflate>9) then
if (my_task == master_task) then
write (nu_diag,*) subname//' WARNING: history_deflate value not valid, setting to 0 '
write (nu_diag,*) subname//' WARNING: Allowed range: integers from 0 to 9 '
endif
history_deflate=0
endif

if(restart_deflate<0 .or. restart_deflate>9) then
if (my_task == master_task) then
write (nu_diag,*) subname//' WARNING: restart_deflate value not valid, setting to 0 '
write (nu_diag,*) subname//' WARNING: Allowed range: integers from 0 to 9 '
endif
restart_deflate=0
if (my_task == master_task) write (nu_diag,*) subname//' ERROR: _deflate and _chunksize not compatible with PIO1'
abort_list = trim(abort_list)//":54"
endif

#else
#ifndef CESMCOUPLED
! history_format not used by nuopc driver
if (history_format/='hdf5' .and. history_deflate/=0) then
if (my_task == master_task) then
write (nu_diag,*) subname//' WARNING: history_deflate not compatible with '//history_format
write (nu_diag,*) subname//' WARNING: netcdf compression only possible with history_type="hdf5" '
endif
history_deflate=0
endif

if (history_format/='hdf5' .and. (history_chunksize(1)/=0 .or. history_chunksize(2)/=0)) then
Expand All @@ -1811,7 +1792,6 @@ subroutine input_data
write (nu_diag,*) subname//' WARNING: restart_deflate not compatible with '//restart_format
write (nu_diag,*) subname//' WARNING: netcdf compression only possible with restart_type="hdf5" '
endif
restart_deflate=0
endif

if (restart_format/='hdf5' .and. (restart_chunksize(1)/=0 .or. restart_chunksize(2)/=0)) then
Expand All @@ -1820,8 +1800,19 @@ subroutine input_data
write (nu_diag,*) subname//' WARNING: netcdf chunking only possible with restart_type="hdf5" '
endif
endif

#endif

if(history_deflate<0 .or. history_deflate>9) then
if (my_task == master_task) write (nu_diag,*) subname//&
' ERROR: history_deflate value not valid. Allowed range: integers from 0 to 9 '
abort_list = trim(abort_list)//":55"
endif

if(restart_deflate<0 .or. restart_deflate>9) then
if (my_task == master_task) write (nu_diag,*) subname//&
' ERROR: restart_deflate value not valid. Allowed range: integers from 0 to 9 '
abort_list = trim(abort_list)//":56"
endif
#endif

! Implicit solver input validation
Expand Down
106 changes: 68 additions & 38 deletions cicecore/cicedyn/infrastructure/io/io_netcdf/ice_history_write.F90
Original file line number Diff line number Diff line change
Expand Up @@ -45,6 +45,8 @@ module ice_history_write

public :: ice_write_hist

integer (kind=int_kind) :: imtid,jmtid

!=======================================================================

contains
Expand Down Expand Up @@ -90,7 +92,7 @@ subroutine ice_write_hist (ns)
real (kind=dbl_kind), dimension(nx_block,ny_block,max_blocks) :: work1

integer (kind=int_kind) :: i,k,ic,n,nn, &
ncid,status,imtid,jmtid,kmtidi,kmtids,kmtidb, cmtid,timid,varid, &
ncid,status,kmtidi,kmtids,kmtidb, cmtid,timid,varid, &
nvertexid,ivertex,kmtida,iflag, fmtid
integer (kind=int_kind), dimension(3) :: dimid
integer (kind=int_kind), dimension(4) :: dimidz
Expand Down Expand Up @@ -454,9 +456,9 @@ subroutine ice_write_hist (ns)
endif
enddo

!-----------------------------------------------------------------
! define attributes for time-variant variables
!-----------------------------------------------------------------
!-----------------------------------------------------------------
! define attributes for time-variant variables
!-----------------------------------------------------------------

do n=1,num_avail_hist_fields_2D
if (avail_hist_fields(n)%vhistfreq == histfreq(ns) .or. write_ic) then
Expand All @@ -475,31 +477,43 @@ subroutine ice_write_hist (ns)
endif
enddo ! num_avail_hist_fields_3Dc

dimidz(1) = imtid
dimidz(2) = jmtid
dimidz(3) = kmtidi
dimidz(4) = timid

do n = n3Dccum + 1, n3Dzcum
if (avail_hist_fields(n)%vhistfreq == histfreq(ns) .or. write_ic) then
call ice_hist_field_def(ncid, avail_hist_fields(n),lprecision, dimidz,ns)
endif
enddo ! num_avail_hist_fields_3Dz

dimidz(1) = imtid
dimidz(2) = jmtid
dimidz(3) = kmtidb
dimidz(4) = timid

do n = n3Dzcum + 1, n3Dbcum
if (avail_hist_fields(n)%vhistfreq == histfreq(ns) .or. write_ic) then
call ice_hist_field_def(ncid, avail_hist_fields(n),lprecision, dimidz,ns)
endif
enddo ! num_avail_hist_fields_3Db

dimidz(1) = imtid
dimidz(2) = jmtid
dimidz(3) = kmtida
dimidz(4) = timid

do n = n3Dbcum + 1, n3Dacum
if (avail_hist_fields(n)%vhistfreq == histfreq(ns) .or. write_ic) then
call ice_hist_field_def(ncid, avail_hist_fields(n),lprecision, dimidz,ns)
endif
enddo ! num_avail_hist_fields_3Da

dimidz(1) = imtid
dimidz(2) = jmtid
dimidz(3) = fmtid
dimidz(4) = timid

do n = n3Dacum + 1, n3Dfcum
if (avail_hist_fields(n)%vhistfreq == histfreq(ns) .or. write_ic) then
Expand All @@ -519,15 +533,23 @@ subroutine ice_write_hist (ns)
endif
enddo ! num_avail_hist_fields_4Di

dimidcz(1) = imtid
dimidcz(2) = jmtid
dimidcz(3) = kmtids
dimidcz(4) = cmtid
dimidcz(5) = timid

do n = n4Dicum + 1, n4Dscum
if (avail_hist_fields(n)%vhistfreq == histfreq(ns) .or. write_ic) then
call ice_hist_field_def(ncid, avail_hist_fields(n),lprecision, dimidcz,ns)
endif
enddo ! num_avail_hist_fields_4Ds

dimidcz(1) = imtid
dimidcz(2) = jmtid
dimidcz(3) = fmtid
dimidcz(4) = cmtid
dimidcz(5) = timid

do n = n4Dscum + 1, n4Dfcum
if (avail_hist_fields(n)%vhistfreq == histfreq(ns) .or. write_ic) then
Expand Down Expand Up @@ -1155,7 +1177,7 @@ subroutine ice_hist_field_def(ncid, hfield, lprecision, dimids, ns)
history_precision, hist_avg
use ice_calendar, only: histfreq, histfreq_n, write_ic
#ifdef USE_NETCDF
use netcdf, only: NF90_CHUNKED, nf90_def_var, nf90_put_att
use netcdf, only: NF90_CHUNKED, nf90_def_var, nf90_put_att, nf90_def_var_chunking, nf90_def_var_deflate

integer(kind=int_kind), intent(in) :: ncid, dimids(:), lprecision, ns
type(ice_hist_field), intent(in) :: hfield
Expand All @@ -1164,24 +1186,25 @@ subroutine ice_hist_field_def(ncid, hfield, lprecision, dimids, ns)
integer(kind=int_kind) :: chunks(size(dimids)), i, status, varid

character(len=*), parameter :: subname = '(ice_hist_field_def)'

if (history_format=='hdf5') then
chunks(1)=history_chunksize(1)
chunks(2)=history_chunksize(2)
do i = 3, size(dimids)
chunks(i) = 0
enddo
status = nf90_def_var(ncid, hfield%vname, &
lprecision, dimids, varid, &
chunksizes=chunks, deflate_level=history_deflate)
call ice_check_nc(status, &
subname//' ERROR: defining var '//hfield%vname,file=__FILE__,line=__LINE__)
else
! no chunk and compress
status = nf90_def_var(ncid, hfield%vname, &
lprecision, dimids, varid)
call ice_check_nc(status, &
subname//' ERROR: defining var '//hfield%vname,file=__FILE__,line=__LINE__)

status = nf90_def_var(ncid, hfield%vname, lprecision, dimids, varid)
call ice_check_nc(status, subname//' ERROR: defining var '//trim(hfield%vname),file=__FILE__,line=__LINE__)

if (history_format=='hdf5' .and. size(dimids)>1) then
if (dimids(1)==imtid .and. dimids(2)==jmtid) then
chunks(1)=history_chunksize(1)
chunks(2)=history_chunksize(2)
do i = 3, size(dimids)
chunks(i) = 0
enddo
status = nf90_def_var_chunking(ncid,varid, NF90_CHUNKED, chunksizes=chunks)
call ice_check_nc(status, subname//' ERROR chunking var '//trim(hfield%vname), file=__FILE__, line=__LINE__)
endif
endif

if (history_format=='hdf5' .and. history_deflate/=0) then
status=nf90_def_var_deflate(ncid, varid, shuffle=0, deflate=1, deflate_level=history_deflate)
call ice_check_nc(status, subname//' ERROR deflating var '//trim(hfield%vname), file=__FILE__, line=__LINE__)
endif

! add attributes
Expand Down Expand Up @@ -1300,32 +1323,39 @@ end subroutine ice_write_hist_fill

subroutine ice_hist_coord_def(ncid, coord, lprecision, dimids, varid)

use ice_history_shared, only: history_deflate, history_format
use ice_history_shared, only: history_deflate, history_format, history_chunksize
#ifdef USE_NETCDF
use netcdf, only: nf90_def_var, nf90_put_att
use netcdf, only: nf90_def_var, nf90_put_att, nf90_def_var_chunking, nf90_def_var_deflate, NF90_CHUNKED

integer(kind=int_kind), intent(in) :: ncid, dimids(:), lprecision
type(coord_attributes), intent(in) :: coord
integer(kind=int_kind), intent(inout) :: varid

!local vars
integer(kind=int_kind) :: status
integer(kind=int_kind) ::chunks(size(dimids)), i, status

character(len=*), parameter :: subname = '(ice_hist_coord_def)'

status = nf90_def_var(ncid, coord%short_name, lprecision, dimids, varid)
call ice_check_nc(status, subname//' ERROR: defining coord '//coord%short_name,file=__FILE__,line=__LINE__)

!define var, set deflate, long_name and units
if (history_format=='hdf5' .and. size(dimids)>1 ) then
status = nf90_def_var(ncid, trim(coord%short_name), &
lprecision, dimids, varid, deflate_level=history_deflate)
call ice_check_nc(status, &
subname//' ERROR: defining coord '//coord%short_name,file=__FILE__,line=__LINE__)
else
! no compress
status = nf90_def_var(ncid, coord%short_name, &
lprecision, dimids, varid)
call ice_check_nc(status, &
subname//' ERROR: defining coord '//coord%short_name,file=__FILE__,line=__LINE__)
if (history_format=='hdf5' .and. size(dimids)>1) then
if (dimids(1)==imtid .and. dimids(2)==jmtid) then
chunks(1)=history_chunksize(1)
chunks(2)=history_chunksize(2)
do i = 3, size(dimids)
chunks(i) = 0
enddo
status = nf90_def_var_chunking(ncid,varid, NF90_CHUNKED, chunksizes=chunks)
call ice_check_nc(status, subname//' ERROR chunking var '//trim(coord%short_name), file=__FILE__, line=__LINE__)
endif
endif

if (history_format=='hdf5' .and. history_deflate/=0) then
status=nf90_def_var_deflate(ncid, varid, shuffle=0, deflate=1, deflate_level=history_deflate)
call ice_check_nc(status, subname//' ERROR deflating var '//trim(coord%short_name), file=__FILE__, line=__LINE__)
endif

status = nf90_put_att(ncid,varid,'long_name',trim(coord%long_name))
call ice_check_nc(status, subname// ' ERROR: defining long_name for '//coord%short_name, &
file=__FILE__, line=__LINE__)
Expand Down
41 changes: 25 additions & 16 deletions cicecore/cicedyn/infrastructure/io/io_netcdf/ice_restart.F90
Original file line number Diff line number Diff line change
Expand Up @@ -30,10 +30,12 @@ module ice_restart
implicit none
private
public :: init_restart_write, init_restart_read, &
read_restart_field, write_restart_field, final_restart, &
query_field
read_restart_field, write_restart_field, final_restart, &
query_field

integer (kind=int_kind) :: ncid
integer (kind=int_kind) :: ncid , &
dimid_ni, & ! netCDF identifiers
dimid_nj

!=======================================================================

Expand Down Expand Up @@ -170,8 +172,7 @@ subroutine init_restart_write(filename_spec)
integer (kind=int_kind), allocatable :: dims(:)

integer (kind=int_kind) :: &
dimid_ni, & ! netCDF identifiers
dimid_nj, & !

dimid_ncat, & !
iflag, & ! netCDF creation flag
status ! status variable from netCDF routine
Expand Down Expand Up @@ -890,18 +891,26 @@ subroutine define_rest_field(ncid, vname, dims)

#ifdef USE_NETCDF

if (restart_format=='hdf5') then
chunks(1)=restart_chunksize(1)
chunks(2)=restart_chunksize(2)
do i = 3, size(dims)
chunks(i) = 0
enddo
status = nf90_def_var(ncid,trim(vname),nf90_double,dims,varid, &
chunksizes=chunks, deflate_level=restart_deflate)
else
status = nf90_def_var(ncid,trim(vname),nf90_double,dims,varid)
end if
status = nf90_def_var(ncid,trim(vname),nf90_double,dims,varid)
call ice_check_nc(status, subname//' ERROR: def var '//trim(vname), file=__FILE__, line=__LINE__)

if (restart_format=='hdf5' .and. size(dims)>1) then
if (dims(1)==dimid_ni .and. dims(2)==dimid_nj) then
chunks(1)=restart_chunksize(1)
chunks(2)=restart_chunksize(2)
do i = 3, size(dims)
chunks(i) = 0
enddo
status = nf90_def_var_chunking(ncid,varid, NF90_CHUNKED, chunksizes=chunks)
call ice_check_nc(status, subname//' ERROR: chunking var '//trim(vname), file=__FILE__, line=__LINE__)
endif
endif

if (restart_format=='hdf5' .and. restart_deflate/=0) then
status=nf90_def_var_deflate(ncid, varid, shuffle=0, deflate=1, deflate_level=restart_deflate)
call ice_check_nc(status, subname//' ERROR deflating var '//trim(vname), file=__FILE__, line=__LINE__)
endif

#else
call abort_ice(subname//' ERROR: USE_NETCDF cpp not defined', &
file=__FILE__, line=__LINE__)
Expand Down
Loading

0 comments on commit 4829247

Please sign in to comment.