Skip to content
Snippets Groups Projects
Commit e2731b07 authored by Alex Biehl's avatar Alex Biehl Committed by Alex Biehl
Browse files

Also make TyLit deterministic

parent 879d1fe2
No related branches found
No related tags found
No related merge requests found
......@@ -28,6 +28,7 @@ import Data.Maybe ( maybeToList, mapMaybe, fromMaybe )
import qualified Data.Map as Map
import qualified Data.Set as Set
import GHC.Data.FastString (unpackFS)
import GHC.Core.Class
import GHC.Driver.Session
import GHC.Core (isOrphan)
......@@ -194,7 +195,8 @@ instance Ord SName where
-- For the benefit of the user (looks nice and predictable) and the
-- tests (which prefer output to be deterministic).
data SimpleType = SimpleType SName [SimpleType]
| SimpleTyLit TyLit
| SimpleIntTyLit Integer
| SimpleStringTyLit String
deriving (Eq,Ord)
......@@ -218,7 +220,8 @@ simplify (AppTy t1 t2) = SimpleType s (ts ++ maybeToList (simplify_maybe t2))
simplify (TyVarTy v) = SimpleType (SName (tyVarName v)) []
simplify (TyConApp tc ts) = SimpleType (SName (tyConName tc))
(mapMaybe simplify_maybe ts)
simplify (LitTy l) = SimpleTyLit l
simplify (LitTy (NumTyLit n)) = SimpleIntTyLit n
simplify (LitTy (StrTyLit s)) = SimpleStringTyLit (unpackFS s)
simplify (CastTy ty _) = simplify ty
simplify (CoercionTy _) = error "simplify:Coercion"
......
0% Loading or .
You are about to add 0 people to the discussion. Proceed with caution.
Finish editing this message first!
Please register or to comment