Beginners Digest, Vol 42, Issue 15

2011-12-12 Thread beginners-request
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 
Subject: Re: [Haskell-beginners] Fwd:  Averaging a string of numbers
To: Ben Kolera , beginners@haskell.org
Message-ID: 
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
*


Beginners Digest, Vol 42, Issue 16

2011-12-12 Thread beginners-request
2, st3, st4]



--

Message: 4
Date: Mon, 12 Dec 2011 16:47:37 +0100
From: Giacomo Tesio 
Subject: Re: [Haskell-beginners] Pattern matching over functions
To: Felipe Almeida Lessa 
Cc: simplex.math.servi...@gmail.com, beginners@haskell.org, Daniel
Fischer 
Message-ID:

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 
> 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 
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  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
*


Beginners Digest, Vol 42, Issue 17

2011-12-12 Thread beginners-request
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:  IO ( stuff ) (Paul Monday)
   2. Re:  Fwd: Averaging a string of numbers (Brent Yorgey)
   3. Re:  Fwd: Averaging a string of numbers (goodman@gmail.com)
   4.  In Search Of a clue... (Defining and making use  of a type)
  (Allen S. Rout)
   5. Re:  In Search Of a clue... (Defining and making use of a
  type) (David McBride)
   6. Re:  In Search Of a clue... (Defining and making use of a
  type) (Thomas)
   7. Re:  In Search Of a clue... (Defining and making use of a
  type) (Brent Yorgey)


--

Message: 1
Date: Mon, 12 Dec 2011 10:16:37 -0700
From: Paul Monday 
Subject: Re: [Haskell-beginners] IO ( stuff )
To: beginners@haskell.org
Cc: dmcbr...@neondsl.com
Message-ID: 
Content-Type: text/plain; charset=windows-1252

Thank you SO much for the discussion.  I've learned quite a bit over the course 
of it.  As one would expect, lifting wasn't my only issue ? I had some rather 
annoying Unbox / Boxed / [] problems with the recursion.

I stepped way back finally this morning to think about the problem and the 
discussion points.  

I was able to make use of laziness with the randomRs function.  randomRs is 
nice since there are no side-effects, I get an "infinite" list of random 
numbers that can easily be broken into rows and matrices lazily.

So, here is how I generated two square matrices with rows and columns = n (some 
other artifacts are included here as well, like the Matrix type I'm using)

data Matrix a = Matrix (V.Vector (U.Vector a))
deriving (Show, Eq)

makematrix :: [Float] -> Int -> Int -> [U.Vector Float]
makematrix xs n 0 = []
makematrix xs n r = (U.fromList $ ys) : makematrix zs n (r - 1)
where (ys, zs) = splitAt n xs

main :: IO ()
main = do
args <- getArgs
let n = read (args !! 0) :: Int
let minrange = read (args !! 1) :: Float
let maxrange = read (args !! 2) :: Float
let s = read (args !! 3) :: Int
let g = mkStdGen s
let range = (minrange, maxrange)
let all = randomRs range g

let ma = Matrix $ (V.fromList (makematrix all n n))
let mb = Matrix $ (V.fromList (makematrix (drop (n*n) all)  n n))

...

As with all Haskell I'm learning, I'm 100% sure there are quite a few better 
ways to write this ;-)

Still, again, I can't thank you enough for the thoughtful discussion on IO and 
randomness.  I have avoided running back to Java with my tail between my legs 
for another day.

Paul Monday
Parallel Scientific, LLC.
paul.mon...@parsci.com




On Dec 9, 2011, at 3:05 PM, David McBride wrote:

> I wish I'd known this when I was first beginning, but it is possible
> to do randomness outside of IO, surprisingly easily.  I like to use
> the monadRandom library, which provides some monads and monad
> transformers for this task.  I too became frustrated when I wrote a
> roguelike but could not figure out how to inject randomness into it
> when I wanted.  A program you would write might be like this:
> 
> data Obstacle = Mon (Int, Int) Monster | Door (Int, Int) | Trap (Int,
> Int) deriving (Show, Enum)
> data Monster = Orc | Wolf | Dragon deriving (Show, Enum)
> 
> main = do
>  print =<< evalRandIO randomObstacle
> 
> randomObstacle :: RandomGen g => Rand g Obstacle
> randomObstacle = do
>  x <- getRandomR (0,2::Int)
>  case x of
>0 -> Mon <$> randomLocation <*> randomMonster
>1 -> Door <$> randomLocation
>2 -> Trap <$> randomLocation
> 
> randomLocation :: RandomGen g => Rand g (Int,Int)
> randomLocation = do
>  x <- getRandomR (0,10)
>  y <- getRandomR (0,10)
>  return (x,y)
> 
> randomMonster :: RandomGen g => Rand g Monster
> randomMonster = do
>  x <- getRandomR (0,2::Int)
>  return $ case x of
>0 -> Orc
>1 -> Dragon
>2 -> Wolf
> 
> This way, even though my randomBlah functions do not have IO in them,
> nor do they pass around a stdGen around, but they can be combined
> willy nilly as needed, and only computed when you want them to.  I
> also could have made Random instances for Obstacle and Monster so that
> I did not have to do the cases in the code, making things easier to
> understand.
> 
> On Fri, Dec 9, 2011 at 3:27 PM, Brent Yorgey  wrote:
>>> Does "impurity" from something
>>> like a random number generator or file I/O have to move it's way all
>>> the way through my code?
>> 
>> No, only through the parts that actually have to do file I/O or
>> generate random numbers or whatever.  However, cleanly separating the
>> IO code