liquid-fixpoint-0.6.0.1: Predicate Abstraction-based Horn-Clause/Implication Constraint Solver

Safe HaskellNone
LanguageHaskell98

Language.Fixpoint.Types.Sorts

Contents

Description

This module contains the data types, operations and serialization functions for representing Fixpoint's implication (i.e. subtyping) and well-formedness constraints in Haskell. The actual constraint solving is done by the `fixpoint.native` which is written in Ocaml.

Synopsis

Embedding to Fixpoint Types

data Sort Source #

Constructors

FInt 
FReal 
FNum

numeric kind for Num tyvars

FFrac

numeric kind for Fractional tyvars

FObj !Symbol

uninterpreted type

FVar !Int

fixpoint type variable

FFunc !Sort !Sort

function

FAbs !Int !Sort

type-abstraction

FTC !FTycon 
FApp !Sort !Sort

constructed type

Instances

Eq Sort Source # 

Methods

(==) :: Sort -> Sort -> Bool #

(/=) :: Sort -> Sort -> Bool #

Data Sort Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Sort -> c Sort #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Sort #

toConstr :: Sort -> Constr #

dataTypeOf :: Sort -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c Sort) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Sort) #

gmapT :: (forall b. Data b => b -> b) -> Sort -> Sort #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Sort -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Sort -> r #

gmapQ :: (forall d. Data d => d -> u) -> Sort -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> Sort -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> Sort -> m Sort #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Sort -> m Sort #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Sort -> m Sort #

Ord Sort Source # 

Methods

compare :: Sort -> Sort -> Ordering #

(<) :: Sort -> Sort -> Bool #

(<=) :: Sort -> Sort -> Bool #

(>) :: Sort -> Sort -> Bool #

(>=) :: Sort -> Sort -> Bool #

max :: Sort -> Sort -> Sort #

min :: Sort -> Sort -> Sort #

Show Sort Source # 

Methods

showsPrec :: Int -> Sort -> ShowS #

show :: Sort -> String #

showList :: [Sort] -> ShowS #

Generic Sort Source # 

Associated Types

type Rep Sort :: * -> * #

Methods

from :: Sort -> Rep Sort x #

to :: Rep Sort x -> Sort #

Monoid Sort Source # 

Methods

mempty :: Sort #

mappend :: Sort -> Sort -> Sort #

mconcat :: [Sort] -> Sort #

Binary Sort Source # 

Methods

put :: Sort -> Put #

get :: Get Sort #

putList :: [Sort] -> Put #

NFData Sort Source # 

Methods

rnf :: Sort -> () #

Hashable Sort Source # 

Methods

hashWithSalt :: Int -> Sort -> Int #

hash :: Sort -> Int #

Fixpoint Sort Source # 
Elaborate Sort Source # 

Methods

elaborate :: String -> SEnv Sort -> Sort -> Sort Source #

Defunc Sort Source # 

Methods

defunc :: Sort -> DF Sort Source #

Elaborate (Symbol, Sort) Source # 

Methods

elaborate :: String -> SEnv Sort -> (Symbol, Sort) -> (Symbol, Sort) Source #

Defunc (Symbol, Sort) Source # 

Methods

defunc :: (Symbol, Sort) -> DF (Symbol, Sort) Source #

type Rep Sort Source # 

newtype Sub Source #

Constructors

Sub [(Int, Sort)] 

Instances

Generic Sub Source # 

Associated Types

type Rep Sub :: * -> * #

Methods

from :: Sub -> Rep Sub x #

to :: Rep Sub x -> Sub #

Binary Sub Source # 

Methods

put :: Sub -> Put #

get :: Get Sub #

putList :: [Sub] -> Put #

NFData Sub Source # 

Methods

rnf :: Sub -> () #

type Rep Sub Source # 
type Rep Sub = D1 (MetaData "Sub" "Language.Fixpoint.Types.Sorts" "liquid-fixpoint-0.6.0.1-5mWt9PUazXkTom8QgdiF2" True) (C1 (MetaCons "Sub" PrefixI False) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 [(Int, Sort)])))

data FTycon Source #

Instances

Eq FTycon Source # 

Methods

(==) :: FTycon -> FTycon -> Bool #

(/=) :: FTycon -> FTycon -> Bool #

Data FTycon Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> FTycon -> c FTycon #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c FTycon #

toConstr :: FTycon -> Constr #

dataTypeOf :: FTycon -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c FTycon) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c FTycon) #

gmapT :: (forall b. Data b => b -> b) -> FTycon -> FTycon #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> FTycon -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> FTycon -> r #

gmapQ :: (forall d. Data d => d -> u) -> FTycon -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> FTycon -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> FTycon -> m FTycon #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> FTycon -> m FTycon #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> FTycon -> m FTycon #

Ord FTycon Source # 
Show FTycon Source # 
Generic FTycon Source # 

Associated Types

type Rep FTycon :: * -> * #

Methods

from :: FTycon -> Rep FTycon x #

to :: Rep FTycon x -> FTycon #

Binary FTycon Source # 

Methods

put :: FTycon -> Put #

get :: Get FTycon #

putList :: [FTycon] -> Put #

NFData FTycon Source # 

Methods

rnf :: FTycon -> () #

Hashable FTycon Source # 

Methods

hashWithSalt :: Int -> FTycon -> Int #

hash :: FTycon -> Int #

Fixpoint FTycon Source # 
type Rep FTycon Source # 
type Rep FTycon

intSort :: Sort Source #

Exported Basic Sorts -----------------------------------------------

realSort :: Sort Source #

Exported Basic Sorts -----------------------------------------------

boolSort :: Sort Source #

Exported Basic Sorts -----------------------------------------------

strSort :: Sort Source #

Exported Basic Sorts -----------------------------------------------

funcSort :: Sort Source #

Exported Basic Sorts -----------------------------------------------

fApp :: Sort -> [Sort] -> Sort Source #