Send Beginners mailing list submissions to
        [email protected]

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
        [email protected]

You can reach the person managing the list at
        [email protected]

When replying, please edit your Subject line so it is more specific
than "Re: Contents of Beginners digest..."


Today's Topics:

   1.  A question about an infinite type (Costello, Roger L.)
   2.  Temporary values with polymorphic types (Amy de Buitl?ir)
   3. Re:  Temporary values with polymorphic types (Daniel Fischer)


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

Message: 1
Date: Tue, 28 Feb 2012 12:52:19 +0000
From: "Costello, Roger L." <[email protected]>
Subject: [Haskell-beginners] A question about an infinite type
To: "[email protected]" <[email protected]>
Message-ID:
        <[email protected]>
Content-Type: text/plain; charset="us-ascii"

Hi Folks,

Here is an interesting phenomena:

let f = (\x y -> x y x)

let p = (\x y -> 1)

Now let's evaluate  f p 1

f p 1  = (\x y -> x y x) p 1                -- by replacing f with its 
definition

          = p 1 p                                        -- by substituting x 
with p and y with 1

          = (\x y -> 1) 1 p                     -- by replacing the first p 
with its definition
 
          = 1                                               -- the function 
returns 1 regardless of its arguments

However, Haskell will not proceed with that evaluation because it will first 
determine the

type signature of f and judge it to be an infinite type.

Conversely, if f is omitted and this expression

    p 1 p 

is evaluated then the result 1 is generated.

Why does f p 1 (which evaluates to p 1 p) fail whereas p 1 p succeeds?

What lesson should I learn from this example?

/Roger



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

Message: 2
Date: Tue, 28 Feb 2012 16:53:10 +0000 (UTC)
From: Amy de Buitl?ir <[email protected]>
Subject: [Haskell-beginners] Temporary values with polymorphic types
To: [email protected]
Message-ID: <[email protected]>
Content-Type: text/plain; charset=utf-8

I'm trying to write a function that builds a temporary graph, performs some
operation on the graph, and then returns the result of the operation. The graph
isn't returned. Here's an example. (The real function is much more complicated.)

----- 8< -----
import Data.Graph.Inductive.Graph ( labNodes, mkGraph )

doSomething ? [a] -> [a]
doSomething xs = map snd $ labNodes $ mkGraph xs' []
  where xs' = zip [1..] xs
----- 8< -----

When I load this in GHCI, I get:

amy3.hs:4:39:
    Ambiguous type variable `gr0' in the constraint:
      (Data.Graph.Inductive.Graph.Graph
         gr0) arising from a use of `mkGraph'
    Probable fix: add a type signature that fixes these type variable(s)
    In the second argument of `($)', namely `mkGraph xs' []'
    In the second argument of `($)', namely `labNodes $ mkGraph xs' []'
    In the expression: map snd $ labNodes $ mkGraph xs' []
Failed, modules loaded: none.

>From this, I gather that I need to specify a type for the temporary graph "g"? 
>I
can arbitrarily pick an instance of the Graph class, but what can I put for the
type parameter that it expects? It should be of the same type as the input array
elements. This doesn't compile:

----- 8< -----
import Data.Graph.Inductive.Graph ( labNodes, mkGraph )
import qualified Data.Graph.Inductive.Tree as T ( Gr )

doSomething ? [a] -> [a]
doSomething xs = map snd $ labNodes g
  where xs' = zip [1..] xs
        g = mkGraph xs' [] :: T.Gr a Int
----- 8< -----

amy3.hs:7:21:
    Couldn't match type `a' with `a2'
      `a' is a rigid type variable bound by
          the type signature for doSomething :: [a] -> [a] at amy3.hs:5:1
      `a2' is a rigid type variable bound by
           an expression type signature: T.Gr a2 Int at amy3.hs:7:13
    Expected type: [Data.Graph.Inductive.Graph.LNode a1]
      Actual type: [(Int, a)]
    In the first argument of `mkGraph', namely `xs''
    In the expression: mkGraph xs' [] :: T.Gr a Int
Failed, modules loaded: none.

Thank you in advance for any advice.




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

Message: 3
Date: Tue, 28 Feb 2012 18:28:20 +0100
From: Daniel Fischer <[email protected]>
Subject: Re: [Haskell-beginners] Temporary values with polymorphic
        types
To: [email protected]
Cc: Amy de Buitl?ir <[email protected]>
Message-ID: <[email protected]>
Content-Type: Text/Plain;  charset="utf-8"

On Tuesday 28 February 2012, 17:53:10, Amy de Buitl?ir wrote:
> From this, I gather that I need to specify a type for the temporary
> graph "g"? I can arbitrarily pick an instance of the Graph class, but
> what can I put for the type parameter that it expects? It should be of
> the same type as the input array elements. This doesn't compile:
> 
> ----- 8< -----
> import Data.Graph.Inductive.Graph ( labNodes, mkGraph )
> import qualified Data.Graph.Inductive.Tree as T ( Gr )
> 
> doSomething ? [a] -> [a]
> doSomething xs = map snd $ labNodes g
>   where xs' = zip [1..] xs
>         g = mkGraph xs' [] :: T.Gr a Int
> ----- 8< -----
> 
> amy3.hs:7:21:
>     Couldn't match type `a' with `a2'
>       `a' is a rigid type variable bound by
>           the type signature for doSomething :: [a] -> [a] at
> amy3.hs:5:1 `a2' is a rigid type variable bound by
>            an expression type signature: T.Gr a2 Int at amy3.hs:7:13
>     Expected type: [Data.Graph.Inductive.Graph.LNode a1]
>       Actual type: [(Int, a)]
>     In the first argument of `mkGraph', namely `xs''
>     In the expression: mkGraph xs' [] :: T.Gr a Int
> Failed, modules loaded: none.

The problem is that the 'a' in the type signature for the local g is a 
fresh type variable, not the 'a' from the top level signature.

You can

a) bring the type variable into scope,

{-# LANGUAGE ScopedTypeVariables #-}

doSomething :: forall a. [a] -> [a]
doSomething xs = ...
  where
    xs' = zip [1 .. ] xs
    g :: T.Gr a Int      -- now it's the same a as in the top-level
    g = mkGraph xs' []

b) use a type-restricted alias for mkGraph,

mkGraph' :: [(Int,a)] -> [??] -> T.Gr a Int
mkGraph' = mkGraph

and use mkGraph' in doSomething

There are probably more possibilities, but those are the only ones I found 
without thinking.



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

_______________________________________________
Beginners mailing list
[email protected]
http://www.haskell.org/mailman/listinfo/beginners


End of Beginners Digest, Vol 44, Issue 28
*****************************************

Reply via email to