[Haskell-beginners] Temporary values with polymorphic types

Daniel Fischer daniel.is.fischer at googlemail.com
Tue Feb 28 18:28:20 CET 2012


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.



More information about the Beginners mailing list