mirror of
https://github.com/GaloisInc/cryptol.git
synced 2024-12-16 11:22:33 +03:00
Remove unused constructors from Parser.AST.Type datatype.
This commit is contained in:
parent
9188878c4e
commit
4adb4bc13a
@ -612,10 +612,8 @@ instance Rename Type where
|
||||
go (TFun a b) = TFun <$> go a <*> go b
|
||||
go (TSeq n a) = TSeq <$> go n <*> go a
|
||||
go TBit = return TBit
|
||||
go TInteger = return TInteger
|
||||
go (TNum c) = return (TNum c)
|
||||
go (TChar c) = return (TChar c)
|
||||
go TInf = return TInf
|
||||
|
||||
go (TUser pn ps)
|
||||
|
||||
@ -669,10 +667,8 @@ resolveTypeFixity = go
|
||||
mkTInfix a' op b'
|
||||
|
||||
TBit -> return t
|
||||
TInteger -> return t
|
||||
TNum _ -> return t
|
||||
TChar _ -> return t
|
||||
TInf -> return t
|
||||
TWild -> return t
|
||||
|
||||
|
||||
@ -957,10 +953,8 @@ patternEnv = go
|
||||
typeEnv (TSeq a b) = bindTypes [a,b]
|
||||
|
||||
typeEnv TBit = return mempty
|
||||
typeEnv TInteger = return mempty
|
||||
typeEnv TNum{} = return mempty
|
||||
typeEnv TChar{} = return mempty
|
||||
typeEnv TInf = return mempty
|
||||
|
||||
typeEnv (TUser pn ps) =
|
||||
do mb <- typeExists pn
|
||||
|
@ -315,10 +315,8 @@ data TParam n = TParam { tpName :: n
|
||||
data Type n = TFun (Type n) (Type n) -- ^ @[8] -> [8]@
|
||||
| TSeq (Type n) (Type n) -- ^ @[8] a@
|
||||
| TBit -- ^ @Bit@
|
||||
| TInteger -- ^ @Integer@
|
||||
| TNum Integer -- ^ @10@
|
||||
| TChar Char -- ^ @'a'@
|
||||
| TInf -- ^ @inf@
|
||||
| TUser n [Type n] -- ^ A type variable or synonym
|
||||
|
||||
| TApp TCon [Type n]
|
||||
@ -780,8 +778,6 @@ instance PPName name => PP (Type name) where
|
||||
TTuple ts -> parens $ commaSep $ map pp ts
|
||||
TRecord fs -> braces $ commaSep $ map (ppNamed ":") fs
|
||||
TBit -> text "Bit"
|
||||
TInteger -> text "Integer"
|
||||
TInf -> text "inf"
|
||||
TNum x -> integer x
|
||||
TChar x -> text (show x)
|
||||
TSeq t1 TBit -> brackets (pp t1)
|
||||
@ -983,8 +979,6 @@ instance NoPos (Type name) where
|
||||
TFun x y -> TFun (noPos x) (noPos y)
|
||||
TSeq x y -> TSeq (noPos x) (noPos y)
|
||||
TBit -> TBit
|
||||
TInteger -> TInteger
|
||||
TInf -> TInf
|
||||
TNum n -> TNum n
|
||||
TChar n -> TChar n
|
||||
TLocated x _ -> noPos x
|
||||
|
@ -147,10 +147,8 @@ namesT vs = go
|
||||
TFun t1 t2 -> Set.union (go t1) (go t2)
|
||||
TSeq t1 t2 -> Set.union (go t1) (go t2)
|
||||
TBit -> Set.empty
|
||||
TInteger -> Set.empty
|
||||
TNum _ -> Set.empty
|
||||
TChar _ -> Set.empty
|
||||
TInf -> Set.empty
|
||||
TApp _ ts -> Set.unions (map go ts)
|
||||
TTuple ts -> Set.unions (map go ts)
|
||||
TRecord fs -> Set.unions (map (go . value) fs)
|
||||
@ -292,10 +290,8 @@ tnamesT ty =
|
||||
TFun t1 t2 -> Set.union (tnamesT t1) (tnamesT t2)
|
||||
TSeq t1 t2 -> Set.union (tnamesT t1) (tnamesT t2)
|
||||
TBit -> Set.empty
|
||||
TInteger -> Set.empty
|
||||
TNum _ -> Set.empty
|
||||
TChar __ -> Set.empty
|
||||
TInf -> Set.empty
|
||||
TApp _ ts -> Set.unions (map tnamesT ts)
|
||||
TTuple ts -> Set.unions (map tnamesT ts)
|
||||
TRecord fs -> Set.unions (map (tnamesT . value) fs)
|
||||
|
@ -235,10 +235,8 @@ validDemotedType rng ty =
|
||||
TFun {} -> bad "Function types"
|
||||
TSeq {} -> bad "Sequence types"
|
||||
TBit -> bad "Type bit"
|
||||
TInteger -> bad "Type integer"
|
||||
TNum {} -> ok
|
||||
TChar {} -> ok
|
||||
TInf -> bad "Infinity type"
|
||||
TWild -> bad "Wildcard types"
|
||||
TUser {} -> ok
|
||||
TApp {} -> ok
|
||||
@ -515,10 +513,8 @@ mkProp ty =
|
||||
TFun{} -> err
|
||||
TSeq{} -> err
|
||||
TBit{} -> err
|
||||
TInteger -> err
|
||||
TNum{} -> err
|
||||
TChar{} -> err
|
||||
TInf{} -> err
|
||||
TWild -> err
|
||||
TRecord{} -> err
|
||||
|
||||
|
@ -338,10 +338,8 @@ doCheckType ty k =
|
||||
P.TFun t1 t2 -> tcon (TC TCFun) [t1,t2] k
|
||||
P.TSeq t1 t2 -> tcon (TC TCSeq) [t1,t2] k
|
||||
P.TBit -> tcon (TC TCBit) [] k
|
||||
P.TInteger -> tcon (TC TCInteger) [] k
|
||||
P.TNum n -> tcon (TC (TCNum n)) [] k
|
||||
P.TChar n -> tcon (TC (TCNum $ fromIntegral $ fromEnum n)) [] k
|
||||
P.TInf -> tcon (TC TCInf) [] k
|
||||
P.TApp tc ts ->
|
||||
do it <- tcon tc ts k
|
||||
|
||||
|
Loading…
Reference in New Issue
Block a user