[Haskell-beginners] Drawing Information from a function already defined

aditya siram aditya.siram at gmail.com
Wed Jul 20 18:20:26 CEST 2011


Hi,
For adding constraints I think that using List as a monad is the most
flexible way to go. The first two functions below show the monadic
equivalent of your first two list comprehension examples. The third
shows how to add constraints without having to rewrite the function.
The first two function could have been expressed using only the third
but are presented to show how it was built.

-deech

  import Control.Monad

  -- triples' == [(a,b,c) | c <- [1..10], b <- [1..10], a <- [1..10]]
  triples' = do
    a <- [1 .. 10]
    b <- [1 .. 10]
    c <- [1 .. 10]
    return (a,b,c)

  -- triples'' (\(a,b,c) -> a + b + c == 24) ==
  -- [(a,b,c) | c <- [1..10], b <- [1..10], a <- [1..10], a + b + c == 24]
  triples'' constraint = do
    a <- [1 .. 10]
    b <- [1 .. 10]
    c <- [1 .. 10]
    guard $ constraint (a,b,c)
    return (a,b,c)

  -- triples''' [\(a,b,c) -> a^2 + b^2 == c^2, \(a,b,c) -> a + b + c == 24] ==
  -- [(a,b,c) | c <- [1..10], b <- [1..10], a <- [1..10], a^2 + b^2 =
c^2, a + b + c == 24]
  triples''' :: [(Int,Int,Int) -> Bool] -> [(Int,Int,Int)]
  triples''' constraints = do
    a <- [1 .. 10]
    b <- [1 .. 10]
    c <- [1 .. 10]
    sequence_ $ map (\constraint -> guard $ constraint (a,b,c)) constraints
    return (a,b,c)

On Wed, Jul 20, 2011 at 8:45 AM, Clockwork PC <clockworkpc at gmail.com> wrote:
> Greetings Haskell community,
>
> This is my first ever post so please be gentle...
>
> Here's where I got to:
>
> Jumped into GHCi:
>
> GHCi, version 7.0.3: http://www.haskell.org/ghc/  :? for help
> Loading package ghc-prim ... linking ... done.
> Loading package integer-gmp ... linking ... done.
> Loading package base ... linking ... done.
>
> Defined my function:
>
> Prelude> let rightTriangles = [ (a,b,c) | c <- [1..10], b <- [1..10], a <-
> [1..10], a^2 + b^2 == c^2 ]
>
> Tested my function:
>
> Prelude> rightTriangles
> [(4,3,5),(3,4,5),(8,6,10),(6,8,10)]
>
> Now, I want to define a refinement of this that will only select values
> whose total is 24.
>
> I could write it so:
>
> let rightTriangles = [ (a,b,c) | c <- [1..10], b <- [1..10], a <- [1..10],
> a^2 + b^2 == c^2, a+b+c == 24]
>
> However, it seems like a bit of a waste if I already have "rightTriangles"
> defined.
>
> I tried a few things, but none of them worked:
>
> Prelude> let rightTriangles` = rightTriangles, a+b+c == 24
>
> <interactive>:1:21: parse error on input `='
> Prelude> let rightTriangles` = rightTriangles | a+b+c == 24
>
> <interactive>:1:21: parse error on input `='
> Prelude> let rightTriangles` = [rightTriangles, a+b+c == 24]
>
> <interactive>:1:21: parse error on input `='
> Prelude> let rightTriangles` = [rightTriangles | a+b+c == 24]
>
> <interactive>:1:21: parse error on input `='
>
> Basically, I'm trying to work out how to draw data from a list already to
> hand.
>
> Alexander
>
>
>
> _______________________________________________
> Beginners mailing list
> Beginners at haskell.org
> http://www.haskell.org/mailman/listinfo/beginners
>
>



More information about the Beginners mailing list