!--------------------------------------------------------------------- ! Copyright (C) GFD Dennou Club, 2000-2005. All rights reserved. !--------------------------------------------------------------------- != Put AN_VARIABLES ! ! This file is created by "anvarputtype.m4" by m4 command using ! "intrinsic_types.m4". Don't edit each files directly. ! subroutine ANVarPutReal(var, start, count, stride, imap, siz, value, iostat) use dc_types, only: DP use an_types, only: AN_VARIABLE use an_vartable, only: an_variable_entry, vtable_lookup use netcdf_f77, only: nf_noerr, nf_einval, nf_put_varm_Real use an_file, only: anfiledatamode use dc_trace, only: BeginSub, EndSub, DbgMessage implicit none type(AN_VARIABLE), intent(in):: var integer, intent(in):: start(:) integer, intent(in):: count(:) integer, intent(in):: stride(:) integer, intent(in):: imap(:) integer, intent(in):: siz real, intent(in):: value(siz) integer, intent(out):: iostat integer:: ndims type(an_variable_entry):: ent character(len = *), parameter:: subname = "ANVarPutReal" continue call BeginSub(subname) iostat = vtable_lookup(var, ent) if (iostat /= nf_noerr) goto 999 ndims = 0 if (associated(ent%dimids)) ndims = size(ent%dimids) if (min(size(start), size(count), size(stride), size(imap)) < ndims) then iostat = nf_einval goto 999 endif call DbgMessage("f=%d v=%d sta=%*d c=%*d str=%*d imap=%*d", & & i=(/ent%fileid, ent%varid, start, count, stride, imap/), & & n=(/ndims, ndims, ndims, ndims/)) iostat = anfiledatamode(ent%fileid) if (iostat /= nf_noerr) return iostat = nf_put_varm_Real(ent%fileid, ent%varid, & & start, count, stride, imap, value) 999 continue call EndSub(subname, "iostat=%d", i=(/iostat/)) end subroutine ANVarPutReal subroutine ANVarPutDouble(var, start, count, stride, imap, siz, value, iostat) use dc_types, only: DP use an_types, only: AN_VARIABLE use an_vartable, only: an_variable_entry, vtable_lookup use netcdf_f77, only: nf_noerr, nf_einval, nf_put_varm_Double use an_file, only: anfiledatamode use dc_trace, only: BeginSub, EndSub, DbgMessage implicit none type(AN_VARIABLE), intent(in):: var integer, intent(in):: start(:) integer, intent(in):: count(:) integer, intent(in):: stride(:) integer, intent(in):: imap(:) integer, intent(in):: siz real(DP), intent(in):: value(siz) integer, intent(out):: iostat integer:: ndims type(an_variable_entry):: ent character(len = *), parameter:: subname = "ANVarPutDouble" continue call BeginSub(subname) iostat = vtable_lookup(var, ent) if (iostat /= nf_noerr) goto 999 ndims = 0 if (associated(ent%dimids)) ndims = size(ent%dimids) if (min(size(start), size(count), size(stride), size(imap)) < ndims) then iostat = nf_einval goto 999 endif call DbgMessage("f=%d v=%d sta=%*d c=%*d str=%*d imap=%*d", & & i=(/ent%fileid, ent%varid, start, count, stride, imap/), & & n=(/ndims, ndims, ndims, ndims/)) iostat = anfiledatamode(ent%fileid) if (iostat /= nf_noerr) return iostat = nf_put_varm_Double(ent%fileid, ent%varid, & & start, count, stride, imap, value) 999 continue call EndSub(subname, "iostat=%d", i=(/iostat/)) end subroutine ANVarPutDouble !-- ! vi:set readonly sw=4 ts=8: ! !Local Variables: !mode: f90 !buffer-read-only: t !End: ! !++