Temporary values with polymorphic types

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.

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.
participants (2)
-
Amy de Buitléir
-
Daniel Fischer