ghcide-1.7.0.0: The core of an IDE
Safe HaskellNone
LanguageHaskell2010

Development.IDE.GHC.Compat.Util

Description

GHC Utils and Datastructures re-exports.

Mainly handles module hierarchy re-organisation of GHC from version to= 9.0.

Some Functions, such as toList shadow other function-names. This way this module can be imported qualified more naturally.

Synopsis

Exception handling

data GhcException #

GHC's own exception type error messages all take the form:

     location: error
 

If the location is on the command line, or in GHC itself, then location="ghc". All of the error types below correspond to a location of "ghc", except for ProgramError (where the string is assumed to contain a location already, so we don't print one).

Instances

Instances details
Show GhcException 
Instance details

Defined in Panic

Exception GhcException 
Instance details

Defined in Panic

handleGhcException :: ExceptionMonad m => (GhcException -> m a) -> m a -> m a #

catch :: (ExceptionMonad m, Exception e) => m a -> (e -> m a) -> m a Source #

try :: (ExceptionMonad m, Exception e) => m a -> m (Either e a) Source #

Bags

data Bag a #

Instances

Instances details
Functor Bag 
Instance details

Defined in Bag

Methods

fmap :: (a -> b) -> Bag a -> Bag b #

(<$) :: a -> Bag b -> Bag a #

Foldable Bag 
Instance details

Defined in Bag

Methods

fold :: Monoid m => Bag m -> m #

foldMap :: Monoid m => (a -> m) -> Bag a -> m #

foldMap' :: Monoid m => (a -> m) -> Bag a -> m #

foldr :: (a -> b -> b) -> b -> Bag a -> b #

foldr' :: (a -> b -> b) -> b -> Bag a -> b #

foldl :: (b -> a -> b) -> b -> Bag a -> b #

foldl' :: (b -> a -> b) -> b -> Bag a -> b #

foldr1 :: (a -> a -> a) -> Bag a -> a #

foldl1 :: (a -> a -> a) -> Bag a -> a #

toList :: Bag a -> [a] #

null :: Bag a -> Bool #

length :: Bag a -> Int #

elem :: Eq a => a -> Bag a -> Bool #

maximum :: Ord a => Bag a -> a #

minimum :: Ord a => Bag a -> a #

sum :: Num a => Bag a -> a #

product :: Num a => Bag a -> a #

Traversable Bag 
Instance details

Defined in Bag

Methods

traverse :: Applicative f => (a -> f b) -> Bag a -> f (Bag b) #

sequenceA :: Applicative f => Bag (f a) -> f (Bag a) #

mapM :: Monad m => (a -> m b) -> Bag a -> m (Bag b) #

sequence :: Monad m => Bag (m a) -> m (Bag a) #

Data a => Data (Bag a) 
Instance details

Defined in Bag

Methods

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

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

toConstr :: Bag a -> Constr #

dataTypeOf :: Bag a -> DataType #

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

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

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

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

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

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

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

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

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

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

Show a => Show (Bag a) Source # 
Instance details

Defined in Development.IDE.GHC.Orphans

Methods

showsPrec :: Int -> Bag a -> ShowS #

show :: Bag a -> String #

showList :: [Bag a] -> ShowS #

Outputable a => Outputable (Bag a) 
Instance details

Defined in Bag

Methods

ppr :: Bag a -> SDoc #

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

ToHie a => ToHie (Bag a) 
Instance details

Defined in Compat.HieAst

Methods

toHie :: Bag a -> HieM [HieAST Type]

bagToList :: Bag a -> [a] #

listToBag :: [a] -> Bag a #

unionBags :: Bag a -> Bag a -> Bag a #

Boolean Formula

data BooleanFormula a #

Instances

Instances details
Functor BooleanFormula 
Instance details

Defined in BooleanFormula

Methods

fmap :: (a -> b) -> BooleanFormula a -> BooleanFormula b #

(<$) :: a -> BooleanFormula b -> BooleanFormula a #

Foldable BooleanFormula 
Instance details

Defined in BooleanFormula

Methods

fold :: Monoid m => BooleanFormula m -> m #

foldMap :: Monoid m => (a -> m) -> BooleanFormula a -> m #

foldMap' :: Monoid m => (a -> m) -> BooleanFormula a -> m #

foldr :: (a -> b -> b) -> b -> BooleanFormula a -> b #

foldr' :: (a -> b -> b) -> b -> BooleanFormula a -> b #

foldl :: (b -> a -> b) -> b -> BooleanFormula a -> b #

foldl' :: (b -> a -> b) -> b -> BooleanFormula a -> b #

foldr1 :: (a -> a -> a) -> BooleanFormula a -> a #

foldl1 :: (a -> a -> a) -> BooleanFormula a -> a #

toList :: BooleanFormula a -> [a] #

null :: BooleanFormula a -> Bool #

length :: BooleanFormula a -> Int #

elem :: Eq a => a -> BooleanFormula a -> Bool #

maximum :: Ord a => BooleanFormula a -> a #

minimum :: Ord a => BooleanFormula a -> a #

sum :: Num a => BooleanFormula a -> a #

product :: Num a => BooleanFormula a -> a #

Traversable BooleanFormula 
Instance details

Defined in BooleanFormula

Methods

traverse :: Applicative f => (a -> f b) -> BooleanFormula a -> f (BooleanFormula b) #

sequenceA :: Applicative f => BooleanFormula (f a) -> f (BooleanFormula a) #

mapM :: Monad m => (a -> m b) -> BooleanFormula a -> m (BooleanFormula b) #

sequence :: Monad m => BooleanFormula (m a) -> m (BooleanFormula a) #

Eq a => Eq (BooleanFormula a) 
Instance details

Defined in BooleanFormula

Data a => Data (BooleanFormula a) 
Instance details

Defined in BooleanFormula

Methods

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

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

toConstr :: BooleanFormula a -> Constr #

dataTypeOf :: BooleanFormula a -> DataType #

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

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

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

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

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

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

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

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

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

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

Binary a => Binary (BooleanFormula a) 
Instance details

Defined in BooleanFormula

OutputableBndr a => Outputable (BooleanFormula a) 
Instance details

Defined in BooleanFormula

Annotate name => Annotate (BooleanFormula (Located name)) 
Instance details

Defined in Language.Haskell.GHC.ExactPrint.Annotater

Methods

markAST :: SrcSpan -> BooleanFormula (Located name) -> Annotated () #

ToHie (LBooleanFormula (Located Name)) 
Instance details

Defined in Compat.HieAst

OverridingBool

data OverridingBool #

Constructors

Auto 
Always 
Never 

Instances

Instances details
Show OverridingBool 
Instance details

Defined in Util

Maybes

data MaybeErr err val #

Constructors

Succeeded val 
Failed err 

Instances

Instances details
Monad (MaybeErr err) 
Instance details

Defined in Maybes

Methods

(>>=) :: MaybeErr err a -> (a -> MaybeErr err b) -> MaybeErr err b #

(>>) :: MaybeErr err a -> MaybeErr err b -> MaybeErr err b #

return :: a -> MaybeErr err a #

Functor (MaybeErr err) 
Instance details

Defined in Maybes

Methods

fmap :: (a -> b) -> MaybeErr err a -> MaybeErr err b #

(<$) :: a -> MaybeErr err b -> MaybeErr err a #

Applicative (MaybeErr err) 
Instance details

Defined in Maybes

Methods

pure :: a -> MaybeErr err a #

(<*>) :: MaybeErr err (a -> b) -> MaybeErr err a -> MaybeErr err b #

liftA2 :: (a -> b -> c) -> MaybeErr err a -> MaybeErr err b -> MaybeErr err c #

(*>) :: MaybeErr err a -> MaybeErr err b -> MaybeErr err b #

(<*) :: MaybeErr err a -> MaybeErr err b -> MaybeErr err a #

orElse :: Maybe a -> a -> a infixr 4 #

Flipped version of fromMaybe, useful for chaining.

Pair

data Pair a #

Constructors

Pair 

Fields

Instances

Instances details
Functor Pair 
Instance details

Defined in Pair

Methods

fmap :: (a -> b) -> Pair a -> Pair b #

(<$) :: a -> Pair b -> Pair a #

Applicative Pair 
Instance details

Defined in Pair

Methods

pure :: a -> Pair a #

(<*>) :: Pair (a -> b) -> Pair a -> Pair b #

liftA2 :: (a -> b -> c) -> Pair a -> Pair b -> Pair c #

(*>) :: Pair a -> Pair b -> Pair b #

(<*) :: Pair a -> Pair b -> Pair a #

Foldable Pair 
Instance details

Defined in Pair

Methods

fold :: Monoid m => Pair m -> m #

foldMap :: Monoid m => (a -> m) -> Pair a -> m #

foldMap' :: Monoid m => (a -> m) -> Pair a -> m #

foldr :: (a -> b -> b) -> b -> Pair a -> b #

foldr' :: (a -> b -> b) -> b -> Pair a -> b #

foldl :: (b -> a -> b) -> b -> Pair a -> b #

foldl' :: (b -> a -> b) -> b -> Pair a -> b #

foldr1 :: (a -> a -> a) -> Pair a -> a #

foldl1 :: (a -> a -> a) -> Pair a -> a #

toList :: Pair a -> [a] #

null :: Pair a -> Bool #

length :: Pair a -> Int #

elem :: Eq a => a -> Pair a -> Bool #

maximum :: Ord a => Pair a -> a #

minimum :: Ord a => Pair a -> a #

sum :: Num a => Pair a -> a #

product :: Num a => Pair a -> a #

Traversable Pair 
Instance details

Defined in Pair

Methods

traverse :: Applicative f => (a -> f b) -> Pair a -> f (Pair b) #

sequenceA :: Applicative f => Pair (f a) -> f (Pair a) #

mapM :: Monad m => (a -> m b) -> Pair a -> m (Pair b) #

sequence :: Monad m => Pair (m a) -> m (Pair a) #

Semigroup a => Semigroup (Pair a) 
Instance details

Defined in Pair

Methods

(<>) :: Pair a -> Pair a -> Pair a #

sconcat :: NonEmpty (Pair a) -> Pair a #

stimes :: Integral b => b -> Pair a -> Pair a #

(Semigroup a, Monoid a) => Monoid (Pair a) 
Instance details

Defined in Pair

Methods

mempty :: Pair a #

mappend :: Pair a -> Pair a -> Pair a #

mconcat :: [Pair a] -> Pair a #

Outputable a => Outputable (Pair a) 
Instance details

Defined in Pair

Methods

ppr :: Pair a -> SDoc #

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

EnumSet

data EnumSet a #

toList :: Enum a => EnumSet a -> [a] #

FastString exports

data FastString #

A FastString is a UTF-8 encoded string together with a unique ID. All FastStrings are stored in a global hashtable to support fast O(1) comparison.

It is also associated with a lazy reference to the Z-encoding of this string which is used by the compiler internally.

Instances

Instances details
Eq FastString 
Instance details

Defined in FastString

Data FastString 
Instance details

Defined in FastString

Methods

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

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

toConstr :: FastString -> Constr #

dataTypeOf :: FastString -> DataType #

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

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

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

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

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

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

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

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

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

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

Ord FastString 
Instance details

Defined in FastString

Show FastString 
Instance details

Defined in FastString

IsString FastString 
Instance details

Defined in FastString

Semigroup FastString 
Instance details

Defined in FastString

Monoid FastString 
Instance details

Defined in FastString

NFData FastString 
Instance details

Defined in FastString

Methods

rnf :: FastString -> () #

Uniquable FastString 
Instance details

Defined in Unique

Outputable FastString 
Instance details

Defined in Outputable

Annotate FastString 
Instance details

Defined in Language.Haskell.GHC.ExactPrint.Annotater

Methods

markAST :: SrcSpan -> FastString -> Annotated () #

Annotate (SourceText, FastString) 
Instance details

Defined in Language.Haskell.GHC.ExactPrint.Annotater

unpackFS :: FastString -> String #

Unpacks and decodes the FastString

mkFastString :: String -> FastString #

Creates a UTF-8 encoded FastString from a String

pprHsString :: FastString -> SDoc #

Special combinator for showing string literals.

Fingerprint

data Fingerprint #

Constructors

Fingerprint !Word64 !Word64 

Instances

Instances details
Eq Fingerprint

Since: base-4.4.0.0

Instance details

Defined in GHC.Fingerprint.Type

Ord Fingerprint

Since: base-4.4.0.0

Instance details

Defined in GHC.Fingerprint.Type

Show Fingerprint

Since: base-4.7.0.0

Instance details

Defined in GHC.Fingerprint.Type

Hashable Fingerprint

Since: hashable-1.3.0.0

Instance details

Defined in Data.Hashable.Class

Storable Fingerprint

Since: base-4.4.0.0

Instance details

Defined in Foreign.Storable

Binary Fingerprint

Since: binary-0.7.6.0

Instance details

Defined in Data.Binary.Class

NFData Fingerprint

Since: deepseq-1.4.0.0

Instance details

Defined in Control.DeepSeq

Methods

rnf :: Fingerprint -> () #

Outputable Fingerprint 
Instance details

Defined in Outputable

getFileHash :: FilePath -> IO Fingerprint #

Computes the hash of a given file. This function loops over the handle, running in constant memory.

Since: base-4.7.0.0

Unique

class Uniquable a #

Class of things that we can obtain a Unique from

Minimal complete definition

getUnique

Instances

Instances details
Uniquable Int 
Instance details

Defined in Unique

Methods

getUnique :: Int -> Unique #

Uniquable EvBindsVar 
Instance details

Defined in TcEvidence

Uniquable LocalReg 
Instance details

Defined in CmmExpr

Methods

getUnique :: LocalReg -> Unique #

Uniquable Label 
Instance details

Defined in Hoopl.Label

Methods

getUnique :: Label -> Unique #

Uniquable Class 
Instance details

Defined in Class

Methods

getUnique :: Class -> Unique #

Uniquable CoAxiomRule 
Instance details

Defined in CoAxiom

Uniquable ConLike 
Instance details

Defined in ConLike

Methods

getUnique :: ConLike -> Unique #

Uniquable DataCon 
Instance details

Defined in DataCon

Methods

getUnique :: DataCon -> Unique #

Uniquable PatSyn 
Instance details

Defined in PatSyn

Methods

getUnique :: PatSyn -> Unique #

Uniquable Var 
Instance details

Defined in Var

Methods

getUnique :: Var -> Unique #

Uniquable SourcePackageId 
Instance details

Defined in PackageConfig

Uniquable PackageName 
Instance details

Defined in PackageConfig

Uniquable Unique 
Instance details

Defined in Unique

Methods

getUnique :: Unique -> Unique #

Uniquable Module 
Instance details

Defined in Module

Methods

getUnique :: Module -> Unique #

Uniquable ModuleName 
Instance details

Defined in Module

Uniquable UnitId 
Instance details

Defined in Module

Methods

getUnique :: UnitId -> Unique #

Uniquable InstalledUnitId 
Instance details

Defined in Module

Uniquable ComponentId 
Instance details

Defined in Module

Uniquable FastString 
Instance details

Defined in Unique

Uniquable TyCon 
Instance details

Defined in TyCon

Methods

getUnique :: TyCon -> Unique #

Uniquable OccName 
Instance details

Defined in OccName

Methods

getUnique :: OccName -> Unique #

Uniquable Name 
Instance details

Defined in Name

Methods

getUnique :: Name -> Unique #

Uniquable (CoAxiom br) 
Instance details

Defined in CoAxiom

Methods

getUnique :: CoAxiom br -> Unique #

Uniquable name => Uniquable (AnnTarget name) 
Instance details

Defined in Annotations

Methods

getUnique :: AnnTarget name -> Unique #

data Unique #

Unique identifier.

The type of unique identifiers that are used in many places in GHC for fast ordering and equality tests. You should generate these with the functions from the UniqSupply module

These are sometimes also referred to as "keys" in comments in GHC.

Instances

Instances details
Eq Unique 
Instance details

Defined in Unique

Methods

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

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

Show Unique 
Instance details

Defined in Unique

Uniquable Unique 
Instance details

Defined in Unique

Methods

getUnique :: Unique -> Unique #

Outputable Unique 
Instance details

Defined in Unique

Methods

ppr :: Unique -> SDoc #

pprPrec :: Rational -> Unique -> SDoc #

UniqDFM

plusUDFM :: UniqDFM elt -> UniqDFM elt -> UniqDFM elt #

plusUDFM_C :: (elt -> elt -> elt) -> UniqDFM elt -> UniqDFM elt -> UniqDFM elt #

String Buffer

data StringBuffer #

A StringBuffer is an internal pointer to a sized chunk of bytes. The bytes are intended to be *immutable*. There are pure operations to read the contents of a StringBuffer.

A StringBuffer may have a finalizer, depending on how it was obtained.

Constructors

StringBuffer 

Fields

Instances

Instances details
Show StringBuffer 
Instance details

Defined in StringBuffer

NFData StringBuffer Source # 
Instance details

Defined in Development.IDE.GHC.Orphans

Methods

rnf :: StringBuffer -> () #

hGetStringBuffer :: FilePath -> IO StringBuffer #

Read a file into a StringBuffer. The resulting buffer is automatically managed by the garbage collector.

stringToStringBuffer :: String -> StringBuffer #

Encode a String into a StringBuffer as UTF-8. The resulting buffer is automatically managed by the garbage collector.

nextChar :: StringBuffer -> (Char, StringBuffer) #

Return the first UTF-8 character of a nonempty StringBuffer and as well the remaining portion (analogous to uncons). Warning: The behavior is undefined if the StringBuffer is empty. The result shares the same buffer as the original. Similar to utf8DecodeChar, if the character cannot be decoded as UTF-8, '\0' is returned.

atEnd :: StringBuffer -> Bool #

Check whether a StringBuffer is empty (analogous to null).

Char