liquidhaskell-0.8.10.1: Liquid Types for Haskell
Safe HaskellNone
LanguageHaskell98

Language.Haskell.Liquid.GHC.Misc

Description

This module contains a wrappers and utility functions for accessing GHC module information. It should NEVER depend on ANY module inside the Language.Haskell.Liquid.* tree.

Synopsis

Documentation

mkAlive :: Var -> Id #

srcSpanTick :: Module -> SrcSpan -> Tickish a #

Encoding and Decoding Location --------------------------------------------

stringTyVar :: String -> TyVar #

Generic Helpers for Accessing GHC Innards ---------------------------------

isTmpSymbol :: Symbol -> Bool #

notracePpr :: Outputable a => String -> a -> a #

Pretty Printers -----------------------------------------------------------

tracePpr :: Outputable a => String -> a -> a #

pprShow :: Show a => a -> SDoc #

toFixSDoc :: Fixpoint a => a -> Doc #

pprDoc :: Outputable a => a -> Doc #

showPpr :: Outputable a => a -> String #

newtype Loc #

Manipulating Source Spans -------------------------------------------------

Constructors

L (Int, Int) 

Instances

Instances details
Eq Loc # 
Instance details

Defined in Language.Haskell.Liquid.GHC.Misc

Methods

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

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

Ord Loc # 
Instance details

Defined in Language.Haskell.Liquid.GHC.Misc

Methods

compare :: Loc -> Loc -> Ordering #

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

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

(>) :: Loc -> Loc -> Bool #

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

max :: Loc -> Loc -> Loc #

min :: Loc -> Loc -> Loc #

Show Loc # 
Instance details

Defined in Language.Haskell.Liquid.GHC.Misc

Methods

showsPrec :: Int -> Loc -> ShowS #

show :: Loc -> String #

showList :: [Loc] -> ShowS #

Hashable Loc # 
Instance details

Defined in Language.Haskell.Liquid.GHC.Misc

Methods

hashWithSalt :: Int -> Loc -> Int

hash :: Loc -> Int

ToJSON Loc 
Instance details

Defined in Language.Haskell.Liquid.UX.Annotate

Methods

toJSON :: Loc -> Value

toEncoding :: Loc -> Encoding

toJSONList :: [Loc] -> Value

toEncodingList :: [Loc] -> Encoding

fSrcSpan :: Loc a => a -> SrcSpan #

fSourcePos :: Loc a => a -> SourcePos #

fSrcSpanSrcSpan :: SrcSpan -> SrcSpan #

srcSpanFSrcSpan :: SrcSpan -> SrcSpan #

namedLocSymbol :: (Symbolic a, NamedThing a) => a -> Located Symbol #

varLocInfo :: (Type -> a) -> Var -> Located a #

namedPanic :: NamedThing a => a -> String -> b #

collectArguments :: Int -> CoreExpr -> [Var] #

Manipulating CoreExpr -----------------------------------------------------

isTupleId :: Id -> Bool #

Predicates on CoreExpr and DataCons ---------------------------------------

uniqueHash :: Uniquable a => Int -> a -> Int #

symbolTyConWithKind :: Kind -> Char -> Int -> Symbol -> TyCon #

Symbol Conversions --------------------------------------------------------

symbolTyCon :: Char -> Int -> Symbol -> TyCon #

symbolTyVar :: Symbol -> TyVar #

localVarSymbol :: Var -> Symbol #

exportedVarSymbol :: Var -> Symbol #

splitModuleName :: Symbol -> (Symbol, Symbol) #

Manipulating Symbols ------------------------------------------------------

dropModuleNamesAndUnique :: Symbol -> Symbol #

dropModuleNames :: Symbol -> Symbol #

dropModuleNamesCorrect :: Symbol -> Symbol #

takeModuleNames :: Symbol -> Symbol #

dropModuleUnique :: Symbol -> Symbol #

cmpSymbol :: Symbol -> Symbol -> Bool #

mungeNames :: (String -> [Text] -> Symbol) -> Text -> String -> Symbol -> Symbol #

qualifySymbol :: Symbol -> Symbol -> Symbol #

isQualifiedSym :: Symbol -> Bool #

wrapParens :: (IsString a, Monoid a) => a -> a #

isDictionary :: Symbolic a => a -> Bool #

isMethod :: Symbolic a => a -> Bool #

isInternal :: Symbolic a => a -> Bool #

isWorker :: Symbolic a => a -> Bool #

stripParensSym :: Symbol -> Symbol #

gHC_VERSION :: String #

GHC Compatibility Layer ---------------------------------------------------

ignoreCoreBinds :: HashSet Var -> [CoreBind] -> [CoreBind] #

findVarDef :: Symbol -> [CoreBind] -> Maybe (Var, CoreExpr) #

coreBindSymbols :: CoreBind -> [Symbol] #

simplesymbol :: NamedThing t => t -> Symbol #

binders :: Bind a -> [a] #

isPredExpr :: CoreExpr -> Bool #

The following functions test if a CoreExpr or CoreVar are just types in disguise, e.g. have PredType (in the GHC sense of the word), and so shouldn't appear in refinements.

anyF :: [a -> Bool] -> a -> Bool #

defaultDataCons :: Type -> [AltCon] -> Maybe [(DataCon, [TyVar], [Type])] #

'defaultDataCons t ds' returns the list of '(dc, types)' pairs, corresponding to the _missing_ cases, i.e. _other_ than those in ds, that are being handled by DEFAULT.

Orphan instances

Show Class # 
Instance details

Methods

showsPrec :: Int -> Class -> ShowS #

show :: Class -> String #

showList :: [Class] -> ShowS #

Show Var # 
Instance details

Methods

showsPrec :: Int -> Var -> ShowS #

show :: Var -> String #

showList :: [Var] -> ShowS #

Show TyCon # 
Instance details

Methods

showsPrec :: Int -> TyCon -> ShowS #

show :: TyCon -> String #

showList :: [TyCon] -> ShowS #

Show Name # 
Instance details

Methods

showsPrec :: Int -> Name -> ShowS #

show :: Name -> String #

showList :: [Name] -> ShowS #

NFData Class # 
Instance details

Methods

rnf :: Class -> () #

NFData Type # 
Instance details

Methods

rnf :: Type -> () #

NFData Var # 
Instance details

Methods

rnf :: Var -> () #

NFData TyCon # 
Instance details

Methods

rnf :: TyCon -> () #

Symbolic Class # 
Instance details

Methods

symbol :: Class -> Symbol

Symbolic Var #
NOTE:REFLECT-IMPORTS
we **eschew** the unique suffix for exported vars, to make it possible to lookup names from symbols _across_ modules; anyways exported names are top-level and you shouldn't have local binders that shadow them. However, we **keep** the unique suffix for local variables, as otherwise there are spurious, but extremely problematic, name collisions in the fixpoint environment.
Instance details

Methods

symbol :: Var -> Symbol

Symbolic FastString # 
Instance details

Methods

symbol :: FastString -> Symbol

Symbolic TyCon #

Symbol Instances

Instance details

Methods

symbol :: TyCon -> Symbol

Symbolic Name # 
Instance details

Methods

symbol :: Name -> Symbol

Fixpoint Type # 
Instance details

Methods

toFix :: Type -> Doc

simplify :: Type -> Type

Fixpoint Var # 
Instance details

Methods

toFix :: Var -> Doc

simplify :: Var -> Var

Fixpoint Name # 
Instance details

Methods

toFix :: Name -> Doc

simplify :: Name -> Name

Loc Var # 
Instance details

Methods

srcSpan :: Var -> SrcSpan

Hashable DataCon # 
Instance details

Methods

hashWithSalt :: Int -> DataCon -> Int

hash :: DataCon -> Int

Hashable Var # 
Instance details

Methods

hashWithSalt :: Int -> Var -> Int

hash :: Var -> Int

Hashable SrcSpan # 
Instance details

Methods

hashWithSalt :: Int -> SrcSpan -> Int

hash :: SrcSpan -> Int

Hashable TyCon # 
Instance details

Methods

hashWithSalt :: Int -> TyCon -> Int

hash :: TyCon -> Int

Outputable a => Outputable (HashSet a) # 
Instance details

Methods

ppr :: HashSet a -> SDoc #

pprPrec :: Rational -> HashSet a -> SDoc #