liquidhaskell-boot-0.9.10.1.2: Liquid Types for Haskell
Safe HaskellNone
LanguageHaskell98

Language.Haskell.Liquid.Types.Names

Synopsis

Documentation

data LogicName Source #

A name for an entity that does not exist in Haskell

For instance, this can be used to represent predicate aliases or uninterpreted functions.

Constructors

LogicName 

Fields

  • !Symbol

    Unqualified symbol

  • !Module

    Module where the entity was defined

  • !(Maybe Name)

    If the named entity is the reflection of some Haskell name

GeneratedLogicName Symbol 

Instances

Instances details
NFData LogicName Source # 
Instance details

Defined in Language.Haskell.Liquid.Types.Names

Methods

rnf :: LogicName -> () #

Binary LogicName Source # 
Instance details

Defined in Language.Haskell.Liquid.Types.Names

Data LogicName Source # 
Instance details

Defined in Language.Haskell.Liquid.Types.Names

Methods

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

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

toConstr :: LogicName -> Constr #

dataTypeOf :: LogicName -> DataType #

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

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

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

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

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

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

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

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

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

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

Generic LogicName Source # 
Instance details

Defined in Language.Haskell.Liquid.Types.Names

Associated Types

type Rep LogicName 
Instance details

Defined in Language.Haskell.Liquid.Types.Names

Show LogicName Source # 
Instance details

Defined in Language.Haskell.Liquid.Types.Names

Eq LogicName Source # 
Instance details

Defined in Language.Haskell.Liquid.Types.Names

Ord LogicName Source # 
Instance details

Defined in Language.Haskell.Liquid.Types.Names

Hashable LogicName Source # 
Instance details

Defined in Language.Haskell.Liquid.Types.Names

type Rep LogicName Source # 
Instance details

Defined in Language.Haskell.Liquid.Types.Names

data LHResolvedName Source #

A name whose procedence is known.

Constructors

LHRLogic !LogicName 
LHRGHC !Name

A name for an entity that exists in Haskell

LHRLocal !Symbol

A name for a local variable, e.g. one that is bound by a type alias.

LHRIndex Word

The index of a name in some environment

Before serializing names, they are converted to indices. The names themselves are kept in an environment or table that is serialized separately. This is to acommodate how GHC serializes its Names.

Instances

Instances details
Binary LHResolvedName Source # 
Instance details

Defined in Language.Haskell.Liquid.Types.Names

NFData LHResolvedName Source # 
Instance details

Defined in Language.Haskell.Liquid.Types.Names

Methods

rnf :: LHResolvedName -> () #

Binary LHResolvedName Source # 
Instance details

Defined in Language.Haskell.Liquid.Types.Names

Data LHResolvedName Source # 
Instance details

Defined in Language.Haskell.Liquid.Types.Names

Methods

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

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

toConstr :: LHResolvedName -> Constr #

dataTypeOf :: LHResolvedName -> DataType #

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

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

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

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

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

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

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

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

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

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

Generic LHResolvedName Source # 
Instance details

Defined in Language.Haskell.Liquid.Types.Names

Associated Types

type Rep LHResolvedName 
Instance details

Defined in Language.Haskell.Liquid.Types.Names

Show LHResolvedName Source # 
Instance details

Defined in Language.Haskell.Liquid.Types.Names

Eq LHResolvedName Source # 
Instance details

Defined in Language.Haskell.Liquid.Types.Names

Ord LHResolvedName Source # 
Instance details

Defined in Language.Haskell.Liquid.Types.Names

Hashable LHResolvedName Source # 
Instance details

Defined in Language.Haskell.Liquid.Types.Names

type Rep LHResolvedName Source # 
Instance details

Defined in Language.Haskell.Liquid.Types.Names

data LHName Source #

A name that is potentially unresolved.

Constructors

LHNResolved !LHResolvedName !Symbol

In order to integrate the resolved names gradually, we keep the unresolved names.

LHNUnresolved !LHNameSpace !Symbol 

Instances

Instances details
Binary LHName Source # 
Instance details

Defined in Language.Haskell.Liquid.Types.Names

Methods

put :: LHName -> Put #

get :: Get LHName #

putList :: [LHName] -> Put #

NFData LHName Source # 
Instance details

Defined in Language.Haskell.Liquid.Types.Names

Methods

rnf :: LHName -> () #

Data LHName Source # 
Instance details

Defined in Language.Haskell.Liquid.Types.Names

Methods

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

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

toConstr :: LHName -> Constr #

dataTypeOf :: LHName -> DataType #

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

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

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

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

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

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

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

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

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

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

Generic LHName Source # 
Instance details

Defined in Language.Haskell.Liquid.Types.Names

Associated Types

type Rep LHName 
Instance details

Defined in Language.Haskell.Liquid.Types.Names

Methods

from :: LHName -> Rep LHName x #

to :: Rep LHName x -> LHName #

Show LHName Source # 
Instance details

Defined in Language.Haskell.Liquid.Types.Names

Eq LHName Source #

An Eq instance that ignores the Symbol in resolved names

Instance details

Defined in Language.Haskell.Liquid.Types.Names

Methods

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

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

Ord LHName Source #

An Ord instance that ignores the Symbol in resolved names

Instance details

Defined in Language.Haskell.Liquid.Types.Names

Hashable LHName Source #

A Hashable instance that ignores the Symbol in resolved names

Instance details

Defined in Language.Haskell.Liquid.Types.Names

Methods

hashWithSalt :: Int -> LHName -> Int #

hash :: LHName -> Int #

PPrint LHName Source # 
Instance details

Defined in Language.Haskell.Liquid.Types.Names

Methods

pprintTidy :: Tidy -> LHName -> Doc #

pprintPrec :: Int -> Tidy -> LHName -> Doc #

Expand BareDef Source # 
Instance details

Defined in Language.Haskell.Liquid.Bare.Expand

Expand BareMeasure Source # 
Instance details

Defined in Language.Haskell.Liquid.Bare.Expand

type Rep LHName Source # 
Instance details

Defined in Language.Haskell.Liquid.Types.Names

data LHNameSpace Source #

Instances

Instances details
Binary LHNameSpace Source # 
Instance details

Defined in Language.Haskell.Liquid.Types.Names

NFData LHNameSpace Source # 
Instance details

Defined in Language.Haskell.Liquid.Types.Names

Methods

rnf :: LHNameSpace -> () #

Data LHNameSpace Source # 
Instance details

Defined in Language.Haskell.Liquid.Types.Names

Methods

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

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

toConstr :: LHNameSpace -> Constr #

dataTypeOf :: LHNameSpace -> DataType #

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

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

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

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

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

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

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

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

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

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

Generic LHNameSpace Source # 
Instance details

Defined in Language.Haskell.Liquid.Types.Names

Associated Types

type Rep LHNameSpace 
Instance details

Defined in Language.Haskell.Liquid.Types.Names

type Rep LHNameSpace = D1 ('MetaData "LHNameSpace" "Language.Haskell.Liquid.Types.Names" "liquidhaskell-boot-0.9.10.1.2-inplace" 'False) ((C1 ('MetaCons "LHTcName" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "LHDataConName" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 LHThisModuleNameFlag))) :+: (C1 ('MetaCons "LHVarName" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 LHThisModuleNameFlag)) :+: (C1 ('MetaCons "LHLogicNameBinder" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "LHLogicName" 'PrefixI 'False) (U1 :: Type -> Type))))
Show LHNameSpace Source # 
Instance details

Defined in Language.Haskell.Liquid.Types.Names

Eq LHNameSpace Source # 
Instance details

Defined in Language.Haskell.Liquid.Types.Names

Ord LHNameSpace Source # 
Instance details

Defined in Language.Haskell.Liquid.Types.Names

Hashable LHNameSpace Source # 
Instance details

Defined in Language.Haskell.Liquid.Types.Names

type Rep LHNameSpace Source # 
Instance details

Defined in Language.Haskell.Liquid.Types.Names

type Rep LHNameSpace = D1 ('MetaData "LHNameSpace" "Language.Haskell.Liquid.Types.Names" "liquidhaskell-boot-0.9.10.1.2-inplace" 'False) ((C1 ('MetaCons "LHTcName" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "LHDataConName" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 LHThisModuleNameFlag))) :+: (C1 ('MetaCons "LHVarName" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 LHThisModuleNameFlag)) :+: (C1 ('MetaCons "LHLogicNameBinder" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "LHLogicName" 'PrefixI 'False) (U1 :: Type -> Type))))

data LHThisModuleNameFlag Source #

Whether the name should be looked up in the current module only or in any module

Instances

Instances details
Binary LHThisModuleNameFlag Source # 
Instance details

Defined in Language.Haskell.Liquid.Types.Names

NFData LHThisModuleNameFlag Source # 
Instance details

Defined in Language.Haskell.Liquid.Types.Names

Methods

rnf :: LHThisModuleNameFlag -> () #

Data LHThisModuleNameFlag Source # 
Instance details

Defined in Language.Haskell.Liquid.Types.Names

Methods

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

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

toConstr :: LHThisModuleNameFlag -> Constr #

dataTypeOf :: LHThisModuleNameFlag -> DataType #

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

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

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

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

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

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

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

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

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

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

Generic LHThisModuleNameFlag Source # 
Instance details

Defined in Language.Haskell.Liquid.Types.Names

Associated Types

type Rep LHThisModuleNameFlag 
Instance details

Defined in Language.Haskell.Liquid.Types.Names

type Rep LHThisModuleNameFlag = D1 ('MetaData "LHThisModuleNameFlag" "Language.Haskell.Liquid.Types.Names" "liquidhaskell-boot-0.9.10.1.2-inplace" 'False) (C1 ('MetaCons "LHThisModuleNameF" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "LHAnyModuleNameF" 'PrefixI 'False) (U1 :: Type -> Type))
Show LHThisModuleNameFlag Source # 
Instance details

Defined in Language.Haskell.Liquid.Types.Names

Eq LHThisModuleNameFlag Source # 
Instance details

Defined in Language.Haskell.Liquid.Types.Names

Ord LHThisModuleNameFlag Source # 
Instance details

Defined in Language.Haskell.Liquid.Types.Names

Hashable LHThisModuleNameFlag Source # 
Instance details

Defined in Language.Haskell.Liquid.Types.Names

type Rep LHThisModuleNameFlag Source # 
Instance details

Defined in Language.Haskell.Liquid.Types.Names

type Rep LHThisModuleNameFlag = D1 ('MetaData "LHThisModuleNameFlag" "Language.Haskell.Liquid.Types.Names" "liquidhaskell-boot-0.9.10.1.2-inplace" 'False) (C1 ('MetaCons "LHThisModuleNameF" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "LHAnyModuleNameF" 'PrefixI 'False) (U1 :: Type -> Type))

getLHNameResolved :: HasCallStack => LHName -> LHResolvedName Source #

Get the resolved Symbol from an LHName.

getLHNameSymbol :: LHName -> Symbol Source #

Get the unresolved Symbol from an LHName.

lhNameToResolvedSymbol :: LHName -> Symbol Source #

Converts resolved names to symbols.

One important postcondition of this function is that the symbol for reflected names must match exactly the symbol for the corresponding Haskell function. Otherwise, LH would fail to link the two at various places where it is needed.

mapLHNames :: Data a => (LHName -> LHName) -> a -> a Source #

mapMLocLHNames :: forall m a. (Data a, Monad m) => (Located LHName -> m (Located LHName)) -> a -> m a Source #

reflectGHCName :: Module -> Name -> LHName Source #

Creates a name in the logic namespace for the given Haskell name.

reflectLHName :: HasCallStack => Module -> LHName -> LHName Source #

Creates a name in the logic namespace for the given Haskell name.