[GHC] #8659: GHCi told me to tell you that it crashed
GHC
ghc-devs at haskell.org
Fri Jan 10 02:58:06 UTC 2014
#8659: GHCi told me to tell you that it crashed
------------------------------+-------------------------------------
Reporter: ishkabible | Owner:
Type: bug | Status: new
Priority: normal | Milestone:
Component: GHCi | Version: 7.4.2
Keywords: | Operating System: Unknown/Multiple
Architecture: x86 | Type of failure: None/Unknown
Difficulty: Unknown | Test Case:
Blocked By: | Blocking:
Related Tickets: |
------------------------------+-------------------------------------
I'm using an x86 build of GHCi version 7.4.2 on Windows 7 professional.
I attempted to interpret the following code and GHC crashed and told me to
report the issue.
{{{
module ConstructorTypes where
import Data.List (intercalate)
import VarGenMonad
data ConstructorSpec = Spec {
parrentType :: ConstructorSpec,
specName :: String,
specArgs :: [Type]
} deriving(Eq, Ord)
data ConstructorTypeSpec = ConTypeSpec { conTypeName :: String, conSpecs
:: [ConstructorSpec], numParams :: Int }
data Pattern = Pat ConstructorSpec [Pattern]
| Id String
deriving(Eq, Ord)
--this holds
data Type = Poly Type
| DeBruijnTypeVar Int
| ConType ConstructorTypeSpec
| Type :-> Type
deriving(Eq, Ord, show)
--define Eq and Ord to break infinte chain of type/spec/type/spec/...
instance Eq ConstructorTypeSpec where
t1 == t2 = conTypeName t1 == conTypeName t2
instance Ord ConstructorTypeSpec where
t1 <= t2 = conTypeName t1 <= conTypeName t2
--create own show types to give a nice syntax and avoid infinite loops
instance Show ConstructorSpec where
show (Spec ty name args) = name ++ (concatMap ((' ':) . show) args) ++
" :: " ++ conTypeName ty
instance Show ConstructorTypeSpec where
show (ConTypeSpec name specs vars) = name ++ "=" ++ (concatMap
(("\n\t" ++) . show) specs)
genUniqueVars lst n = take n $ runVarGen lst gen
where gen = do
x <- drawVar
return $ x : gen
{--
toString env (Poly t) = do
a <- drawVar --should advance to next varible
b <- toString (a:env) t --any calls to drawVar in toString should
advance it as well
return $ "(forall " ++ a ++ ")" ++ b
toString env (DeBruijn x) = do
return $ env !! x --no changes are made here however
toString env (ConType spec) = do
names <- mapM_ (toString env) (typeVars spec) --each call to drawVar
in each call toString should advance the internal state
return $ conTypeName spec ++ intercalate " " names
toString env (x :-> y) = do
t1 <- toString env x
t2 <- toString env y
return $ "(" ++ t1 ++ ") -> " ++ t2
--}
}}}
"VarGenMonad" is the following code
{{{
module VarGenMonad (VarGen, runVarGen, runVarGenWith, drawVar) where
import Control.Monad
--effectivlly a state monad of type State a [String]
newtype VarGen a = VarGen { getFunc :: [String] -> (a, [String]) }
--just gets the resulting value (this is what users will interface to)
runVarGen vl vg = runVarGenWith showInt
where showInt 0 = ""
showInt x = show x
--another function the user can interacte with
runVarGenWith f vl vg = fst $ runState vg (makeVarListWith f vl)
--gets the result from a var gen monad after telling it what varibles to
use
runState :: VarGen a -> [String] -> (a, [String])
runState vg vl = (getFunc vg) vl
--creates an infinte list of unique varibles from a finite one
makeVarListWith :: Integral a => (a -> String) -> [String] -> [String]
makeVarListWith f lst = gen lst lst 0
where gen t [] c = gen t t (c + 1)
gen t (x:xs) c = (x ++ f c) : gen t xs c
--implements the monad operations in same fashion as a state monad
instance Monad VarGen where
return x = VarGen $ \s -> (x, s)
cur >>= transform = VarGen func
where func s = runState (transform v) nextList
where (v, nextList) = runState cur s
drawVar :: VarGen String
drawVar = VarGen $ \(x:xs) -> (x, xs)
}}}
this worked before I added "show" (note that it is lowercase cuz I messed
up) to the deriving cluase of my 'Type' type. After fixing it to make it
an upper case S GHC promptly told me what else I had messed up in my code
(that is, it worked correctly).
--
Ticket URL: <http://ghc.haskell.org/trac/ghc/ticket/8659>
GHC <http://www.haskell.org/ghc/>
The Glasgow Haskell Compiler
More information about the ghc-tickets
mailing list