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:  Averaging a string of numbers
      (Dean Herington & Elizabeth Lacey)


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

Message: 1
Date: Mon, 12 Dec 2011 02:18:40 -0500
From: Dean Herington & Elizabeth Lacey <heringtonla...@mindspring.com>
Subject: Re: [Haskell-beginners] Fwd:  Averaging a string of numbers
To: Ben Kolera <ben.kol...@gmail.com>, beginners@haskell.org
Message-ID: <a06240800cb0b587b87a9@[10.0.1.3]>
Content-Type: text/plain; charset="us-ascii" ; format="flowed"

At 8:21 AM +1000 12/12/11, Ben Kolera wrote:
>That is just because you are calling min and max against the Maybe
>rather than on the values inside of your maybes. Max is working
>because there is an instance of Ord for Maybe and
>
>Nothing > Just n > Just ( n + 1 )

You have the right idea, but replace `>` above by `<`.

>
>This is certainly not the most elegant solution ( I am a beginner, too
>) but here is what I would do:
>
>instance Monoid Stats where
>  mempty  = Stats 0 Nothing Nothing 0
>  mappend (Stats sm1 mn1 mx1 len1) (Stats sm2 mn2 mx2 len2) =
>    Stats
>    (sm1 + sm2)
>    (chooseMaybe min mn1 mn2)
>    (chooseMaybe max mx1 mx2)
>    (len1 + len2)
>
>chooseMaybe _ Nothing Nothing   = Nothing
>chooseMaybe _ (Just a) Nothing  = Just a
>chooseMaybe _ Nothing  (Just b) = Just b
>chooseMaybe f (Just a) (Just b) = Just $ f a b
>
>
>Hopefully this quick answer can get you on your way to solving your
>problem and we can both learn a better way of doing it when someone
>optimises my solution. ;)

You've got the principle just right.  Here's a way to cast it that 
makes it apparent that `Stats` is a monoid in a "componentwise" 
fashion.


{-# LANGUAGE GeneralizedNewtypeDeriving #-}

import Data.Monoid
import Control.Applicative


-- | Monoid under minimum.
newtype Minimum a = Minimum { getMinimum :: Maybe a }
     deriving (Eq, Ord, Functor, Applicative, Read, Show)

instance Ord a => Monoid (Minimum a) where
     mempty  = Minimum Nothing
     mappend = liftA2 min

-- | Monoid under maximum.
newtype Maximum a = Maximum { getMaximum :: Maybe a }
     deriving (Eq, Ord, Functor, Applicative, Read, Show)

instance Ord a => Monoid (Maximum a) where
     mempty  = Maximum Nothing
     mappend = liftA2 max

data Stats = Stats {
       ct :: Sum Int,
       sm :: Sum Double,
       mn :: Minimum Double,
       mx :: Maximum Double }
     deriving (Eq, Show, Read)

instance Monoid Stats where
     mempty = Stats mempty mempty mempty mempty
     mappend (Stats ct1 sm1 mn1 mx1) (Stats ct2 sm2 mn2 mx2) =
         Stats (ct1 `mappend` ct2)
               (sm1 `mappend` sm2)
               (mn1 `mappend` mn2)
               (mx1 `mappend` mx2)


mkStats v = Stats (Sum 1) (Sum v) (Minimum (Just v)) (Maximum (Just v))

st0, st1, st2, st3 :: Stats

st0 = mempty
st1 = mkStats 1
st2 = mkStats 2
st3 = st1 `mappend` st2

main = mapM_ print [st0, st1, st2, st3]



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

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


End of Beginners Digest, Vol 42, Issue 15
*****************************************

Reply via email to