
Hello Haskellers, I isolated to a not so small piece:
{-# OPTIONS -fglasgow-exts #-} {-# LANGUAGE UndecidableInstances #-}
import Control.Monad.Identity import Control.Monad.Reader import Control.Monad.State import qualified Data.List as L import qualified Data.Map as M import Data.Array
import IOExts The type of a regular expression.
data Re t = ReOr [Re t] | ReCat [Re t] | ReStar (Re t) | RePlus (Re t) | ReOpt (Re t) | ReTerm [t] deriving (Show)
The internal type of a regular expression.
type SimplRe t = Int data SimplRe' t = SReOr (SimplRe t) (SimplRe t) | SReCat (SimplRe t) (SimplRe t) | SReStar (SimplRe t) | SReLambda | SReNullSet | SReTerm t deriving (Eq, Ord, Show)
The regular expression builder monad.
data (Ord t) => ReRead t = ReRead { rerNullSet :: SimplRe t, rerLambda :: SimplRe t }
data (Ord t) => ReState t = ReState { resFwdMap :: M.Map (SimplRe t) (ReInfo t), resBwdMap :: M.Map (SimplRe' t) (SimplRe t), resNext :: Int, resQueue :: ([SimplRe t], [SimplRe t]), resStatesDone :: [SimplRe t] }
type ReM m t a = StateT (ReState t) (ReaderT (ReRead t) m) a
TEMP WNH Dfa construction
data ReDfaState t = ReDfaState { dfaFinal :: Bool, dfaTrans :: [(t, SimplRe t)] } deriving (Show)
TEMP WNH The ReInfo type
data ReInfo t = ReInfo { reiSRE :: SimplRe' t, reiNullable :: Bool, reiDfa :: Maybe (ReDfaState t) } deriving (Show)
TEMP WNH
class (Monad m, Ord t) => ReVars m t where { } instance (Monad m, Ord t) => ReVars m t where { }
TEMP WNH
remLookupFwd :: (ReVars m t) => SimplRe t -> ReM m t (ReInfo t) remLookupFwd re = do fwd <- gets resFwdMap -- let { Just reinfo = M.lookup fwd re } -- PROBLEM reinfo <- M.lookup fwd re -- PROBLEM return reinfo
When I "compile" with ghci I get: Dfa_exp.lhs:91:32: Couldn't match expected type `M.Map (M.Map (SimplRe t) (ReInfo t)) t1' against inferred type `SimplRe t2' In the second argument of `M.lookup', namely `re' In a 'do' expression: reinfo <- M.lookup fwd re In the expression: do fwd <- gets resFwdMap reinfo <- M.lookup fwd re return reinfo I trimmed the original code down a lot! But still can't why I am getting type check errors!!! Help! Kind regards, Vasili