My first functioning haskell project - a steganography utility

Hey there all, I've just completed my first functional haskell project - a simple utility for steganography - hiding messages within the least significant bit of another sort of data file. Therefore, I was wondering if any of you had any pointers about how I could refactor or otherwise improve my code? Any input would be greatly appreciated - whether howling great errors or smaller points of "good haskell style". In particular, I'd be really interested in whether my type declarations are correct - for instance, whether I have been to specific or not specific enough in specifying the types of my functions (Integral vs Int, etc). In addition, I keep feeling that my Steganograph 'smells like' a monad and/or functor , as it 'wraps around' a message - however, I'm having trouble defining quite how I could achieve construct a monadic type representing a steganograph. Is my hunch incorrect, or is there a way of doing this that I haven't yet discovered? The sources is here: http://gist.github.com/473862 Cheers, Tim

Hey there all, I've just completed my first functional haskell project - a simple utility for steganography - hiding messages within the least significant bit of another sort of data file. Therefore, I was wondering if any of you had any pointers about how I could refactor or otherwise improve my code? Any input would be greatly appreciated - whether howling great errors or smaller points of "good haskell style". In particular, I'd be really interested in whether my type declarations are correct - for instance, whether I have been to specific or not specific enough in specifying the types of my functions (Integral vs Int, etc). In addition, I keep feeling that my Steganograph 'smells like' a monad and/or functor , as it 'wraps around' a message - however, I'm having trouble defining quite how I could achieve construct a monadic type representing a steganograph. Is my hunch incorrect, or is there a way of doing this that I haven't yet discovered? The sources is here: http://gist.github.com/473862 Cheers, Tim

Hi Tim,
I have a small remark. You can use maybe from Data.Maybe: b -> (a -> b) ->
Maybe a -> b
to create your maybe plus function:
maybePlus x y = maybe 0 id $ liftM2 (+) x y
That is somewhat cleaner.
Greets,
Edgar
On Tue, Jul 13, 2010 at 3:37 PM, Tim Cowlishaw
Hey there all,
I've just completed my first functional haskell project - a simple utility for steganography - hiding messages within the least significant bit of another sort of data file.
Therefore, I was wondering if any of you had any pointers about how I could refactor or otherwise improve my code? Any input would be greatly appreciated - whether howling great errors or smaller points of "good haskell style". In particular, I'd be really interested in whether my type declarations are correct - for instance, whether I have been to specific or not specific enough in specifying the types of my functions (Integral vs Int, etc).
In addition, I keep feeling that my Steganograph 'smells like' a monad and/or functor , as it 'wraps around' a message - however, I'm having trouble defining quite how I could achieve construct a monadic type representing a steganograph. Is my hunch incorrect, or is there a way of doing this that I haven't yet discovered?
The sources is here: http://gist.github.com/473862
Cheers,
Tim
_______________________________________________ Beginners mailing list Beginners@haskell.org http://www.haskell.org/mailman/listinfo/beginners

On 13 Jul 2010, at 15:31, edgar klerks wrote:
You can use maybe from Data.Maybe: b -> (a -> b) -> Maybe a -> b
to create your maybe plus function:
maybePlus x y = maybe 0 id $ liftM2 (+) x y
That is somewhat cleaner.
Aah thanks Edgar - I'd meant to ask about this specifically actually, as addition is a monoid over the real numbers and therefore has an identity element, I was wondering if there was an easier way to generalise it to cope with arguments in the Maybe monad. As far as I can see, this is precisely what you describe above. Therefore, would I be right in saying that your approach can be generalised to any function which forms a monoid over a specific type? I'm imagining something like: maybeMonoid :: (a -> a -> a) -> a -> (Maybe a -> Maybe a -> a) maybeMonoid f identity = maybe identity id $ liftM2 f Thanks for the feedback! Cheers, Tim

Hi Tim,
I am not too deep into category theory. But the Data.Monoid class defines
the identity as mempty. And the binary operation as mappend. So that would
be:
maybePlus = maybe mempty id $ liftM2 (mappend) x y
You only have to define Num as Monoid, because there are more monoids
possible. (Multiplication, addition etc).
That would look something like this:
instance (Num a) => Monoid a where ...
Have a look at the monoid class:
http://haskell.org/ghc/docs/6.12.2/html/libraries/base-4.2.0.1/Data-Monoid.h...
Greets,
Edgar
On Tue, Jul 13, 2010 at 4:39 PM, Tim Cowlishaw
On 13 Jul 2010, at 15:31, edgar klerks wrote:
You can use maybe from Data.Maybe: b -> (a -> b) -> Maybe a -> b
to create your maybe plus function:
maybePlus x y = maybe 0 id $ liftM2 (+) x y
That is somewhat cleaner.
Aah thanks Edgar - I'd meant to ask about this specifically actually, as addition is a monoid over the real numbers and therefore has an identity element, I was wondering if there was an easier way to generalise it to cope with arguments in the Maybe monad. As far as I can see, this is precisely what you describe above. Therefore, would I be right in saying that your approach can be generalised to any function which forms a monoid over a specific type?
I'm imagining something like:
maybeMonoid :: (a -> a -> a) -> a -> (Maybe a -> Maybe a -> a) maybeMonoid f identity = maybe identity id $ liftM2 f
Thanks for the feedback!
Cheers,
Tim

On Tue, Jul 13, 2010 at 03:39:50PM +0100, Tim Cowlishaw wrote:
On 13 Jul 2010, at 15:31, edgar klerks wrote:
You can use maybe from Data.Maybe: b -> (a -> b) -> Maybe a -> b
to create your maybe plus function:
maybePlus x y = maybe 0 id $ liftM2 (+) x y
Note that 'maybe foo id' is better written 'fromMaybe foo'.
maybeMonoid :: (a -> a -> a) -> a -> (Maybe a -> Maybe a -> a) maybeMonoid f identity = maybe identity id $ liftM2 f
If it really is an instance of the Monoid type class then you could just write: maybeMonoid :: (Monoid a) => Maybe a -> Maybe a -> a maybeMonoid x y = fromMaybe mempty $ liftM2 mappend x y -Brent

On 13 Jul 2010, at 15:51, Brent Yorgey wrote:
If it really is an instance of the Monoid type class then you could just write:
maybeMonoid :: (Monoid a) => Maybe a -> Maybe a -> a maybeMonoid x y = fromMaybe mempty $ liftM2 mappend x y
Aha, yes! that's exactly what I was getting at. Presumably I would also then define Instance Monoid Int where mempty = 0 mappend = (+) (of course, Z also forms a monoid under multiplication, but we're not interested in that in this instance) Cheers, Tim

On Tue, Jul 13, 2010 at 04:00:28PM +0100, Tim Cowlishaw wrote:
On 13 Jul 2010, at 15:51, Brent Yorgey wrote:
If it really is an instance of the Monoid type class then you could just write:
maybeMonoid :: (Monoid a) => Maybe a -> Maybe a -> a maybeMonoid x y = fromMaybe mempty $ liftM2 mappend x y
Aha, yes! that's exactly what I was getting at. Presumably I would also then define
Instance Monoid Int where mempty = 0 mappend = (+)
There is already such an instance defined in Data.Monoid, but since (as you note) Int has (at least) two common Monoid instances, the instance is for a newtype wrapper around Int, namely Sum. i.e. it looks like newtype Sum a = Sum { getSum :: a } instance Num a => Monoid (Sum a) where mempty = Sum 0 (Sum x) `mappend` (Sum y) = Sum (x + y) -Brent

On 13 Jul 2010, at 15:51, Brent Yorgey wrote:
If it really is an instance of the Monoid type class then you could just write:
maybeMonoid :: (Monoid a) => Maybe a -> Maybe a -> a maybeMonoid x y = fromMaybe mempty $ liftM2 mappend x y
actually, looking at it again, it'd be something like maybeMonoid :: (Monoid a) => Maybe a -> Maybe a -> a maybeMonoid :: x y = (fromMaybe mempty x) `mappend` (fromMaybe mempty y) Cheers, Tim

-----BEGIN PGP SIGNED MESSAGE----- Hash: SHA1 On 7/13/10 11:20 , Tim Cowlishaw wrote:
actually, looking at it again, it'd be something like
maybeMonoid :: (Monoid a) => Maybe a -> Maybe a -> a maybeMonoid :: x y = (fromMaybe mempty x) `mappend` (fromMaybe mempty y)
Which in turn can be written as:
maybeMonoid = mappend `on` (fromMaybe mempty)
("on" is in Data.Function: "g `on` f" expresses the "\x y -> (f x) `g` (f y)" idiom.) - -- brandon s. allbery [linux,solaris,freebsd,perl] allbery@kf8nh.com system administrator [openafs,heimdal,too many hats] allbery@ece.cmu.edu electrical and computer engineering, carnegie mellon university KF8NH -----BEGIN PGP SIGNATURE----- Version: GnuPG v2.0.10 (Darwin) Comment: Using GnuPG with Mozilla - http://enigmail.mozdev.org/ iEYEARECAAYFAkw8rE8ACgkQIn7hlCsL25XrugCdFLhDalZflo2P8h4XkdCODqAw tcEAn0siZ8CK0+NKay0dz991kBxkvEjh =Actk -----END PGP SIGNATURE-----

On Tue, Jul 13, 2010 at 02:37:17PM +0100, Tim Cowlishaw wrote:
Hey there all,
I've just completed my first functional haskell project - a simple utility for steganography - hiding messages within the least significant bit of another sort of data file.
Therefore, I was wondering if any of you had any pointers about how I could refactor or otherwise improve my code? Any input would be greatly appreciated - whether howling great errors or smaller points of "good haskell style". In particular, I'd be really interested in whether my type declarations are correct - for instance, whether I have been to specific or not specific enough in specifying the types of my functions (Integral vs Int, etc).
- I would write (.&. mask) instead of (flip (.&.) $ mask). - decimalNumber is a funny name for a function that interprets a binary number. =) Also, I'd write it using a left fold, which is (1) nicer than using explicit recursion and (2) more efficient than what you have written, since it avoids having to recompute the length of the remaining elements and a power of 2 every time. Like this: import Data.List (foldl') decimalNumber = foldl' (\n b -> 2*n + b) 0 Also, note that your call to fromIntegral in decimalNumber is unnecessary. - groupInto is available (as 'chunk') from the 'split' package on Hackage. - The 'map fromIntegral' applied to (asBits message) seems to be unnecessary. asBits returns a [Word8] and the result you are looking for is also [Word8]. - You don't need to nest where clauses like that, all the bindings in a where clause can be mutually recursive. Just put everything in the outermost where. As a matter of fact, your code strikes me as a bit where-happy; I would move quite a few of your nested helper functions out to the top level. This makes testing a lot easier. You can always choose to not export them from the module if you want to hide them. - binaryDigits seems overly complicated. How about: binaryDigits = reverse . bits bits 0 = [] bits n = (n .&. 1) : bits (n `div` 2) I have a few other suggestions but I'll stop there for now as I should get back to work. =) Perhaps I'll send more later if no one else does. -Brent

On 13 Jul 2010, at 16:18, Brent Yorgey wrote:
[Lots of great suggestions]
Aah, thanks for all of that! I also should probably be working, so will take a look through later. It all looks like great stuff though. Cheers, Tim
participants (5)
-
Brandon S Allbery KF8NH
-
Brent Yorgey
-
edgar klerks
-
Tim Cowlishaw
-
Tim Cowlishaw