Re: [Haskell-beginners] Fwd: Averaging a string of numbers

There is some magic here that I'm not quite groking. Sorry for my
slowness; but I seem to be missing a step:
This is how I'd expect liftA2 to work ( and is why I didn't use lift
in my initial response ):
*Main Control.Applicative Data.Monoid> liftA2 max Nothing (Just 1)
Nothing
I expected all the magic to be the applicative class instance that was
generated for Maximum by the GeneralizedNewtypeDeriving extension, but
why do these not work?
*Main Control.Applicative Data.Monoid> liftA2 max (Maximum Nothing)
(Maximum (Just 1))
Maximum {getMaximum = Nothing}
*Main Control.Applicative Data.Monoid> mempty `mappend` (Maximum (Just
1)) `mappend` (Maximum (Just 2) )
Maximum {getMaximum = Nothing}
When this obviously works just fine?
*Main Control.Applicative Data.Monoid> main
Stats {ct = Sum {getSum = 0}, sm = Sum {getSum = 0.0}, mn = Minimum
{getMinimum = Nothing}, mx = Maximum {getMaximum = Nothing}}
Stats {ct = Sum {getSum = 1}, sm = Sum {getSum = 1.0}, mn = Minimum
{getMinimum = Just 1.0}, mx = Maximum {getMaximum = Just 1.0}}
Stats {ct = Sum {getSum = 1}, sm = Sum {getSum = 2.0}, mn = Minimum
{getMinimum = Just 2.0}, mx = Maximum {getMaximum = Just 2.0}}
Stats {ct = Sum {getSum = 2}, sm = Sum {getSum = 3.0}, mn = Minimum
{getMinimum = Just 1.0}, mx = Maximum {getMaximum = Just 2.0}}
Sorry if I am missing something obvious and this question is really silly!
On Mon, Dec 12, 2011 at 5:18 PM, Dean Herington & Elizabeth Lacey
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]

At 9:04 PM +1000 12/12/11, Ben Kolera wrote:
There is some magic here that I'm not quite groking. Sorry for my slowness; but I seem to be missing a step:
Oops, my bad! The magic is an inadequate test ;-). Thanks for spotting the bug! The magic I was trying to leverage is this instance from Data.Monoid: instance Monoid a => Monoid (Maybe a) where mempty = Nothing Nothing `mappend` m = m m `mappend` Nothing = m Just m1 `mappend` Just m2 = Just (m1 `mappend` m2) I've implemented it correctly (I hope) for `Minimum` in my revised code below. But the usability suffers with that approach. Better, I think, is to keep the original interface and implement it correctly (as I hope to have done for `Maximum`). You'll note that it incorporates essentially your original `chooseMaybe` function.
This is how I'd expect liftA2 to work ( and is why I didn't use lift in my initial response ):
*Main Control.Applicative Data.Monoid> liftA2 max Nothing (Just 1) Nothing
I expected all the magic to be the applicative class instance that was generated for Maximum by the GeneralizedNewtypeDeriving extension, but why do these not work?
*Main Control.Applicative Data.Monoid> liftA2 max (Maximum Nothing) (Maximum (Just 1)) Maximum {getMaximum = Nothing} *Main Control.Applicative Data.Monoid> mempty `mappend` (Maximum (Just 1)) `mappend` (Maximum (Just 2) ) Maximum {getMaximum = Nothing}
When this obviously works just fine?
*Main Control.Applicative Data.Monoid> main Stats {ct = Sum {getSum = 0}, sm = Sum {getSum = 0.0}, mn = Minimum {getMinimum = Nothing}, mx = Maximum {getMaximum = Nothing}} Stats {ct = Sum {getSum = 1}, sm = Sum {getSum = 1.0}, mn = Minimum {getMinimum = Just 1.0}, mx = Maximum {getMaximum = Just 1.0}} Stats {ct = Sum {getSum = 1}, sm = Sum {getSum = 2.0}, mn = Minimum {getMinimum = Just 2.0}, mx = Maximum {getMaximum = Just 2.0}} Stats {ct = Sum {getSum = 2}, sm = Sum {getSum = 3.0}, mn = Minimum {getMinimum = Just 1.0}, mx = Maximum {getMaximum = Just 2.0}}
Sorry if I am missing something obvious and this question is really silly!
On Mon, Dec 12, 2011 at 5:18 PM, Dean Herington & Elizabeth Lacey
wrote: 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]
{-# LANGUAGE GeneralizedNewtypeDeriving #-} import Data.Monoid import Control.Applicative import Control.Monad -- The approach taken for `Minimum` is for illustration. -- The approach taken for `Maximum` is recommended for its better usability. -- | Monoid under minimum. newtype Minimum a = Minimum { getMinimum :: a } deriving (Eq, Ord, Read, Show) instance Ord a => Monoid (Minimum a) where mempty = error "There is no minimum of an empty set." Minimum x `mappend` Minimum y = Minimum (x `min` y) -- | 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 Maximum (Just x) `mappend` Maximum (Just y) = Maximum $ Just (x `max` y) Maximum x `mappend` Maximum y = Maximum $ x `mplus` y data Stats = Stats { ct :: Sum Int, sm :: Sum Double, mn :: Maybe (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) (Just (Minimum v)) (Maximum (Just v)) st0, st1, st2, st3 :: Stats st0 = mempty st1 = mkStats 1 st2 = mkStats 2 st3 = st1 `mappend` st2 st4 = st0 `mappend` st1 main = mapM_ print [st0, st1, st2, st3, st4]

On Mon, Dec 12, 2011 at 10:00:35AM -0500, Dean Herington wrote:
At 9:04 PM +1000 12/12/11, Ben Kolera wrote:
There is some magic here that I'm not quite groking. Sorry for my slowness; but I seem to be missing a step:
Oops, my bad! The magic is an inadequate test ;-). Thanks for spotting the bug!
The magic I was trying to leverage is this instance from Data.Monoid:
instance Monoid a => Monoid (Maybe a) where mempty = Nothing Nothing `mappend` m = m m `mappend` Nothing = m Just m1 `mappend` Just m2 = Just (m1 `mappend` m2)
Just to provide a bit of perspective at this point: the reason this Monoid instance for (Maybe a) can't be used is because it requires a to be an instance of Monoid... but numbers under min/max DON'T form a Monoid since there is no identity element. In fact, that's the very reason why we wanted to use Maybe in the first place! I therefore consider this Monoid instance for Maybe "broken". What we really want is instance Semigroup a => Monoid (Maybe a) where ... A semigroup is a set with an associative binary operation (but not necessarily an identity element). Maybe turns any semigroup into a monoid by adding a "synthetic" identity element (namely, Nothing). In fact, such an instance is provided in the 'semigroups' package on Hackage (except for a type called Option instead of Maybe). Maybe someday we will get semigroups defined in 'base'. That would be nice. -Brent

I'll just chime in at this point to say thanks everyone for the discussion. It's a little above my level of comprehension, so I'll continue digesting what's been offered here. I don't have anything else to add but if you all want to continue refining the solution I'm sure many of us would benefit :) Thanks again -- -Michael Wayne Goodman
participants (4)
-
Ben Kolera
-
Brent Yorgey
-
Dean Herington
-
goodman.m.w@gmail.com