Send Beginners mailing list submissions to
        beginners@haskell.org

To subscribe or unsubscribe via the World Wide Web, visit
        http://www.haskell.org/mailman/listinfo/beginners
or, via email, send a message with subject or body 'help' to
        beginners-requ...@haskell.org

You can reach the person managing the list at
        beginners-ow...@haskell.org

When replying, please edit your Subject line so it is more specific
than "Re: Contents of Beginners digest..."


Today's Topics:

   1. Re:  Fwd: My first functioning haskell project - a
      steganography utility (Tim Cowlishaw)
   2. Re:  Fwd: My first functioning haskell project    - a
      steganography utility (Brent Yorgey)
   3. Re:  Fwd: My first functioning haskell project - a
      steganography utility (Tim Cowlishaw)
   4. Re:  Fwd: My first functioning haskell project - a
      steganography utility (Tim Cowlishaw)
   5. Re:  Fwd: My first functioning haskell project    - a
      steganography utility (Brent Yorgey)


----------------------------------------------------------------------

Message: 1
Date: Tue, 13 Jul 2010 16:00:28 +0100
From: Tim Cowlishaw <t...@timcowlishaw.co.uk>
Subject: Re: [Haskell-beginners] Fwd: My first functioning haskell
        project - a     steganography utility
To: Brent Yorgey <byor...@seas.upenn.edu>
Cc: beginners@haskell.org
Message-ID: <54d09fe4-c52e-4a97-9d3c-c21a4b963...@timcowlishaw.co.uk>
Content-Type: text/plain; charset=us-ascii


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

------------------------------

Message: 2
Date: Tue, 13 Jul 2010 16:18:59 +0100
From: Brent Yorgey <byor...@seas.upenn.edu>
Subject: Re: [Haskell-beginners] Fwd: My first functioning haskell
        project - a steganography utility
To: beginners@haskell.org
Message-ID: <20100713151859.gb15...@seas.upenn.edu>
Content-Type: text/plain; charset=us-ascii

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


------------------------------

Message: 3
Date: Tue, 13 Jul 2010 16:20:44 +0100
From: Tim Cowlishaw <t...@timcowlishaw.co.uk>
Subject: Re: [Haskell-beginners] Fwd: My first functioning haskell
        project - a     steganography utility
To: Brent Yorgey <byor...@seas.upenn.edu>
Cc: beginners@haskell.org
Message-ID: <9cc8da68-ba0c-44a7-9e9f-0f592b2e3...@timcowlishaw.co.uk>
Content-Type: text/plain; charset=us-ascii


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


------------------------------

Message: 4
Date: Tue, 13 Jul 2010 16:22:48 +0100
From: Tim Cowlishaw <t...@timcowlishaw.co.uk>
Subject: Re: [Haskell-beginners] Fwd: My first functioning haskell
        project - a     steganography utility
To: Brent Yorgey <byor...@seas.upenn.edu>
Cc: beginners@haskell.org
Message-ID: <4bfaa9e7-b8f0-463d-a5c7-f9fe2369d...@timcowlishaw.co.uk>
Content-Type: text/plain; charset=us-ascii

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







------------------------------

Message: 5
Date: Tue, 13 Jul 2010 16:34:26 +0100
From: Brent Yorgey <byor...@seas.upenn.edu>
Subject: Re: [Haskell-beginners] Fwd: My first functioning haskell
        project - a steganography utility
To: beginners@haskell.org
Message-ID: <20100713153425.gc15...@seas.upenn.edu>
Content-Type: text/plain; charset=us-ascii

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


------------------------------

_______________________________________________
Beginners mailing list
Beginners@haskell.org
http://www.haskell.org/mailman/listinfo/beginners


End of Beginners Digest, Vol 25, Issue 30
*****************************************

Reply via email to