Binary: Put -> Builder
Don Stewart
dons at galois.com
Thu Feb 12 12:51:27 EST 2009
ross:
> On Thu, Feb 12, 2009 at 07:40:21AM -0800, Don Stewart wrote:
> > ross:
> > > On Thu, Feb 12, 2009 at 07:28:07AM -0800, Don Stewart wrote:
> > > > ross:
> > > > > Here's a concrete suggestion: have Data.Binary.Put export the existing
> > > > > function
> > > > >
> > > > > tell :: Builder -> Put
> > > > >
> > > > > and also
> > > > >
> > > > > execPut :: PutM a -> Builder
> > > > > execPut = sndS . unPut
> > > >
> > > > What's the use case?
> > >
> > > Quoting a previous message:
> > > > I imagine one might want to make a Builder for a composite object,
> > > > using the Binary instances of some types. And one might want to go
> > > > the other way too, defining a Binary instance using an existing Builder.
> >
> > Sounds good. Do you just want these exposed as is?
>
> Yes, though Antoine's suggestion of exporting tell as putBuilder may
> be better.
Is this what you're looking for?
Thu Feb 12 09:47:34 PST 2009 Don Stewart <dons at galois.com>
* Expose Builder/Put relationship, courtesy Ross
New patches:
[Expose Builder/Put relationship, courtesy Ross
Don Stewart <dons at galois.com>**20090212174734] {
hunk ./src/Data/Binary/Put.hs 22
, PutM(..)
, runPut
, runPutM
+ , putBuilder
+ , execPut
-- * Flushing the implicit parse state
, flush
hunk ./src/Data/Binary/Put.hs 112
tell b = Put $ PairS () b
{-# INLINE tell #-}
+putBuilder :: Builder -> Put
+putBuilder = tell
+{-# INLINE putBuilder #-}
+
+-- | Run the 'Put' monad
+execPut :: PutM a -> Builder
+execPut = sndS . unPut
+{-# INLINE execPut #-}
+
-- | Run the 'Put' monad with a serialiser
runPut :: Put -> L.ByteString
runPut = toLazyByteString . sndS . unPut
}
More information about the Libraries
mailing list