Newer
Older
if ( Any( tpfields(jp)%ndimlist(:) == NMNHDIM_UNKNOWN ) ) &
call Print_msg( NVERB_ERROR, 'IO', 'Write_diachro_nc4', &
'some dimensions are unknown for variable '//trim(tpfields(jp)%cmnhname) )
icount = Count( tpfields(jp)%ndimlist(:) /= NMNHDIM_UNUSED )
if ( tpfields(jp)%ndims /= icount ) &
call Print_msg( NVERB_ERROR, 'IO', 'Write_diachro_nc4', &
'ndims is not coherent with ndimlist for variable '//trim(tpfields(jp)%cmnhname) )
if ( jp == 1 ) then
idims = icount
else
if ( idims /= icount ) &
call Print_msg( NVERB_ERROR, 'IO', 'Write_diachro_nc4', &
'number of dimensions not the same for all tpfields for variable '//trim(tpfields(jp)%cmnhname) )
end if
end do
!The dimension list should be the same for all tpfields entries
do jp = 2, Size( tpfields )
do ji = 1, NMNHMAXDIMS

WAUTELET Philippe
committed
if ( tpfields(jp)%ndimlist(ji) /= tpfields(1)%ndimlist(ji) ) then

WAUTELET Philippe
committed
!For SERIES: it is possible to have NMNHDIM_NI and NMNHDIM_NI_U in the different tpfields

WAUTELET Philippe
committed
!For SERIES: it is possible to have NMNHDIM_SERIES_LEVEL and NMNHDIM_SERIES_LEVEL_W in the different tpfields

WAUTELET Philippe
committed
if ( tpfields(jp)%ndimlist(ji) /= NMNHDIM_NI .and. tpfields(jp)%ndimlist(ji) /= NMNHDIM_NI_U .and. &
tpfields(jp)%ndimlist(ji) /= NMNHDIM_SERIES_LEVEL .and. tpfields(jp)%ndimlist(ji) /= NMNHDIM_SERIES_LEVEL_W ) then

WAUTELET Philippe
committed
call Print_msg( NVERB_ERROR, 'IO', 'Write_diachro_nc4', &
'some dimensions are not the same for all tpfields entries for variable '//trim(tpfields(jp)%cmnhname) )
end if
end if
end do
end do

WAUTELET Philippe
committed
!Check that if cartesian and no horizontal compression, parameters are as expected

WAUTELET Philippe
committed
if ( yshape == 'Cartesian' .and. .not. tpbudiachro%licompress .and. .not. tpbudiachro%ljcompress ) then

WAUTELET Philippe
committed
icorr = Merge( 1, 0, tpbudiachro%lkcompress )

WAUTELET Philippe
committed
if ( ( idims + icorr ) /= 3 .and. ( idims + icorr ) /= 4 ) then

WAUTELET Philippe
committed
call Print_msg( NVERB_ERROR, 'IO', 'Write_diachro_nc4', &
'unexpected number of dimensions for cartesian shape without horizontal compression for variable ' &
// Trim( tpfields(1)%cmnhname ) )
end if
if ( ( tpfields(1)%ndimlist(1) /= NMNHDIM_BUDGET_CART_NI &
.and. tpfields(1)%ndimlist(1) /= NMNHDIM_BUDGET_CART_NI_U &
.and. tpfields(1)%ndimlist(1) /= NMNHDIM_BUDGET_CART_NI_V ) &
.or. ( tpfields(1)%ndimlist(2) /= NMNHDIM_BUDGET_CART_NJ &
.and. tpfields(1)%ndimlist(2) /= NMNHDIM_BUDGET_CART_NJ_U &
.and. tpfields(1)%ndimlist(2) /= NMNHDIM_BUDGET_CART_NJ_V ) &

WAUTELET Philippe
committed
.or. ( .not. tpbudiachro%lkcompress &

WAUTELET Philippe
committed
.and. tpfields(1)%ndimlist(3) /= NMNHDIM_BUDGET_CART_LEVEL &
.and. tpfields(1)%ndimlist(3) /= NMNHDIM_BUDGET_CART_LEVEL_W ) &

WAUTELET Philippe
committed
.or. ( ( idims + icorr ) == 4 .and. tpfields(1)%ndimlist(6) /= NMNHDIM_BUDGET_NGROUPS ) ) then
call Print_msg( NVERB_ERROR, 'IO', 'Write_diachro_nc4', &
'unexpected dimensions for CART without horizontal compression for variable ' &
// Trim( tpfields(1)%cmnhname ) )
end if
end if

WAUTELET Philippe
committed

WAUTELET Philippe
committed
select case ( idims )
case (0)

WAUTELET Philippe
committed
!Remark: [ integer:: ] is a constructor for a zero-size array of integers, [] is not allowed (type can not be determined)

WAUTELET Philippe
committed
call Diachro_one_field_write_nc4( tzfile, tpbudiachro, tpfields(1), pvar, [ integer:: ], gsplit, gdistributed )

WAUTELET Philippe
committed
case (1)

WAUTELET Philippe
committed
if ( Any ( tpfields(1)%ndimlist(4) == [ NMNHDIM_BUDGET_LES_TIME, NMNHDIM_BUDGET_LES_AVG_TIME, NMNHDIM_SERIES_TIME ] ) ) then

WAUTELET Philippe
committed
if ( Size( tpfields ) /= 1 ) call Print_msg( NVERB_FATAL, 'IO', 'Write_diachro_nc4', &
'wrong size of tpfields (variable '//trim(tpfields(1)%cmnhname)//')' )

WAUTELET Philippe
committed
call Diachro_one_field_write_nc4( tzfile, tpbudiachro, tpfields(1), pvar, [ 4 ], gsplit, gdistributed )

WAUTELET Philippe
committed
else if ( Any( tpfields(1)%ndimlist(1) == [ NMNHDIM_NI, NMNHDIM_NI_U, NMNHDIM_NI_V, NMNHDIM_BUDGET_CART_NI, &
NMNHDIM_BUDGET_CART_NI_U, NMNHDIM_BUDGET_CART_NI_V ] ) ) then

WAUTELET Philippe
committed
if ( Size( tpfields ) /= 1 ) call Print_msg( NVERB_FATAL, 'IO', 'Write_diachro_nc4', &
'wrong size of tpfields (variable '//trim(tpfields(1)%cmnhname)//')' )

WAUTELET Philippe
committed

WAUTELET Philippe
committed
call Diachro_one_field_write_nc4( tzfile, tpbudiachro, tpfields(1), pvar, [ 1 ], gsplit, gdistributed )

WAUTELET Philippe
committed

WAUTELET Philippe
committed
else if ( Any( tpfields(1)%ndimlist(2) == [ NMNHDIM_NJ, NMNHDIM_NJ_U, NMNHDIM_NJ_V, NMNHDIM_BUDGET_CART_NJ, &
NMNHDIM_BUDGET_CART_NJ_U, NMNHDIM_BUDGET_CART_NJ_V ] ) ) then

WAUTELET Philippe
committed
if ( Size( tpfields ) /= 1 ) call Print_msg( NVERB_FATAL, 'IO', 'Write_diachro_nc4', &
'wrong size of tpfields (variable '//trim(tpfields(1)%cmnhname)//')' )

WAUTELET Philippe
committed
call Diachro_one_field_write_nc4( tzfile, tpbudiachro, tpfields(1), pvar, [ 2 ], gsplit, gdistributed )

WAUTELET Philippe
committed
else if ( Any( tpfields(1)%ndimlist(3) == [ NMNHDIM_LEVEL, NMNHDIM_LEVEL_W, &
NMNHDIM_BUDGET_CART_LEVEL, NMNHDIM_BUDGET_CART_LEVEL_W ] ) ) then

WAUTELET Philippe
committed
if ( Size( tpfields ) /= 1 ) call Print_msg( NVERB_FATAL, 'IO', 'Write_diachro_nc4', &
'wrong size of tpfields (variable '//trim(tpfields(1)%cmnhname)//')' )

WAUTELET Philippe
committed
call Diachro_one_field_write_nc4( tzfile, tpbudiachro, tpfields(1), pvar, [ 3 ], gsplit, gdistributed )

WAUTELET Philippe
committed
else if ( tpfields(1)%ndimlist(6) == NMNHDIM_BUDGET_NGROUPS .or. tpfields(1)%ndimlist(6) == NMNHDIM_PROFILER_PROC ) then

WAUTELET Philippe
committed
do ji = 1, Size( pvar, 6 )

WAUTELET Philippe
committed
!Remark: [ integer:: ] is a constructor for a zero-size array of integers, [] is not allowed (type can not be determined)

WAUTELET Philippe
committed
call Diachro_one_field_write_nc4( tzfile, tpbudiachro, tpfields(ji), pvar(:,:,:,:,:,ji:ji), [ integer:: ], &
gsplit, gdistributed )

WAUTELET Philippe
committed
end do
else
call Print_msg( NVERB_FATAL, 'IO', 'Write_diachro_nc4', &

WAUTELET Philippe
committed
'case not yet implemented (1D variable '//trim(tpfields(1)%cmnhname)//')' )
end if
case (2)

WAUTELET Philippe
committed

WAUTELET Philippe
committed
if ( Any( tpfields(1)%ndimlist(1) == [ NMNHDIM_NI, NMNHDIM_NI_U, NMNHDIM_NI_V, NMNHDIM_BUDGET_CART_NI, &
NMNHDIM_BUDGET_CART_NI_U, NMNHDIM_BUDGET_CART_NI_V ] ) &
.and. Any( tpfields(1)%ndimlist(2) == [ NMNHDIM_NJ, NMNHDIM_NJ_U, NMNHDIM_NJ_V, NMNHDIM_BUDGET_CART_NJ, &
NMNHDIM_BUDGET_CART_NJ_U, NMNHDIM_BUDGET_CART_NJ_V ] ) ) then
if ( Size( tpfields ) /= 1 ) call Print_msg( NVERB_FATAL, 'IO', 'Write_diachro_nc4', &
'wrong size of tpfields (variable '//trim(tpfields(1)%cmnhname)//')' )

WAUTELET Philippe
committed
call Diachro_one_field_write_nc4( tzfile, tpbudiachro, tpfields(1), pvar, [ 1, 2 ], gsplit, gdistributed, &

WAUTELET Philippe
committed
iil, iih, ijl, ijh, ikl, ikh )

WAUTELET Philippe
committed
else if ( Any( tpfields(1)%ndimlist(1) == [ NMNHDIM_NI, NMNHDIM_NI_U, NMNHDIM_NI_V, NMNHDIM_BUDGET_CART_NI, &
NMNHDIM_BUDGET_CART_NI_U, NMNHDIM_BUDGET_CART_NI_V ] ) &
.and. Any( tpfields(1)%ndimlist(3) == [ NMNHDIM_LEVEL, NMNHDIM_LEVEL_W, &
NMNHDIM_BUDGET_CART_LEVEL, NMNHDIM_BUDGET_CART_LEVEL_W ] ) ) then
if ( Size( tpfields ) /= 1 ) call Print_msg( NVERB_FATAL, 'IO', 'Write_diachro_nc4', &
'wrong size of tpfields (variable '//trim(tpfields(1)%cmnhname)//')' )

WAUTELET Philippe
committed
call Diachro_one_field_write_nc4( tzfile, tpbudiachro, tpfields(1), pvar, [ 1, 3 ], gsplit, gdistributed )

WAUTELET Philippe
committed
else if ( Any( tpfields(1)%ndimlist(2) == [ NMNHDIM_NJ, NMNHDIM_NJ_U, NMNHDIM_NJ_V, NMNHDIM_BUDGET_CART_NJ, &
NMNHDIM_BUDGET_CART_NJ_U, NMNHDIM_BUDGET_CART_NJ_V ] ) &
.and. Any( tpfields(1)%ndimlist(3) == [ NMNHDIM_LEVEL, NMNHDIM_LEVEL_W, &
NMNHDIM_BUDGET_CART_LEVEL, NMNHDIM_BUDGET_CART_LEVEL_W ] ) ) then
if ( Size( tpfields ) /= 1 ) call Print_msg( NVERB_FATAL, 'IO', 'Write_diachro_nc4', &
'wrong size of tpfields (variable '//trim(tpfields(1)%cmnhname)//')' )

WAUTELET Philippe
committed
call Diachro_one_field_write_nc4( tzfile, tpbudiachro, tpfields(1), pvar, [ 2, 3 ], gsplit, gdistributed )

WAUTELET Philippe
committed
else if ( Any( tpfields(1)%ndimlist(1) == [ NMNHDIM_BUDGET_CART_NI, NMNHDIM_BUDGET_CART_NI_U, NMNHDIM_BUDGET_CART_NI_V ] ) &
.and. tpfields(1)%ndimlist(6) == NMNHDIM_BUDGET_NGROUPS ) then

WAUTELET Philippe
committed
! Loop on the processes

WAUTELET Philippe
committed
do ji = 1, Size( pvar, 6 )

WAUTELET Philippe
committed
call Diachro_one_field_write_nc4( tzfile, tpbudiachro, tpfields(ji), pvar(:,:,:,:,:,ji:ji), [ 1 ], gsplit, gdistributed )

WAUTELET Philippe
committed
end do
else if ( Any( tpfields(1)%ndimlist(2) == [ NMNHDIM_BUDGET_CART_NJ, NMNHDIM_BUDGET_CART_NJ_U, NMNHDIM_BUDGET_CART_NJ_V ] ) &
.and. tpfields(1)%ndimlist(6) == NMNHDIM_BUDGET_NGROUPS ) then

WAUTELET Philippe
committed
! Loop on the processes

WAUTELET Philippe
committed
do ji = 1, Size( pvar, 6 )

WAUTELET Philippe
committed
call Diachro_one_field_write_nc4( tzfile, tpbudiachro, tpfields(ji), pvar(:,:,:,:,:,ji:ji), [ 2 ], gsplit, gdistributed )

WAUTELET Philippe
committed
end do
else if ( tpfields(1)%ndimlist(3) == NMNHDIM_BUDGET_LES_LEVEL &
.and. ( tpfields(1)%ndimlist(4) == NMNHDIM_BUDGET_LES_TIME &
.or. tpfields(1)%ndimlist(4) == NMNHDIM_BUDGET_LES_AVG_TIME ) ) then
if ( Size( tpfields ) /= 1 ) call Print_msg( NVERB_FATAL, 'IO', 'Write_diachro_nc4', &
'wrong size of tpfields (variable '//trim(tpfields(1)%cmnhname)//')' )

WAUTELET Philippe
committed
call Diachro_one_field_write_nc4( tzfile, tpbudiachro, tpfields(1), pvar, [ 3, 4 ], gsplit, gdistributed )

WAUTELET Philippe
committed
else if ( Any( tpfields(1)%ndimlist(3) == [ NMNHDIM_BUDGET_CART_LEVEL, NMNHDIM_BUDGET_CART_LEVEL_W ] ) &
.and. tpfields(1)%ndimlist(6) == NMNHDIM_BUDGET_NGROUPS ) then

WAUTELET Philippe
committed
! Loop on the processes

WAUTELET Philippe
committed
do ji = 1, Size( pvar, 6 )

WAUTELET Philippe
committed
call Diachro_one_field_write_nc4( tzfile, tpbudiachro, tpfields(ji), pvar(:,:,:,:,:,ji:ji), [ 3 ], gsplit, gdistributed )

WAUTELET Philippe
committed
end do

WAUTELET Philippe
committed
else if ( tpfields(1)%ndimlist(4) == NMNHDIM_BUDGET_TIME .and. tpfields(1)%ndimlist(5) == NMNHDIM_BUDGET_MASK_NBUMASK ) then
if ( Size( tpfields ) /= 1 ) call Print_msg( NVERB_FATAL, 'IO', 'Write_diachro_nc4', &
'wrong size of tpfields (variable '//trim(tpfields(1)%cmnhname)//')' )

WAUTELET Philippe
committed
call Diachro_one_field_write_nc4( tzfile, tpbudiachro, tpfields(1), pvar, [ 4, 5 ], gsplit, gdistributed )
else if ( ( tpfields(1)%ndimlist(4) == NMNHDIM_BUDGET_LES_TIME &

WAUTELET Philippe
committed
.or. tpfields(1)%ndimlist(4) == NMNHDIM_BUDGET_LES_AVG_TIME ) &
.and. tpfields(1)%ndimlist(5) == NMNHDIM_BUDGET_LES_SV ) then
if ( Size( tpfields ) /= 1 ) call Print_msg( NVERB_FATAL, 'IO', 'Write_diachro_nc4', &
'wrong size of tpfields (variable '//trim(tpfields(1)%cmnhname)//')' )

WAUTELET Philippe
committed
call Diachro_one_field_write_nc4( tzfile, tpbudiachro, tpfields(1), pvar, [ 4, 5 ], gsplit, gdistributed )
else if ( tpfields(1)%ndimlist(4) == NMNHDIM_FLYER_TIME &
.and. tpfields(1)%ndimlist(6) == NMNHDIM_FLYER_PROC ) then
!Correspond to FLYER_DIACHRO
!Create local time dimension
if ( isp == tzfile%nmaster_rank) then

WAUTELET Philippe
committed
istatus = NF90_INQ_DIMID( ilevelids(NLVL_GROUP), 'time_flyer', idimid )
if ( istatus == NF90_NOERR ) then
!Dimension already exists, check that it is not changed
istatus = NF90_INQUIRE_DIMENSION( ilevelids(NLVL_GROUP), idimid, len = ilen )
if ( ilen /= Int( Size( pvar, 4), kind = CDFINT ) ) &
call Print_msg( NVERB_FATAL, 'IO', 'Write_diachro_nc4', 'time_flyer dimension has changed' )
else
!Dimension does not exist yet, create it
istatus = NF90_DEF_DIM( ilevelids(NLVL_GROUP), 'time_flyer', Int( Size( pvar, 4), kind = CDFINT ), idimid )
if ( istatus /= NF90_NOERR ) &
call IO_Err_handle_nc4( istatus, 'Write_diachro_nc4', 'NF90_DEF_DIM', Trim( tpfields(1)%cmnhname ) )
end if
end if

WAUTELET Philippe
committed
! Loop on the processes
do ji = 1, Size( pvar, 6 )
call Diachro_one_field_write_nc4( tzfile, tpbudiachro, tpfields(ji), pvar(:,:,:,:,:,ji:ji), [ 4 ], gsplit, gdistributed )
end do
else if ( tpfields(1)%ndimlist(4) == NMNHDIM_PROFILER_TIME &
.and. tpfields(1)%ndimlist(6) == NMNHDIM_PROFILER_PROC ) then
!Correspond to WRITE_PROFILER_n

WAUTELET Philippe
committed
! Loop on the processes
do ji = 1, Size( pvar, 6 )

WAUTELET Philippe
committed
call Diachro_one_field_write_nc4( tzfile, tpbudiachro, tpfields(ji), pvar(:,:,:,:,:,ji:ji), [ 4 ], gsplit, gdistributed )
end do
else if ( tpfields(1)%ndimlist(4) == NMNHDIM_SERIES_TIME &
.and. tpfields(1)%ndimlist(6) == NMNHDIM_SERIES_PROC ) then
!Correspond to WRITE_SERIES_n

WAUTELET Philippe
committed
! Loop on the processes
do ji = 1, Size( pvar, 6 )

WAUTELET Philippe
committed
call Diachro_one_field_write_nc4( tzfile, tpbudiachro, tpfields(ji), pvar(:,:,:,:,:,ji:ji), [ 4 ], gsplit, gdistributed )

WAUTELET Philippe
committed
else if ( ( tpfields(1)%ndimlist(3) == NMNHDIM_SERIES_LEVEL .or. tpfields(1)%ndimlist(3) == NMNHDIM_SERIES_LEVEL_W ) &
.and. tpfields(1)%ndimlist(4) == NMNHDIM_SERIES_TIME ) then
!Correspond to WRITE_SERIES_n
if ( Size( tpfields ) /= 1 ) call Print_msg( NVERB_FATAL, 'IO', 'Write_diachro_nc4', &
'wrong size of tpfields (variable '//trim(tpfields(1)%cmnhname)//')' )
call Diachro_one_field_write_nc4( tzfile, tpbudiachro, tpfields(1), pvar(:,:,:,:,:,:), [ 3, 4 ], gsplit, gdistributed )

WAUTELET Philippe
committed
else if ( tpfields(1)%ndimlist(4) == NMNHDIM_STATION_TIME &
.and. tpfields(1)%ndimlist(6) == NMNHDIM_STATION_PROC ) then
!Correspond to WRITE_STATION_n
! Loop on the processes
do ji = 1, Size( pvar, 6 )
call Diachro_one_field_write_nc4( tzfile, tpbudiachro, tpfields(ji), pvar(:,:,:,:,:,ji:ji), [ 4 ], gsplit, gdistributed )
end do
else
call Print_msg( NVERB_FATAL, 'IO', 'Write_diachro_nc4', &

WAUTELET Philippe
committed
'case not yet implemented (2D variable '//trim(tpfields(1)%cmnhname)//')' )
end if
case (3)

WAUTELET Philippe
committed
if ( Any( tpfields(1)%ndimlist(1) == [ NMNHDIM_NI, NMNHDIM_NI_U, NMNHDIM_NI_V, NMNHDIM_BUDGET_CART_NI, &
NMNHDIM_BUDGET_CART_NI_U, NMNHDIM_BUDGET_CART_NI_V ] ) &
.and. Any( tpfields(1)%ndimlist(2) == [ NMNHDIM_NJ, NMNHDIM_NJ_U, NMNHDIM_NJ_V, NMNHDIM_BUDGET_CART_NJ, &
NMNHDIM_BUDGET_CART_NJ_U, NMNHDIM_BUDGET_CART_NJ_V ] ) &
.and. Any( tpfields(1)%ndimlist(3) == [ NMNHDIM_LEVEL, NMNHDIM_LEVEL_W, &
NMNHDIM_BUDGET_CART_LEVEL, NMNHDIM_BUDGET_CART_LEVEL_W ] ) ) then
if ( Size( tpfields ) /= 1 ) call Print_msg( NVERB_FATAL, 'IO', 'Write_diachro_nc4', &
'wrong size of tpfields (variable '//trim(tpfields(1)%cmnhname)//')' )

WAUTELET Philippe
committed
call Diachro_one_field_write_nc4( tzfile, tpbudiachro, tpfields(1), pvar, [ 1, 2, 3 ], gsplit, gdistributed, &

WAUTELET Philippe
committed
iil, iih, ijl, ijh, ikl, ikh )

WAUTELET Philippe
committed
else if ( Any(tpfields(1)%ndimlist(1) == [ NMNHDIM_BUDGET_CART_NI, NMNHDIM_BUDGET_CART_NI_U, NMNHDIM_BUDGET_CART_NI_V ]) &
.and. Any(tpfields(1)%ndimlist(2) == [ NMNHDIM_BUDGET_CART_NJ, NMNHDIM_BUDGET_CART_NJ_U, NMNHDIM_BUDGET_CART_NJ_V ]) &

WAUTELET Philippe
committed
.and. tpfields(1)%ndimlist(6) == NMNHDIM_BUDGET_NGROUPS ) then

WAUTELET Philippe
committed
! Loop on the processes
do ji = 1, Size( pvar, 6 )

WAUTELET Philippe
committed
call Diachro_one_field_write_nc4( tzfile, tpbudiachro, tpfields(ji), pvar(:,:,:,:,:,ji:ji), [ 1, 2 ], &
gsplit, gdistributed, iil, iih, ijl, ijh, ikl, ikh )

WAUTELET Philippe
committed
end do
else if ( Any ( tpfields(1)%ndimlist(1) == [ NMNHDIM_BUDGET_CART_NI, NMNHDIM_BUDGET_CART_NI_U, &
NMNHDIM_BUDGET_CART_NI_V ] ) &
.and. Any ( tpfields(1)%ndimlist(3) == [ NMNHDIM_BUDGET_CART_LEVEL, NMNHDIM_BUDGET_CART_LEVEL_W ] ) &
.and. tpfields(1)%ndimlist(6) == NMNHDIM_BUDGET_NGROUPS ) then

WAUTELET Philippe
committed
! Loop on the processes
do ji = 1, Size( pvar, 6 )

WAUTELET Philippe
committed
call Diachro_one_field_write_nc4( tzfile, tpbudiachro, tpfields(ji), pvar(:,:,:,:,:,ji:ji), [ 1, 3 ], gsplit, gdistributed )

WAUTELET Philippe
committed
end do
else if ( Any ( tpfields(1)%ndimlist(2) == [ NMNHDIM_BUDGET_CART_NJ, NMNHDIM_BUDGET_CART_NJ_U, &
NMNHDIM_BUDGET_CART_NJ_V ] ) &
.and. Any ( tpfields(1)%ndimlist(3) == [ NMNHDIM_BUDGET_CART_LEVEL, NMNHDIM_BUDGET_CART_LEVEL_W ] ) &
.and. tpfields(1)%ndimlist(6) == NMNHDIM_BUDGET_NGROUPS ) then

WAUTELET Philippe
committed
! Loop on the processes
do ji = 1, Size( pvar, 6 )

WAUTELET Philippe
committed
call Diachro_one_field_write_nc4( tzfile, tpbudiachro, tpfields(ji), pvar(:,:,:,:,:,ji:ji), [ 2, 3 ], gsplit, gdistributed )

WAUTELET Philippe
committed
end do

WAUTELET Philippe
committed
else if ( ( tpfields(1)%ndimlist(3) == NMNHDIM_BUDGET_MASK_LEVEL &
.or. tpfields(1)%ndimlist(3) == NMNHDIM_BUDGET_MASK_LEVEL_W ) &
.and. tpfields(1)%ndimlist(4) == NMNHDIM_BUDGET_TIME &
.and. tpfields(1)%ndimlist(5) == NMNHDIM_BUDGET_MASK_NBUMASK ) then
!Correspond to Store_one_budget_rho (MASK)
if ( Size( tpfields ) /= 1 ) call Print_msg( NVERB_FATAL, 'IO', 'Write_diachro_nc4', &
'wrong size of tpfields (variable '//trim(tpfields(1)%cmnhname)//')' )

WAUTELET Philippe
committed
call Diachro_one_field_write_nc4( tzfile, tpbudiachro, tpfields(1), pvar, [ 3, 4, 5 ], gsplit, gdistributed, &

WAUTELET Philippe
committed
iil, iih, ijl, ijh, ikl, ikh )

WAUTELET Philippe
committed
else if ( tpfields(1)%ndimlist(3) == NMNHDIM_BUDGET_LES_LEVEL &
.and. ( tpfields(1)%ndimlist(4) == NMNHDIM_BUDGET_LES_TIME &
.or. tpfields(1)%ndimlist(4) == NMNHDIM_BUDGET_LES_AVG_TIME ) &
.and. tpfields(1)%ndimlist(6) == NMNHDIM_BUDGET_LES_MASK ) then
if ( nles_masks /= Size( pvar, 6 ) ) &
call Print_msg( NVERB_FATAL, 'IO', 'Write_diachro_nc4', &
'last dimension size of pvar is not equal to nles_masks (variable ' &
// Trim( tpfields(1)%cmnhname ) // ')' )

WAUTELET Philippe
committed
! Loop on the processes
do ji = 1, Size( pvar, 6 )

WAUTELET Philippe
committed
call Diachro_one_field_write_nc4( tzfile, tpbudiachro, tpfields(ji), pvar(:,:,:,:,:,ji:ji), [ 3, 4 ], gsplit, gdistributed )
end do
else if ( tpfields(1)%ndimlist(3) == NMNHDIM_BUDGET_LES_LEVEL &
.and. ( tpfields(1)%ndimlist(4) == NMNHDIM_BUDGET_LES_TIME &
.or. tpfields(1)%ndimlist(4) == NMNHDIM_BUDGET_LES_AVG_TIME ) &
.and. tpfields(1)%ndimlist(6) == NMNHDIM_BUDGET_TERM ) then

WAUTELET Philippe
committed
! Loop on the processes
do ji = 1, Size( pvar, 6 )

WAUTELET Philippe
committed
call Diachro_one_field_write_nc4( tzfile, tpbudiachro, tpfields(ji), pvar(:,:,:,:,:,ji:ji), [ 3, 4 ], gsplit, gdistributed )

WAUTELET Philippe
committed
else if ( tpfields(1)%ndimlist(3) == NMNHDIM_BUDGET_LES_LEVEL &
.and. ( tpfields(1)%ndimlist(4) == NMNHDIM_BUDGET_LES_TIME &
.or. tpfields(1)%ndimlist(4) == NMNHDIM_BUDGET_LES_AVG_TIME ) &
.and. tpfields(1)%ndimlist(5) == NMNHDIM_BUDGET_LES_PDF ) then
if ( Size( tpfields ) /= 1 ) call Print_msg( NVERB_FATAL, 'IO', 'Write_diachro_nc4', &
'wrong size of tpfields (variable '//trim(tpfields(1)%cmnhname)//')' )
call Diachro_one_field_write_nc4( tzfile, tpbudiachro, tpfields(1), pvar, [ 3, 4, 5 ], gsplit, gdistributed )

WAUTELET Philippe
committed
else if ( tpfields(1)%ndimlist(3) == NMNHDIM_BUDGET_LES_LEVEL &
.and. ( tpfields(1)%ndimlist(4) == NMNHDIM_BUDGET_LES_TIME &
.or. tpfields(1)%ndimlist(4) == NMNHDIM_BUDGET_LES_AVG_TIME ) &
.and. tpfields(1)%ndimlist(5) == NMNHDIM_BUDGET_LES_SV ) then
if ( Size( tpfields ) /= 1 ) call Print_msg( NVERB_FATAL, 'IO', 'Write_diachro_nc4', &
'wrong size of tpfields (variable '//trim(tpfields(1)%cmnhname)//')' )

WAUTELET Philippe
committed
call Diachro_one_field_write_nc4( tzfile, tpbudiachro, tpfields(1), pvar, [ 3, 4, 5 ], gsplit, gdistributed, &

WAUTELET Philippe
committed
iil, iih, ijl, ijh, ikl, ikh )

WAUTELET Philippe
committed
else if ( tpfields(1)%ndimlist(1) == NMNHDIM_SPECTRA_2PTS_NI &
.and. tpfields(1)%ndimlist(3) == NMNHDIM_SPECTRA_LEVEL &
.and. ( tpfields(1)%ndimlist(4) == NMNHDIM_BUDGET_LES_TIME &
.or. tpfields(1)%ndimlist(4) == NMNHDIM_BUDGET_LES_AVG_TIME ) ) then
if ( Size( tpfields ) /= 1 ) call Print_msg( NVERB_FATAL, 'IO', 'Write_diachro_nc4', &
'wrong size of tpfields (variable '//trim(tpfields(1)%cmnhname)//')' )

WAUTELET Philippe
committed
call Diachro_one_field_write_nc4( tzfile, tpbudiachro, tpfields(1), pvar, [ 1, 3, 4 ], gsplit, gdistributed, &

WAUTELET Philippe
committed
iil, iih, ijl, ijh, ikl, ikh )
else if ( tpfields(1)%ndimlist(2) == NMNHDIM_SPECTRA_2PTS_NJ &
.and. tpfields(1)%ndimlist(3) == NMNHDIM_SPECTRA_LEVEL &
.and. ( tpfields(1)%ndimlist(4) == NMNHDIM_BUDGET_LES_TIME &
.or. tpfields(1)%ndimlist(4) == NMNHDIM_BUDGET_LES_AVG_TIME ) ) then
if ( Size( tpfields ) /= 1 ) call Print_msg( NVERB_FATAL, 'IO', 'Write_diachro_nc4', &
'wrong size of tpfields (variable '//trim(tpfields(1)%cmnhname)//')' )

WAUTELET Philippe
committed
call Diachro_one_field_write_nc4( tzfile, tpbudiachro, tpfields(1), pvar, [ 2, 3, 4 ], gsplit, gdistributed, &

WAUTELET Philippe
committed
iil, iih, ijl, ijh, ikl, ikh )
else if ( ( tpfields(1)%ndimlist(3) == NMNHDIM_LEVEL .or. tpfields(1)%ndimlist(3) == NMNHDIM_LEVEL_W ) &
.and. tpfields(1)%ndimlist(4) == NMNHDIM_FLYER_TIME &
.and. tpfields(1)%ndimlist(6) == NMNHDIM_FLYER_PROC ) then
!Correspond to FLYER_DIACHRO
!Create local time dimension
if ( isp == tzfile%nmaster_rank) then

WAUTELET Philippe
committed
istatus = NF90_INQ_DIMID( ilevelids(NLVL_GROUP), 'time_flyer', idimid )
if ( istatus == NF90_NOERR ) then
!Dimension already exists, check that it is not changed
istatus = NF90_INQUIRE_DIMENSION( ilevelids(NLVL_GROUP), idimid, len = ilen )
if ( ilen /= Int( Size( pvar, 4), kind = CDFINT ) ) &
call Print_msg( NVERB_FATAL, 'IO', 'Write_diachro_nc4', 'time_flyer dimension has changed' )
else
!Dimension does not exist yet, create it
istatus = NF90_DEF_DIM( ilevelids(NLVL_GROUP), 'time_flyer', Int( Size( pvar, 4), kind = CDFINT ), idimid )
if ( istatus /= NF90_NOERR ) &
call IO_Err_handle_nc4( istatus, 'Write_diachro_nc4', 'NF90_DEF_DIM', Trim( tpfields(1)%cmnhname ) )
end if
end if

WAUTELET Philippe
committed
! Loop on the processes
do ji = 1, Size( pvar, 6 )

WAUTELET Philippe
committed
call Diachro_one_field_write_nc4( tzfile, tpbudiachro, tpfields(ji), pvar(:,:,:,:,:,ji:ji), [ 3, 4 ], gsplit, gdistributed )
else if ( ( tpfields(1)%ndimlist(3) == NMNHDIM_LEVEL .or. tpfields(1)%ndimlist(3) == NMNHDIM_LEVEL_W ) &
.and. tpfields(1)%ndimlist(4) == NMNHDIM_PROFILER_TIME &
.and. tpfields(1)%ndimlist(6) == NMNHDIM_PROFILER_PROC ) then
!Correspond to PROFILER_DIACHRO_n

WAUTELET Philippe
committed
! Loop on the processes
do ji = 1, Size( pvar, 6 )

WAUTELET Philippe
committed
call Diachro_one_field_write_nc4( tzfile, tpbudiachro, tpfields(ji), pvar(:,:,:,:,:,ji:ji), [ 3, 4 ], gsplit, gdistributed )

WAUTELET Philippe
committed
else if ( ( tpfields(1)%ndimlist(3) == NMNHDIM_SERIES_LEVEL .or. tpfields(1)%ndimlist(3) == NMNHDIM_SERIES_LEVEL_W ) &
.and. tpfields(1)%ndimlist(4) == NMNHDIM_SERIES_TIME &
.and. tpfields(1)%ndimlist(6) == NMNHDIM_SERIES_PROC ) then
!Correspond to PROFILER_DIACHRO_n

WAUTELET Philippe
committed
! Loop on the processes
do ji = 1, Size( pvar, 6 )

WAUTELET Philippe
committed
call Diachro_one_field_write_nc4( tzfile, tpbudiachro, tpfields(ji), pvar(:,:,:,:,:,ji:ji), [ 3, 4 ], gsplit, gdistributed )
end do
else if ( ( tpfields(1)%ndimlist(1) == NMNHDIM_NI .or. tpfields(1)%ndimlist(1) == NMNHDIM_NI_U ) &
.and. tpfields(1)%ndimlist(4) == NMNHDIM_SERIES_TIME &
.and. tpfields(1)%ndimlist(6) == NMNHDIM_SERIES_PROC ) then
!Correspond to PROFILER_DIACHRO_n

WAUTELET Philippe
committed
! Loop on the processes
do ji = 1, Size( pvar, 6 )

WAUTELET Philippe
committed
call Diachro_one_field_write_nc4( tzfile, tpbudiachro, tpfields(ji), pvar(:,:,:,:,:,ji:ji), [ 1, 4 ], gsplit, gdistributed )
else if ( ( tpfields(1)%ndimlist(2) == NMNHDIM_NJ .or. tpfields(1)%ndimlist(2) == NMNHDIM_NJ_U ) &
.and. tpfields(1)%ndimlist(4) == NMNHDIM_SERIES_TIME &
.and. tpfields(1)%ndimlist(6) == NMNHDIM_SERIES_PROC ) then
! Loop on the processes
do ji = 1, Size( pvar, 6 )

WAUTELET Philippe
committed
call Diachro_one_field_write_nc4( tzfile, tpbudiachro, tpfields(ji), pvar(:,:,:,:,:,ji:ji), [ 2, 4 ], gsplit, gdistributed )
end do

WAUTELET Philippe
committed
else if ( tpfields(1)%ndimlist(4) == NMNHDIM_BUDGET_TIME &
.and. tpfields(1)%ndimlist(5) == NMNHDIM_BUDGET_MASK_NBUMASK &
.and. tpfields(1)%ndimlist(6) == NMNHDIM_BUDGET_NGROUPS ) then

WAUTELET Philippe
committed
! Loop on the processes

WAUTELET Philippe
committed
do ji = 1, Size( pvar, 6 )

WAUTELET Philippe
committed
call Diachro_one_field_write_nc4( tzfile, tpbudiachro, tpfields(ji), pvar(:,:,:,:,:,ji:ji), [ 4, 5 ], gsplit, gdistributed )

WAUTELET Philippe
committed
end do
else
call Print_msg( NVERB_FATAL, 'IO', 'Write_diachro_nc4', &

WAUTELET Philippe
committed
'case not yet implemented (3D variable '//trim(tpfields(1)%cmnhname)//')' )
end if
case (4)

WAUTELET Philippe
committed
if ( Any( tpfields(1)%ndimlist(1) == [ NMNHDIM_BUDGET_CART_NI, NMNHDIM_BUDGET_CART_NI_U, NMNHDIM_BUDGET_CART_NI_V ] ) &
.and. Any( tpfields(1)%ndimlist(2) == [ NMNHDIM_BUDGET_CART_NJ, NMNHDIM_BUDGET_CART_NJ_U, NMNHDIM_BUDGET_CART_NJ_V ] ) &
.and. Any( tpfields(1)%ndimlist(3) == [ NMNHDIM_BUDGET_CART_LEVEL,NMNHDIM_BUDGET_CART_LEVEL_W ] ) &
.and. tpfields(1)%ndimlist(6) == NMNHDIM_BUDGET_NGROUPS ) then
!Correspond to Store_one_budget (CART)
! Loop on the processes

WAUTELET Philippe
committed
do ji = 1, Size( pvar, 6 )

WAUTELET Philippe
committed
call Diachro_one_field_write_nc4( tzfile, tpbudiachro, tpfields(ji), pvar(:,:,:,:,:,ji:ji), [ 1, 2, 3 ], &
gsplit, gdistributed, iil, iih, ijl, ijh, ikl, ikh )

WAUTELET Philippe
committed
elseif ( ( tpfields(1)%ndimlist(3) == NMNHDIM_BUDGET_MASK_LEVEL &
.or. tpfields(1)%ndimlist(3) == NMNHDIM_BUDGET_MASK_LEVEL_W ) &

WAUTELET Philippe
committed
.and. tpfields(1)%ndimlist(4) == NMNHDIM_BUDGET_TIME &
.and. tpfields(1)%ndimlist(5) == NMNHDIM_BUDGET_MASK_NBUMASK &
.and. tpfields(1)%ndimlist(6) == NMNHDIM_BUDGET_NGROUPS ) then
!Correspond to Store_one_budget (MASK)
! Loop on the processes

WAUTELET Philippe
committed
do ji = 1, Size( pvar, 6 )

WAUTELET Philippe
committed
call Diachro_one_field_write_nc4( tzfile, tpbudiachro, tpfields(ji), pvar(:,:,:,:,:,ji:ji), [ 3, 4, 5 ], &
gsplit, gdistributed, iil, iih, ijl, ijh, ikl, ikh )

WAUTELET Philippe
committed
else if ( tpfields(1)%ndimlist(3) == NMNHDIM_BUDGET_LES_LEVEL &
.and. ( tpfields(1)%ndimlist(4) == NMNHDIM_BUDGET_LES_TIME &
.or. tpfields(1)%ndimlist(4) == NMNHDIM_BUDGET_LES_AVG_TIME ) &
.and. tpfields(1)%ndimlist(5) == NMNHDIM_BUDGET_LES_SV &
.and. tpfields(1)%ndimlist(6) == NMNHDIM_BUDGET_LES_MASK ) then
if ( nles_masks /= Size( pvar, 6 ) ) &
call Print_msg( NVERB_FATAL, 'IO', 'Write_diachro_nc4', &
'last dimension size of pvar is not equal to nles_masks (variable ' &
// Trim( tpfields(1)%cmnhname ) // ')' )

WAUTELET Philippe
committed
! Loop on the processes
do ji = 1, Size( pvar, 6 )

WAUTELET Philippe
committed
call Diachro_one_field_write_nc4( tzfile, tpbudiachro, tpfields(ji), pvar(:,:,:,:,:,ji:ji), [ 3, 4, 5 ], &
gsplit, gdistributed, iil, iih, ijl, ijh, ikl, ikh )

WAUTELET Philippe
committed
else if ( tpfields(1)%ndimlist(3) == NMNHDIM_BUDGET_LES_LEVEL &
.and. ( tpfields(1)%ndimlist(4) == NMNHDIM_BUDGET_LES_TIME &
.or. tpfields(1)%ndimlist(4) == NMNHDIM_BUDGET_LES_AVG_TIME ) &
.and. tpfields(1)%ndimlist(5) == NMNHDIM_BUDGET_LES_SV &
.and. tpfields(1)%ndimlist(6) == NMNHDIM_BUDGET_TERM ) then

WAUTELET Philippe
committed
! Loop on the processes
do ji = 1, Size( pvar, 6 )

WAUTELET Philippe
committed
call Diachro_one_field_write_nc4( tzfile, tpbudiachro, tpfields(ji), pvar(:,:,:,:,:,ji:ji), [ 3, 4, 5 ], &
gsplit, gdistributed, iil, iih, ijl, ijh, ikl, ikh )

WAUTELET Philippe
committed
else if ( tpfields(1)%ndimlist(1) == NMNHDIM_SPECTRA_SPEC_NI &
.and. tpfields(1)%ndimlist(3) == NMNHDIM_SPECTRA_LEVEL &
.and. ( tpfields(1)%ndimlist(4) == NMNHDIM_BUDGET_LES_TIME &
.or. tpfields(1)%ndimlist(4) == NMNHDIM_BUDGET_LES_AVG_TIME ) &
.and. tpfields(1)%ndimlist(5) == NMNHDIM_COMPLEX ) then
!Correspond to LES_DIACHRO_SPEC
if ( Size( tpfields ) /= 1 ) call Print_msg( NVERB_FATAL, 'IO', 'Write_diachro_nc4', &
'wrong size of tpfields (variable '//trim(tpfields(1)%cmnhname)//')' )

WAUTELET Philippe
committed
call Diachro_one_field_write_nc4( tzfile, tpbudiachro, tpfields(1), pvar, [ 1, 3, 4, 5 ], gsplit, gdistributed )

WAUTELET Philippe
committed
else if ( tpfields(1)%ndimlist(2) == NMNHDIM_SPECTRA_SPEC_NJ &
.and. tpfields(1)%ndimlist(3) == NMNHDIM_SPECTRA_LEVEL &
.and. ( tpfields(1)%ndimlist(4) == NMNHDIM_BUDGET_LES_TIME &
.or. tpfields(1)%ndimlist(4) == NMNHDIM_BUDGET_LES_AVG_TIME ) &
.and. tpfields(1)%ndimlist(5) == NMNHDIM_COMPLEX ) then
!Correspond to LES_DIACHRO_SPEC
if ( Size( tpfields ) /= 1 ) call Print_msg( NVERB_FATAL, 'IO', 'Write_diachro_nc4', &
'wrong size of tpfields (variable '//trim(tpfields(1)%cmnhname)//')' )

WAUTELET Philippe
committed
call Diachro_one_field_write_nc4( tzfile, tpbudiachro, tpfields(1), pvar, [ 2, 3, 4, 5 ], gsplit, gdistributed )
else
call Print_msg( NVERB_FATAL, 'IO', 'Write_diachro_nc4', &

WAUTELET Philippe
committed
'case not yet implemented (4D variable '//trim(tpfields(1)%cmnhname)//')' )
end if
! case (5)
! case (6)
case default
do ji = 1, Size( pvar, 6 )

WAUTELET Philippe
committed
call Diachro_one_field_write_nc4( tzfile, tpbudiachro, tpfields(ji), pvar(:,:,:,:,:,ji:ji), [ 1, 2, 3, 4, 5 ], &

WAUTELET Philippe
committed
gsplit, gdistributed )

WAUTELET Philippe
committed
end select
1463
1464
1465
1466
1467
1468
1469
1470
1471
1472
1473
1474
1475
1476
1477
1478
1479
1480
1481
1482
1483
1484
1485
1486
1487
1488
1489
1490
1491
!Write X and Y position of the flyer
if ( Present( tpflyer ) ) then
if ( lcartesian ) then
ystdnameprefix = 'plane'
else
ystdnameprefix = 'projection'
endif
tzfield%cmnhname = 'X'
tzfield%cstdname = Trim( ystdnameprefix ) // '_x_coordinate'
tzfield%clongname = 'x-position of the flyer'
tzfield%cunits = 'm'
tzfield%cdir = '--'
tzfield%ccomment = ''
tzfield%ngrid = 0
tzfield%ntype = TYPEREAL
tzfield%ltimedep = .false.
tzfield%ndims = 1
tzfield%ndimlist(1) = NMNHDIM_FLYER_TIME
tzfield%ndimlist(2:) = NMNHDIM_UNUSED
call IO_Field_write( tzfile, tzfield, tpflyer%x )
tzfield%cmnhname = 'Y'
tzfield%cstdname = Trim( ystdnameprefix ) // '_y_coordinate'
tzfield%clongname = 'y-position of the flyer'
call IO_Field_write( tzfile, tzfield, tpflyer%y )
end if
end subroutine Write_diachro_nc4

WAUTELET Philippe
committed

WAUTELET Philippe
committed

WAUTELET Philippe
committed
subroutine Diachro_one_field_write_nc4( tpfile, tpbudiachro, tpfield, pvar, kdims, osplit, odistributed, &
kil, kih, kjl, kjh, kkl, kkh )

WAUTELET Philippe
committed
use modd_budget, only: NLVL_CATEGORY, NLVL_GROUP, NLVL_SHAPE, nbutshift, nbusubwrite, tbudiachrometadata

WAUTELET Philippe
committed
use modd_field, only: tfielddata, tfield_metadata_base
use modd_io, only: isp, tfiledata
use modd_parameters, only: jphext

WAUTELET Philippe
committed

WAUTELET Philippe
committed
use mode_io_field_write, only: IO_Field_create, IO_Field_write, IO_Field_write_box

WAUTELET Philippe
committed

WAUTELET Philippe
committed
type(tfiledata), intent(in) :: tpfile !File to write

WAUTELET Philippe
committed
type(tbudiachrometadata), intent(in) :: tpbudiachro

WAUTELET Philippe
committed
1507
1508
1509
1510
1511
1512
1513
1514
1515
1516
1517
1518
1519
1520
1521
1522
1523
1524
1525
1526
1527
class(tfield_metadata_base), intent(in) :: tpfield
real, dimension(:,:,:,:,:,:), intent(in) :: pvar
integer, dimension(:), intent(in) :: kdims !List of indices of dimensions to use
logical, intent(in) :: osplit
logical, intent(in) :: odistributed !.T. if data is distributed among all processes
integer, intent(in), optional :: kil, kih
integer, intent(in), optional :: kjl, kjh
integer, intent(in), optional :: kkl, kkh
integer :: idims
integer :: ibutimepos
integer :: ji
integer, dimension(size(shape(pvar))) :: isizes_alldims
integer, dimension(:), allocatable :: ioffset
integer, dimension(:), allocatable :: isizes
real :: zdata0d
real, dimension(:), allocatable :: zdata1d
real, dimension(:,:), allocatable :: zdata2d
real, dimension(:,:,:), allocatable :: zdata3d
real, dimension(:,:,:,:), allocatable :: zdata4d
real, dimension(:,:,:,:,:), allocatable :: zdata5d
type(tfielddata) :: tzfield

WAUTELET Philippe
committed
idims = Size( kdims )
if ( odistributed ) then

WAUTELET Philippe
committed
if ( idims /= 2 .and. idims /= 3 ) &

WAUTELET Philippe
committed
call Print_msg( NVERB_FATAL, 'IO', 'Diachro_one_field_write_nc4', &
'odistributed=.true. not allowed for dims/=3, field: ' //Trim( tzfield%cmnhname ) )

WAUTELET Philippe
committed
if ( tpbudiachro%clevels(NLVL_SHAPE) /= 'Cartesian' ) &

WAUTELET Philippe
committed
call Print_msg( NVERB_FATAL, 'IO', 'Diachro_one_field_write_nc4', &
'odistributed=.true. not allowed for shape/=cartesian, field: ' //Trim( tzfield%cmnhname ) )

WAUTELET Philippe
committed
end if
if ( osplit ) then
if ( idims > 3 ) &
call Print_msg( NVERB_FATAL, 'IO', 'Diachro_one_field_write_nc4', &
'osplit=.true. not allowed for dims>3, field: ' //Trim( tzfield%cmnhname ) )

WAUTELET Philippe
committed
if ( tpbudiachro%clevels(NLVL_CATEGORY) /= 'Budgets' ) &

WAUTELET Philippe
committed
call Print_msg( NVERB_FATAL, 'IO', 'Diachro_one_field_write_nc4', &
'osplit=.true. not allowed for category/=budget, field: ' //Trim( tzfield%cmnhname ) )

WAUTELET Philippe
committed
1550
1551
1552
1553
1554
1555
1556
1557
1558
1559
1560
1561
1562
1563
1564
1565
1566
1567
1568
1569
1570
1571
1572
1573
1574
1575
1576
1577
1578
1579
1580
1581
1582
1583
1584
1585
1586
1587
1588
1589
1590
1591
1592
1593
1594
1595
1596
1597
1598
1599
1600
1601
1602
1603
1604
1605
1606
1607
1608
1609
1610
1611
1612
1613
1614
1615
1616
1617
1618
end if
Allocate( isizes(idims) )
isizes_alldims = 1
do ji = 1, idims
isizes(ji) = Size( pvar, kdims(ji) )
isizes_alldims(kdims(ji)) = isizes(ji)
end do
call Prepare_diachro_write( tpfield, tzfield, kdims, osplit, odistributed, ibutimepos )
NDIMS: select case( idims )
case ( 0 ) NDIMS
zdata0d = pvar(1, 1, 1, 1, 1, 1)
if ( osplit ) then
!Create the metadata of the field (has to be done only once)
if ( nbutshift == 1 ) call IO_Field_create( tpfile, tzfield )
call IO_Field_write( tpfile, tzfield, [ zdata0d ], koffset= [ ( nbutshift - 1 ) * nbusubwrite ] )
else
call IO_Field_write( tpfile, tzfield, zdata0d )
end if
case ( 1 ) NDIMS
! Copy selected dimensions into zdata (+ auto-allocate it)
zdata1d = Reshape ( pvar(1:isizes_alldims(1), 1:isizes_alldims(2), 1:isizes_alldims(3), &
1:isizes_alldims(4), 1:isizes_alldims(5), 1:isizes_alldims(6)), &
isizes(1:1) )
if ( osplit ) then
!Create the metadata of the field (has to be done only once)
if ( nbutshift == 1 ) call IO_Field_create( tpfile, tzfield )
Allocate( ioffset( tzfield%ndims ) )
ioffset(:) = 0
ioffset(ibutimepos) = ( nbutshift - 1 ) * nbusubwrite
if ( tzfield%ndims == idims ) then
!No time dimension was added in Prepare_diachro_write
call IO_Field_write( tpfile, tzfield, zdata1d(:), koffset = ioffset )
else if ( tzfield%ndims == ( idims + 1 ) ) then
!A time dimension was added in Prepare_diachro_write
call IO_Field_write( tpfile, tzfield, Reshape( zdata1d, [ Size(zdata1d,1), 1 ] ), &
koffset = ioffset )
else
call Print_msg( NVERB_FATAL, 'IO', 'Diachro_one_field_write_nc4', &
'probable bug for ' //Trim( tzfield%cmnhname ) )
end if
else !.not. osplit
call IO_Field_write( tpfile, tzfield, zdata1d )
end if
case ( 2 ) NDIMS
! Copy selected dimensions into zdata (+ auto-allocate it)
zdata2d = Reshape ( pvar(1:isizes_alldims(1), 1:isizes_alldims(2), 1:isizes_alldims(3), &
1:isizes_alldims(4), 1:isizes_alldims(5), 1:isizes_alldims(6)), &
isizes(1:2) )
if ( osplit ) then
!Create the metadata of the field (has to be done only once)
if ( nbutshift == 1 ) call IO_Field_create( tpfile, tzfield )
Allocate( ioffset( tzfield%ndims ) )
ioffset(:) = 0
ioffset(ibutimepos) = ( nbutshift - 1 ) * nbusubwrite

WAUTELET Philippe
committed
if ( odistributed ) then
if ( tzfield%ndims == idims ) then
!No time dimension was added in Prepare_diachro_write
call IO_Field_write_box( tpfile, tzfield, 'BUDGET', &
zdata2d, &
kil + jphext, kih + jphext, kjl + jphext, kjh + jphext, &
koffset = ioffset )
else if ( tzfield%ndims == ( idims + 1 ) ) then
!A time dimension was added in Prepare_diachro_write
call IO_Field_write_box( tpfile, tzfield, 'BUDGET', &
Reshape( zdata2d, [ Size(zdata2d,1), Size(zdata2d,2), 1 ] ), &
kil + jphext, kih + jphext, kjl + jphext, kjh + jphext, &
koffset = ioffset )
else
call Print_msg( NVERB_FATAL, 'IO', 'Diachro_one_field_write_nc4', &
'probable bug for ' //Trim( tzfield%cmnhname ) )
end if

WAUTELET Philippe
committed
else

WAUTELET Philippe
committed
!Data is already collected on the master process
if ( tzfield%ndims == idims ) then
!No time dimension was added in Prepare_diachro_write
call IO_Field_write( tpfile, tzfield, zdata2d(:,:), koffset = ioffset )
else if ( tzfield%ndims == ( idims + 1 ) ) then
!A time dimension was added in Prepare_diachro_write
call IO_Field_write( tpfile, tzfield, Reshape( zdata2d, [ Size(zdata2d,1), Size(zdata2d,2), 1 ] ), &
koffset = ioffset )
else
call Print_msg( NVERB_FATAL, 'IO', 'Diachro_one_field_write_nc4', &
'probable bug for ' //Trim( tzfield%cmnhname ) )
end if

WAUTELET Philippe
committed
end if
else !.not. osplit

WAUTELET Philippe
committed
if ( odistributed ) then
call IO_Field_write_box( tpfile, tzfield, 'BUDGET', zdata2d, &
kil + jphext, kih + jphext, kjl + jphext, kjh + jphext )
else
!Data is already collected on the master process
call IO_Field_write( tpfile, tzfield, zdata2d )
end if

WAUTELET Philippe
committed
end if
case ( 3 ) NDIMS
! Copy selected dimensions into zdata (+ auto-allocate it)
zdata3d = Reshape ( pvar(1:isizes_alldims(1), 1:isizes_alldims(2), 1:isizes_alldims(3), &
1:isizes_alldims(4), 1:isizes_alldims(5), 1:isizes_alldims(6)), &
isizes(1:3) )
if ( osplit ) then
!Create the metadata of the field (has to be done only once)
if ( nbutshift == 1 ) call IO_Field_create( tpfile, tzfield )
Allocate( ioffset( tzfield%ndims ) )
ioffset(:) = 0
ioffset(ibutimepos) = ( nbutshift - 1 ) * nbusubwrite
if ( odistributed ) then
if ( tzfield%ndims == idims ) then
!No time dimension was added in Prepare_diachro_write

WAUTELET Philippe
committed
call IO_Field_write_box( tpfile, tzfield, 'BUDGET', &
zdata3d, &
kil + jphext, kih + jphext, kjl + jphext, kjh + jphext, &
koffset = ioffset )

WAUTELET Philippe
committed
else if ( tzfield%ndims == ( idims + 1 ) ) then
!A time dimension was added in Prepare_diachro_write

WAUTELET Philippe
committed
call IO_Field_write_box( tpfile, tzfield, 'BUDGET', &
Reshape( zdata3d, [ Size(zdata3d,1), Size(zdata3d,2), Size(zdata3d,3), 1 ] ), &
kil + jphext, kih + jphext, kjl + jphext, kjh + jphext, &
koffset = ioffset )

WAUTELET Philippe
committed
else
call Print_msg( NVERB_FATAL, 'IO', 'Diachro_one_field_write_nc4', &

WAUTELET Philippe
committed
'probable bug for ' //Trim( tzfield%cmnhname ) )

WAUTELET Philippe
committed
end if
else
!Data is already collected on the master process
if ( tzfield%ndims == idims ) then
!No time dimension was added in Prepare_diachro_write
call IO_Field_write( tpfile, tzfield, zdata3d(:,:,:), koffset = ioffset )
else if ( tzfield%ndims == ( idims + 1 ) ) then
!A time dimension was added in Prepare_diachro_write
call IO_Field_write( tpfile, tzfield, Reshape( zdata3d, [ Size(zdata3d,1), Size(zdata3d,2), Size(zdata3d,3), 1 ] ), &
koffset = ioffset )
else
call Print_msg( NVERB_FATAL, 'IO', 'Diachro_one_field_write_nc4', &

WAUTELET Philippe
committed
'probable bug for ' //Trim( tzfield%cmnhname ) )

WAUTELET Philippe
committed
1704
1705
1706
1707
1708
1709
1710
1711
1712
1713
1714
1715
1716
1717
1718
1719
1720
1721
1722
1723
1724
1725
1726
1727
1728
1729
1730
1731
1732
1733
1734
1735
1736
1737
1738
1739
1740
1741
1742
1743
1744
1745
1746
end if
end if
else !.not. osplit
if ( odistributed ) then
call IO_Field_write_box( tpfile, tzfield, 'BUDGET', zdata3d, &
kil + jphext, kih + jphext, kjl + jphext, kjh + jphext )
else
!Data is already collected on the master process
call IO_Field_write( tpfile, tzfield, zdata3d )
end if
end if
case ( 4 ) NDIMS
! Copy selected dimensions into zdata (+ auto-allocate it)
zdata4d = Reshape ( pvar(1:isizes_alldims(1), 1:isizes_alldims(2), 1:isizes_alldims(3), &
1:isizes_alldims(4), 1:isizes_alldims(5), 1:isizes_alldims(6)), &
isizes(1:4) )
call IO_Field_write( tpfile, tzfield, zdata4d )
case ( 5 ) NDIMS
! Copy selected dimensions into zdata (+ auto-allocate it)
zdata5d = Reshape ( pvar(1:isizes_alldims(1), 1:isizes_alldims(2), 1:isizes_alldims(3), &
1:isizes_alldims(4), 1:isizes_alldims(5), 1:isizes_alldims(6)), &
isizes(1:5) )
call IO_Field_write( tpfile, tzfield, zdata5d )
case default NDIMS
call Print_msg( NVERB_ERROR, 'IO', 'Diachro_one_field_write_nc4', Trim( tpfile%cname ) // &
': unsupported number of dimensions' )
return
end select NDIMS
end subroutine Diachro_one_field_write_nc4
subroutine Prepare_diachro_write( tpfieldin, tpfieldout, kdims, osplit, odistributed, kbutimepos )
use modd_field, only: NMNHDIM_BUDGET_TIME, NMNHDIM_UNUSED, NMNHMAXDIMS, tfielddata, tfield_metadata_base

WAUTELET Philippe
committed
class(tfield_metadata_base), intent(in) :: tpfieldin
type(tfielddata), intent(out) :: tpfieldout
integer, dimension(:), intent(in) :: kdims ! List of indices of dimensions to use

WAUTELET Philippe
committed
logical, intent(in) :: osplit
logical, intent(in) :: odistributed ! .true. if data is distributed among all the processes
integer, intent(out) :: kbutimepos

WAUTELET Philippe
committed
integer :: idims

WAUTELET Philippe
committed
integer :: jdim

WAUTELET Philippe
committed
idims = Size( kdims )
if ( idims > NMNHMAXDIMS ) call Print_msg( NVERB_FATAL, 'IO', 'Prepare_diachro_write', &
'kdims is too big for ' //Trim( tpfieldin%cmnhname ) )
tpfieldout%cmnhname = tpfieldin%cmnhname
tpfieldout%cstdname = tpfieldin%cstdname
tpfieldout%clongname = tpfieldin%clongname
tpfieldout%cunits = tpfieldin%cunits

WAUTELET Philippe
committed
if ( .not. odistributed ) then
tpfieldout%cdir = '--'
else
tpfieldout%cdir = 'XY'
end if

WAUTELET Philippe
committed
tpfieldout%ccomment = tpfieldin%ccomment
tpfieldout%ngrid = tpfieldin%ngrid
tpfieldout%ntype = tpfieldin%ntype
tpfieldout%ltimedep = .false.
tpfieldout%ndims = idims
do jdim = 1, idims
tpfieldout%ndimlist(jdim) = tpfieldin%ndimlist(kdims(jdim))
end do
tpfieldout%ndimlist(idims + 1:) = NMNHDIM_UNUSED

WAUTELET Philippe
committed
kbutimepos = -1

WAUTELET Philippe
committed
!Add budget time dimension if required

WAUTELET Philippe
committed
if ( osplit ) then
do jdim = 1, idims
if ( tpfieldout%ndimlist(jdim) == NMNHDIM_BUDGET_TIME ) then
kbutimepos = jdim
exit
end if
end do
!budget time dimension was not found => add it
if ( kbutimepos == -1 ) then
idims = idims + 1
if ( idims > NMNHMAXDIMS ) call Print_msg( NVERB_FATAL, 'IO', 'Prepare_diachro_write', &
'impossible to add NMNHDIM_BUDGET_TIME dimension for ' //Trim( tpfieldin%cmnhname ) )
kbutimepos = idims
tpfieldout%ndims = idims
tpfieldout%ndimlist(idims) = NMNHDIM_BUDGET_TIME

WAUTELET Philippe
committed
end if
end if

WAUTELET Philippe
committed

WAUTELET Philippe
committed
end subroutine Prepare_diachro_write

WAUTELET Philippe
committed
subroutine Att_write_c0( hlevel, kgrpid, hattname, hdata )
use NETCDF, only: NF90_GET_ATT, NF90_INQUIRE_ATTRIBUTE, NF90_PUT_ATT, NF90_CHAR, NF90_GLOBAL, NF90_NOERR
use modd_precision, only: CDFINT

WAUTELET Philippe
committed
use mode_io_tools_nc4, only: IO_Err_handle_nc4, IO_Mnhname_clean

WAUTELET Philippe
committed
character(len=*), intent(in) :: hlevel
integer(kind=CDFINT), intent(in) :: kgrpid
character(len=*), intent(in) :: hattname
character(len=*), intent(in) :: hdata

WAUTELET Philippe
committed
character(len=Len(hattname)) :: yattname

WAUTELET Philippe
committed
character(len=:), allocatable :: yatt
integer(kind=CDFINT) :: ilen
integer(kind=CDFINT) :: istatus
integer(kind=CDFINT) :: itype

WAUTELET Philippe
committed
call IO_Mnhname_clean( hattname, yattname )
istatus = NF90_INQUIRE_ATTRIBUTE( kgrpid, NF90_GLOBAL, yattname, xtype = itype, len = ilen )

WAUTELET Philippe
committed
if (istatus == NF90_NOERR ) then

WAUTELET Philippe
committed
call Print_msg( NVERB_DEBUG, 'IO', 'Write_diachro_nc4', 'attribute ' // yattname // ' already exists for ' // Trim( hlevel ) )

WAUTELET Philippe
committed
if ( itype /= NF90_CHAR ) then

WAUTELET Philippe
committed
call Print_msg( NVERB_ERROR, 'IO', 'Write_diachro_nc4', 'type for attribute ' // yattname // &

WAUTELET Philippe
committed
' has changed for ' // Trim( hlevel ) )
return
end if
Allocate( character(len=ilen) :: yatt )

WAUTELET Philippe
committed
istatus = NF90_GET_ATT( kgrpid, NF90_GLOBAL, yattname, yatt )

WAUTELET Philippe
committed
if ( yatt == Trim( hdata ) ) then

WAUTELET Philippe
committed
call Print_msg( NVERB_DEBUG, 'IO', 'Write_diachro_nc4', 'attribute ' // yattname // ' is unchanged for ' // Trim( hlevel ) )

WAUTELET Philippe
committed
!If unchanged, no need to write it again => return
return
else

WAUTELET Philippe
committed
cmnhmsg(1) = 'attribute ' // yattname // ' has changed for ' // Trim( hlevel )

WAUTELET Philippe
committed
cmnhmsg(2) = yatt // ' -> ' // Trim( hdata )
call Print_msg( NVERB_WARNING, 'IO', 'Write_diachro_nc4' )
end if
end if

WAUTELET Philippe
committed
istatus = NF90_PUT_ATT( kgrpid, NF90_GLOBAL, yattname, Trim( hdata ) )
if (istatus /= NF90_NOERR ) &

WAUTELET Philippe
committed
call IO_Err_handle_nc4( istatus, 'Write_diachro_nc4', 'NF90_PUT_ATT', Trim( yattname ) // ' for '// Trim( hlevel ) // ' group' )
end subroutine Att_write_c0

WAUTELET Philippe
committed
subroutine Att_write_i0( hlevel, kgrpid, hattname, kdata )
use NETCDF, only: NF90_GET_ATT, NF90_INQUIRE_ATTRIBUTE, NF90_PUT_ATT, NF90_GLOBAL, NF90_NOERR

WAUTELET Philippe
committed
use modd_precision, only: CDFINT, MNHINT_NF90

WAUTELET Philippe
committed
use mode_io_tools_nc4, only: IO_Err_handle_nc4, IO_Mnhname_clean

WAUTELET Philippe
committed
character(len=*), intent(in) :: hlevel
integer(kind=CDFINT), intent(in) :: kgrpid
character(len=*), intent(in) :: hattname
integer, intent(in) :: kdata

WAUTELET Philippe
committed
character(len=Len(hattname)) :: yattname

WAUTELET Philippe
committed
integer :: iatt
integer(kind=CDFINT) :: ilen
integer(kind=CDFINT) :: istatus

WAUTELET Philippe
committed
integer(kind=CDFINT) :: itype

WAUTELET Philippe
committed
call IO_Mnhname_clean( hattname, yattname )
istatus = NF90_INQUIRE_ATTRIBUTE( kgrpid, NF90_GLOBAL, yattname, xtype = itype, len = ilen )

WAUTELET Philippe
committed
if (istatus == NF90_NOERR ) then

WAUTELET Philippe
committed
call Print_msg( NVERB_DEBUG, 'IO', 'Write_diachro_nc4', 'attribute ' // yattname // ' already exists for ' // Trim( hlevel ) )

WAUTELET Philippe
committed
if ( itype /= MNHINT_NF90 ) then

WAUTELET Philippe
committed
call Print_msg( NVERB_ERROR, 'IO', 'Write_diachro_nc4', 'type for attribute ' // yattname // &

WAUTELET Philippe
committed
' has changed for ' // Trim( hlevel ) )
return
end if
if ( ilen /= 1 ) then

WAUTELET Philippe
committed
call Print_msg( NVERB_ERROR, 'IO', 'Write_diachro_nc4', 'size of attribute ' // yattname // &

WAUTELET Philippe
committed
' has changed for ' // Trim( hlevel ) )
return
end if

WAUTELET Philippe
committed
istatus = NF90_GET_ATT( kgrpid, NF90_GLOBAL, yattname, iatt )

WAUTELET Philippe
committed
if ( iatt == kdata ) then

WAUTELET Philippe
committed
call Print_msg( NVERB_DEBUG, 'IO', 'Write_diachro_nc4', 'attribute ' // yattname // ' is unchanged for ' // Trim( hlevel ) )

WAUTELET Philippe
committed
!If unchanged, no need to write it again => return
return
else

WAUTELET Philippe
committed
cmnhmsg(1) = 'attribute ' // yattname // ' has changed for ' // Trim( hlevel )

WAUTELET Philippe
committed
Write( cmnhmsg(2), '( I0, " -> ", I0 )' ) iatt, kdata
call Print_msg( NVERB_WARNING, 'IO', 'Write_diachro_nc4' )
end if
end if

WAUTELET Philippe
committed
istatus = NF90_PUT_ATT( kgrpid, NF90_GLOBAL, yattname, kdata )
if (istatus /= NF90_NOERR ) &

WAUTELET Philippe
committed
call IO_Err_handle_nc4( istatus, 'Write_diachro_nc4', 'NF90_PUT_ATT', Trim( yattname ) // ' for '// Trim( hlevel ) // ' group' )
end subroutine Att_write_i0

WAUTELET Philippe
committed
subroutine Att_write_x0( hlevel, kgrpid, hattname, pdata )
use NETCDF, only: NF90_GET_ATT, NF90_INQUIRE_ATTRIBUTE, NF90_PUT_ATT, NF90_GLOBAL, NF90_NOERR

WAUTELET Philippe
committed
use modd_precision, only: CDFINT, MNHREAL_NF90

WAUTELET Philippe
committed
use mode_io_tools_nc4, only: IO_Err_handle_nc4, IO_Mnhname_clean

WAUTELET Philippe
committed
character(len=*), intent(in) :: hlevel
integer(kind=CDFINT), intent(in) :: kgrpid
character(len=*), intent(in) :: hattname
real, intent(in) :: pdata

WAUTELET Philippe
committed
character(len=Len(hattname)) :: yattname

WAUTELET Philippe
committed
integer(kind=CDFINT) :: ilen
integer(kind=CDFINT) :: istatus

WAUTELET Philippe
committed
integer(kind=CDFINT) :: itype
real :: zatt

WAUTELET Philippe
committed
call IO_Mnhname_clean( hattname, yattname )
istatus = NF90_INQUIRE_ATTRIBUTE( kgrpid, NF90_GLOBAL, yattname, xtype = itype, len = ilen )

WAUTELET Philippe
committed
if (istatus == NF90_NOERR ) then

WAUTELET Philippe
committed
call Print_msg( NVERB_DEBUG, 'IO', 'Write_diachro_nc4', 'attribute ' // yattname // ' already exists for ' // Trim( hlevel ) )

WAUTELET Philippe
committed
if ( itype /= MNHREAL_NF90 ) then

WAUTELET Philippe
committed
call Print_msg( NVERB_ERROR, 'IO', 'Write_diachro_nc4', 'type for attribute ' // yattname // &

WAUTELET Philippe
committed
' has changed for ' // Trim( hlevel ) )
return
end if
if ( ilen /= 1 ) then

WAUTELET Philippe
committed
call Print_msg( NVERB_ERROR, 'IO', 'Write_diachro_nc4', 'size of attribute ' // yattname // &

WAUTELET Philippe
committed
' has changed for ' // Trim( hlevel ) )
return
end if

WAUTELET Philippe
committed
istatus = NF90_GET_ATT( kgrpid, NF90_GLOBAL, yattname, zatt )

WAUTELET Philippe
committed
if ( zatt == pdata ) then

WAUTELET Philippe
committed
call Print_msg( NVERB_DEBUG, 'IO', 'Write_diachro_nc4', 'attribute ' // yattname // ' is unchanged for ' // Trim( hlevel ) )

WAUTELET Philippe
committed
!If unchanged, no need to write it again => return
return
else

WAUTELET Philippe
committed
cmnhmsg(1) = 'attribute ' // yattname // ' has changed for ' // Trim( hlevel )

WAUTELET Philippe
committed
Write( cmnhmsg(2), '( F15.7, " -> ", F15.7 )' ) zatt, pdata
call Print_msg( NVERB_WARNING, 'IO', 'Write_diachro_nc4' )
end if
end if

WAUTELET Philippe
committed
istatus = NF90_PUT_ATT( kgrpid, NF90_GLOBAL, yattname, pdata )
if (istatus /= NF90_NOERR ) &

WAUTELET Philippe
committed
call IO_Err_handle_nc4( istatus, 'Write_diachro_nc4', 'NF90_PUT_ATT', Trim( yattname ) // ' for '// Trim( hlevel ) // ' group' )
end subroutine Att_write_x0

WAUTELET Philippe
committed
subroutine Move_to_next_level( kpreviouslevelid, gpreviousleveldefined, oleveluse, hlevelname, gleveldefined, klevelid )
use NETCDF, only: NF90_DEF_GRP, NF90_INQ_NCID, NF90_NOERR
use modd_precision, only: CDFINT

WAUTELET Philippe
committed
use mode_io_tools_nc4, only: IO_Err_handle_nc4, IO_Mnhname_clean

WAUTELET Philippe
committed
integer(kind=CDFINT), intent(in) :: kpreviouslevelid
logical, intent(in) :: gpreviousleveldefined
logical, intent(in) :: oleveluse

WAUTELET Philippe
committed
! character(len=*), intent(inout) :: hlevelname

WAUTELET Philippe
committed
character(len=*), intent(in) :: hlevelname

WAUTELET Philippe
committed
logical, intent(out) :: gleveldefined
integer(kind=CDFINT), intent(out) :: klevelid

WAUTELET Philippe
committed
character(len=Len(hlevelname)) :: ylevelname

WAUTELET Philippe
committed
integer(kind=CDFINT) :: istatus

WAUTELET Philippe
committed
call IO_Mnhname_clean( hlevelname, ylevelname )

WAUTELET Philippe
committed
if ( oleveluse ) then

WAUTELET Philippe
committed
istatus = NF90_INQ_NCID( kpreviouslevelid, Trim( ylevelname ), klevelid )

WAUTELET Philippe
committed
if ( istatus == NF90_NOERR ) then
gleveldefined = .true.
else
gleveldefined = .false.

WAUTELET Philippe
committed
istatus = NF90_DEF_GRP( kpreviouslevelid, Trim( ylevelname ), klevelid )

WAUTELET Philippe
committed
if ( istatus /= NF90_NOERR ) &

WAUTELET Philippe
committed
call IO_Err_handle_nc4( istatus, 'Move_to_next_level', 'NF90_DEF_GRP', 'for ' // Trim( ylevelname ) )