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 (Ben Kolera)
   2. Re:  Pattern matching over functions (Ken KAWAMOTO)
   3. Re:  Fwd: Averaging a string of numbers (Dean Herington)
   4. Re:  Pattern matching over functions (Giacomo Tesio)
   5. Re:  Pattern matching over functions (Ertugrul S?ylemez)


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

Message: 1
Date: Mon, 12 Dec 2011 21:04:52 +1000
From: Ben Kolera <ben.kol...@gmail.com>
Subject: Re: [Haskell-beginners] Fwd: Averaging a string of numbers
To: "Dean Herington & Elizabeth Lacey" <heringtonla...@mindspring.com>
Cc: beginners@haskell.org
Message-ID:
        <CAPmqrp96gY7sRmPQcb3qGuM1QZ7bh_FBaMaq3nSJ_=mu1bz...@mail.gmail.com>
Content-Type: text/plain; charset=ISO-8859-1

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
<heringtonla...@mindspring.com> 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]



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

Message: 2
Date: Mon, 12 Dec 2011 23:11:05 +0900
From: Ken KAWAMOTO <kentaro.kawam...@gmail.com>
Subject: Re: [Haskell-beginners] Pattern matching over functions
To: Felipe Almeida Lessa <felipe.le...@gmail.com>,      Daniel Fischer
        <daniel.is.fisc...@googlemail.com>
Cc: simplex.math.servi...@gmail.com, beginners@haskell.org
Message-ID:
        <CAGByEKNRjQ4GXZWcKfebtozv3q=QDXL_2A=iGufuzb=w8jg...@mail.gmail.com>
Content-Type: text/plain; charset=ISO-8859-1

Thanks Daniel and Felipe.

To me it seems Daniel's foo doesn't break referential transparency
because we can always replace "foo (+3) (\x -> x+3)" with "Yay :)",
and "foo (+3) somethingWhichIsTheSameButCan'tBeProvedToBe" with "Nay
:(".
It just contradicts our expectation that "foo (+3) something....ToBe"
should return "Yay :)", which is another story.

On Mon, Dec 12, 2011 at 3:24 AM, Daniel Fischer
<daniel.is.fisc...@googlemail.com> wrote:
> But it's not possible, so all you have is that for some pairs of functions
> equality can be proved, for some pairs it can be disproved and for some
> pairs, it cannot be decided.

This sounds like quite common function behavior as we can see in
  f n = if n > 0 then True else if n == 0 then f 0 else False
Here, f 1 returns True, f (-1) returns False, and f 0 doesn't
terminate. Still f is referentially transparent, isn't it?
If so, why can we not say foo is referentially transparent?

On the other hand, I agree that Felipe's obviouslyEqual is not
referentially transparent as its behavior really depends on how
Haskell runtime allocates functions (thunks) in memory.


I understand that we cannot construct such a function that always
terminates and decides functions' equality (equality defined as, say,
"f1 equals f2 iff f1 x == f2 x for any argument x").
But again, does this have something to do with referential transparency?
Isn't this just because it's undecidable problem?



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

Message: 3
Date: Mon, 12 Dec 2011 10:00:35 -0500
From: Dean Herington <heringtonla...@mindspring.com>
Subject: Re: [Haskell-beginners] Fwd: Averaging a string of numbers
To: Ben Kolera <ben.kol...@gmail.com>
Cc: beginners@haskell.org
Message-ID: <a06240801cb0bc403bc00@[10.0.1.3]>
Content-Type: text/plain; charset="us-ascii" ; format="flowed"

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
><heringtonla...@mindspring.com> 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]



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

Message: 4
Date: Mon, 12 Dec 2011 16:47:37 +0100
From: Giacomo Tesio <giac...@tesio.it>
Subject: Re: [Haskell-beginners] Pattern matching over functions
To: Felipe Almeida Lessa <felipe.le...@gmail.com>
Cc: simplex.math.servi...@gmail.com, beginners@haskell.org,     Daniel
        Fischer <daniel.is.fisc...@googlemail.com>
Message-ID:
        <cahl7psfrnozrz3hjp+nbbhowwkmvdyjotdimgubisx_mg2l...@mail.gmail.com>
Content-Type: text/plain; charset="utf-8"

Actually, it looks like a dirty technological impedence.

Haskell makes functions first class values, but still data values are
easier to handle than functions, since their type can implement the Eq
typeclass, thanks to constructor matches.


While I got your point, I'm still  wondering about functions as constructor
of other functions thus it would be possible to match to the function name
like we do for type constructors.
I can't have an insight about why this is wrong. Why can't we treat
functions as constructors?


The point, I guess, is that this would assign a kind of "identity" to
morphisms that belong to a category. I see how this might be wrong:
functions can be equivalent exactly like integers, but they are just harder
to implement.

Thus we are back to the dirty technical problem of evaluating function
equivalence.


Giacomo

On Mon, Dec 12, 2011 at 2:27 AM, Felipe Almeida Lessa <
felipe.le...@gmail.com> wrote:

> On Sun, Dec 11, 2011 at 8:09 PM, Graham Gill <math.simp...@gmail.com>
> wrote:
> > Excellent, thanks Daniel and Felipe.
> >
> > We don't even need to invoke infinite or undecidable problems, since it's
> > easy to construct equal functions for which determining equality would be
> > prohibitively expensive. If then you can only check equality for some
> > functions, because you want compilation to finish, say, within the
> > programmer's lifetime, you lose referential transparency.
>
> Note that the time isn't spent on compilation time, but on run time!
> Which is actually worse ;-).
>
> Also note that it is possible to imagine something like
>
>  obviouslyEqual :: a -> a -> Bool
>
> where 'obviouslyEqual x y' is 'True' when it's easy to see that they
> are equal or 'False' if you can't decide.  Actually, with GHC you may
> say
>
>  {-# LANGUAGE MagicHash #-}
>
>  import GHC.Exts
>
>  obviouslyEqual :: a -> a -> Bool
>  obviouslyEqual a b =
>    case I# (reallyUnsafePtrEquality# a b) of
>      0 -> False
>      _ -> True
>
> However, this functions is *not* referentially transparent (exercise:
> show an example of how obviouslyEqual breaks referential
> transparency).  reallyUnsafePtrEquality# is really unsafe for a reason
> =).
>
> Cheers,
>
> --
> Felipe.
>
> _______________________________________________
> Beginners mailing list
> Beginners@haskell.org
> http://www.haskell.org/mailman/listinfo/beginners
>
-------------- next part --------------
An HTML attachment was scrubbed...
URL: 
<http://www.haskell.org/pipermail/beginners/attachments/20111212/223d11fb/attachment-0001.htm>

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

Message: 5
Date: Mon, 12 Dec 2011 16:58:33 +0100
From: Ertugrul S?ylemez <e...@ertes.de>
Subject: Re: [Haskell-beginners] Pattern matching over functions
To: beginners@haskell.org
Message-ID: <20111212165833.7d867...@angst.streitmacht.eu>
Content-Type: text/plain; charset="us-ascii"

Graham Gill <math.simp...@gmail.com> wrote:

> > > But then we would lose referential transparency.
> >
> > As I understand, this would be against lazy evaluation since it
> > would request to evaluate expressions in lambda, but I don't see how
> > this relates to referential transparency.  Can you elaborate this a
> > little bit?
>
> I second the question.

Referential transparency /requires/ that

    id x = x

even if 'x' is a function, and this can, as Brent already noted,
arbitrarily complicated.  If pattern matching could tell f from id f,
then referential transparency is violated.  The only possible way to
tell f from id f is very unsafe and needs IO, hence not usable in
pattern matching.


Greets,
Ertugrul

-- 
nightmare = unsafePerformIO (getWrongWife >>= sex)
http://ertes.de/
-------------- next part --------------
A non-text attachment was scrubbed...
Name: signature.asc
Type: application/pgp-signature
Size: 836 bytes
Desc: not available
URL: 
<http://www.haskell.org/pipermail/beginners/attachments/20111212/543b59a0/attachment.pgp>

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

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


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

Reply via email to