intensional-datatys-0.2.0.0: A GHC Core plugin for intensional datatype refinement checking
Safe HaskellNone
LanguageHaskell2010

Intensional.Constructors

Synopsis

Documentation

data Side Source #

Constructors

L 
R 

data K (s :: Side) where Source #

Constructors

Dom :: DataType Name -> K s 
Con :: Name -> SrcSpan -> K 'L 
Set :: UniqSet Name -> SrcSpan -> K 'R 

Instances

Instances details
Eq (K s) Source # 
Instance details

Defined in Intensional.Constructors

Methods

(==) :: K s -> K s -> Bool #

(/=) :: K s -> K s -> Bool #

Hashable (K s) Source # 
Instance details

Defined in Intensional.Constructors

Methods

hashWithSalt :: Int -> K s -> Int #

hash :: K s -> Int #

Binary (K 'L) Source # 
Instance details

Defined in Intensional.Constructors

Methods

put_ :: BinHandle -> K 'L -> IO () #

put :: BinHandle -> K 'L -> IO (Bin (K 'L)) #

get :: BinHandle -> IO (K 'L) #

Binary (K 'R) Source # 
Instance details

Defined in Intensional.Constructors

Methods

put_ :: BinHandle -> K 'R -> IO () #

put :: BinHandle -> K 'R -> IO (Bin (K 'R)) #

get :: BinHandle -> IO (K 'R) #

Outputable (K s) Source # 
Instance details

Defined in Intensional.Constructors

Methods

ppr :: K s -> SDoc #

pprPrec :: Rational -> K s -> SDoc #

Refined (K l) Source # 
Instance details

Defined in Intensional.Constructors

Methods

domain :: K l -> Domain Source #

rename :: RVar -> RVar -> K l -> K l Source #

prpr :: (RVar -> SDoc) -> K l -> SDoc Source #

type ConL = K 'L Source #

type ConR = K 'R Source #

toAtomic :: K l -> K r -> [(K 'L, K 'R)] Source #

getLocation :: K a -> SrcSpan Source #

Assuming k is either a Con or Set atom, getLocation k is the associated span.

Orphan instances

Hashable Unique Source # 
Instance details

Methods

hashWithSalt :: Int -> Unique -> Int #

hash :: Unique -> Int #

Hashable Name Source # 
Instance details

Methods

hashWithSalt :: Int -> Name -> Int #

hash :: Name -> Int #