[Haskell-cafe] Architecturally flawed
Tillmann Rendel
rendel at daimi.au.dk
Mon Jul 14 02:47:47 EDT 2008
Andrew Coppin wrote:
> [design of a bitwise binary library]
>
> (This would all be so trivial in an OO language. Just make an Encoder
> object that updates its own state internally and talks to a Source
> object and a Destination object for its data...)
I guess it's on the same level of trivialness in Haskell, too, but to be
fair, I haven't tried it... I would proceed as follows:
(1) Try to not shadow names from the mtl or other standard packages.
I choose BitSink and BitSource instead of Reader and Writer.
(2) Select a small number of primitive operations.
I select the operations "read n bits" and "put n bits" as primitive
operations. As interface format, I choose [Boolean], which is
not exactly optimized, but easy to understand.
It is easy to implement operations for single bits, bytes etc. on
top of this operations. We will later include them into the
typeclass, but we will first make the [Boolean]-based operations
correct.
(2) Make BitSink and BitSource composable, e.g., as monad transformers.
The type classes could look like:
class MonadBitSource m where
getBits :: Int -> m [Boolean]
class MonadBitSink m where
putBits :: [Boolean] -> m ()
And we need a lot of trivial instances for the various mtl monad
transformers in the style of:
instance MonadBitSink m => MonadBitSink (ReaderT m) where
putBits = lift . putBits
(3) Write a very simple implementation to (a) check that the typeclasses
makes sense and is implementable and (b) have a test-implementation
for later correctness tests.
The easiest implementation I can think of consists of a state monad
which handles a list of booleans. It could look like this:
newtype BitListT m a = BitListT (StateT [Boolean] m a)
deriving (Functor, Monad, MonadReader r, MonadWriter w, ...)
You should be able to derive all mtl classes except
MonadTransformer, MonadIO and MonadState. Instantiate these
yourself:
instance MonadTransformer BitListT where
lift (BitListT p) = BitListT (lift p)
instance MonadIO m => MonadIO (BitListT m) where
liftIO = lift . liftIO
We want to hide BitListT's state and expose a state in the nested
monad to the user, if there is any.
instance MonadState s m => MonadState s (BitListT m) where
get = lift get
put = lift . put
Finally, the real stuff:
instance MonadBitSink (BitListT m) where
putBits x = BitListT $ modify (++ x)
instance MonadBitSource (BitListT m) where
getBits n = BitListT $ do
result <- gets (take n)
guard (length result == n)
modify (drop n)
return result
runSinkBitListT :: BitListT m a -> m (BitListT ([Boolean], a))
runSinkBitListT (BitListT p) = return $ runState p []
runSourceBitListT :: BitListT m a -> [Boolean] -> m a
runSourceBitListT (BitListT p) bits = return $ evalState p bits
(4) Check the simple implementation
Now we can write quickcheck properties (if you believe in XP, you
can write them before (3), of course) to check our simple
implementation and document the specification. given simple function
runSink = runIdentity . runSinkBitListT and runSource bits =
runIdentity . runSourceBitListT bits, we have such properties as
forall n . forall bits . length bits >= n ==>
length (runSource (getBits n)) == n
forall bits . runSource (getBits (length bits)) == bits
forall a . forall b .
(runSource (liftM2 (++) (getBits a) (getBits b)))
== runSource (getBits (a + b))
forall p . forall q .
runSink p ++ runSink q == runSink (p ++ q)
usw. Use the tricks already mentioned in this thread for the last
property. Don't forget to write properties for the high-level
interface putWord8 etc.
(5) Write a more realistic instance, e.g. by replacing [Boolean] through
(Int, ByteString) and doing clever things in getBits / putBits. Test
this instance both with the existing properties and against the
simple instance, i.e., verify that getBits and setBits means the
same in both monads.
(6) move the high-level functions getWord8 & Co. into the typeclass,
keep the definition as defaults. they are fine for BitListT, but
implement your own versions for the other instance. Quickcheck them
against the properties, against the simple implementation in
BitListT and against the default definitions.
(7) if you need tracing, use liftIO (print ...) and finally understand
what's the point about monad transformer stacks and MonadIO and
why you almost always want to define a monad transformer instead
of a monad.
(8) Write your LZW stuff with
newtype EncoderT s m a = EncoderT (StateT (LZW s) (BitSink m) a)
deriving (a lot of stuff)
(9) Have fun!
Tillmann
More information about the Haskell-Cafe
mailing list