| Safe Haskell | Safe-Inferred | 
|---|---|
| Language | GHC2021 | 
Development.IDE.GHC.Compat.Util
Description
Synopsis
- class MonadThrow m => MonadCatch (m :: Type -> Type)
- data GhcException
- handleGhcException :: ExceptionMonad m => (GhcException -> m a) -> m a -> m a
- catch :: (HasCallStack, MonadCatch m, Exception e) => m a -> (e -> m a) -> m a
- try :: (HasCallStack, MonadCatch m, Exception e) => m a -> m (Either e a)
- data Bag a
- bagToList :: Bag a -> [a]
- listToBag :: [a] -> Bag a
- unionBags :: Bag a -> Bag a -> Bag a
- isEmptyBag :: Bag a -> Bool
- type LBooleanFormula a = LocatedL (BooleanFormula a)
- data BooleanFormula a- = Var a
- | And [LBooleanFormula a]
- | Or [LBooleanFormula a]
- | Parens (LBooleanFormula a)
 
- data OverridingBool
- data MaybeErr err val
- orElse :: Maybe a -> a -> a
- data Pair a = Pair {}
- data EnumSet a
- toList :: Enum a => EnumSet a -> [a]
- data FastString
- newtype LexicalFastString = LexicalFastString FastString
- uniq :: FastString -> Int
- unpackFS :: FastString -> String
- mkFastString :: String -> FastString
- fsLit :: String -> FastString
- pprHsString :: FastString -> SDoc
- data Fingerprint = Fingerprint !Word64 !Word64
- getFileHash :: FilePath -> IO Fingerprint
- fingerprintData :: Ptr Word8 -> Int -> IO Fingerprint
- fingerprintString :: String -> Fingerprint
- fingerprintFingerprints :: [Fingerprint] -> Fingerprint
- class Uniquable a
- nonDetCmpUnique :: Unique -> Unique -> Ordering
- getUnique :: Uniquable a => a -> Unique
- data Unique
- mkUnique :: Char -> Int -> Unique
- newTagUnique :: Unique -> Char -> Unique
- emptyUDFM :: UniqDFM key elt
- plusUDFM :: UniqDFM key elt -> UniqDFM key elt -> UniqDFM key elt
- plusUDFM_C :: (elt -> elt -> elt) -> UniqDFM key elt -> UniqDFM key elt -> UniqDFM key elt
- data StringBuffer = StringBuffer {}
- hGetStringBuffer :: FilePath -> IO StringBuffer
- stringToStringBuffer :: String -> StringBuffer
- nextChar :: StringBuffer -> (Char, StringBuffer)
- atEnd :: StringBuffer -> Bool
Exception handling
class MonadThrow m => MonadCatch (m :: Type -> Type) #
A class for monads which allow exceptions to be caught, in particular
 exceptions which were thrown by throwM.
Instances should obey the following law:
catch (throwM e) f = f e
Note that the ability to catch an exception does not guarantee that we can
 deal with all possible exit points from a computation. Some monads, such as
 continuation-based stacks, allow for more than just a success/failure
 strategy, and therefore catch cannot be used by those monads to properly
 implement a function such as finally. For more information, see
 MonadMask.
Minimal complete definition
Instances
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
| Exception GhcException | |
| Defined in GHC.Utils.Panic Methods toException :: GhcException -> SomeException # fromException :: SomeException -> Maybe GhcException # displayException :: GhcException -> String # | |
| Show GhcException | |
| Defined in GHC.Utils.Panic Methods showsPrec :: Int -> GhcException -> ShowS # show :: GhcException -> String # showList :: [GhcException] -> ShowS # | |
handleGhcException :: ExceptionMonad m => (GhcException -> m a) -> m a -> m a #
catch :: (HasCallStack, MonadCatch m, Exception e) => m a -> (e -> m a) -> m a #
Same as upstream catch, but will not catch asynchronous
 exceptions
Since: safe-exceptions-0.1.0.0
try :: (HasCallStack, MonadCatch m, Exception e) => m a -> m (Either e a) #
Same as upstream try, but will not catch asynchronous
 exceptions
Since: safe-exceptions-0.1.0.0
Bags
Instances
| Foldable Bag | |
| Defined in GHC.Data.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 # elem :: Eq a => a -> Bag a -> Bool # maximum :: Ord a => Bag a -> a # | |
| Traversable Bag | |
| Functor Bag | |
| Data a => Data (Bag a) | |
| Defined in GHC.Data.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) # 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) # | |
| Monoid (Bag a) | |
| Semigroup (Bag a) | |
| IsList (Bag a) | |
| Show a => Show (Bag a) Source # | |
| ToHie a => ToHie (Bag a) | |
| Defined in GHC.Iface.Ext.Ast | |
| Outputable a => Outputable (Bag a) | |
| Defined in GHC.Data.Bag | |
| type Item (Bag a) | |
| Defined in GHC.Data.Bag | |
isEmptyBag :: Bag a -> Bool #
Boolean Formula
type LBooleanFormula a = LocatedL (BooleanFormula a) #
data BooleanFormula a #
Constructors
| Var a | |
| And [LBooleanFormula a] | |
| Or [LBooleanFormula a] | |
| Parens (LBooleanFormula a) | 
Instances
OverridingBool
data OverridingBool #
Instances
Maybes
Instances
| Applicative (MaybeErr err) | |
| Defined in GHC.Data.Maybe | |
| Functor (MaybeErr err) | |
| Monad (MaybeErr err) | |
Pair
Instances
| Foldable Pair | |
| Defined in GHC.Data.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 # elem :: Eq a => a -> Pair a -> Bool # maximum :: Ord a => Pair a -> a # | |
| Traversable Pair | |
| Applicative Pair | |
| Functor Pair | |
| (Semigroup a, Monoid a) => Monoid (Pair a) | |
| Semigroup a => Semigroup (Pair a) | |
| Outputable a => Outputable (Pair a) | |
| Defined in GHC.Data.Pair | |
EnumSet
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
newtype LexicalFastString #
Lexical FastString
This is a simple FastString wrapper with an Ord instance using
 lexicalCompareFS (i.e. which compares FastStrings on their String
 representation). Hence it is deterministic from one run to the other.
Constructors
| LexicalFastString FastString | 
Instances
uniq :: FastString -> Int #
unpackFS :: FastString -> String #
Lazily unpacks and decodes the FastString
mkFastString :: String -> FastString #
Creates a UTF-8 encoded FastString from a String
fsLit :: String -> FastString #
pprHsString :: FastString -> SDoc #
Special combinator for showing string literals.
Fingerprint
data Fingerprint #
Constructors
| Fingerprint !Word64 !Word64 | 
Instances
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
fingerprintData :: Ptr Word8 -> Int -> IO Fingerprint #
fingerprintString :: String -> Fingerprint #
Unique
Class of things that we can obtain a Unique from
Minimal complete definition
Instances
nonDetCmpUnique :: Unique -> Unique -> Ordering #
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
| Show Unique | |
| Uniquable Unique | |
| Defined in GHC.Types.Unique | |
| Outputable Unique | |
| Defined in GHC.Types.Unique | |
| Eq Unique | |
newTagUnique :: Unique -> Char -> Unique #
UniqDFM
plusUDFM_C :: (elt -> elt -> elt) -> UniqDFM key elt -> UniqDFM key elt -> UniqDFM key 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 | |
Instances
| Show StringBuffer | |
| Defined in GHC.Data.StringBuffer Methods showsPrec :: Int -> StringBuffer -> ShowS # show :: StringBuffer -> String # showList :: [StringBuffer] -> ShowS # | |
| NFData StringBuffer Source # | |
| 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).