Wrapping Code
Dominic Steinitz
dominic.steinitz at blueyonder.co.uk
Sat Oct 25 13:28:06 EDT 2003
Does anyone have any views on how to "wrap" code that has been designed to
take input from handles but you now want to take input from strings? I want
to make minimal changes to a module that already works and to code that uses
that module. Here's my thinking below. I'd be interested in other approaches
and pros and cons.
Dominic.
I thought I would only ever have to parse ASN.1 from a socket or a file. So
I have ended up with a lot of functions like this:
getTagOctets :: Handle -> IO OctetStream
getTagOctets h =
do x <- hGetChar h
let y = fromIntegral (ord x) in
if not (testBit y msb)
then return [y]
else do ys <- getTagOctets h
return ((clearBit y msb):ys)
It turns out I need to be able to parse ASN.1 from a string. So my first
thought was:
tagOctets :: String -> (String,OctetStream)
tagOctets s =
let y = fromIntegral $ ord $ head s in
if not $ testBit y $ msb
then (tail s,[y])
else let (s',ys) = tagOctets $ tail s in
(s',((clearBit y msb):ys))
Now this is very similar and the type signature suggests state monads. So my
second thought was this:
tagOctets' :: State String OctetStream
tagOctets'=
do (x:xs) <- get
put xs
let y = fromIntegral (ord x) in
if not (testBit y msb)
then return [y]
else do ys <- tagOctets'
return ((clearBit y msb):ys)
Even nearer but still not good enough. So I went for type class:
class Monad m => Foo m where
get' :: Handle -> m Char
instance Foo IO where
get' = hGetChar
instance Foo (State String) where
get' = \_ -> do (x:xs) <- get; put xs; return x
And now I can write:
tagOctets'' h =
do x <- get' h
let y = fromIntegral (ord x) in
if not (testBit y msb)
then return [y]
else do ys <- tagOctets'' h
return ((clearBit y msb):ys)
I can now use this either with a handle or with a string:
test'' :: (OctetStream,String)
test'' = runState (tagOctets'' stdin) (map (chr . fromIntegral) (encode $
toASN NoTag NULL))
test =
do ofh <- openFile "tst.txt" WriteMode
hPutStr ofh (map (chr . fromIntegral) (encode (toASN NoTag NULL)))
hClose ofh
ifh <- openFile "tst.txt" ReadMode
(ts::OctetStream) <- tagOctets'' ifh
putStrLn $ show ts
More information about the Haskell
mailing list