[Haskell-cafe] Solved but strange error in type inference
Brent Yorgey
byorgey at seas.upenn.edu
Tue Jan 3 17:58:56 CET 2012
The other much simpler solution no one has mentioned yet is to just
pull 'subsome' out as its own top-level declaration. Having such a
big function nested locally within a 'let' is ugly anyway, and it
makes it harder to test and debug than necessary.
-Brent
On Tue, Jan 03, 2012 at 05:44:01PM +0100, Yves Parès wrote:
> Remove subsome type signature. You are redeclaring type variables which
> obviously cannot match those of legSome.
> This cannot work without scoped type variables (and ad-hoc foralls to bring
> them to scope, of course).
>
> 2012/1/3 Yucheng Zhang <yczhang89 at gmail.com>
>
> > As I investigated the code more carefully, I found that the type
> > unification
> > failure may not be related to the suspected class constraint on data
> > constructor.
> >
> > I have made minor changes to the original code to remove the Ord
> > constraint,
> > including introducing a FakedMap with no requirement on Ord. The type
> > unification
> > failure continues:
> >
> > > Couldn't match type `nt1' with `nt'
> > > `nt1' is a rigid type variable bound by
> > > the type signature for
> > > subsome :: [RRule nt1 t1 s1] -> Either String ([t1], s1)
> > > at xx.hs:34:19
> > > `nt' is a rigid type variable bound by
> > > the type signature for
> > > legSome :: LegGram nt t s -> nt -> Either String ([t], s)
> > > at xx.hs:29:1
> > > Expected type: [Symbols nt1 t1]
> > > Actual type: [Symbols nt t]
> > > In the first argument of `makeWord', namely `r'
> > > In the expression: makeWord r
> >
> > The complete changed code follows:
> >
> >
> > data Symbols nt t = NT nt -- ^ non terminal
> > | T t -- ^ terminal
> > deriving (Eq, Ord)
> >
> > type Sem s = [s]->s
> >
> > data Rule nt t s = Rule { refined :: nt
> > , expression :: [Symbols nt t]
> > , emit :: Sem s
> > }
> >
> > type RRule nt t s = ([Symbols nt t], Sem s)
> >
> >
> >
> > data FakedMap a b = FakedMap
> >
> > delete :: k -> FakedMap k a -> FakedMap k a
> > delete a b = b
> >
> > lookup :: k -> FakedMap k a -> Maybe a
> > lookup a b = Nothing
> >
> >
> >
> > data LegGram nt t s = LegGram (FakedMap nt [RRule nt t s])
> >
> > legSome :: LegGram nt t s -> nt -> Either String ([t], s)
> > legSome (LegGram g) ntV =
> > case Main.lookup ntV g of
> > Nothing -> Left "No word accepted!"
> > Just l -> let sg = legSome (LegGram (Main.delete ntV g))
> > subsome :: [RRule nt t s] -> Either String ([t], s)
> > subsome [] = Left "No word accepted!"
> > subsome ((r,sem):l) =
> > let makeWord [] = Right ([],[])
> > makeWord ((NT nnt):ll) =
> > do (m, ss) <- sg nnt
> > (mm, sss) <- makeWord ll
> > return (m++mm, ss:sss)
> > makeWord ((T tt):ll) =
> > do (mm, sss) <- makeWord ll
> > return (tt:mm, sss)
> > in
> > case makeWord r of
> > Right (ll, mm) -> Right (ll, sem mm)
> > Left err -> subsome l
> > in subsome l
> >
> > _______________________________________________
> > Haskell-Cafe mailing list
> > Haskell-Cafe at haskell.org
> > http://www.haskell.org/mailman/listinfo/haskell-cafe
> >
> _______________________________________________
> Haskell-Cafe mailing list
> Haskell-Cafe at haskell.org
> http://www.haskell.org/mailman/listinfo/haskell-cafe
More information about the Haskell-Cafe
mailing list