Skip to content

Commit

Permalink
Update history_format, restart_format, add options cdf1, cdf2, cdf5,
Browse files Browse the repository at this point in the history
hdf5, pnetcdf1, pnetcdf2, pnetcdf5.  Deprecate lcdf64.  But still provide
backward compatibility with old namelist.  Update test suite and
documentation.
  • Loading branch information
apcraig committed Jan 24, 2024
1 parent 7a4b95e commit 9804049
Show file tree
Hide file tree
Showing 23 changed files with 264 additions and 116 deletions.
116 changes: 111 additions & 5 deletions cicecore/cicedyn/general/ice_init.F90
Original file line number Diff line number Diff line change
Expand Up @@ -78,7 +78,7 @@ subroutine input_data
restart_fsd, restart_iso, restart_snow
use ice_restart_shared, only: &
restart, restart_ext, restart_coszen, restart_dir, restart_file, pointer_file, &
runid, runtype, use_restart_time, restart_format, lcdf64
runid, runtype, use_restart_time, restart_format
use ice_history_shared, only: hist_avg, history_dir, history_file, hist_suffix, &
incond_dir, incond_file, version_name, &
history_precision, history_format, hist_time_axis
Expand Down Expand Up @@ -163,6 +163,7 @@ subroutine input_data
logical (kind=log_kind) :: tr_iso, tr_aero, tr_fsd, tr_snow
logical (kind=log_kind) :: tr_pond_lvl, tr_pond_topo
integer (kind=int_kind) :: numin, numax ! unit number limits
logical (kind=log_kind) :: lcdf64 ! deprecated, backwards compatibility

integer (kind=int_kind) :: rplvl, rptopo
real (kind=dbl_kind) :: Cf, ksno, puny, ice_ref_salinity, Tocnfrz
Expand Down Expand Up @@ -326,7 +327,7 @@ subroutine input_data
histfreq_base(:) = 'zero' ! output frequency reference date
hist_avg(:) = .true. ! if true, write time-averages (not snapshots)
hist_suffix(:) = 'x' ! appended to 'history_file' in filename when not 'x'
history_format = 'default' ! history file format
history_format = 'cdf2'! history file format
hist_time_axis = 'end' ! History file time axis averaging interval position

history_dir = './' ! write to executable dir for default
Expand All @@ -347,7 +348,7 @@ subroutine input_data
restart_ext = .false. ! if true, read/write ghost cells
restart_coszen = .false. ! if true, read/write coszen
pointer_file = 'ice.restart_file'
restart_format = 'default' ! restart file format
restart_format = 'cdf2' ! restart file format
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 @@ -1232,6 +1233,111 @@ subroutine input_data
abort_list = trim(abort_list)//":1"
endif

if (history_format /= 'cdf1' .and. &
history_format /= 'cdf2' .and. &
history_format /= 'cdf5' .and. &
history_format /= 'hdf5' .and. &
history_format /= 'pnetcdf1' .and. &
history_format /= 'pnetcdf2' .and. &
history_format /= 'pnetcdf5' .and. &
history_format /= 'pio_netcdf' .and. & ! backwards compatibility
history_format /= 'pio_pnetcdf' .and. & ! backwards compatibility
history_format /= 'default') then ! backwards compatibility
if (my_task == master_task) then
write(nu_diag,*) subname//' ERROR: history_format unknown = ',trim(history_format)
endif
abort_list = trim(abort_list)//":50"
endif

if (restart_format /= 'cdf1' .and. &
restart_format /= 'cdf2' .and. &
restart_format /= 'cdf5' .and. &
restart_format /= 'hdf5' .and. &
restart_format /= 'pnetcdf1' .and. &
restart_format /= 'pnetcdf2' .and. &
restart_format /= 'pnetcdf5' .and. &
restart_format /= 'pio_netcdf' .and. & ! backwards compatibility
restart_format /= 'pio_pnetcdf' .and. & ! backwards compatibility
restart_format /= 'default') then ! backwards compatibility
if (my_task == master_task) then
write(nu_diag,*) subname//' ERROR: restart_format unknown = ',trim(restart_format)
endif
abort_list = trim(abort_list)//":51"
endif

! backwards compatibility
if (lcdf64) then
if (my_task == master_task) then
write(nu_diag,*) subname//' WARNING: lcdf64 is deprecated, please update namelist settings'
endif

if (history_format == 'default' .or. history_format == 'pio_netcdf') then
if (my_task == master_task) then
write(nu_diag,*) subname//' WARNING: history_format='//trim(history_format)// &
' is deprecated, please update namelist settings'
endif
history_format = 'cdf2'
elseif (history_format == 'pio_pnetcdf') then
if (my_task == master_task) then
write(nu_diag,*) subname//' WARNING: history_format='//trim(history_format)// &
' is deprecated, please update namelist settings'
endif
history_format = 'pnetcdf2'
else
if (my_task == master_task) then
write(nu_diag,*) subname//' ERROR: lcdf64 is T and history_format not supported for '//trim(history_format)
endif
abort_list = trim(abort_list)//":52"
endif

if (restart_format == 'default' .or. restart_format == 'pio_netcdf') then
if (my_task == master_task) then
write(nu_diag,*) subname//' WARNING: restart_format='//trim(restart_format)// &
' is deprecated, please update namelist settings'
endif
restart_format = 'cdf2'
elseif (restart_format == 'pio_pnetcdf') then
if (my_task == master_task) then
write(nu_diag,*) subname//' WARNING: restart_format='//trim(restart_format)// &
' is deprecated, please update namelist settings'
endif
restart_format = 'pnetcdf2'
else
if (my_task == master_task) then
write(nu_diag,*) subname//' ERROR: lcdf64 is T and restart_format not supported for '//trim(restart_format)
endif
abort_list = trim(abort_list)//":53"
endif
else
if (history_format == 'default' .or. history_format == 'pio_netcdf') then
if (my_task == master_task) then
write(nu_diag,*) subname//' WARNING: history_format='//trim(history_format)// &
' is deprecated, please update namelist settings'
endif
history_format = 'cdf1'
elseif (history_format == 'pio_pnetcdf') then
if (my_task == master_task) then
write(nu_diag,*) subname//' WARNING: history_format='//trim(history_format)// &
' is deprecated, please update namelist settings'
endif
history_format = 'pnetcdf1'
endif

if (restart_format == 'default' .or. restart_format == 'pio_netcdf') then
if (my_task == master_task) then
write(nu_diag,*) subname//' WARNING: restart_format='//trim(restart_format)// &
' is deprecated, please update namelist settings'
endif
restart_format = 'cdf1'
elseif (restart_format == 'pio_pnetcdf') then
if (my_task == master_task) then
write(nu_diag,*) subname//' WARNING: restart_format='//trim(restart_format)// &
' is deprecated, please update namelist settings'
endif
restart_format = 'pnetcdf1'
endif
endif

if (ktransport <= 0) then
advection = 'none'
endif
Expand Down Expand Up @@ -1504,7 +1610,7 @@ subroutine input_data
write (nu_diag,*) subname//' ERROR: snow grain radius is activated'
write (nu_diag,*) subname//' ERROR: Must use shortwave=dEdd or dEdd_snicar_ad'
endif
abort_list = trim(abort_list)//":29"
abort_list = trim(abort_list)//":17"
endif

if ((rfracmin < -puny .or. rfracmin > c1+puny) .or. &
Expand Down Expand Up @@ -2377,7 +2483,7 @@ subroutine input_data
write(nu_diag,1011) ' restart_ext = ', restart_ext
write(nu_diag,1011) ' restart_coszen = ', restart_coszen
write(nu_diag,1031) ' restart_format = ', trim(restart_format)
write(nu_diag,1011) ' lcdf64 = ', lcdf64
! write(nu_diag,1011) ' lcdf64 = ', lcdf64 ! deprecated
write(nu_diag,1031) ' restart_file = ', trim(restart_file)
write(nu_diag,1031) ' pointer_file = ', trim(pointer_file)
write(nu_diag,1011) ' use_restart_time = ', use_restart_time
Expand Down
15 changes: 12 additions & 3 deletions cicecore/cicedyn/infrastructure/io/io_netcdf/ice_history_write.F90
Original file line number Diff line number Diff line change
Expand Up @@ -61,7 +61,6 @@ subroutine ice_write_hist (ns)
lont_bounds, latt_bounds, lonu_bounds, latu_bounds, &
lonn_bounds, latn_bounds, lone_bounds, late_bounds
use ice_history_shared
use ice_restart_shared, only: lcdf64
#ifdef CESMCOUPLED
use ice_restart_shared, only: runid
#endif
Expand Down Expand Up @@ -148,8 +147,18 @@ subroutine ice_write_hist (ns)
endif

! create file
iflag = nf90_clobber
if (lcdf64) iflag = ior(iflag,nf90_64bit_offset)
if (history_format == 'cdf1') then
iflag = nf90_clobber
elseif (history_format == 'cdf2') then
iflag = ior(nf90_clobber,nf90_64bit_offset)
elseif (history_format == 'cdf5') then
iflag = ior(nf90_clobber,nf90_64bit_data)
elseif (history_format == 'hdf5') then
iflag = ior(nf90_clobber,nf90_netcdf4)
else
call abort_ice(subname//' ERROR: history_format not allowed for '//trim(history_format), &
file=__FILE__, line=__LINE__)
endif
status = nf90_create(ncfile(ns), iflag, ncid)
call ice_check_nc(status, subname// ' ERROR: creating history ncfile '//ncfile(ns), &
file=__FILE__, line=__LINE__)
Expand Down
16 changes: 13 additions & 3 deletions cicecore/cicedyn/infrastructure/io/io_netcdf/ice_restart.F90
Original file line number Diff line number Diff line change
Expand Up @@ -18,7 +18,7 @@ module ice_restart
use ice_read_write, only: ice_check_nc
use ice_restart_shared, only: &
restart_ext, restart_dir, restart_file, pointer_file, &
runid, use_restart_time, lcdf64, lenstr, restart_coszen
runid, use_restart_time, lenstr, restart_coszen, restart_format
use ice_fileunits, only: nu_diag, nu_rst_pointer
use ice_exit, only: abort_ice
use icepack_intfc, only: icepack_query_parameters
Expand Down Expand Up @@ -216,8 +216,18 @@ subroutine init_restart_write(filename_spec)
write(nu_rst_pointer,'(a)') filename
close(nu_rst_pointer)

iflag = 0
if (lcdf64) iflag = nf90_64bit_offset
if (restart_format == 'cdf1') then
iflag = nf90_clobber
elseif (restart_format == 'cdf2') then
iflag = ior(nf90_clobber,nf90_64bit_offset)
elseif (restart_format == 'cdf5') then
iflag = ior(nf90_clobber,nf90_64bit_data)
elseif (restart_format == 'hdf5') then
iflag = ior(nf90_clobber,nf90_netcdf4)
else
call abort_ice(subname//' ERROR: restart_format not allowed for '//trim(restart_format), &
file=__FILE__, line=__LINE__)
endif
status = nf90_create(trim(filename), iflag, ncid)
call ice_check_nc(status, subname//' ERROR: creating '//trim(filename), file=__FILE__, line=__LINE__)

Expand Down
16 changes: 4 additions & 12 deletions cicecore/cicedyn/infrastructure/io/io_pio2/ice_history_write.F90
Original file line number Diff line number Diff line change
Expand Up @@ -57,7 +57,7 @@ subroutine ice_write_hist (ns)
lonn_bounds, latn_bounds, lone_bounds, late_bounds
use ice_history_shared
use ice_arrays_column, only: hin_max, floe_rad_c
use ice_restart_shared, only: runid, lcdf64
use ice_restart_shared, only: runid
use ice_pio
use pio

Expand All @@ -78,7 +78,6 @@ subroutine ice_write_hist (ns)
character (char_len) :: title
character (char_len) :: time_period_freq = 'none'
character (char_len_long) :: ncfile(max_nstrm)
integer (kind=int_kind) :: iotype

integer (kind=int_kind) :: icategory,ind,i_aice,boundid

Expand Down Expand Up @@ -167,11 +166,9 @@ subroutine ice_write_hist (ns)
call broadcast_scalar(filename, master_task)

! create file
iotype = PIO_IOTYPE_NETCDF
if (history_format == 'pio_pnetcdf') iotype = PIO_IOTYPE_PNETCDF
File%fh=-1
call ice_pio_init(mode='write', filename=trim(filename), File=File, &
clobber=.true., cdf64=lcdf64, iotype=iotype)
clobber=.true., fformat=trim(history_format))

call ice_pio_initdecomp(iodesc=iodesc2d, precision=history_precision)
call ice_pio_initdecomp(ndim3=ncat_hist, iodesc=iodesc3dc, precision=history_precision)
Expand Down Expand Up @@ -741,13 +738,8 @@ subroutine ice_write_hist (ns)
call ice_pio_check(pio_put_att(File,pio_global,'history',trim(start_time)), &
subname//' ERROR: defining att history '//trim(start_time),file=__FILE__,line=__LINE__)

if (history_format == 'pio_pnetcdf') then
call ice_pio_check(pio_put_att(File,pio_global,'io_flavor','io_pio pnetcdf'), &
subname//' ERROR: defining att io_flavor',file=__FILE__,line=__LINE__)
else
call ice_pio_check(pio_put_att(File,pio_global,'io_flavor','io_pio netcdf'), &
subname//' ERROR: defining att io_flavor',file=__FILE__,line=__LINE__)
endif
call ice_pio_check(pio_put_att(File,pio_global,'io_flavor','io_pio '//trim(history_format)), &
subname//' ERROR: defining att io_flavor',file=__FILE__,line=__LINE__)

!-----------------------------------------------------------------
! end define mode
Expand Down
49 changes: 29 additions & 20 deletions cicecore/cicedyn/infrastructure/io/io_pio2/ice_pio.F90
Original file line number Diff line number Diff line change
Expand Up @@ -44,7 +44,7 @@ module ice_pio
! Initialize the io subsystem
! 2009-Feb-17 - J. Edwards - initial version

subroutine ice_pio_init(mode, filename, File, clobber, cdf64, iotype)
subroutine ice_pio_init(mode, filename, File, clobber, fformat)

#ifdef CESMCOUPLED
use shr_pio_mod, only: shr_pio_getiosys, shr_pio_getiotype
Expand All @@ -59,16 +59,16 @@ subroutine ice_pio_init(mode, filename, File, clobber, cdf64, iotype)
character(len=*) , intent(in), optional :: filename
type(file_desc_t) , intent(inout), optional :: File
logical , intent(in), optional :: clobber
logical , intent(in), optional :: cdf64
integer , intent(in), optional :: iotype
character(len=*) , intent(in), optional :: fformat

! local variables

integer (int_kind) :: &
nml_error ! namelist read error flag

integer :: nprocs , istride, basetask, numiotasks, rearranger, pio_iotype, status, nmode
logical :: lclobber, lcdf64, exists
integer :: nprocs , istride, basetask, numiotasks, rearranger
integer ::pio_iotype, status, nmode0, nmode
logical :: lclobber, exists
logical, save :: first_call = .true.
character(len=*), parameter :: subname = '(ice_pio_init)'

Expand All @@ -86,12 +86,26 @@ subroutine ice_pio_init(mode, filename, File, clobber, cdf64, iotype)
#endif

!--- initialize type of io
!pio_iotype = PIO_IOTYPE_PNETCDF
!pio_iotype = PIO_IOTYPE_NETCDF4C
!pio_iotype = PIO_IOTYPE_NETCDF4P
pio_iotype = PIO_IOTYPE_NETCDF
if (present(iotype)) then
pio_iotype = iotype

lclobber = .false.
if (present(clobber)) lclobber=clobber

if (fformat(1:3) == 'cdf') then
pio_iotype = PIO_IOTYPE_NETCDF
elseif (fformat(1:3) == 'hdf') then
pio_iotype = PIO_IOTYPE_NETCDF4P
elseif (fformat(1:7) == 'pnetcdf') then
pio_iotype = PIO_IOTYPE_PNETCDF
else
call abort_ice(subname//' ERROR: format not allowed for '//trim(fformat), &
file=__FILE__, line=__LINE__)
endif

nmode0 = 0
if (fformat == 'cdf2' .or. fformat == 'pnetcdf2') then
nmode0 = PIO_64BIT_OFFSET
elseif (fformat == 'cdf5' .or. fformat == 'pnetcdf5') then
nmode0 = PIO_64BIT_DATA
endif

!--- initialize ice_pio_subsystem
Expand All @@ -102,12 +116,14 @@ subroutine ice_pio_init(mode, filename, File, clobber, cdf64, iotype)
!--tcraig this should work better but it causes pio2.4.4 to fail for reasons unknown
! numiotasks = 1 + (nprocs-basetask-1)/istride
rearranger = PIO_REARR_BOX

if (my_task == master_task) then
write(nu_diag,*) subname,' nprocs = ',nprocs
write(nu_diag,*) subname,' istride = ',istride
write(nu_diag,*) subname,' basetask = ',basetask
write(nu_diag,*) subname,' numiotasks = ',numiotasks
write(nu_diag,*) subname,' pio_iotype = ',pio_iotype
write(nu_diag,*) subname,' nmode = ',nmode0
end if

call pio_init(my_task, MPI_COMM_ICE, numiotasks, master_task, istride, &
Expand Down Expand Up @@ -139,19 +155,13 @@ subroutine ice_pio_init(mode, filename, File, clobber, cdf64, iotype)
if (present(mode) .and. present(filename) .and. present(File)) then

if (trim(mode) == 'write') then
lclobber = .false.
if (present(clobber)) lclobber=clobber

lcdf64 = .false.
if (present(cdf64)) lcdf64=cdf64

if (File%fh<0) then
! filename not open
inquire(file=trim(filename),exist=exists)
if (exists) then
if (lclobber) then
nmode = pio_clobber
if (lcdf64) nmode = ior(nmode,PIO_64BIT_OFFSET)
nmode = ior(PIO_CLOBBER,nmode0)
status = pio_createfile(ice_pio_subsystem, File, pio_iotype, trim(filename), nmode)
call ice_pio_check(status, subname//' ERROR: Failed to create file '//trim(filename), &
file=__FILE__,line=__LINE__)
Expand All @@ -168,8 +178,7 @@ subroutine ice_pio_init(mode, filename, File, clobber, cdf64, iotype)
end if
endif
else
nmode = pio_noclobber
if (lcdf64) nmode = ior(nmode,PIO_64BIT_OFFSET)
nmode = ior(PIO_NOCLOBBER,nmode0)
status = pio_createfile(ice_pio_subsystem, File, pio_iotype, trim(filename), nmode)
call ice_pio_check( status, subname//' ERROR: Failed to create file '//trim(filename), &
file=__FILE__,line=__LINE__)
Expand Down
Loading

0 comments on commit 9804049

Please sign in to comment.