Perhaps you should give us the error the compiler give you.

Plus:
data LegGram nt t s = Ord nt => LegGram (M.Map nt [RRule nt t s])
will become invalid. Currently, such class constraints are ignored.

You should remove the 'Ord nt' constraint and add it to you legSome function. (Maybe that's a track to solve your problem...)


You have also another solution: make your LegGram type available for all Ord nt (with GADTs or ExistentialQuantification), thus making you unable to know which type 'nt' exactly is:

data LegGram t s = forall nt. Ord nt => LegGram (M.Map nt [RRule nt t s])
or
data LegGram t s where
    LegGram :: Ord nt => M.Map nt [RRule nt t s] -> LegGram t s
should be both valid. I tend to prefer the latter (the use of a GADT), as it makes you declare and handle your type constructor just like any function.
But I don't know if it fits you requirements.


2012/1/3 AUGER Cédric <sedrikov@gmail.com>

Hi all, I am an Haskell newbie; can someone explain me why there is
no reported error in @legSome@ but there is one in @legSomeb@

(I used leksah as an IDE, and my compiler is:
$ ghc -v
Glasgow Haskell Compiler, Version 7.2.1, stage 2 booted by GHC version
6.12.3 )

What I do not understand is that the only difference was a typing
anotation to help the type inference, but I believed that this
annotation was already given by the signature I give, so I am quite
lost.

Thanks in advance!

======================================================================
{-# OPTIONS_GHC -XScopedTypeVariables #-}
-- why isn't this option always enabled...

{-# OPTIONS_GHC -XGADTs #-}

import Data.Word
import qualified Data.Map as M
import qualified Data.Set as S

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 LegGram nt t s = Ord nt => LegGram (M.Map nt [RRule nt t s])

legSome :: LegGram nt t s -> nt -> Either String ([t], s)
--         ^^^^^^^^^^^^^^
--            isn't this redundant?
--                    vvvvvvvvvvvvvv
legSome ((LegGram g)::LegGram nt t s) ntV =
  case M.lookup ntV g of
    Nothing -> Left "No word accepted!"
    Just l -> let sg = legSome (LegGram (M.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

legSomeb :: LegGram nt t s -> nt -> Either String ([t], s)
-- but without it I have an error reported
legSomeb (LegGram g) ntV =
  case M.lookup ntV g of
    Nothing -> Left "No word accepted!"
    Just l -> let sg = legSomeb (LegGram (M.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@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe