{-# LANGUAGE DeriveTraversable #-}
{-# LANGUAGE DeriveDataTypeable #-}
{-# LANGUAGE GeneralizedNewtypeDeriving #-}
{-# LANGUAGE TypeSynonymInstances #-}
{-# LANGUAGE FlexibleInstances #-}
{-# LANGUAGE ScopedTypeVariables #-}
{-# LANGUAGE OverloadedStrings #-}
module GHC.Iface.Ext.Types where
import GHC.Prelude
import GHC.Settings.Config
import GHC.Utils.Binary
import GHC.Data.FastString ( FastString )
import GHC.Builtin.Utils
import GHC.Iface.Type
import GHC.Unit.Module ( ModuleName, Module )
import GHC.Types.Name
import GHC.Utils.Outputable hiding ( (<>) )
import GHC.Types.SrcLoc
import GHC.Types.Avail
import GHC.Types.Unique
import qualified GHC.Utils.Outputable as O ( (<>) )
import GHC.Utils.Misc
import qualified Data.Array as A
import qualified Data.Map as M
import qualified Data.Set as S
import Data.ByteString ( ByteString )
import Data.Data ( Typeable, Data )
import Data.Semigroup ( Semigroup(..) )
import Data.Word ( Word8 )
import Control.Applicative ( (<|>) )
import Data.Coerce ( coerce )
import Data.Function ( on )
type Span = RealSrcSpan
hieVersion :: Integer
hieVersion :: Integer
hieVersion = String -> Integer
forall a. Read a => String -> a
External instance of the constraint type Read Integer
read (String
cProjectVersionInt String -> String -> String
forall a. [a] -> [a] -> [a]
++ String
cProjectPatchLevel) :: Integer
data HieFile = HieFile
{ HieFile -> String
hie_hs_file :: FilePath
, HieFile -> Module
hie_module :: Module
, HieFile -> Array TypeIndex (HieType TypeIndex)
hie_types :: A.Array TypeIndex HieTypeFlat
, HieFile -> HieASTs TypeIndex
hie_asts :: HieASTs TypeIndex
, HieFile -> [AvailInfo]
hie_exports :: [AvailInfo]
, HieFile -> ByteString
hie_hs_src :: ByteString
}
instance Binary HieFile where
put_ :: BinHandle -> HieFile -> IO ()
put_ BinHandle
bh HieFile
hf = do
BinHandle -> String -> IO ()
forall a. Binary a => BinHandle -> a -> IO ()
External instance of the constraint type forall a. Binary a => Binary [a]
External instance of the constraint type Binary Char
put_ BinHandle
bh (String -> IO ()) -> String -> IO ()
forall a b. (a -> b) -> a -> b
$ HieFile -> String
hie_hs_file HieFile
hf
BinHandle -> Module -> IO ()
forall a. Binary a => BinHandle -> a -> IO ()
External instance of the constraint type forall a. Binary a => Binary (GenModule a)
External instance of the constraint type Binary (GenUnit UnitId)
put_ BinHandle
bh (Module -> IO ()) -> Module -> IO ()
forall a b. (a -> b) -> a -> b
$ HieFile -> Module
hie_module HieFile
hf
BinHandle -> Array TypeIndex (HieType TypeIndex) -> IO ()
forall a. Binary a => BinHandle -> a -> IO ()
External instance of the constraint type forall a b. (Ix a, Binary a, Binary b) => Binary (Array a b)
External instance of the constraint type Ix TypeIndex
External instance of the constraint type Binary TypeIndex
Instance of class: Binary of the constraint type Binary (HieType TypeIndex)
put_ BinHandle
bh (Array TypeIndex (HieType TypeIndex) -> IO ())
-> Array TypeIndex (HieType TypeIndex) -> IO ()
forall a b. (a -> b) -> a -> b
$ HieFile -> Array TypeIndex (HieType TypeIndex)
hie_types HieFile
hf
BinHandle -> HieASTs TypeIndex -> IO ()
forall a. Binary a => BinHandle -> a -> IO ()
Instance of class: Binary of the constraint type Binary (HieASTs TypeIndex)
put_ BinHandle
bh (HieASTs TypeIndex -> IO ()) -> HieASTs TypeIndex -> IO ()
forall a b. (a -> b) -> a -> b
$ HieFile -> HieASTs TypeIndex
hie_asts HieFile
hf
BinHandle -> [AvailInfo] -> IO ()
forall a. Binary a => BinHandle -> a -> IO ()
External instance of the constraint type forall a. Binary a => Binary [a]
External instance of the constraint type Binary AvailInfo
put_ BinHandle
bh ([AvailInfo] -> IO ()) -> [AvailInfo] -> IO ()
forall a b. (a -> b) -> a -> b
$ HieFile -> [AvailInfo]
hie_exports HieFile
hf
BinHandle -> ByteString -> IO ()
forall a. Binary a => BinHandle -> a -> IO ()
External instance of the constraint type Binary ByteString
put_ BinHandle
bh (ByteString -> IO ()) -> ByteString -> IO ()
forall a b. (a -> b) -> a -> b
$ HieFile -> ByteString
hie_hs_src HieFile
hf
get :: BinHandle -> IO HieFile
get BinHandle
bh = String
-> Module
-> Array TypeIndex (HieType TypeIndex)
-> HieASTs TypeIndex
-> [AvailInfo]
-> ByteString
-> HieFile
HieFile
(String
-> Module
-> Array TypeIndex (HieType TypeIndex)
-> HieASTs TypeIndex
-> [AvailInfo]
-> ByteString
-> HieFile)
-> IO String
-> IO
(Module
-> Array TypeIndex (HieType TypeIndex)
-> HieASTs TypeIndex
-> [AvailInfo]
-> ByteString
-> HieFile)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
External instance of the constraint type Functor IO
<$> BinHandle -> IO String
forall a. Binary a => BinHandle -> IO a
External instance of the constraint type forall a. Binary a => Binary [a]
External instance of the constraint type Binary Char
get BinHandle
bh
IO
(Module
-> Array TypeIndex (HieType TypeIndex)
-> HieASTs TypeIndex
-> [AvailInfo]
-> ByteString
-> HieFile)
-> IO Module
-> IO
(Array TypeIndex (HieType TypeIndex)
-> HieASTs TypeIndex -> [AvailInfo] -> ByteString -> HieFile)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
External instance of the constraint type Applicative IO
<*> BinHandle -> IO Module
forall a. Binary a => BinHandle -> IO a
External instance of the constraint type forall a. Binary a => Binary (GenModule a)
External instance of the constraint type Binary (GenUnit UnitId)
get BinHandle
bh
IO
(Array TypeIndex (HieType TypeIndex)
-> HieASTs TypeIndex -> [AvailInfo] -> ByteString -> HieFile)
-> IO (Array TypeIndex (HieType TypeIndex))
-> IO (HieASTs TypeIndex -> [AvailInfo] -> ByteString -> HieFile)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
External instance of the constraint type Applicative IO
<*> BinHandle -> IO (Array TypeIndex (HieType TypeIndex))
forall a. Binary a => BinHandle -> IO a
External instance of the constraint type forall a b. (Ix a, Binary a, Binary b) => Binary (Array a b)
External instance of the constraint type Ix TypeIndex
External instance of the constraint type Binary TypeIndex
Instance of class: Binary of the constraint type Binary (HieType TypeIndex)
get BinHandle
bh
IO (HieASTs TypeIndex -> [AvailInfo] -> ByteString -> HieFile)
-> IO (HieASTs TypeIndex)
-> IO ([AvailInfo] -> ByteString -> HieFile)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
External instance of the constraint type Applicative IO
<*> BinHandle -> IO (HieASTs TypeIndex)
forall a. Binary a => BinHandle -> IO a
Instance of class: Binary of the constraint type Binary (HieASTs TypeIndex)
get BinHandle
bh
IO ([AvailInfo] -> ByteString -> HieFile)
-> IO [AvailInfo] -> IO (ByteString -> HieFile)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
External instance of the constraint type Applicative IO
<*> BinHandle -> IO [AvailInfo]
forall a. Binary a => BinHandle -> IO a
External instance of the constraint type forall a. Binary a => Binary [a]
External instance of the constraint type Binary AvailInfo
get BinHandle
bh
IO (ByteString -> HieFile) -> IO ByteString -> IO HieFile
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
External instance of the constraint type Applicative IO
<*> BinHandle -> IO ByteString
forall a. Binary a => BinHandle -> IO a
External instance of the constraint type Binary ByteString
get BinHandle
bh
type TypeIndex = Int
data HieType a
= HTyVarTy Name
| HAppTy a (HieArgs a)
| HTyConApp IfaceTyCon (HieArgs a)
| HForAllTy ((Name, a),ArgFlag) a
| HFunTy a a
| HQualTy a a
| HLitTy IfaceTyLit
| HCastTy a
| HCoercionTy
deriving (a -> HieType b -> HieType a
(a -> b) -> HieType a -> HieType b
(forall a b. (a -> b) -> HieType a -> HieType b)
-> (forall a b. a -> HieType b -> HieType a) -> Functor HieType
forall a b. a -> HieType b -> HieType a
forall a b. (a -> b) -> HieType a -> HieType b
forall (f :: * -> *).
(forall a b. (a -> b) -> f a -> f b)
-> (forall a b. a -> f b -> f a) -> Functor f
<$ :: a -> HieType b -> HieType a
$c<$ :: forall a b. a -> HieType b -> HieType a
fmap :: (a -> b) -> HieType a -> HieType b
$cfmap :: forall a b. (a -> b) -> HieType a -> HieType b
Instance of class: Functor of the constraint type Functor HieArgs
Instance of class: Functor of the constraint type Functor HieArgs
Instance of class: Functor of the constraint type Functor HieArgs
Functor, HieType a -> Bool
(a -> m) -> HieType a -> m
(a -> b -> b) -> b -> HieType a -> b
(forall m. Monoid m => HieType m -> m)
-> (forall m a. Monoid m => (a -> m) -> HieType a -> m)
-> (forall m a. Monoid m => (a -> m) -> HieType a -> m)
-> (forall a b. (a -> b -> b) -> b -> HieType a -> b)
-> (forall a b. (a -> b -> b) -> b -> HieType a -> b)
-> (forall b a. (b -> a -> b) -> b -> HieType a -> b)
-> (forall b a. (b -> a -> b) -> b -> HieType a -> b)
-> (forall a. (a -> a -> a) -> HieType a -> a)
-> (forall a. (a -> a -> a) -> HieType a -> a)
-> (forall a. HieType a -> [a])
-> (forall a. HieType a -> Bool)
-> (forall a. HieType a -> TypeIndex)
-> (forall a. Eq a => a -> HieType a -> Bool)
-> (forall a. Ord a => HieType a -> a)
-> (forall a. Ord a => HieType a -> a)
-> (forall a. Num a => HieType a -> a)
-> (forall a. Num a => HieType a -> a)
-> Foldable HieType
forall a. Eq a => a -> HieType a -> Bool
forall a. Num a => HieType a -> a
forall a. Ord a => HieType a -> a
forall m. Monoid m => HieType m -> m
forall a. HieType a -> Bool
forall a. HieType a -> TypeIndex
forall a. HieType a -> [a]
forall a. (a -> a -> a) -> HieType a -> a
forall m a. Monoid m => (a -> m) -> HieType a -> m
forall b a. (b -> a -> b) -> b -> HieType a -> b
forall a b. (a -> b -> b) -> b -> HieType a -> b
forall (t :: * -> *).
(forall m. Monoid m => t m -> m)
-> (forall m a. Monoid m => (a -> m) -> t a -> m)
-> (forall m a. Monoid m => (a -> m) -> t a -> m)
-> (forall a b. (a -> b -> b) -> b -> t a -> b)
-> (forall a b. (a -> b -> b) -> b -> t a -> b)
-> (forall b a. (b -> a -> b) -> b -> t a -> b)
-> (forall b a. (b -> a -> b) -> b -> t a -> b)
-> (forall a. (a -> a -> a) -> t a -> a)
-> (forall a. (a -> a -> a) -> t a -> a)
-> (forall a. t a -> [a])
-> (forall a. t a -> Bool)
-> (forall a. t a -> TypeIndex)
-> (forall a. Eq a => a -> t a -> Bool)
-> (forall a. Ord a => t a -> a)
-> (forall a. Ord a => t a -> a)
-> (forall a. Num a => t a -> a)
-> (forall a. Num a => t a -> a)
-> Foldable t
product :: HieType a -> a
$cproduct :: forall a. Num a => HieType a -> a
sum :: HieType a -> a
$csum :: forall a. Num a => HieType a -> a
minimum :: HieType a -> a
$cminimum :: forall a. Ord a => HieType a -> a
maximum :: HieType a -> a
$cmaximum :: forall a. Ord a => HieType a -> a
elem :: a -> HieType a -> Bool
$celem :: forall a. Eq a => a -> HieType a -> Bool
length :: HieType a -> TypeIndex
$clength :: forall a. HieType a -> TypeIndex
null :: HieType a -> Bool
$cnull :: forall a. HieType a -> Bool
toList :: HieType a -> [a]
$ctoList :: forall a. HieType a -> [a]
foldl1 :: (a -> a -> a) -> HieType a -> a
$cfoldl1 :: forall a. (a -> a -> a) -> HieType a -> a
foldr1 :: (a -> a -> a) -> HieType a -> a
$cfoldr1 :: forall a. (a -> a -> a) -> HieType a -> a
foldl' :: (b -> a -> b) -> b -> HieType a -> b
$cfoldl' :: forall b a. (b -> a -> b) -> b -> HieType a -> b
foldl :: (b -> a -> b) -> b -> HieType a -> b
$cfoldl :: forall b a. (b -> a -> b) -> b -> HieType a -> b
foldr' :: (a -> b -> b) -> b -> HieType a -> b
$cfoldr' :: forall a b. (a -> b -> b) -> b -> HieType a -> b
foldr :: (a -> b -> b) -> b -> HieType a -> b
$cfoldr :: forall a b. (a -> b -> b) -> b -> HieType a -> b
foldMap' :: (a -> m) -> HieType a -> m
$cfoldMap' :: forall m a. Monoid m => (a -> m) -> HieType a -> m
foldMap :: (a -> m) -> HieType a -> m
$cfoldMap :: forall m a. Monoid m => (a -> m) -> HieType a -> m
fold :: HieType m -> m
$cfold :: forall m. Monoid m => HieType m -> m
Instance of class: Foldable of the constraint type Foldable HieArgs
Instance of class: Foldable of the constraint type Foldable HieArgs
Evidence bound by a type signature of the constraint type Monoid m
Instance of class: Foldable of the constraint type Foldable HieArgs
Foldable, Functor HieType
Foldable HieType
Functor HieType
-> Foldable HieType
-> (forall (f :: * -> *) a b.
Applicative f =>
(a -> f b) -> HieType a -> f (HieType b))
-> (forall (f :: * -> *) a.
Applicative f =>
HieType (f a) -> f (HieType a))
-> (forall (m :: * -> *) a b.
Monad m =>
(a -> m b) -> HieType a -> m (HieType b))
-> (forall (m :: * -> *) a.
Monad m =>
HieType (m a) -> m (HieType a))
-> Traversable HieType
(a -> f b) -> HieType a -> f (HieType b)
forall (t :: * -> *).
Functor t
-> Foldable t
-> (forall (f :: * -> *) a b.
Applicative f =>
(a -> f b) -> t a -> f (t b))
-> (forall (f :: * -> *) a. Applicative f => t (f a) -> f (t a))
-> (forall (m :: * -> *) a b.
Monad m =>
(a -> m b) -> t a -> m (t b))
-> (forall (m :: * -> *) a. Monad m => t (m a) -> m (t a))
-> Traversable t
forall (m :: * -> *) a. Monad m => HieType (m a) -> m (HieType a)
forall (f :: * -> *) a.
Applicative f =>
HieType (f a) -> f (HieType a)
forall (m :: * -> *) a b.
Monad m =>
(a -> m b) -> HieType a -> m (HieType b)
forall (f :: * -> *) a b.
Applicative f =>
(a -> f b) -> HieType a -> f (HieType b)
sequence :: HieType (m a) -> m (HieType a)
$csequence :: forall (m :: * -> *) a. Monad m => HieType (m a) -> m (HieType a)
mapM :: (a -> m b) -> HieType a -> m (HieType b)
$cmapM :: forall (m :: * -> *) a b.
Monad m =>
(a -> m b) -> HieType a -> m (HieType b)
sequenceA :: HieType (f a) -> f (HieType a)
$csequenceA :: forall (f :: * -> *) a.
Applicative f =>
HieType (f a) -> f (HieType a)
traverse :: (a -> f b) -> HieType a -> f (HieType b)
$ctraverse :: forall (f :: * -> *) a b.
Applicative f =>
(a -> f b) -> HieType a -> f (HieType b)
External instance of the constraint type forall (f :: * -> *). Applicative f => Functor f
External instance of the constraint type forall (f :: * -> *). Applicative f => Functor f
Evidence bound by a type signature of the constraint type Applicative f
Instance of class: Traversable of the constraint type Traversable HieArgs
Evidence bound by a type signature of the constraint type Applicative f
Instance of class: Foldable of the constraint type Foldable HieType
Instance of class: Functor of the constraint type Functor HieType
Instance of class: Functor of the constraint type Functor HieType
Instance of class: Traversable of the constraint type Traversable HieArgs
Instance of class: Foldable of the constraint type Foldable HieType
Traversable, HieType a -> HieType a -> Bool
(HieType a -> HieType a -> Bool)
-> (HieType a -> HieType a -> Bool) -> Eq (HieType a)
forall a. Eq a => HieType a -> HieType a -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: HieType a -> HieType a -> Bool
$c/= :: forall a. Eq a => HieType a -> HieType a -> Bool
== :: HieType a -> HieType a -> Bool
$c== :: forall a. Eq a => HieType a -> HieType a -> Bool
External instance of the constraint type Eq ArgFlag
External instance of the constraint type Eq IfaceTyLit
External instance of the constraint type Eq ArgFlag
External instance of the constraint type forall a b. (Eq a, Eq b) => Eq (a, b)
External instance of the constraint type Eq Name
Evidence bound by a type signature of the constraint type Eq a
External instance of the constraint type forall a b. (Eq a, Eq b) => Eq (a, b)
External instance of the constraint type Eq IfaceTyCon
Instance of class: Eq of the constraint type forall a. Eq a => Eq (HieArgs a)
Instance of class: Eq of the constraint type forall a. Eq a => Eq (HieArgs a)
Evidence bound by a type signature of the constraint type Eq a
External instance of the constraint type Eq Name
External instance of the constraint type Eq Name
Evidence bound by a type signature of the constraint type Eq a
Eq)
type HieTypeFlat = HieType TypeIndex
newtype HieTypeFix = Roll (HieType (HieTypeFix))
instance Binary (HieType TypeIndex) where
put_ :: BinHandle -> HieType TypeIndex -> IO ()
put_ BinHandle
bh (HTyVarTy Name
n) = do
BinHandle -> Word8 -> IO ()
putByte BinHandle
bh Word8
0
BinHandle -> Name -> IO ()
forall a. Binary a => BinHandle -> a -> IO ()
External instance of the constraint type Binary Name
put_ BinHandle
bh Name
n
put_ BinHandle
bh (HAppTy TypeIndex
a HieArgs TypeIndex
b) = do
BinHandle -> Word8 -> IO ()
putByte BinHandle
bh Word8
1
BinHandle -> TypeIndex -> IO ()
forall a. Binary a => BinHandle -> a -> IO ()
External instance of the constraint type Binary TypeIndex
put_ BinHandle
bh TypeIndex
a
BinHandle -> HieArgs TypeIndex -> IO ()
forall a. Binary a => BinHandle -> a -> IO ()
Instance of class: Binary of the constraint type Binary (HieArgs TypeIndex)
put_ BinHandle
bh HieArgs TypeIndex
b
put_ BinHandle
bh (HTyConApp IfaceTyCon
n HieArgs TypeIndex
xs) = do
BinHandle -> Word8 -> IO ()
putByte BinHandle
bh Word8
2
BinHandle -> IfaceTyCon -> IO ()
forall a. Binary a => BinHandle -> a -> IO ()
External instance of the constraint type Binary IfaceTyCon
put_ BinHandle
bh IfaceTyCon
n
BinHandle -> HieArgs TypeIndex -> IO ()
forall a. Binary a => BinHandle -> a -> IO ()
Instance of class: Binary of the constraint type Binary (HieArgs TypeIndex)
put_ BinHandle
bh HieArgs TypeIndex
xs
put_ BinHandle
bh (HForAllTy ((Name, TypeIndex), ArgFlag)
bndr TypeIndex
a) = do
BinHandle -> Word8 -> IO ()
putByte BinHandle
bh Word8
3
BinHandle -> ((Name, TypeIndex), ArgFlag) -> IO ()
forall a. Binary a => BinHandle -> a -> IO ()
External instance of the constraint type forall a b. (Binary a, Binary b) => Binary (a, b)
External instance of the constraint type forall a b. (Binary a, Binary b) => Binary (a, b)
External instance of the constraint type Binary Name
External instance of the constraint type Binary TypeIndex
External instance of the constraint type Binary ArgFlag
put_ BinHandle
bh ((Name, TypeIndex), ArgFlag)
bndr
BinHandle -> TypeIndex -> IO ()
forall a. Binary a => BinHandle -> a -> IO ()
External instance of the constraint type Binary TypeIndex
put_ BinHandle
bh TypeIndex
a
put_ BinHandle
bh (HFunTy TypeIndex
a TypeIndex
b) = do
BinHandle -> Word8 -> IO ()
putByte BinHandle
bh Word8
4
BinHandle -> TypeIndex -> IO ()
forall a. Binary a => BinHandle -> a -> IO ()
External instance of the constraint type Binary TypeIndex
put_ BinHandle
bh TypeIndex
a
BinHandle -> TypeIndex -> IO ()
forall a. Binary a => BinHandle -> a -> IO ()
External instance of the constraint type Binary TypeIndex
put_ BinHandle
bh TypeIndex
b
put_ BinHandle
bh (HQualTy TypeIndex
a TypeIndex
b) = do
BinHandle -> Word8 -> IO ()
putByte BinHandle
bh Word8
5
BinHandle -> TypeIndex -> IO ()
forall a. Binary a => BinHandle -> a -> IO ()
External instance of the constraint type Binary TypeIndex
put_ BinHandle
bh TypeIndex
a
BinHandle -> TypeIndex -> IO ()
forall a. Binary a => BinHandle -> a -> IO ()
External instance of the constraint type Binary TypeIndex
put_ BinHandle
bh TypeIndex
b
put_ BinHandle
bh (HLitTy IfaceTyLit
l) = do
BinHandle -> Word8 -> IO ()
putByte BinHandle
bh Word8
6
BinHandle -> IfaceTyLit -> IO ()
forall a. Binary a => BinHandle -> a -> IO ()
External instance of the constraint type Binary IfaceTyLit
put_ BinHandle
bh IfaceTyLit
l
put_ BinHandle
bh (HCastTy TypeIndex
a) = do
BinHandle -> Word8 -> IO ()
putByte BinHandle
bh Word8
7
BinHandle -> TypeIndex -> IO ()
forall a. Binary a => BinHandle -> a -> IO ()
External instance of the constraint type Binary TypeIndex
put_ BinHandle
bh TypeIndex
a
put_ BinHandle
bh (HieType TypeIndex
HCoercionTy) = BinHandle -> Word8 -> IO ()
putByte BinHandle
bh Word8
8
get :: BinHandle -> IO (HieType TypeIndex)
get BinHandle
bh = do
(Word8
t :: Word8) <- BinHandle -> IO Word8
forall a. Binary a => BinHandle -> IO a
External instance of the constraint type Binary Word8
get BinHandle
bh
case Word8
t of
Word8
0 -> Name -> HieType TypeIndex
forall a. Name -> HieType a
HTyVarTy (Name -> HieType TypeIndex) -> IO Name -> IO (HieType TypeIndex)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
External instance of the constraint type Functor IO
<$> BinHandle -> IO Name
forall a. Binary a => BinHandle -> IO a
External instance of the constraint type Binary Name
get BinHandle
bh
Word8
1 -> TypeIndex -> HieArgs TypeIndex -> HieType TypeIndex
forall a. a -> HieArgs a -> HieType a
HAppTy (TypeIndex -> HieArgs TypeIndex -> HieType TypeIndex)
-> IO TypeIndex -> IO (HieArgs TypeIndex -> HieType TypeIndex)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
External instance of the constraint type Functor IO
<$> BinHandle -> IO TypeIndex
forall a. Binary a => BinHandle -> IO a
External instance of the constraint type Binary TypeIndex
get BinHandle
bh IO (HieArgs TypeIndex -> HieType TypeIndex)
-> IO (HieArgs TypeIndex) -> IO (HieType TypeIndex)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
External instance of the constraint type Applicative IO
<*> BinHandle -> IO (HieArgs TypeIndex)
forall a. Binary a => BinHandle -> IO a
Instance of class: Binary of the constraint type Binary (HieArgs TypeIndex)
get BinHandle
bh
Word8
2 -> IfaceTyCon -> HieArgs TypeIndex -> HieType TypeIndex
forall a. IfaceTyCon -> HieArgs a -> HieType a
HTyConApp (IfaceTyCon -> HieArgs TypeIndex -> HieType TypeIndex)
-> IO IfaceTyCon -> IO (HieArgs TypeIndex -> HieType TypeIndex)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
External instance of the constraint type Functor IO
<$> BinHandle -> IO IfaceTyCon
forall a. Binary a => BinHandle -> IO a
External instance of the constraint type Binary IfaceTyCon
get BinHandle
bh IO (HieArgs TypeIndex -> HieType TypeIndex)
-> IO (HieArgs TypeIndex) -> IO (HieType TypeIndex)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
External instance of the constraint type Applicative IO
<*> BinHandle -> IO (HieArgs TypeIndex)
forall a. Binary a => BinHandle -> IO a
Instance of class: Binary of the constraint type Binary (HieArgs TypeIndex)
get BinHandle
bh
Word8
3 -> ((Name, TypeIndex), ArgFlag) -> TypeIndex -> HieType TypeIndex
forall a. ((Name, a), ArgFlag) -> a -> HieType a
HForAllTy (((Name, TypeIndex), ArgFlag) -> TypeIndex -> HieType TypeIndex)
-> IO ((Name, TypeIndex), ArgFlag)
-> IO (TypeIndex -> HieType TypeIndex)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
External instance of the constraint type Functor IO
<$> BinHandle -> IO ((Name, TypeIndex), ArgFlag)
forall a. Binary a => BinHandle -> IO a
External instance of the constraint type forall a b. (Binary a, Binary b) => Binary (a, b)
External instance of the constraint type forall a b. (Binary a, Binary b) => Binary (a, b)
External instance of the constraint type Binary Name
External instance of the constraint type Binary TypeIndex
External instance of the constraint type Binary ArgFlag
get BinHandle
bh IO (TypeIndex -> HieType TypeIndex)
-> IO TypeIndex -> IO (HieType TypeIndex)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
External instance of the constraint type Applicative IO
<*> BinHandle -> IO TypeIndex
forall a. Binary a => BinHandle -> IO a
External instance of the constraint type Binary TypeIndex
get BinHandle
bh
Word8
4 -> TypeIndex -> TypeIndex -> HieType TypeIndex
forall a. a -> a -> HieType a
HFunTy (TypeIndex -> TypeIndex -> HieType TypeIndex)
-> IO TypeIndex -> IO (TypeIndex -> HieType TypeIndex)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
External instance of the constraint type Functor IO
<$> BinHandle -> IO TypeIndex
forall a. Binary a => BinHandle -> IO a
External instance of the constraint type Binary TypeIndex
get BinHandle
bh IO (TypeIndex -> HieType TypeIndex)
-> IO TypeIndex -> IO (HieType TypeIndex)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
External instance of the constraint type Applicative IO
<*> BinHandle -> IO TypeIndex
forall a. Binary a => BinHandle -> IO a
External instance of the constraint type Binary TypeIndex
get BinHandle
bh
Word8
5 -> TypeIndex -> TypeIndex -> HieType TypeIndex
forall a. a -> a -> HieType a
HQualTy (TypeIndex -> TypeIndex -> HieType TypeIndex)
-> IO TypeIndex -> IO (TypeIndex -> HieType TypeIndex)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
External instance of the constraint type Functor IO
<$> BinHandle -> IO TypeIndex
forall a. Binary a => BinHandle -> IO a
External instance of the constraint type Binary TypeIndex
get BinHandle
bh IO (TypeIndex -> HieType TypeIndex)
-> IO TypeIndex -> IO (HieType TypeIndex)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
External instance of the constraint type Applicative IO
<*> BinHandle -> IO TypeIndex
forall a. Binary a => BinHandle -> IO a
External instance of the constraint type Binary TypeIndex
get BinHandle
bh
Word8
6 -> IfaceTyLit -> HieType TypeIndex
forall a. IfaceTyLit -> HieType a
HLitTy (IfaceTyLit -> HieType TypeIndex)
-> IO IfaceTyLit -> IO (HieType TypeIndex)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
External instance of the constraint type Functor IO
<$> BinHandle -> IO IfaceTyLit
forall a. Binary a => BinHandle -> IO a
External instance of the constraint type Binary IfaceTyLit
get BinHandle
bh
Word8
7 -> TypeIndex -> HieType TypeIndex
forall a. a -> HieType a
HCastTy (TypeIndex -> HieType TypeIndex)
-> IO TypeIndex -> IO (HieType TypeIndex)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
External instance of the constraint type Functor IO
<$> BinHandle -> IO TypeIndex
forall a. Binary a => BinHandle -> IO a
External instance of the constraint type Binary TypeIndex
get BinHandle
bh
Word8
8 -> HieType TypeIndex -> IO (HieType TypeIndex)
forall (m :: * -> *) a. Monad m => a -> m a
External instance of the constraint type Monad IO
return HieType TypeIndex
forall a. HieType a
HCoercionTy
Word8
_ -> String -> IO (HieType TypeIndex)
forall a. String -> a
panic String
"Binary (HieArgs Int): invalid tag"
newtype HieArgs a = HieArgs [(Bool,a)]
deriving (a -> HieArgs b -> HieArgs a
(a -> b) -> HieArgs a -> HieArgs b
(forall a b. (a -> b) -> HieArgs a -> HieArgs b)
-> (forall a b. a -> HieArgs b -> HieArgs a) -> Functor HieArgs
forall a b. a -> HieArgs b -> HieArgs a
forall a b. (a -> b) -> HieArgs a -> HieArgs b
forall (f :: * -> *).
(forall a b. (a -> b) -> f a -> f b)
-> (forall a b. a -> f b -> f a) -> Functor f
<$ :: a -> HieArgs b -> HieArgs a
$c<$ :: forall a b. a -> HieArgs b -> HieArgs a
fmap :: (a -> b) -> HieArgs a -> HieArgs b
$cfmap :: forall a b. (a -> b) -> HieArgs a -> HieArgs b
External instance of the constraint type Functor []
Functor, HieArgs a -> Bool
(a -> m) -> HieArgs a -> m
(a -> b -> b) -> b -> HieArgs a -> b
(forall m. Monoid m => HieArgs m -> m)
-> (forall m a. Monoid m => (a -> m) -> HieArgs a -> m)
-> (forall m a. Monoid m => (a -> m) -> HieArgs a -> m)
-> (forall a b. (a -> b -> b) -> b -> HieArgs a -> b)
-> (forall a b. (a -> b -> b) -> b -> HieArgs a -> b)
-> (forall b a. (b -> a -> b) -> b -> HieArgs a -> b)
-> (forall b a. (b -> a -> b) -> b -> HieArgs a -> b)
-> (forall a. (a -> a -> a) -> HieArgs a -> a)
-> (forall a. (a -> a -> a) -> HieArgs a -> a)
-> (forall a. HieArgs a -> [a])
-> (forall a. HieArgs a -> Bool)
-> (forall a. HieArgs a -> TypeIndex)
-> (forall a. Eq a => a -> HieArgs a -> Bool)
-> (forall a. Ord a => HieArgs a -> a)
-> (forall a. Ord a => HieArgs a -> a)
-> (forall a. Num a => HieArgs a -> a)
-> (forall a. Num a => HieArgs a -> a)
-> Foldable HieArgs
forall a. Eq a => a -> HieArgs a -> Bool
forall a. Num a => HieArgs a -> a
forall a. Ord a => HieArgs a -> a
forall m. Monoid m => HieArgs m -> m
forall a. HieArgs a -> Bool
forall a. HieArgs a -> TypeIndex
forall a. HieArgs a -> [a]
forall a. (a -> a -> a) -> HieArgs a -> a
forall m a. Monoid m => (a -> m) -> HieArgs a -> m
forall b a. (b -> a -> b) -> b -> HieArgs a -> b
forall a b. (a -> b -> b) -> b -> HieArgs a -> b
forall (t :: * -> *).
(forall m. Monoid m => t m -> m)
-> (forall m a. Monoid m => (a -> m) -> t a -> m)
-> (forall m a. Monoid m => (a -> m) -> t a -> m)
-> (forall a b. (a -> b -> b) -> b -> t a -> b)
-> (forall a b. (a -> b -> b) -> b -> t a -> b)
-> (forall b a. (b -> a -> b) -> b -> t a -> b)
-> (forall b a. (b -> a -> b) -> b -> t a -> b)
-> (forall a. (a -> a -> a) -> t a -> a)
-> (forall a. (a -> a -> a) -> t a -> a)
-> (forall a. t a -> [a])
-> (forall a. t a -> Bool)
-> (forall a. t a -> TypeIndex)
-> (forall a. Eq a => a -> t a -> Bool)
-> (forall a. Ord a => t a -> a)
-> (forall a. Ord a => t a -> a)
-> (forall a. Num a => t a -> a)
-> (forall a. Num a => t a -> a)
-> Foldable t
product :: HieArgs a -> a
$cproduct :: forall a. Num a => HieArgs a -> a
sum :: HieArgs a -> a
$csum :: forall a. Num a => HieArgs a -> a
minimum :: HieArgs a -> a
$cminimum :: forall a. Ord a => HieArgs a -> a
maximum :: HieArgs a -> a
$cmaximum :: forall a. Ord a => HieArgs a -> a
elem :: a -> HieArgs a -> Bool
$celem :: forall a. Eq a => a -> HieArgs a -> Bool
length :: HieArgs a -> TypeIndex
$clength :: forall a. HieArgs a -> TypeIndex
null :: HieArgs a -> Bool
$cnull :: forall a. HieArgs a -> Bool
toList :: HieArgs a -> [a]
$ctoList :: forall a. HieArgs a -> [a]
foldl1 :: (a -> a -> a) -> HieArgs a -> a
$cfoldl1 :: forall a. (a -> a -> a) -> HieArgs a -> a
foldr1 :: (a -> a -> a) -> HieArgs a -> a
$cfoldr1 :: forall a. (a -> a -> a) -> HieArgs a -> a
foldl' :: (b -> a -> b) -> b -> HieArgs a -> b
$cfoldl' :: forall b a. (b -> a -> b) -> b -> HieArgs a -> b
foldl :: (b -> a -> b) -> b -> HieArgs a -> b
$cfoldl :: forall b a. (b -> a -> b) -> b -> HieArgs a -> b
foldr' :: (a -> b -> b) -> b -> HieArgs a -> b
$cfoldr' :: forall a b. (a -> b -> b) -> b -> HieArgs a -> b
foldr :: (a -> b -> b) -> b -> HieArgs a -> b
$cfoldr :: forall a b. (a -> b -> b) -> b -> HieArgs a -> b
foldMap' :: (a -> m) -> HieArgs a -> m
$cfoldMap' :: forall m a. Monoid m => (a -> m) -> HieArgs a -> m
foldMap :: (a -> m) -> HieArgs a -> m
$cfoldMap :: forall m a. Monoid m => (a -> m) -> HieArgs a -> m
fold :: HieArgs m -> m
$cfold :: forall m. Monoid m => HieArgs m -> m
External instance of the constraint type Foldable []
Evidence bound by a type signature of the constraint type Monoid m
Foldable, Functor HieArgs
Foldable HieArgs
Functor HieArgs
-> Foldable HieArgs
-> (forall (f :: * -> *) a b.
Applicative f =>
(a -> f b) -> HieArgs a -> f (HieArgs b))
-> (forall (f :: * -> *) a.
Applicative f =>
HieArgs (f a) -> f (HieArgs a))
-> (forall (m :: * -> *) a b.
Monad m =>
(a -> m b) -> HieArgs a -> m (HieArgs b))
-> (forall (m :: * -> *) a.
Monad m =>
HieArgs (m a) -> m (HieArgs a))
-> Traversable HieArgs
(a -> f b) -> HieArgs a -> f (HieArgs b)
forall (t :: * -> *).
Functor t
-> Foldable t
-> (forall (f :: * -> *) a b.
Applicative f =>
(a -> f b) -> t a -> f (t b))
-> (forall (f :: * -> *) a. Applicative f => t (f a) -> f (t a))
-> (forall (m :: * -> *) a b.
Monad m =>
(a -> m b) -> t a -> m (t b))
-> (forall (m :: * -> *) a. Monad m => t (m a) -> m (t a))
-> Traversable t
forall (m :: * -> *) a. Monad m => HieArgs (m a) -> m (HieArgs a)
forall (f :: * -> *) a.
Applicative f =>
HieArgs (f a) -> f (HieArgs a)
forall (m :: * -> *) a b.
Monad m =>
(a -> m b) -> HieArgs a -> m (HieArgs b)
forall (f :: * -> *) a b.
Applicative f =>
(a -> f b) -> HieArgs a -> f (HieArgs b)
sequence :: HieArgs (m a) -> m (HieArgs a)
$csequence :: forall (m :: * -> *) a. Monad m => HieArgs (m a) -> m (HieArgs a)
mapM :: (a -> m b) -> HieArgs a -> m (HieArgs b)
$cmapM :: forall (m :: * -> *) a b.
Monad m =>
(a -> m b) -> HieArgs a -> m (HieArgs b)
sequenceA :: HieArgs (f a) -> f (HieArgs a)
$csequenceA :: forall (f :: * -> *) a.
Applicative f =>
HieArgs (f a) -> f (HieArgs a)
traverse :: (a -> f b) -> HieArgs a -> f (HieArgs b)
$ctraverse :: forall (f :: * -> *) a b.
Applicative f =>
(a -> f b) -> HieArgs a -> f (HieArgs b)
External instance of the constraint type Traversable []
External instance of the constraint type forall (f :: * -> *). Applicative f => Functor f
Evidence bound by a type signature of the constraint type Applicative f
Evidence bound by a type signature of the constraint type Applicative f
Instance of class: Foldable of the constraint type Foldable HieArgs
Instance of class: Functor of the constraint type Functor HieArgs
External instance of the constraint type forall (f :: * -> *). Applicative f => Functor f
Instance of class: Functor of the constraint type Functor HieArgs
Instance of class: Foldable of the constraint type Foldable HieArgs
Traversable, HieArgs a -> HieArgs a -> Bool
(HieArgs a -> HieArgs a -> Bool)
-> (HieArgs a -> HieArgs a -> Bool) -> Eq (HieArgs a)
forall a. Eq a => HieArgs a -> HieArgs a -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: HieArgs a -> HieArgs a -> Bool
$c/= :: forall a. Eq a => HieArgs a -> HieArgs a -> Bool
== :: HieArgs a -> HieArgs a -> Bool
$c== :: forall a. Eq a => HieArgs a -> HieArgs a -> Bool
External instance of the constraint type Eq Bool
External instance of the constraint type Eq Bool
External instance of the constraint type Eq Bool
External instance of the constraint type forall a b. (Eq a, Eq b) => Eq (a, b)
External instance of the constraint type Eq Bool
Evidence bound by a type signature of the constraint type Eq a
External instance of the constraint type forall a b. (Eq a, Eq b) => Eq (a, b)
External instance of the constraint type Eq Bool
Evidence bound by a type signature of the constraint type Eq a
External instance of the constraint type forall a. Eq a => Eq [a]
Evidence bound by a type signature of the constraint type Eq a
External instance of the constraint type forall a b. (Eq a, Eq b) => Eq (a, b)
Eq)
instance Binary (HieArgs TypeIndex) where
put_ :: BinHandle -> HieArgs TypeIndex -> IO ()
put_ BinHandle
bh (HieArgs [(Bool, TypeIndex)]
xs) = BinHandle -> [(Bool, TypeIndex)] -> IO ()
forall a. Binary a => BinHandle -> a -> IO ()
External instance of the constraint type forall a. Binary a => Binary [a]
External instance of the constraint type forall a b. (Binary a, Binary b) => Binary (a, b)
External instance of the constraint type Binary Bool
External instance of the constraint type Binary TypeIndex
put_ BinHandle
bh [(Bool, TypeIndex)]
xs
get :: BinHandle -> IO (HieArgs TypeIndex)
get BinHandle
bh = [(Bool, TypeIndex)] -> HieArgs TypeIndex
forall a. [(Bool, a)] -> HieArgs a
HieArgs ([(Bool, TypeIndex)] -> HieArgs TypeIndex)
-> IO [(Bool, TypeIndex)] -> IO (HieArgs TypeIndex)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
External instance of the constraint type Functor IO
<$> BinHandle -> IO [(Bool, TypeIndex)]
forall a. Binary a => BinHandle -> IO a
External instance of the constraint type forall a. Binary a => Binary [a]
External instance of the constraint type forall a b. (Binary a, Binary b) => Binary (a, b)
External instance of the constraint type Binary Bool
External instance of the constraint type Binary TypeIndex
get BinHandle
bh
newtype HieASTs a = HieASTs { HieASTs a -> Map FastString (HieAST a)
getAsts :: (M.Map FastString (HieAST a)) }
deriving (a -> HieASTs b -> HieASTs a
(a -> b) -> HieASTs a -> HieASTs b
(forall a b. (a -> b) -> HieASTs a -> HieASTs b)
-> (forall a b. a -> HieASTs b -> HieASTs a) -> Functor HieASTs
forall a b. a -> HieASTs b -> HieASTs a
forall a b. (a -> b) -> HieASTs a -> HieASTs b
forall (f :: * -> *).
(forall a b. (a -> b) -> f a -> f b)
-> (forall a b. a -> f b -> f a) -> Functor f
<$ :: a -> HieASTs b -> HieASTs a
$c<$ :: forall a b. a -> HieASTs b -> HieASTs a
fmap :: (a -> b) -> HieASTs a -> HieASTs b
$cfmap :: forall a b. (a -> b) -> HieASTs a -> HieASTs b
Instance of class: Functor of the constraint type Functor HieAST
External instance of the constraint type forall k. Functor (Map k)
Functor, HieASTs a -> Bool
(a -> m) -> HieASTs a -> m
(a -> b -> b) -> b -> HieASTs a -> b
(forall m. Monoid m => HieASTs m -> m)
-> (forall m a. Monoid m => (a -> m) -> HieASTs a -> m)
-> (forall m a. Monoid m => (a -> m) -> HieASTs a -> m)
-> (forall a b. (a -> b -> b) -> b -> HieASTs a -> b)
-> (forall a b. (a -> b -> b) -> b -> HieASTs a -> b)
-> (forall b a. (b -> a -> b) -> b -> HieASTs a -> b)
-> (forall b a. (b -> a -> b) -> b -> HieASTs a -> b)
-> (forall a. (a -> a -> a) -> HieASTs a -> a)
-> (forall a. (a -> a -> a) -> HieASTs a -> a)
-> (forall a. HieASTs a -> [a])
-> (forall a. HieASTs a -> Bool)
-> (forall a. HieASTs a -> TypeIndex)
-> (forall a. Eq a => a -> HieASTs a -> Bool)
-> (forall a. Ord a => HieASTs a -> a)
-> (forall a. Ord a => HieASTs a -> a)
-> (forall a. Num a => HieASTs a -> a)
-> (forall a. Num a => HieASTs a -> a)
-> Foldable HieASTs
forall a. Eq a => a -> HieASTs a -> Bool
forall a. Num a => HieASTs a -> a
forall a. Ord a => HieASTs a -> a
forall m. Monoid m => HieASTs m -> m
forall a. HieASTs a -> Bool
forall a. HieASTs a -> TypeIndex
forall a. HieASTs a -> [a]
forall a. (a -> a -> a) -> HieASTs a -> a
forall m a. Monoid m => (a -> m) -> HieASTs a -> m
forall b a. (b -> a -> b) -> b -> HieASTs a -> b
forall a b. (a -> b -> b) -> b -> HieASTs a -> b
forall (t :: * -> *).
(forall m. Monoid m => t m -> m)
-> (forall m a. Monoid m => (a -> m) -> t a -> m)
-> (forall m a. Monoid m => (a -> m) -> t a -> m)
-> (forall a b. (a -> b -> b) -> b -> t a -> b)
-> (forall a b. (a -> b -> b) -> b -> t a -> b)
-> (forall b a. (b -> a -> b) -> b -> t a -> b)
-> (forall b a. (b -> a -> b) -> b -> t a -> b)
-> (forall a. (a -> a -> a) -> t a -> a)
-> (forall a. (a -> a -> a) -> t a -> a)
-> (forall a. t a -> [a])
-> (forall a. t a -> Bool)
-> (forall a. t a -> TypeIndex)
-> (forall a. Eq a => a -> t a -> Bool)
-> (forall a. Ord a => t a -> a)
-> (forall a. Ord a => t a -> a)
-> (forall a. Num a => t a -> a)
-> (forall a. Num a => t a -> a)
-> Foldable t
product :: HieASTs a -> a
$cproduct :: forall a. Num a => HieASTs a -> a
sum :: HieASTs a -> a
$csum :: forall a. Num a => HieASTs a -> a
minimum :: HieASTs a -> a
$cminimum :: forall a. Ord a => HieASTs a -> a
maximum :: HieASTs a -> a
$cmaximum :: forall a. Ord a => HieASTs a -> a
elem :: a -> HieASTs a -> Bool
$celem :: forall a. Eq a => a -> HieASTs a -> Bool
length :: HieASTs a -> TypeIndex
$clength :: forall a. HieASTs a -> TypeIndex
null :: HieASTs a -> Bool
$cnull :: forall a. HieASTs a -> Bool
toList :: HieASTs a -> [a]
$ctoList :: forall a. HieASTs a -> [a]
foldl1 :: (a -> a -> a) -> HieASTs a -> a
$cfoldl1 :: forall a. (a -> a -> a) -> HieASTs a -> a
foldr1 :: (a -> a -> a) -> HieASTs a -> a
$cfoldr1 :: forall a. (a -> a -> a) -> HieASTs a -> a
foldl' :: (b -> a -> b) -> b -> HieASTs a -> b
$cfoldl' :: forall b a. (b -> a -> b) -> b -> HieASTs a -> b
foldl :: (b -> a -> b) -> b -> HieASTs a -> b
$cfoldl :: forall b a. (b -> a -> b) -> b -> HieASTs a -> b
foldr' :: (a -> b -> b) -> b -> HieASTs a -> b
$cfoldr' :: forall a b. (a -> b -> b) -> b -> HieASTs a -> b
foldr :: (a -> b -> b) -> b -> HieASTs a -> b
$cfoldr :: forall a b. (a -> b -> b) -> b -> HieASTs a -> b
foldMap' :: (a -> m) -> HieASTs a -> m
$cfoldMap' :: forall m a. Monoid m => (a -> m) -> HieASTs a -> m
foldMap :: (a -> m) -> HieASTs a -> m
$cfoldMap :: forall m a. Monoid m => (a -> m) -> HieASTs a -> m
fold :: HieASTs m -> m
$cfold :: forall m. Monoid m => HieASTs m -> m
External instance of the constraint type forall k. Foldable (Map k)
Evidence bound by a type signature of the constraint type Monoid m
Instance of class: Foldable of the constraint type Foldable HieAST
Foldable, Functor HieASTs
Foldable HieASTs
Functor HieASTs
-> Foldable HieASTs
-> (forall (f :: * -> *) a b.
Applicative f =>
(a -> f b) -> HieASTs a -> f (HieASTs b))
-> (forall (f :: * -> *) a.
Applicative f =>
HieASTs (f a) -> f (HieASTs a))
-> (forall (m :: * -> *) a b.
Monad m =>
(a -> m b) -> HieASTs a -> m (HieASTs b))
-> (forall (m :: * -> *) a.
Monad m =>
HieASTs (m a) -> m (HieASTs a))
-> Traversable HieASTs
(a -> f b) -> HieASTs a -> f (HieASTs b)
forall (t :: * -> *).
Functor t
-> Foldable t
-> (forall (f :: * -> *) a b.
Applicative f =>
(a -> f b) -> t a -> f (t b))
-> (forall (f :: * -> *) a. Applicative f => t (f a) -> f (t a))
-> (forall (m :: * -> *) a b.
Monad m =>
(a -> m b) -> t a -> m (t b))
-> (forall (m :: * -> *) a. Monad m => t (m a) -> m (t a))
-> Traversable t
forall (m :: * -> *) a. Monad m => HieASTs (m a) -> m (HieASTs a)
forall (f :: * -> *) a.
Applicative f =>
HieASTs (f a) -> f (HieASTs a)
forall (m :: * -> *) a b.
Monad m =>
(a -> m b) -> HieASTs a -> m (HieASTs b)
forall (f :: * -> *) a b.
Applicative f =>
(a -> f b) -> HieASTs a -> f (HieASTs b)
sequence :: HieASTs (m a) -> m (HieASTs a)
$csequence :: forall (m :: * -> *) a. Monad m => HieASTs (m a) -> m (HieASTs a)
mapM :: (a -> m b) -> HieASTs a -> m (HieASTs b)
$cmapM :: forall (m :: * -> *) a b.
Monad m =>
(a -> m b) -> HieASTs a -> m (HieASTs b)
sequenceA :: HieASTs (f a) -> f (HieASTs a)
$csequenceA :: forall (f :: * -> *) a.
Applicative f =>
HieASTs (f a) -> f (HieASTs a)
traverse :: (a -> f b) -> HieASTs a -> f (HieASTs b)
$ctraverse :: forall (f :: * -> *) a b.
Applicative f =>
(a -> f b) -> HieASTs a -> f (HieASTs b)
External instance of the constraint type forall k. Traversable (Map k)
External instance of the constraint type forall (f :: * -> *). Applicative f => Functor f
Evidence bound by a type signature of the constraint type Applicative f
Evidence bound by a type signature of the constraint type Applicative f
Instance of class: Foldable of the constraint type Foldable HieASTs
Instance of class: Functor of the constraint type Functor HieASTs
Instance of class: Functor of the constraint type Functor HieASTs
External instance of the constraint type forall (f :: * -> *). Applicative f => Functor f
Instance of class: Traversable of the constraint type Traversable HieAST
Instance of class: Foldable of the constraint type Foldable HieASTs
Traversable)
instance Binary (HieASTs TypeIndex) where
put_ :: BinHandle -> HieASTs TypeIndex -> IO ()
put_ BinHandle
bh HieASTs TypeIndex
asts = BinHandle -> [(FastString, HieAST TypeIndex)] -> IO ()
forall a. Binary a => BinHandle -> a -> IO ()
External instance of the constraint type forall a. Binary a => Binary [a]
External instance of the constraint type forall a b. (Binary a, Binary b) => Binary (a, b)
External instance of the constraint type Binary FastString
Instance of class: Binary of the constraint type Binary (HieAST TypeIndex)
put_ BinHandle
bh ([(FastString, HieAST TypeIndex)] -> IO ())
-> [(FastString, HieAST TypeIndex)] -> IO ()
forall a b. (a -> b) -> a -> b
$ Map FastString (HieAST TypeIndex)
-> [(FastString, HieAST TypeIndex)]
forall k a. Map k a -> [(k, a)]
M.toAscList (Map FastString (HieAST TypeIndex)
-> [(FastString, HieAST TypeIndex)])
-> Map FastString (HieAST TypeIndex)
-> [(FastString, HieAST TypeIndex)]
forall a b. (a -> b) -> a -> b
$ HieASTs TypeIndex -> Map FastString (HieAST TypeIndex)
forall a. HieASTs a -> Map FastString (HieAST a)
getAsts HieASTs TypeIndex
asts
get :: BinHandle -> IO (HieASTs TypeIndex)
get BinHandle
bh = Map FastString (HieAST TypeIndex) -> HieASTs TypeIndex
forall a. Map FastString (HieAST a) -> HieASTs a
HieASTs (Map FastString (HieAST TypeIndex) -> HieASTs TypeIndex)
-> IO (Map FastString (HieAST TypeIndex)) -> IO (HieASTs TypeIndex)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
External instance of the constraint type Functor IO
<$> ([(FastString, HieAST TypeIndex)]
-> Map FastString (HieAST TypeIndex))
-> IO [(FastString, HieAST TypeIndex)]
-> IO (Map FastString (HieAST TypeIndex))
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
External instance of the constraint type Functor IO
fmap [(FastString, HieAST TypeIndex)]
-> Map FastString (HieAST TypeIndex)
forall k a. [(k, a)] -> Map k a
M.fromDistinctAscList (BinHandle -> IO [(FastString, HieAST TypeIndex)]
forall a. Binary a => BinHandle -> IO a
External instance of the constraint type forall a. Binary a => Binary [a]
External instance of the constraint type forall a b. (Binary a, Binary b) => Binary (a, b)
External instance of the constraint type Binary FastString
Instance of class: Binary of the constraint type Binary (HieAST TypeIndex)
get BinHandle
bh)
instance Outputable a => Outputable (HieASTs a) where
ppr :: HieASTs a -> SDoc
ppr (HieASTs Map FastString (HieAST a)
asts) = (FastString -> HieAST a -> SDoc -> SDoc)
-> SDoc -> Map FastString (HieAST a) -> SDoc
forall k a b. (k -> a -> b -> b) -> b -> Map k a -> b
M.foldrWithKey FastString -> HieAST a -> SDoc -> SDoc
forall {a} {a}.
(Outputable a, Outputable a) =>
a -> a -> SDoc -> SDoc
Instance of class: Outputable of the constraint type forall a. Outputable a => Outputable (HieAST a)
Evidence bound by a type signature of the constraint type Outputable a
External instance of the constraint type Outputable FastString
go SDoc
"" Map FastString (HieAST a)
asts
where
go :: a -> a -> SDoc -> SDoc
go a
k a
a SDoc
rest = [SDoc] -> SDoc
vcat ([SDoc] -> SDoc) -> [SDoc] -> SDoc
forall a b. (a -> b) -> a -> b
$
[ SDoc
"File: " SDoc -> SDoc -> SDoc
O.<> a -> SDoc
forall a. Outputable a => a -> SDoc
Evidence bound by a type signature of the constraint type Outputable a
ppr a
k
, a -> SDoc
forall a. Outputable a => a -> SDoc
Evidence bound by a type signature of the constraint type Outputable a
ppr a
a
, SDoc
rest
]
data HieAST a =
Node
{ HieAST a -> SourcedNodeInfo a
sourcedNodeInfo :: SourcedNodeInfo a
, HieAST a -> Span
nodeSpan :: Span
, HieAST a -> [HieAST a]
nodeChildren :: [HieAST a]
} deriving (a -> HieAST b -> HieAST a
(a -> b) -> HieAST a -> HieAST b
(forall a b. (a -> b) -> HieAST a -> HieAST b)
-> (forall a b. a -> HieAST b -> HieAST a) -> Functor HieAST
forall a b. a -> HieAST b -> HieAST a
forall a b. (a -> b) -> HieAST a -> HieAST b
forall (f :: * -> *).
(forall a b. (a -> b) -> f a -> f b)
-> (forall a b. a -> f b -> f a) -> Functor f
<$ :: a -> HieAST b -> HieAST a
$c<$ :: forall a b. a -> HieAST b -> HieAST a
fmap :: (a -> b) -> HieAST a -> HieAST b
$cfmap :: forall a b. (a -> b) -> HieAST a -> HieAST b
Instance of class: Functor of the constraint type Functor SourcedNodeInfo
Instance of class: Functor of the constraint type Functor HieAST
External instance of the constraint type Functor []
Functor, HieAST a -> Bool
(a -> m) -> HieAST a -> m
(a -> b -> b) -> b -> HieAST a -> b
(forall m. Monoid m => HieAST m -> m)
-> (forall m a. Monoid m => (a -> m) -> HieAST a -> m)
-> (forall m a. Monoid m => (a -> m) -> HieAST a -> m)
-> (forall a b. (a -> b -> b) -> b -> HieAST a -> b)
-> (forall a b. (a -> b -> b) -> b -> HieAST a -> b)
-> (forall b a. (b -> a -> b) -> b -> HieAST a -> b)
-> (forall b a. (b -> a -> b) -> b -> HieAST a -> b)
-> (forall a. (a -> a -> a) -> HieAST a -> a)
-> (forall a. (a -> a -> a) -> HieAST a -> a)
-> (forall a. HieAST a -> [a])
-> (forall a. HieAST a -> Bool)
-> (forall a. HieAST a -> TypeIndex)
-> (forall a. Eq a => a -> HieAST a -> Bool)
-> (forall a. Ord a => HieAST a -> a)
-> (forall a. Ord a => HieAST a -> a)
-> (forall a. Num a => HieAST a -> a)
-> (forall a. Num a => HieAST a -> a)
-> Foldable HieAST
forall a. Eq a => a -> HieAST a -> Bool
forall a. Num a => HieAST a -> a
forall a. Ord a => HieAST a -> a
forall m. Monoid m => HieAST m -> m
forall a. HieAST a -> Bool
forall a. HieAST a -> TypeIndex
forall a. HieAST a -> [a]
forall a. (a -> a -> a) -> HieAST a -> a
forall m a. Monoid m => (a -> m) -> HieAST a -> m
forall b a. (b -> a -> b) -> b -> HieAST a -> b
forall a b. (a -> b -> b) -> b -> HieAST a -> b
forall (t :: * -> *).
(forall m. Monoid m => t m -> m)
-> (forall m a. Monoid m => (a -> m) -> t a -> m)
-> (forall m a. Monoid m => (a -> m) -> t a -> m)
-> (forall a b. (a -> b -> b) -> b -> t a -> b)
-> (forall a b. (a -> b -> b) -> b -> t a -> b)
-> (forall b a. (b -> a -> b) -> b -> t a -> b)
-> (forall b a. (b -> a -> b) -> b -> t a -> b)
-> (forall a. (a -> a -> a) -> t a -> a)
-> (forall a. (a -> a -> a) -> t a -> a)
-> (forall a. t a -> [a])
-> (forall a. t a -> Bool)
-> (forall a. t a -> TypeIndex)
-> (forall a. Eq a => a -> t a -> Bool)
-> (forall a. Ord a => t a -> a)
-> (forall a. Ord a => t a -> a)
-> (forall a. Num a => t a -> a)
-> (forall a. Num a => t a -> a)
-> Foldable t
product :: HieAST a -> a
$cproduct :: forall a. Num a => HieAST a -> a
sum :: HieAST a -> a
$csum :: forall a. Num a => HieAST a -> a
minimum :: HieAST a -> a
$cminimum :: forall a. Ord a => HieAST a -> a
maximum :: HieAST a -> a
$cmaximum :: forall a. Ord a => HieAST a -> a
elem :: a -> HieAST a -> Bool
$celem :: forall a. Eq a => a -> HieAST a -> Bool
length :: HieAST a -> TypeIndex
$clength :: forall a. HieAST a -> TypeIndex
null :: HieAST a -> Bool
$cnull :: forall a. HieAST a -> Bool
toList :: HieAST a -> [a]
$ctoList :: forall a. HieAST a -> [a]
foldl1 :: (a -> a -> a) -> HieAST a -> a
$cfoldl1 :: forall a. (a -> a -> a) -> HieAST a -> a
foldr1 :: (a -> a -> a) -> HieAST a -> a
$cfoldr1 :: forall a. (a -> a -> a) -> HieAST a -> a
foldl' :: (b -> a -> b) -> b -> HieAST a -> b
$cfoldl' :: forall b a. (b -> a -> b) -> b -> HieAST a -> b
foldl :: (b -> a -> b) -> b -> HieAST a -> b
$cfoldl :: forall b a. (b -> a -> b) -> b -> HieAST a -> b
foldr' :: (a -> b -> b) -> b -> HieAST a -> b
$cfoldr' :: forall a b. (a -> b -> b) -> b -> HieAST a -> b
foldr :: (a -> b -> b) -> b -> HieAST a -> b
$cfoldr :: forall a b. (a -> b -> b) -> b -> HieAST a -> b
foldMap' :: (a -> m) -> HieAST a -> m
$cfoldMap' :: forall m a. Monoid m => (a -> m) -> HieAST a -> m
foldMap :: (a -> m) -> HieAST a -> m
$cfoldMap :: forall m a. Monoid m => (a -> m) -> HieAST a -> m
fold :: HieAST m -> m
$cfold :: forall m. Monoid m => HieAST m -> m
Evidence bound by a type signature of the constraint type Monoid m
External instance of the constraint type Foldable []
Instance of class: Foldable of the constraint type Foldable SourcedNodeInfo
Instance of class: Foldable of the constraint type Foldable HieAST
Foldable, Functor HieAST
Foldable HieAST
Functor HieAST
-> Foldable HieAST
-> (forall (f :: * -> *) a b.
Applicative f =>
(a -> f b) -> HieAST a -> f (HieAST b))
-> (forall (f :: * -> *) a.
Applicative f =>
HieAST (f a) -> f (HieAST a))
-> (forall (m :: * -> *) a b.
Monad m =>
(a -> m b) -> HieAST a -> m (HieAST b))
-> (forall (m :: * -> *) a.
Monad m =>
HieAST (m a) -> m (HieAST a))
-> Traversable HieAST
(a -> f b) -> HieAST a -> f (HieAST b)
forall (t :: * -> *).
Functor t
-> Foldable t
-> (forall (f :: * -> *) a b.
Applicative f =>
(a -> f b) -> t a -> f (t b))
-> (forall (f :: * -> *) a. Applicative f => t (f a) -> f (t a))
-> (forall (m :: * -> *) a b.
Monad m =>
(a -> m b) -> t a -> m (t b))
-> (forall (m :: * -> *) a. Monad m => t (m a) -> m (t a))
-> Traversable t
forall (m :: * -> *) a. Monad m => HieAST (m a) -> m (HieAST a)
forall (f :: * -> *) a.
Applicative f =>
HieAST (f a) -> f (HieAST a)
forall (m :: * -> *) a b.
Monad m =>
(a -> m b) -> HieAST a -> m (HieAST b)
forall (f :: * -> *) a b.
Applicative f =>
(a -> f b) -> HieAST a -> f (HieAST b)
sequence :: HieAST (m a) -> m (HieAST a)
$csequence :: forall (m :: * -> *) a. Monad m => HieAST (m a) -> m (HieAST a)
mapM :: (a -> m b) -> HieAST a -> m (HieAST b)
$cmapM :: forall (m :: * -> *) a b.
Monad m =>
(a -> m b) -> HieAST a -> m (HieAST b)
sequenceA :: HieAST (f a) -> f (HieAST a)
$csequenceA :: forall (f :: * -> *) a.
Applicative f =>
HieAST (f a) -> f (HieAST a)
traverse :: (a -> f b) -> HieAST a -> f (HieAST b)
$ctraverse :: forall (f :: * -> *) a b.
Applicative f =>
(a -> f b) -> HieAST a -> f (HieAST b)
Evidence bound by a type signature of the constraint type Applicative f
Instance of class: Foldable of the constraint type Foldable HieAST
Instance of class: Functor of the constraint type Functor HieAST
Instance of class: Functor of the constraint type Functor HieAST
External instance of the constraint type Traversable []
Instance of class: Traversable of the constraint type Traversable SourcedNodeInfo
Instance of class: Traversable of the constraint type Traversable HieAST
Instance of class: Foldable of the constraint type Foldable HieAST
Traversable)
instance Binary (HieAST TypeIndex) where
put_ :: BinHandle -> HieAST TypeIndex -> IO ()
put_ BinHandle
bh HieAST TypeIndex
ast = do
BinHandle -> SourcedNodeInfo TypeIndex -> IO ()
forall a. Binary a => BinHandle -> a -> IO ()
Instance of class: Binary of the constraint type Binary (SourcedNodeInfo TypeIndex)
put_ BinHandle
bh (SourcedNodeInfo TypeIndex -> IO ())
-> SourcedNodeInfo TypeIndex -> IO ()
forall a b. (a -> b) -> a -> b
$ HieAST TypeIndex -> SourcedNodeInfo TypeIndex
forall a. HieAST a -> SourcedNodeInfo a
sourcedNodeInfo HieAST TypeIndex
ast
BinHandle -> Span -> IO ()
forall a. Binary a => BinHandle -> a -> IO ()
External instance of the constraint type Binary Span
put_ BinHandle
bh (Span -> IO ()) -> Span -> IO ()
forall a b. (a -> b) -> a -> b
$ HieAST TypeIndex -> Span
forall a. HieAST a -> Span
nodeSpan HieAST TypeIndex
ast
BinHandle -> [HieAST TypeIndex] -> IO ()
forall a. Binary a => BinHandle -> a -> IO ()
External instance of the constraint type forall a. Binary a => Binary [a]
Instance of class: Binary of the constraint type Binary (HieAST TypeIndex)
put_ BinHandle
bh ([HieAST TypeIndex] -> IO ()) -> [HieAST TypeIndex] -> IO ()
forall a b. (a -> b) -> a -> b
$ HieAST TypeIndex -> [HieAST TypeIndex]
forall a. HieAST a -> [HieAST a]
nodeChildren HieAST TypeIndex
ast
get :: BinHandle -> IO (HieAST TypeIndex)
get BinHandle
bh = SourcedNodeInfo TypeIndex
-> Span -> [HieAST TypeIndex] -> HieAST TypeIndex
forall a. SourcedNodeInfo a -> Span -> [HieAST a] -> HieAST a
Node
(SourcedNodeInfo TypeIndex
-> Span -> [HieAST TypeIndex] -> HieAST TypeIndex)
-> IO (SourcedNodeInfo TypeIndex)
-> IO (Span -> [HieAST TypeIndex] -> HieAST TypeIndex)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
External instance of the constraint type Functor IO
<$> BinHandle -> IO (SourcedNodeInfo TypeIndex)
forall a. Binary a => BinHandle -> IO a
Instance of class: Binary of the constraint type Binary (SourcedNodeInfo TypeIndex)
get BinHandle
bh
IO (Span -> [HieAST TypeIndex] -> HieAST TypeIndex)
-> IO Span -> IO ([HieAST TypeIndex] -> HieAST TypeIndex)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
External instance of the constraint type Applicative IO
<*> BinHandle -> IO Span
forall a. Binary a => BinHandle -> IO a
External instance of the constraint type Binary Span
get BinHandle
bh
IO ([HieAST TypeIndex] -> HieAST TypeIndex)
-> IO [HieAST TypeIndex] -> IO (HieAST TypeIndex)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
External instance of the constraint type Applicative IO
<*> BinHandle -> IO [HieAST TypeIndex]
forall a. Binary a => BinHandle -> IO a
External instance of the constraint type forall a. Binary a => Binary [a]
Instance of class: Binary of the constraint type Binary (HieAST TypeIndex)
get BinHandle
bh
instance Outputable a => Outputable (HieAST a) where
ppr :: HieAST a -> SDoc
ppr (Node SourcedNodeInfo a
ni Span
sp [HieAST a]
ch) = SDoc -> TypeIndex -> SDoc -> SDoc
hang SDoc
header TypeIndex
2 SDoc
rest
where
header :: SDoc
header = String -> SDoc
text String
"Node@" SDoc -> SDoc -> SDoc
O.<> Span -> SDoc
forall a. Outputable a => a -> SDoc
External instance of the constraint type Outputable Span
ppr Span
sp SDoc -> SDoc -> SDoc
O.<> SDoc
":" SDoc -> SDoc -> SDoc
<+> SourcedNodeInfo a -> SDoc
forall a. Outputable a => a -> SDoc
Instance of class: Outputable of the constraint type forall a. Outputable a => Outputable (SourcedNodeInfo a)
Evidence bound by a type signature of the constraint type Outputable a
ppr SourcedNodeInfo a
ni
rest :: SDoc
rest = [SDoc] -> SDoc
vcat ((HieAST a -> SDoc) -> [HieAST a] -> [SDoc]
forall a b. (a -> b) -> [a] -> [b]
map HieAST a -> SDoc
forall a. Outputable a => a -> SDoc
Instance of class: Outputable of the constraint type forall a. Outputable a => Outputable (HieAST a)
Evidence bound by a type signature of the constraint type Outputable a
ppr [HieAST a]
ch)
newtype SourcedNodeInfo a = SourcedNodeInfo { SourcedNodeInfo a -> Map NodeOrigin (NodeInfo a)
getSourcedNodeInfo :: (M.Map NodeOrigin (NodeInfo a)) }
deriving (a -> SourcedNodeInfo b -> SourcedNodeInfo a
(a -> b) -> SourcedNodeInfo a -> SourcedNodeInfo b
(forall a b. (a -> b) -> SourcedNodeInfo a -> SourcedNodeInfo b)
-> (forall a b. a -> SourcedNodeInfo b -> SourcedNodeInfo a)
-> Functor SourcedNodeInfo
forall a b. a -> SourcedNodeInfo b -> SourcedNodeInfo a
forall a b. (a -> b) -> SourcedNodeInfo a -> SourcedNodeInfo b
forall (f :: * -> *).
(forall a b. (a -> b) -> f a -> f b)
-> (forall a b. a -> f b -> f a) -> Functor f
<$ :: a -> SourcedNodeInfo b -> SourcedNodeInfo a
$c<$ :: forall a b. a -> SourcedNodeInfo b -> SourcedNodeInfo a
fmap :: (a -> b) -> SourcedNodeInfo a -> SourcedNodeInfo b
$cfmap :: forall a b. (a -> b) -> SourcedNodeInfo a -> SourcedNodeInfo b
Instance of class: Functor of the constraint type Functor NodeInfo
External instance of the constraint type forall k. Functor (Map k)
Functor, SourcedNodeInfo a -> Bool
(a -> m) -> SourcedNodeInfo a -> m
(a -> b -> b) -> b -> SourcedNodeInfo a -> b
(forall m. Monoid m => SourcedNodeInfo m -> m)
-> (forall m a. Monoid m => (a -> m) -> SourcedNodeInfo a -> m)
-> (forall m a. Monoid m => (a -> m) -> SourcedNodeInfo a -> m)
-> (forall a b. (a -> b -> b) -> b -> SourcedNodeInfo a -> b)
-> (forall a b. (a -> b -> b) -> b -> SourcedNodeInfo a -> b)
-> (forall b a. (b -> a -> b) -> b -> SourcedNodeInfo a -> b)
-> (forall b a. (b -> a -> b) -> b -> SourcedNodeInfo a -> b)
-> (forall a. (a -> a -> a) -> SourcedNodeInfo a -> a)
-> (forall a. (a -> a -> a) -> SourcedNodeInfo a -> a)
-> (forall a. SourcedNodeInfo a -> [a])
-> (forall a. SourcedNodeInfo a -> Bool)
-> (forall a. SourcedNodeInfo a -> TypeIndex)
-> (forall a. Eq a => a -> SourcedNodeInfo a -> Bool)
-> (forall a. Ord a => SourcedNodeInfo a -> a)
-> (forall a. Ord a => SourcedNodeInfo a -> a)
-> (forall a. Num a => SourcedNodeInfo a -> a)
-> (forall a. Num a => SourcedNodeInfo a -> a)
-> Foldable SourcedNodeInfo
forall a. Eq a => a -> SourcedNodeInfo a -> Bool
forall a. Num a => SourcedNodeInfo a -> a
forall a. Ord a => SourcedNodeInfo a -> a
forall m. Monoid m => SourcedNodeInfo m -> m
forall a. SourcedNodeInfo a -> Bool
forall a. SourcedNodeInfo a -> TypeIndex
forall a. SourcedNodeInfo a -> [a]
forall a. (a -> a -> a) -> SourcedNodeInfo a -> a
forall m a. Monoid m => (a -> m) -> SourcedNodeInfo a -> m
forall b a. (b -> a -> b) -> b -> SourcedNodeInfo a -> b
forall a b. (a -> b -> b) -> b -> SourcedNodeInfo a -> b
forall (t :: * -> *).
(forall m. Monoid m => t m -> m)
-> (forall m a. Monoid m => (a -> m) -> t a -> m)
-> (forall m a. Monoid m => (a -> m) -> t a -> m)
-> (forall a b. (a -> b -> b) -> b -> t a -> b)
-> (forall a b. (a -> b -> b) -> b -> t a -> b)
-> (forall b a. (b -> a -> b) -> b -> t a -> b)
-> (forall b a. (b -> a -> b) -> b -> t a -> b)
-> (forall a. (a -> a -> a) -> t a -> a)
-> (forall a. (a -> a -> a) -> t a -> a)
-> (forall a. t a -> [a])
-> (forall a. t a -> Bool)
-> (forall a. t a -> TypeIndex)
-> (forall a. Eq a => a -> t a -> Bool)
-> (forall a. Ord a => t a -> a)
-> (forall a. Ord a => t a -> a)
-> (forall a. Num a => t a -> a)
-> (forall a. Num a => t a -> a)
-> Foldable t
product :: SourcedNodeInfo a -> a
$cproduct :: forall a. Num a => SourcedNodeInfo a -> a
sum :: SourcedNodeInfo a -> a
$csum :: forall a. Num a => SourcedNodeInfo a -> a
minimum :: SourcedNodeInfo a -> a
$cminimum :: forall a. Ord a => SourcedNodeInfo a -> a
maximum :: SourcedNodeInfo a -> a
$cmaximum :: forall a. Ord a => SourcedNodeInfo a -> a
elem :: a -> SourcedNodeInfo a -> Bool
$celem :: forall a. Eq a => a -> SourcedNodeInfo a -> Bool
length :: SourcedNodeInfo a -> TypeIndex
$clength :: forall a. SourcedNodeInfo a -> TypeIndex
null :: SourcedNodeInfo a -> Bool
$cnull :: forall a. SourcedNodeInfo a -> Bool
toList :: SourcedNodeInfo a -> [a]
$ctoList :: forall a. SourcedNodeInfo a -> [a]
foldl1 :: (a -> a -> a) -> SourcedNodeInfo a -> a
$cfoldl1 :: forall a. (a -> a -> a) -> SourcedNodeInfo a -> a
foldr1 :: (a -> a -> a) -> SourcedNodeInfo a -> a
$cfoldr1 :: forall a. (a -> a -> a) -> SourcedNodeInfo a -> a
foldl' :: (b -> a -> b) -> b -> SourcedNodeInfo a -> b
$cfoldl' :: forall b a. (b -> a -> b) -> b -> SourcedNodeInfo a -> b
foldl :: (b -> a -> b) -> b -> SourcedNodeInfo a -> b
$cfoldl :: forall b a. (b -> a -> b) -> b -> SourcedNodeInfo a -> b
foldr' :: (a -> b -> b) -> b -> SourcedNodeInfo a -> b
$cfoldr' :: forall a b. (a -> b -> b) -> b -> SourcedNodeInfo a -> b
foldr :: (a -> b -> b) -> b -> SourcedNodeInfo a -> b
$cfoldr :: forall a b. (a -> b -> b) -> b -> SourcedNodeInfo a -> b
foldMap' :: (a -> m) -> SourcedNodeInfo a -> m
$cfoldMap' :: forall m a. Monoid m => (a -> m) -> SourcedNodeInfo a -> m
foldMap :: (a -> m) -> SourcedNodeInfo a -> m
$cfoldMap :: forall m a. Monoid m => (a -> m) -> SourcedNodeInfo a -> m
fold :: SourcedNodeInfo m -> m
$cfold :: forall m. Monoid m => SourcedNodeInfo m -> m
Evidence bound by a type signature of the constraint type Monoid m
External instance of the constraint type forall k. Foldable (Map k)
Instance of class: Foldable of the constraint type Foldable NodeInfo
Foldable, Functor SourcedNodeInfo
Foldable SourcedNodeInfo
Functor SourcedNodeInfo
-> Foldable SourcedNodeInfo
-> (forall (f :: * -> *) a b.
Applicative f =>
(a -> f b) -> SourcedNodeInfo a -> f (SourcedNodeInfo b))
-> (forall (f :: * -> *) a.
Applicative f =>
SourcedNodeInfo (f a) -> f (SourcedNodeInfo a))
-> (forall (m :: * -> *) a b.
Monad m =>
(a -> m b) -> SourcedNodeInfo a -> m (SourcedNodeInfo b))
-> (forall (m :: * -> *) a.
Monad m =>
SourcedNodeInfo (m a) -> m (SourcedNodeInfo a))
-> Traversable SourcedNodeInfo
(a -> f b) -> SourcedNodeInfo a -> f (SourcedNodeInfo b)
forall (t :: * -> *).
Functor t
-> Foldable t
-> (forall (f :: * -> *) a b.
Applicative f =>
(a -> f b) -> t a -> f (t b))
-> (forall (f :: * -> *) a. Applicative f => t (f a) -> f (t a))
-> (forall (m :: * -> *) a b.
Monad m =>
(a -> m b) -> t a -> m (t b))
-> (forall (m :: * -> *) a. Monad m => t (m a) -> m (t a))
-> Traversable t
forall (m :: * -> *) a.
Monad m =>
SourcedNodeInfo (m a) -> m (SourcedNodeInfo a)
forall (f :: * -> *) a.
Applicative f =>
SourcedNodeInfo (f a) -> f (SourcedNodeInfo a)
forall (m :: * -> *) a b.
Monad m =>
(a -> m b) -> SourcedNodeInfo a -> m (SourcedNodeInfo b)
forall (f :: * -> *) a b.
Applicative f =>
(a -> f b) -> SourcedNodeInfo a -> f (SourcedNodeInfo b)
sequence :: SourcedNodeInfo (m a) -> m (SourcedNodeInfo a)
$csequence :: forall (m :: * -> *) a.
Monad m =>
SourcedNodeInfo (m a) -> m (SourcedNodeInfo a)
mapM :: (a -> m b) -> SourcedNodeInfo a -> m (SourcedNodeInfo b)
$cmapM :: forall (m :: * -> *) a b.
Monad m =>
(a -> m b) -> SourcedNodeInfo a -> m (SourcedNodeInfo b)
sequenceA :: SourcedNodeInfo (f a) -> f (SourcedNodeInfo a)
$csequenceA :: forall (f :: * -> *) a.
Applicative f =>
SourcedNodeInfo (f a) -> f (SourcedNodeInfo a)
traverse :: (a -> f b) -> SourcedNodeInfo a -> f (SourcedNodeInfo b)
$ctraverse :: forall (f :: * -> *) a b.
Applicative f =>
(a -> f b) -> SourcedNodeInfo a -> f (SourcedNodeInfo b)
External instance of the constraint type forall (f :: * -> *). Applicative f => Functor f
Evidence bound by a type signature of the constraint type Applicative f
Evidence bound by a type signature of the constraint type Applicative f
Instance of class: Foldable of the constraint type Foldable SourcedNodeInfo
Instance of class: Functor of the constraint type Functor SourcedNodeInfo
Instance of class: Functor of the constraint type Functor SourcedNodeInfo
External instance of the constraint type forall k. Traversable (Map k)
External instance of the constraint type forall (f :: * -> *). Applicative f => Functor f
Instance of class: Traversable of the constraint type Traversable NodeInfo
Instance of class: Foldable of the constraint type Foldable SourcedNodeInfo
Traversable)
instance Binary (SourcedNodeInfo TypeIndex) where
put_ :: BinHandle -> SourcedNodeInfo TypeIndex -> IO ()
put_ BinHandle
bh SourcedNodeInfo TypeIndex
asts = BinHandle -> [(NodeOrigin, NodeInfo TypeIndex)] -> IO ()
forall a. Binary a => BinHandle -> a -> IO ()
External instance of the constraint type forall a. Binary a => Binary [a]
External instance of the constraint type forall a b. (Binary a, Binary b) => Binary (a, b)
Instance of class: Binary of the constraint type Binary NodeOrigin
Instance of class: Binary of the constraint type Binary (NodeInfo TypeIndex)
put_ BinHandle
bh ([(NodeOrigin, NodeInfo TypeIndex)] -> IO ())
-> [(NodeOrigin, NodeInfo TypeIndex)] -> IO ()
forall a b. (a -> b) -> a -> b
$ Map NodeOrigin (NodeInfo TypeIndex)
-> [(NodeOrigin, NodeInfo TypeIndex)]
forall k a. Map k a -> [(k, a)]
M.toAscList (Map NodeOrigin (NodeInfo TypeIndex)
-> [(NodeOrigin, NodeInfo TypeIndex)])
-> Map NodeOrigin (NodeInfo TypeIndex)
-> [(NodeOrigin, NodeInfo TypeIndex)]
forall a b. (a -> b) -> a -> b
$ SourcedNodeInfo TypeIndex -> Map NodeOrigin (NodeInfo TypeIndex)
forall a. SourcedNodeInfo a -> Map NodeOrigin (NodeInfo a)
getSourcedNodeInfo SourcedNodeInfo TypeIndex
asts
get :: BinHandle -> IO (SourcedNodeInfo TypeIndex)
get BinHandle
bh = Map NodeOrigin (NodeInfo TypeIndex) -> SourcedNodeInfo TypeIndex
forall a. Map NodeOrigin (NodeInfo a) -> SourcedNodeInfo a
SourcedNodeInfo (Map NodeOrigin (NodeInfo TypeIndex) -> SourcedNodeInfo TypeIndex)
-> IO (Map NodeOrigin (NodeInfo TypeIndex))
-> IO (SourcedNodeInfo TypeIndex)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
External instance of the constraint type Functor IO
<$> ([(NodeOrigin, NodeInfo TypeIndex)]
-> Map NodeOrigin (NodeInfo TypeIndex))
-> IO [(NodeOrigin, NodeInfo TypeIndex)]
-> IO (Map NodeOrigin (NodeInfo TypeIndex))
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
External instance of the constraint type Functor IO
fmap [(NodeOrigin, NodeInfo TypeIndex)]
-> Map NodeOrigin (NodeInfo TypeIndex)
forall k a. [(k, a)] -> Map k a
M.fromDistinctAscList (BinHandle -> IO [(NodeOrigin, NodeInfo TypeIndex)]
forall a. Binary a => BinHandle -> IO a
External instance of the constraint type forall a. Binary a => Binary [a]
External instance of the constraint type forall a b. (Binary a, Binary b) => Binary (a, b)
Instance of class: Binary of the constraint type Binary NodeOrigin
Instance of class: Binary of the constraint type Binary (NodeInfo TypeIndex)
get BinHandle
bh)
instance Outputable a => Outputable (SourcedNodeInfo a) where
ppr :: SourcedNodeInfo a -> SDoc
ppr (SourcedNodeInfo Map NodeOrigin (NodeInfo a)
asts) = (NodeOrigin -> NodeInfo a -> SDoc -> SDoc)
-> SDoc -> Map NodeOrigin (NodeInfo a) -> SDoc
forall k a b. (k -> a -> b -> b) -> b -> Map k a -> b
M.foldrWithKey NodeOrigin -> NodeInfo a -> SDoc -> SDoc
forall {a} {a}.
(Outputable a, Outputable a) =>
a -> a -> SDoc -> SDoc
Instance of class: Outputable of the constraint type forall a. Outputable a => Outputable (NodeInfo a)
Evidence bound by a type signature of the constraint type Outputable a
Instance of class: Outputable of the constraint type Outputable NodeOrigin
go SDoc
"" Map NodeOrigin (NodeInfo a)
asts
where
go :: a -> a -> SDoc -> SDoc
go a
k a
a SDoc
rest = [SDoc] -> SDoc
vcat ([SDoc] -> SDoc) -> [SDoc] -> SDoc
forall a b. (a -> b) -> a -> b
$
[ SDoc
"Source: " SDoc -> SDoc -> SDoc
O.<> a -> SDoc
forall a. Outputable a => a -> SDoc
Evidence bound by a type signature of the constraint type Outputable a
ppr a
k
, a -> SDoc
forall a. Outputable a => a -> SDoc
Evidence bound by a type signature of the constraint type Outputable a
ppr a
a
, SDoc
rest
]
data NodeOrigin
= SourceInfo
| GeneratedInfo
deriving (NodeOrigin -> NodeOrigin -> Bool
(NodeOrigin -> NodeOrigin -> Bool)
-> (NodeOrigin -> NodeOrigin -> Bool) -> Eq NodeOrigin
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: NodeOrigin -> NodeOrigin -> Bool
$c/= :: NodeOrigin -> NodeOrigin -> Bool
== :: NodeOrigin -> NodeOrigin -> Bool
$c== :: NodeOrigin -> NodeOrigin -> Bool
Eq, TypeIndex -> NodeOrigin
NodeOrigin -> TypeIndex
NodeOrigin -> [NodeOrigin]
NodeOrigin -> NodeOrigin
NodeOrigin -> NodeOrigin -> [NodeOrigin]
NodeOrigin -> NodeOrigin -> NodeOrigin -> [NodeOrigin]
(NodeOrigin -> NodeOrigin)
-> (NodeOrigin -> NodeOrigin)
-> (TypeIndex -> NodeOrigin)
-> (NodeOrigin -> TypeIndex)
-> (NodeOrigin -> [NodeOrigin])
-> (NodeOrigin -> NodeOrigin -> [NodeOrigin])
-> (NodeOrigin -> NodeOrigin -> [NodeOrigin])
-> (NodeOrigin -> NodeOrigin -> NodeOrigin -> [NodeOrigin])
-> Enum NodeOrigin
forall a.
(a -> a)
-> (a -> a)
-> (TypeIndex -> a)
-> (a -> TypeIndex)
-> (a -> [a])
-> (a -> a -> [a])
-> (a -> a -> [a])
-> (a -> a -> a -> [a])
-> Enum a
enumFromThenTo :: NodeOrigin -> NodeOrigin -> NodeOrigin -> [NodeOrigin]
$cenumFromThenTo :: NodeOrigin -> NodeOrigin -> NodeOrigin -> [NodeOrigin]
enumFromTo :: NodeOrigin -> NodeOrigin -> [NodeOrigin]
$cenumFromTo :: NodeOrigin -> NodeOrigin -> [NodeOrigin]
enumFromThen :: NodeOrigin -> NodeOrigin -> [NodeOrigin]
$cenumFromThen :: NodeOrigin -> NodeOrigin -> [NodeOrigin]
enumFrom :: NodeOrigin -> [NodeOrigin]
$cenumFrom :: NodeOrigin -> [NodeOrigin]
fromEnum :: NodeOrigin -> TypeIndex
$cfromEnum :: NodeOrigin -> TypeIndex
toEnum :: TypeIndex -> NodeOrigin
$ctoEnum :: TypeIndex -> NodeOrigin
pred :: NodeOrigin -> NodeOrigin
$cpred :: NodeOrigin -> NodeOrigin
succ :: NodeOrigin -> NodeOrigin
$csucc :: NodeOrigin -> NodeOrigin
External instance of the constraint type Enum TypeIndex
External instance of the constraint type Show TypeIndex
External instance of the constraint type Show TypeIndex
External instance of the constraint type forall a. (a ~ Char) => IsString [a]
External instance of the constraint type forall a. (a ~ Char) => IsString [a]
External instance of the constraint type Ord TypeIndex
External instance of the constraint type Ord TypeIndex
External instance of the constraint type Num TypeIndex
External instance of the constraint type Eq TypeIndex
Enum, Eq NodeOrigin
Eq NodeOrigin
-> (NodeOrigin -> NodeOrigin -> Ordering)
-> (NodeOrigin -> NodeOrigin -> Bool)
-> (NodeOrigin -> NodeOrigin -> Bool)
-> (NodeOrigin -> NodeOrigin -> Bool)
-> (NodeOrigin -> NodeOrigin -> Bool)
-> (NodeOrigin -> NodeOrigin -> NodeOrigin)
-> (NodeOrigin -> NodeOrigin -> NodeOrigin)
-> Ord NodeOrigin
NodeOrigin -> NodeOrigin -> Bool
NodeOrigin -> NodeOrigin -> Ordering
NodeOrigin -> NodeOrigin -> NodeOrigin
forall a.
Eq a
-> (a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
min :: NodeOrigin -> NodeOrigin -> NodeOrigin
$cmin :: NodeOrigin -> NodeOrigin -> NodeOrigin
max :: NodeOrigin -> NodeOrigin -> NodeOrigin
$cmax :: NodeOrigin -> NodeOrigin -> NodeOrigin
>= :: NodeOrigin -> NodeOrigin -> Bool
$c>= :: NodeOrigin -> NodeOrigin -> Bool
> :: NodeOrigin -> NodeOrigin -> Bool
$c> :: NodeOrigin -> NodeOrigin -> Bool
<= :: NodeOrigin -> NodeOrigin -> Bool
$c<= :: NodeOrigin -> NodeOrigin -> Bool
< :: NodeOrigin -> NodeOrigin -> Bool
$c< :: NodeOrigin -> NodeOrigin -> Bool
compare :: NodeOrigin -> NodeOrigin -> Ordering
$ccompare :: NodeOrigin -> NodeOrigin -> Ordering
Instance of class: Eq of the constraint type Eq NodeOrigin
Instance of class: Ord of the constraint type Ord NodeOrigin
Instance of class: Eq of the constraint type Eq NodeOrigin
Ord)
instance Outputable NodeOrigin where
ppr :: NodeOrigin -> SDoc
ppr NodeOrigin
SourceInfo = String -> SDoc
text String
"From source"
ppr NodeOrigin
GeneratedInfo = String -> SDoc
text String
"generated by ghc"
instance Binary NodeOrigin where
put_ :: BinHandle -> NodeOrigin -> IO ()
put_ BinHandle
bh NodeOrigin
b = BinHandle -> Word8 -> IO ()
putByte BinHandle
bh (TypeIndex -> Word8
forall a b. (Integral a, Num b) => a -> b
External instance of the constraint type Num Word8
External instance of the constraint type Integral TypeIndex
fromIntegral (NodeOrigin -> TypeIndex
forall a. Enum a => a -> TypeIndex
Instance of class: Enum of the constraint type Enum NodeOrigin
fromEnum NodeOrigin
b))
get :: BinHandle -> IO NodeOrigin
get BinHandle
bh = do Word8
x <- BinHandle -> IO Word8
getByte BinHandle
bh; NodeOrigin -> IO NodeOrigin
forall (f :: * -> *) a. Applicative f => a -> f a
External instance of the constraint type Applicative IO
pure (NodeOrigin -> IO NodeOrigin) -> NodeOrigin -> IO NodeOrigin
forall a b. (a -> b) -> a -> b
$! (TypeIndex -> NodeOrigin
forall a. Enum a => TypeIndex -> a
Instance of class: Enum of the constraint type Enum NodeOrigin
toEnum (Word8 -> TypeIndex
forall a b. (Integral a, Num b) => a -> b
External instance of the constraint type Num TypeIndex
External instance of the constraint type Integral Word8
fromIntegral Word8
x))
data NodeInfo a = NodeInfo
{ NodeInfo a -> Set (FastString, FastString)
nodeAnnotations :: S.Set (FastString,FastString)
, NodeInfo a -> [a]
nodeType :: [a]
, NodeInfo a -> NodeIdentifiers a
nodeIdentifiers :: NodeIdentifiers a
} deriving (a -> NodeInfo b -> NodeInfo a
(a -> b) -> NodeInfo a -> NodeInfo b
(forall a b. (a -> b) -> NodeInfo a -> NodeInfo b)
-> (forall a b. a -> NodeInfo b -> NodeInfo a) -> Functor NodeInfo
forall a b. a -> NodeInfo b -> NodeInfo a
forall a b. (a -> b) -> NodeInfo a -> NodeInfo b
forall (f :: * -> *).
(forall a b. (a -> b) -> f a -> f b)
-> (forall a b. a -> f b -> f a) -> Functor f
<$ :: a -> NodeInfo b -> NodeInfo a
$c<$ :: forall a b. a -> NodeInfo b -> NodeInfo a
fmap :: (a -> b) -> NodeInfo a -> NodeInfo b
$cfmap :: forall a b. (a -> b) -> NodeInfo a -> NodeInfo b
Instance of class: Functor of the constraint type Functor IdentifierDetails
External instance of the constraint type forall k. Functor (Map k)
External instance of the constraint type Functor []
Functor, NodeInfo a -> Bool
(a -> m) -> NodeInfo a -> m
(a -> b -> b) -> b -> NodeInfo a -> b
(forall m. Monoid m => NodeInfo m -> m)
-> (forall m a. Monoid m => (a -> m) -> NodeInfo a -> m)
-> (forall m a. Monoid m => (a -> m) -> NodeInfo a -> m)
-> (forall a b. (a -> b -> b) -> b -> NodeInfo a -> b)
-> (forall a b. (a -> b -> b) -> b -> NodeInfo a -> b)
-> (forall b a. (b -> a -> b) -> b -> NodeInfo a -> b)
-> (forall b a. (b -> a -> b) -> b -> NodeInfo a -> b)
-> (forall a. (a -> a -> a) -> NodeInfo a -> a)
-> (forall a. (a -> a -> a) -> NodeInfo a -> a)
-> (forall a. NodeInfo a -> [a])
-> (forall a. NodeInfo a -> Bool)
-> (forall a. NodeInfo a -> TypeIndex)
-> (forall a. Eq a => a -> NodeInfo a -> Bool)
-> (forall a. Ord a => NodeInfo a -> a)
-> (forall a. Ord a => NodeInfo a -> a)
-> (forall a. Num a => NodeInfo a -> a)
-> (forall a. Num a => NodeInfo a -> a)
-> Foldable NodeInfo
forall a. Eq a => a -> NodeInfo a -> Bool
forall a. Num a => NodeInfo a -> a
forall a. Ord a => NodeInfo a -> a
forall m. Monoid m => NodeInfo m -> m
forall a. NodeInfo a -> Bool
forall a. NodeInfo a -> TypeIndex
forall a. NodeInfo a -> [a]
forall a. (a -> a -> a) -> NodeInfo a -> a
forall m a. Monoid m => (a -> m) -> NodeInfo a -> m
forall b a. (b -> a -> b) -> b -> NodeInfo a -> b
forall a b. (a -> b -> b) -> b -> NodeInfo a -> b
forall (t :: * -> *).
(forall m. Monoid m => t m -> m)
-> (forall m a. Monoid m => (a -> m) -> t a -> m)
-> (forall m a. Monoid m => (a -> m) -> t a -> m)
-> (forall a b. (a -> b -> b) -> b -> t a -> b)
-> (forall a b. (a -> b -> b) -> b -> t a -> b)
-> (forall b a. (b -> a -> b) -> b -> t a -> b)
-> (forall b a. (b -> a -> b) -> b -> t a -> b)
-> (forall a. (a -> a -> a) -> t a -> a)
-> (forall a. (a -> a -> a) -> t a -> a)
-> (forall a. t a -> [a])
-> (forall a. t a -> Bool)
-> (forall a. t a -> TypeIndex)
-> (forall a. Eq a => a -> t a -> Bool)
-> (forall a. Ord a => t a -> a)
-> (forall a. Ord a => t a -> a)
-> (forall a. Num a => t a -> a)
-> (forall a. Num a => t a -> a)
-> Foldable t
product :: NodeInfo a -> a
$cproduct :: forall a. Num a => NodeInfo a -> a
sum :: NodeInfo a -> a
$csum :: forall a. Num a => NodeInfo a -> a
minimum :: NodeInfo a -> a
$cminimum :: forall a. Ord a => NodeInfo a -> a
maximum :: NodeInfo a -> a
$cmaximum :: forall a. Ord a => NodeInfo a -> a
elem :: a -> NodeInfo a -> Bool
$celem :: forall a. Eq a => a -> NodeInfo a -> Bool
length :: NodeInfo a -> TypeIndex
$clength :: forall a. NodeInfo a -> TypeIndex
null :: NodeInfo a -> Bool
$cnull :: forall a. NodeInfo a -> Bool
toList :: NodeInfo a -> [a]
$ctoList :: forall a. NodeInfo a -> [a]
foldl1 :: (a -> a -> a) -> NodeInfo a -> a
$cfoldl1 :: forall a. (a -> a -> a) -> NodeInfo a -> a
foldr1 :: (a -> a -> a) -> NodeInfo a -> a
$cfoldr1 :: forall a. (a -> a -> a) -> NodeInfo a -> a
foldl' :: (b -> a -> b) -> b -> NodeInfo a -> b
$cfoldl' :: forall b a. (b -> a -> b) -> b -> NodeInfo a -> b
foldl :: (b -> a -> b) -> b -> NodeInfo a -> b
$cfoldl :: forall b a. (b -> a -> b) -> b -> NodeInfo a -> b
foldr' :: (a -> b -> b) -> b -> NodeInfo a -> b
$cfoldr' :: forall a b. (a -> b -> b) -> b -> NodeInfo a -> b
foldr :: (a -> b -> b) -> b -> NodeInfo a -> b
$cfoldr :: forall a b. (a -> b -> b) -> b -> NodeInfo a -> b
foldMap' :: (a -> m) -> NodeInfo a -> m
$cfoldMap' :: forall m a. Monoid m => (a -> m) -> NodeInfo a -> m
foldMap :: (a -> m) -> NodeInfo a -> m
$cfoldMap :: forall m a. Monoid m => (a -> m) -> NodeInfo a -> m
fold :: NodeInfo m -> m
$cfold :: forall m. Monoid m => NodeInfo m -> m
Evidence bound by a type signature of the constraint type Monoid m
External instance of the constraint type forall k. Foldable (Map k)
External instance of the constraint type Foldable []
Instance of class: Foldable of the constraint type Foldable IdentifierDetails
Foldable, Functor NodeInfo
Foldable NodeInfo
Functor NodeInfo
-> Foldable NodeInfo
-> (forall (f :: * -> *) a b.
Applicative f =>
(a -> f b) -> NodeInfo a -> f (NodeInfo b))
-> (forall (f :: * -> *) a.
Applicative f =>
NodeInfo (f a) -> f (NodeInfo a))
-> (forall (m :: * -> *) a b.
Monad m =>
(a -> m b) -> NodeInfo a -> m (NodeInfo b))
-> (forall (m :: * -> *) a.
Monad m =>
NodeInfo (m a) -> m (NodeInfo a))
-> Traversable NodeInfo
(a -> f b) -> NodeInfo a -> f (NodeInfo b)
forall (t :: * -> *).
Functor t
-> Foldable t
-> (forall (f :: * -> *) a b.
Applicative f =>
(a -> f b) -> t a -> f (t b))
-> (forall (f :: * -> *) a. Applicative f => t (f a) -> f (t a))
-> (forall (m :: * -> *) a b.
Monad m =>
(a -> m b) -> t a -> m (t b))
-> (forall (m :: * -> *) a. Monad m => t (m a) -> m (t a))
-> Traversable t
forall (m :: * -> *) a. Monad m => NodeInfo (m a) -> m (NodeInfo a)
forall (f :: * -> *) a.
Applicative f =>
NodeInfo (f a) -> f (NodeInfo a)
forall (m :: * -> *) a b.
Monad m =>
(a -> m b) -> NodeInfo a -> m (NodeInfo b)
forall (f :: * -> *) a b.
Applicative f =>
(a -> f b) -> NodeInfo a -> f (NodeInfo b)
sequence :: NodeInfo (m a) -> m (NodeInfo a)
$csequence :: forall (m :: * -> *) a. Monad m => NodeInfo (m a) -> m (NodeInfo a)
mapM :: (a -> m b) -> NodeInfo a -> m (NodeInfo b)
$cmapM :: forall (m :: * -> *) a b.
Monad m =>
(a -> m b) -> NodeInfo a -> m (NodeInfo b)
sequenceA :: NodeInfo (f a) -> f (NodeInfo a)
$csequenceA :: forall (f :: * -> *) a.
Applicative f =>
NodeInfo (f a) -> f (NodeInfo a)
traverse :: (a -> f b) -> NodeInfo a -> f (NodeInfo b)
$ctraverse :: forall (f :: * -> *) a b.
Applicative f =>
(a -> f b) -> NodeInfo a -> f (NodeInfo b)
Evidence bound by a type signature of the constraint type Applicative f
Instance of class: Foldable of the constraint type Foldable NodeInfo
Instance of class: Functor of the constraint type Functor NodeInfo
Instance of class: Functor of the constraint type Functor NodeInfo
External instance of the constraint type forall k. Traversable (Map k)
External instance of the constraint type Traversable []
Instance of class: Traversable of the constraint type Traversable IdentifierDetails
Instance of class: Foldable of the constraint type Foldable NodeInfo
Traversable)
instance Binary (NodeInfo TypeIndex) where
put_ :: BinHandle -> NodeInfo TypeIndex -> IO ()
put_ BinHandle
bh NodeInfo TypeIndex
ni = do
BinHandle -> [(FastString, FastString)] -> IO ()
forall a. Binary a => BinHandle -> a -> IO ()
External instance of the constraint type forall a. Binary a => Binary [a]
External instance of the constraint type forall a b. (Binary a, Binary b) => Binary (a, b)
External instance of the constraint type Binary FastString
External instance of the constraint type Binary FastString
put_ BinHandle
bh ([(FastString, FastString)] -> IO ())
-> [(FastString, FastString)] -> IO ()
forall a b. (a -> b) -> a -> b
$ Set (FastString, FastString) -> [(FastString, FastString)]
forall a. Set a -> [a]
S.toAscList (Set (FastString, FastString) -> [(FastString, FastString)])
-> Set (FastString, FastString) -> [(FastString, FastString)]
forall a b. (a -> b) -> a -> b
$ NodeInfo TypeIndex -> Set (FastString, FastString)
forall a. NodeInfo a -> Set (FastString, FastString)
nodeAnnotations NodeInfo TypeIndex
ni
BinHandle -> [TypeIndex] -> IO ()
forall a. Binary a => BinHandle -> a -> IO ()
External instance of the constraint type forall a. Binary a => Binary [a]
External instance of the constraint type Binary TypeIndex
put_ BinHandle
bh ([TypeIndex] -> IO ()) -> [TypeIndex] -> IO ()
forall a b. (a -> b) -> a -> b
$ NodeInfo TypeIndex -> [TypeIndex]
forall a. NodeInfo a -> [a]
nodeType NodeInfo TypeIndex
ni
BinHandle -> [(Identifier, IdentifierDetails TypeIndex)] -> IO ()
forall a. Binary a => BinHandle -> a -> IO ()
External instance of the constraint type forall a. Binary a => Binary [a]
External instance of the constraint type forall a b. (Binary a, Binary b) => Binary (a, b)
External instance of the constraint type forall a b. (Binary a, Binary b) => Binary (Either a b)
External instance of the constraint type Binary ModuleName
External instance of the constraint type Binary Name
Instance of class: Binary of the constraint type Binary (IdentifierDetails TypeIndex)
put_ BinHandle
bh ([(Identifier, IdentifierDetails TypeIndex)] -> IO ())
-> [(Identifier, IdentifierDetails TypeIndex)] -> IO ()
forall a b. (a -> b) -> a -> b
$ Map Identifier (IdentifierDetails TypeIndex)
-> [(Identifier, IdentifierDetails TypeIndex)]
forall k a. Map k a -> [(k, a)]
M.toList (Map Identifier (IdentifierDetails TypeIndex)
-> [(Identifier, IdentifierDetails TypeIndex)])
-> Map Identifier (IdentifierDetails TypeIndex)
-> [(Identifier, IdentifierDetails TypeIndex)]
forall a b. (a -> b) -> a -> b
$ NodeInfo TypeIndex -> Map Identifier (IdentifierDetails TypeIndex)
forall a. NodeInfo a -> NodeIdentifiers a
nodeIdentifiers NodeInfo TypeIndex
ni
get :: BinHandle -> IO (NodeInfo TypeIndex)
get BinHandle
bh = Set (FastString, FastString)
-> [TypeIndex]
-> Map Identifier (IdentifierDetails TypeIndex)
-> NodeInfo TypeIndex
forall a.
Set (FastString, FastString)
-> [a] -> NodeIdentifiers a -> NodeInfo a
NodeInfo
(Set (FastString, FastString)
-> [TypeIndex]
-> Map Identifier (IdentifierDetails TypeIndex)
-> NodeInfo TypeIndex)
-> IO (Set (FastString, FastString))
-> IO
([TypeIndex]
-> Map Identifier (IdentifierDetails TypeIndex)
-> NodeInfo TypeIndex)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
External instance of the constraint type Functor IO
<$> ([(FastString, FastString)] -> Set (FastString, FastString))
-> IO [(FastString, FastString)]
-> IO (Set (FastString, FastString))
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
External instance of the constraint type Functor IO
fmap ([(FastString, FastString)] -> Set (FastString, FastString)
forall a. [a] -> Set a
S.fromDistinctAscList) (BinHandle -> IO [(FastString, FastString)]
forall a. Binary a => BinHandle -> IO a
External instance of the constraint type forall a. Binary a => Binary [a]
External instance of the constraint type forall a b. (Binary a, Binary b) => Binary (a, b)
External instance of the constraint type Binary FastString
External instance of the constraint type Binary FastString
get BinHandle
bh)
IO
([TypeIndex]
-> Map Identifier (IdentifierDetails TypeIndex)
-> NodeInfo TypeIndex)
-> IO [TypeIndex]
-> IO
(Map Identifier (IdentifierDetails TypeIndex)
-> NodeInfo TypeIndex)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
External instance of the constraint type Applicative IO
<*> BinHandle -> IO [TypeIndex]
forall a. Binary a => BinHandle -> IO a
External instance of the constraint type forall a. Binary a => Binary [a]
External instance of the constraint type Binary TypeIndex
get BinHandle
bh
IO
(Map Identifier (IdentifierDetails TypeIndex)
-> NodeInfo TypeIndex)
-> IO (Map Identifier (IdentifierDetails TypeIndex))
-> IO (NodeInfo TypeIndex)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
External instance of the constraint type Applicative IO
<*> ([(Identifier, IdentifierDetails TypeIndex)]
-> Map Identifier (IdentifierDetails TypeIndex))
-> IO [(Identifier, IdentifierDetails TypeIndex)]
-> IO (Map Identifier (IdentifierDetails TypeIndex))
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
External instance of the constraint type Functor IO
fmap ([(Identifier, IdentifierDetails TypeIndex)]
-> Map Identifier (IdentifierDetails TypeIndex)
forall k a. Ord k => [(k, a)] -> Map k a
External instance of the constraint type forall a b. (Ord a, Ord b) => Ord (Either a b)
External instance of the constraint type Ord ModuleName
External instance of the constraint type Ord Name
M.fromList) (BinHandle -> IO [(Identifier, IdentifierDetails TypeIndex)]
forall a. Binary a => BinHandle -> IO a
External instance of the constraint type forall a. Binary a => Binary [a]
External instance of the constraint type forall a b. (Binary a, Binary b) => Binary (a, b)
External instance of the constraint type forall a b. (Binary a, Binary b) => Binary (Either a b)
External instance of the constraint type Binary ModuleName
External instance of the constraint type Binary Name
Instance of class: Binary of the constraint type Binary (IdentifierDetails TypeIndex)
get BinHandle
bh)
instance Outputable a => Outputable (NodeInfo a) where
ppr :: NodeInfo a -> SDoc
ppr (NodeInfo Set (FastString, FastString)
anns [a]
typs NodeIdentifiers a
idents) = SDoc -> SDoc
braces (SDoc -> SDoc) -> SDoc -> SDoc
forall a b. (a -> b) -> a -> b
$ [SDoc] -> SDoc
fsep ([SDoc] -> SDoc) -> [SDoc] -> SDoc
forall a b. (a -> b) -> a -> b
$ SDoc -> [SDoc] -> [SDoc]
punctuate SDoc
", "
[ SDoc -> SDoc
parens (String -> SDoc
text String
"annotations:" SDoc -> SDoc -> SDoc
<+> Set (FastString, FastString) -> SDoc
forall a. Outputable a => a -> SDoc
External instance of the constraint type forall a. Outputable a => Outputable (Set a)
External instance of the constraint type forall a b. (Outputable a, Outputable b) => Outputable (a, b)
External instance of the constraint type Outputable FastString
External instance of the constraint type Outputable FastString
ppr Set (FastString, FastString)
anns)
, SDoc -> SDoc
parens (String -> SDoc
text String
"types:" SDoc -> SDoc -> SDoc
<+> [a] -> SDoc
forall a. Outputable a => a -> SDoc
External instance of the constraint type forall a. Outputable a => Outputable [a]
Evidence bound by a type signature of the constraint type Outputable a
ppr [a]
typs)
, SDoc -> SDoc
parens (String -> SDoc
text String
"identifier info:" SDoc -> SDoc -> SDoc
<+> NodeIdentifiers a -> SDoc
forall a. Outputable a => NodeIdentifiers a -> SDoc
Evidence bound by a type signature of the constraint type Outputable a
pprNodeIdents NodeIdentifiers a
idents)
]
pprNodeIdents :: Outputable a => NodeIdentifiers a -> SDoc
pprNodeIdents :: NodeIdentifiers a -> SDoc
pprNodeIdents NodeIdentifiers a
ni = SDoc -> SDoc
braces (SDoc -> SDoc) -> SDoc -> SDoc
forall a b. (a -> b) -> a -> b
$ [SDoc] -> SDoc
fsep ([SDoc] -> SDoc) -> [SDoc] -> SDoc
forall a b. (a -> b) -> a -> b
$ SDoc -> [SDoc] -> [SDoc]
punctuate SDoc
", " ([SDoc] -> [SDoc]) -> [SDoc] -> [SDoc]
forall a b. (a -> b) -> a -> b
$ ((Identifier, IdentifierDetails a) -> SDoc)
-> [(Identifier, IdentifierDetails a)] -> [SDoc]
forall a b. (a -> b) -> [a] -> [b]
map (Identifier, IdentifierDetails a) -> SDoc
forall {a}. Outputable a => (Identifier, a) -> SDoc
Instance of class: Outputable of the constraint type forall a. Outputable a => Outputable (IdentifierDetails a)
Evidence bound by a type signature of the constraint type Outputable a
go ([(Identifier, IdentifierDetails a)] -> [SDoc])
-> [(Identifier, IdentifierDetails a)] -> [SDoc]
forall a b. (a -> b) -> a -> b
$ NodeIdentifiers a -> [(Identifier, IdentifierDetails a)]
forall k a. Map k a -> [(k, a)]
M.toList NodeIdentifiers a
ni
where
go :: (Identifier, a) -> SDoc
go (Identifier
i,a
id) = SDoc -> SDoc
parens (SDoc -> SDoc) -> SDoc -> SDoc
forall a b. (a -> b) -> a -> b
$ [SDoc] -> SDoc
hsep ([SDoc] -> SDoc) -> [SDoc] -> SDoc
forall a b. (a -> b) -> a -> b
$ SDoc -> [SDoc] -> [SDoc]
punctuate SDoc
", " [Identifier -> SDoc
pprIdentifier Identifier
i, a -> SDoc
forall a. Outputable a => a -> SDoc
Evidence bound by a type signature of the constraint type Outputable a
ppr a
id]
pprIdentifier :: Identifier -> SDoc
pprIdentifier :: Identifier -> SDoc
pprIdentifier (Left ModuleName
mod) = String -> SDoc
text String
"module" SDoc -> SDoc -> SDoc
<+> ModuleName -> SDoc
forall a. Outputable a => a -> SDoc
External instance of the constraint type Outputable ModuleName
ppr ModuleName
mod
pprIdentifier (Right Name
name) = String -> SDoc
text String
"name" SDoc -> SDoc -> SDoc
<+> Name -> SDoc
forall a. Outputable a => a -> SDoc
External instance of the constraint type Outputable Name
ppr Name
name
type Identifier = Either ModuleName Name
type NodeIdentifiers a = M.Map Identifier (IdentifierDetails a)
data IdentifierDetails a = IdentifierDetails
{ IdentifierDetails a -> Maybe a
identType :: Maybe a
, IdentifierDetails a -> Set ContextInfo
identInfo :: S.Set ContextInfo
} deriving (IdentifierDetails a -> IdentifierDetails a -> Bool
(IdentifierDetails a -> IdentifierDetails a -> Bool)
-> (IdentifierDetails a -> IdentifierDetails a -> Bool)
-> Eq (IdentifierDetails a)
forall a.
Eq a =>
IdentifierDetails a -> IdentifierDetails a -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: IdentifierDetails a -> IdentifierDetails a -> Bool
$c/= :: forall a.
Eq a =>
IdentifierDetails a -> IdentifierDetails a -> Bool
== :: IdentifierDetails a -> IdentifierDetails a -> Bool
$c== :: forall a.
Eq a =>
IdentifierDetails a -> IdentifierDetails a -> Bool
Instance of class: Eq of the constraint type Eq ContextInfo
External instance of the constraint type forall a. Eq a => Eq (Set a)
External instance of the constraint type forall a. Eq a => Eq (Maybe a)
Instance of class: Eq of the constraint type Eq ContextInfo
Evidence bound by a type signature of the constraint type Eq a
Eq, a -> IdentifierDetails b -> IdentifierDetails a
(a -> b) -> IdentifierDetails a -> IdentifierDetails b
(forall a b.
(a -> b) -> IdentifierDetails a -> IdentifierDetails b)
-> (forall a b. a -> IdentifierDetails b -> IdentifierDetails a)
-> Functor IdentifierDetails
forall a b. a -> IdentifierDetails b -> IdentifierDetails a
forall a b. (a -> b) -> IdentifierDetails a -> IdentifierDetails b
forall (f :: * -> *).
(forall a b. (a -> b) -> f a -> f b)
-> (forall a b. a -> f b -> f a) -> Functor f
<$ :: a -> IdentifierDetails b -> IdentifierDetails a
$c<$ :: forall a b. a -> IdentifierDetails b -> IdentifierDetails a
fmap :: (a -> b) -> IdentifierDetails a -> IdentifierDetails b
$cfmap :: forall a b. (a -> b) -> IdentifierDetails a -> IdentifierDetails b
External instance of the constraint type Functor Maybe
Functor, IdentifierDetails a -> Bool
(a -> m) -> IdentifierDetails a -> m
(a -> b -> b) -> b -> IdentifierDetails a -> b
(forall m. Monoid m => IdentifierDetails m -> m)
-> (forall m a. Monoid m => (a -> m) -> IdentifierDetails a -> m)
-> (forall m a. Monoid m => (a -> m) -> IdentifierDetails a -> m)
-> (forall a b. (a -> b -> b) -> b -> IdentifierDetails a -> b)
-> (forall a b. (a -> b -> b) -> b -> IdentifierDetails a -> b)
-> (forall b a. (b -> a -> b) -> b -> IdentifierDetails a -> b)
-> (forall b a. (b -> a -> b) -> b -> IdentifierDetails a -> b)
-> (forall a. (a -> a -> a) -> IdentifierDetails a -> a)
-> (forall a. (a -> a -> a) -> IdentifierDetails a -> a)
-> (forall a. IdentifierDetails a -> [a])
-> (forall a. IdentifierDetails a -> Bool)
-> (forall a. IdentifierDetails a -> TypeIndex)
-> (forall a. Eq a => a -> IdentifierDetails a -> Bool)
-> (forall a. Ord a => IdentifierDetails a -> a)
-> (forall a. Ord a => IdentifierDetails a -> a)
-> (forall a. Num a => IdentifierDetails a -> a)
-> (forall a. Num a => IdentifierDetails a -> a)
-> Foldable IdentifierDetails
forall a. Eq a => a -> IdentifierDetails a -> Bool
forall a. Num a => IdentifierDetails a -> a
forall a. Ord a => IdentifierDetails a -> a
forall m. Monoid m => IdentifierDetails m -> m
forall a. IdentifierDetails a -> Bool
forall a. IdentifierDetails a -> TypeIndex
forall a. IdentifierDetails a -> [a]
forall a. (a -> a -> a) -> IdentifierDetails a -> a
forall m a. Monoid m => (a -> m) -> IdentifierDetails a -> m
forall b a. (b -> a -> b) -> b -> IdentifierDetails a -> b
forall a b. (a -> b -> b) -> b -> IdentifierDetails a -> b
forall (t :: * -> *).
(forall m. Monoid m => t m -> m)
-> (forall m a. Monoid m => (a -> m) -> t a -> m)
-> (forall m a. Monoid m => (a -> m) -> t a -> m)
-> (forall a b. (a -> b -> b) -> b -> t a -> b)
-> (forall a b. (a -> b -> b) -> b -> t a -> b)
-> (forall b a. (b -> a -> b) -> b -> t a -> b)
-> (forall b a. (b -> a -> b) -> b -> t a -> b)
-> (forall a. (a -> a -> a) -> t a -> a)
-> (forall a. (a -> a -> a) -> t a -> a)
-> (forall a. t a -> [a])
-> (forall a. t a -> Bool)
-> (forall a. t a -> TypeIndex)
-> (forall a. Eq a => a -> t a -> Bool)
-> (forall a. Ord a => t a -> a)
-> (forall a. Ord a => t a -> a)
-> (forall a. Num a => t a -> a)
-> (forall a. Num a => t a -> a)
-> Foldable t
product :: IdentifierDetails a -> a
$cproduct :: forall a. Num a => IdentifierDetails a -> a
sum :: IdentifierDetails a -> a
$csum :: forall a. Num a => IdentifierDetails a -> a
minimum :: IdentifierDetails a -> a
$cminimum :: forall a. Ord a => IdentifierDetails a -> a
maximum :: IdentifierDetails a -> a
$cmaximum :: forall a. Ord a => IdentifierDetails a -> a
elem :: a -> IdentifierDetails a -> Bool
$celem :: forall a. Eq a => a -> IdentifierDetails a -> Bool
length :: IdentifierDetails a -> TypeIndex
$clength :: forall a. IdentifierDetails a -> TypeIndex
null :: IdentifierDetails a -> Bool
$cnull :: forall a. IdentifierDetails a -> Bool
toList :: IdentifierDetails a -> [a]
$ctoList :: forall a. IdentifierDetails a -> [a]
foldl1 :: (a -> a -> a) -> IdentifierDetails a -> a
$cfoldl1 :: forall a. (a -> a -> a) -> IdentifierDetails a -> a
foldr1 :: (a -> a -> a) -> IdentifierDetails a -> a
$cfoldr1 :: forall a. (a -> a -> a) -> IdentifierDetails a -> a
foldl' :: (b -> a -> b) -> b -> IdentifierDetails a -> b
$cfoldl' :: forall b a. (b -> a -> b) -> b -> IdentifierDetails a -> b
foldl :: (b -> a -> b) -> b -> IdentifierDetails a -> b
$cfoldl :: forall b a. (b -> a -> b) -> b -> IdentifierDetails a -> b
foldr' :: (a -> b -> b) -> b -> IdentifierDetails a -> b
$cfoldr' :: forall a b. (a -> b -> b) -> b -> IdentifierDetails a -> b
foldr :: (a -> b -> b) -> b -> IdentifierDetails a -> b
$cfoldr :: forall a b. (a -> b -> b) -> b -> IdentifierDetails a -> b
foldMap' :: (a -> m) -> IdentifierDetails a -> m
$cfoldMap' :: forall m a. Monoid m => (a -> m) -> IdentifierDetails a -> m
foldMap :: (a -> m) -> IdentifierDetails a -> m
$cfoldMap :: forall m a. Monoid m => (a -> m) -> IdentifierDetails a -> m
fold :: IdentifierDetails m -> m
$cfold :: forall m. Monoid m => IdentifierDetails m -> m
External instance of the constraint type Foldable Maybe
Evidence bound by a type signature of the constraint type Monoid m
Foldable, Functor IdentifierDetails
Foldable IdentifierDetails
Functor IdentifierDetails
-> Foldable IdentifierDetails
-> (forall (f :: * -> *) a b.
Applicative f =>
(a -> f b) -> IdentifierDetails a -> f (IdentifierDetails b))
-> (forall (f :: * -> *) a.
Applicative f =>
IdentifierDetails (f a) -> f (IdentifierDetails a))
-> (forall (m :: * -> *) a b.
Monad m =>
(a -> m b) -> IdentifierDetails a -> m (IdentifierDetails b))
-> (forall (m :: * -> *) a.
Monad m =>
IdentifierDetails (m a) -> m (IdentifierDetails a))
-> Traversable IdentifierDetails
(a -> f b) -> IdentifierDetails a -> f (IdentifierDetails b)
forall (t :: * -> *).
Functor t
-> Foldable t
-> (forall (f :: * -> *) a b.
Applicative f =>
(a -> f b) -> t a -> f (t b))
-> (forall (f :: * -> *) a. Applicative f => t (f a) -> f (t a))
-> (forall (m :: * -> *) a b.
Monad m =>
(a -> m b) -> t a -> m (t b))
-> (forall (m :: * -> *) a. Monad m => t (m a) -> m (t a))
-> Traversable t
forall (m :: * -> *) a.
Monad m =>
IdentifierDetails (m a) -> m (IdentifierDetails a)
forall (f :: * -> *) a.
Applicative f =>
IdentifierDetails (f a) -> f (IdentifierDetails a)
forall (m :: * -> *) a b.
Monad m =>
(a -> m b) -> IdentifierDetails a -> m (IdentifierDetails b)
forall (f :: * -> *) a b.
Applicative f =>
(a -> f b) -> IdentifierDetails a -> f (IdentifierDetails b)
sequence :: IdentifierDetails (m a) -> m (IdentifierDetails a)
$csequence :: forall (m :: * -> *) a.
Monad m =>
IdentifierDetails (m a) -> m (IdentifierDetails a)
mapM :: (a -> m b) -> IdentifierDetails a -> m (IdentifierDetails b)
$cmapM :: forall (m :: * -> *) a b.
Monad m =>
(a -> m b) -> IdentifierDetails a -> m (IdentifierDetails b)
sequenceA :: IdentifierDetails (f a) -> f (IdentifierDetails a)
$csequenceA :: forall (f :: * -> *) a.
Applicative f =>
IdentifierDetails (f a) -> f (IdentifierDetails a)
traverse :: (a -> f b) -> IdentifierDetails a -> f (IdentifierDetails b)
$ctraverse :: forall (f :: * -> *) a b.
Applicative f =>
(a -> f b) -> IdentifierDetails a -> f (IdentifierDetails b)
External instance of the constraint type Traversable Maybe
External instance of the constraint type forall (f :: * -> *). Applicative f => Functor f
Evidence bound by a type signature of the constraint type Applicative f
Evidence bound by a type signature of the constraint type Applicative f
Instance of class: Foldable of the constraint type Foldable IdentifierDetails
Instance of class: Functor of the constraint type Functor IdentifierDetails
Instance of class: Functor of the constraint type Functor IdentifierDetails
External instance of the constraint type forall (f :: * -> *). Applicative f => Functor f
Instance of class: Foldable of the constraint type Foldable IdentifierDetails
Traversable)
instance Outputable a => Outputable (IdentifierDetails a) where
ppr :: IdentifierDetails a -> SDoc
ppr IdentifierDetails a
x = String -> SDoc
text String
"Details: " SDoc -> SDoc -> SDoc
<+> Maybe a -> SDoc
forall a. Outputable a => a -> SDoc
External instance of the constraint type forall a. Outputable a => Outputable (Maybe a)
Evidence bound by a type signature of the constraint type Outputable a
ppr (IdentifierDetails a -> Maybe a
forall a. IdentifierDetails a -> Maybe a
identType IdentifierDetails a
x) SDoc -> SDoc -> SDoc
<+> Set ContextInfo -> SDoc
forall a. Outputable a => a -> SDoc
External instance of the constraint type forall a. Outputable a => Outputable (Set a)
Instance of class: Outputable of the constraint type Outputable ContextInfo
ppr (IdentifierDetails a -> Set ContextInfo
forall a. IdentifierDetails a -> Set ContextInfo
identInfo IdentifierDetails a
x)
instance Semigroup (IdentifierDetails a) where
IdentifierDetails a
d1 <> :: IdentifierDetails a -> IdentifierDetails a -> IdentifierDetails a
<> IdentifierDetails a
d2 = Maybe a -> Set ContextInfo -> IdentifierDetails a
forall a. Maybe a -> Set ContextInfo -> IdentifierDetails a
IdentifierDetails (IdentifierDetails a -> Maybe a
forall a. IdentifierDetails a -> Maybe a
identType IdentifierDetails a
d1 Maybe a -> Maybe a -> Maybe a
forall (f :: * -> *) a. Alternative f => f a -> f a -> f a
External instance of the constraint type Alternative Maybe
<|> IdentifierDetails a -> Maybe a
forall a. IdentifierDetails a -> Maybe a
identType IdentifierDetails a
d2)
(Set ContextInfo -> Set ContextInfo -> Set ContextInfo
forall a. Ord a => Set a -> Set a -> Set a
Instance of class: Ord of the constraint type Ord ContextInfo
S.union (IdentifierDetails a -> Set ContextInfo
forall a. IdentifierDetails a -> Set ContextInfo
identInfo IdentifierDetails a
d1) (IdentifierDetails a -> Set ContextInfo
forall a. IdentifierDetails a -> Set ContextInfo
identInfo IdentifierDetails a
d2))
instance Monoid (IdentifierDetails a) where
mempty :: IdentifierDetails a
mempty = Maybe a -> Set ContextInfo -> IdentifierDetails a
forall a. Maybe a -> Set ContextInfo -> IdentifierDetails a
IdentifierDetails Maybe a
forall a. Maybe a
Nothing Set ContextInfo
forall a. Set a
S.empty
instance Binary (IdentifierDetails TypeIndex) where
put_ :: BinHandle -> IdentifierDetails TypeIndex -> IO ()
put_ BinHandle
bh IdentifierDetails TypeIndex
dets = do
BinHandle -> Maybe TypeIndex -> IO ()
forall a. Binary a => BinHandle -> a -> IO ()
External instance of the constraint type forall a. Binary a => Binary (Maybe a)
External instance of the constraint type Binary TypeIndex
put_ BinHandle
bh (Maybe TypeIndex -> IO ()) -> Maybe TypeIndex -> IO ()
forall a b. (a -> b) -> a -> b
$ IdentifierDetails TypeIndex -> Maybe TypeIndex
forall a. IdentifierDetails a -> Maybe a
identType IdentifierDetails TypeIndex
dets
BinHandle -> [ContextInfo] -> IO ()
forall a. Binary a => BinHandle -> a -> IO ()
External instance of the constraint type forall a. Binary a => Binary [a]
Instance of class: Binary of the constraint type Binary ContextInfo
put_ BinHandle
bh ([ContextInfo] -> IO ()) -> [ContextInfo] -> IO ()
forall a b. (a -> b) -> a -> b
$ Set ContextInfo -> [ContextInfo]
forall a. Set a -> [a]
S.toList (Set ContextInfo -> [ContextInfo])
-> Set ContextInfo -> [ContextInfo]
forall a b. (a -> b) -> a -> b
$ IdentifierDetails TypeIndex -> Set ContextInfo
forall a. IdentifierDetails a -> Set ContextInfo
identInfo IdentifierDetails TypeIndex
dets
get :: BinHandle -> IO (IdentifierDetails TypeIndex)
get BinHandle
bh = Maybe TypeIndex -> Set ContextInfo -> IdentifierDetails TypeIndex
forall a. Maybe a -> Set ContextInfo -> IdentifierDetails a
IdentifierDetails
(Maybe TypeIndex -> Set ContextInfo -> IdentifierDetails TypeIndex)
-> IO (Maybe TypeIndex)
-> IO (Set ContextInfo -> IdentifierDetails TypeIndex)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
External instance of the constraint type Functor IO
<$> BinHandle -> IO (Maybe TypeIndex)
forall a. Binary a => BinHandle -> IO a
External instance of the constraint type forall a. Binary a => Binary (Maybe a)
External instance of the constraint type Binary TypeIndex
get BinHandle
bh
IO (Set ContextInfo -> IdentifierDetails TypeIndex)
-> IO (Set ContextInfo) -> IO (IdentifierDetails TypeIndex)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
External instance of the constraint type Applicative IO
<*> ([ContextInfo] -> Set ContextInfo)
-> IO [ContextInfo] -> IO (Set ContextInfo)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
External instance of the constraint type Functor IO
fmap [ContextInfo] -> Set ContextInfo
forall a. [a] -> Set a
S.fromDistinctAscList (BinHandle -> IO [ContextInfo]
forall a. Binary a => BinHandle -> IO a
External instance of the constraint type forall a. Binary a => Binary [a]
Instance of class: Binary of the constraint type Binary ContextInfo
get BinHandle
bh)
data ContextInfo
= Use
| MatchBind
| IEThing IEType
| TyDecl
| ValBind
BindType
Scope
(Maybe Span)
| PatternBind
Scope
Scope
(Maybe Span)
| ClassTyDecl (Maybe Span)
| Decl
DeclType
(Maybe Span)
| TyVarBind Scope TyVarScope
| RecField RecFieldContext (Maybe Span)
| EvidenceVarBind
EvVarSource
Scope
(Maybe Span)
| EvidenceVarUse
deriving (ContextInfo -> ContextInfo -> Bool
(ContextInfo -> ContextInfo -> Bool)
-> (ContextInfo -> ContextInfo -> Bool) -> Eq ContextInfo
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: ContextInfo -> ContextInfo -> Bool
$c/= :: ContextInfo -> ContextInfo -> Bool
== :: ContextInfo -> ContextInfo -> Bool
$c== :: ContextInfo -> ContextInfo -> Bool
External instance of the constraint type Eq Span
External instance of the constraint type Eq Span
External instance of the constraint type forall a. Eq a => Eq (Maybe a)
External instance of the constraint type Eq Span
Instance of class: Eq of the constraint type Eq Scope
External instance of the constraint type forall a. Eq a => Eq (Maybe a)
Instance of class: Eq of the constraint type Eq EvVarSource
Instance of class: Eq of the constraint type Eq IEType
Instance of class: Eq of the constraint type Eq RecFieldContext
Instance of class: Eq of the constraint type Eq BindType
Instance of class: Eq of the constraint type Eq DeclType
Instance of class: Eq of the constraint type Eq Scope
Instance of class: Eq of the constraint type Eq TyVarScope
Eq, Eq ContextInfo
Eq ContextInfo
-> (ContextInfo -> ContextInfo -> Ordering)
-> (ContextInfo -> ContextInfo -> Bool)
-> (ContextInfo -> ContextInfo -> Bool)
-> (ContextInfo -> ContextInfo -> Bool)
-> (ContextInfo -> ContextInfo -> Bool)
-> (ContextInfo -> ContextInfo -> ContextInfo)
-> (ContextInfo -> ContextInfo -> ContextInfo)
-> Ord ContextInfo
ContextInfo -> ContextInfo -> Bool
ContextInfo -> ContextInfo -> Ordering
ContextInfo -> ContextInfo -> ContextInfo
forall a.
Eq a
-> (a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
min :: ContextInfo -> ContextInfo -> ContextInfo
$cmin :: ContextInfo -> ContextInfo -> ContextInfo
max :: ContextInfo -> ContextInfo -> ContextInfo
$cmax :: ContextInfo -> ContextInfo -> ContextInfo
>= :: ContextInfo -> ContextInfo -> Bool
$c>= :: ContextInfo -> ContextInfo -> Bool
> :: ContextInfo -> ContextInfo -> Bool
$c> :: ContextInfo -> ContextInfo -> Bool
<= :: ContextInfo -> ContextInfo -> Bool
$c<= :: ContextInfo -> ContextInfo -> Bool
< :: ContextInfo -> ContextInfo -> Bool
$c< :: ContextInfo -> ContextInfo -> Bool
compare :: ContextInfo -> ContextInfo -> Ordering
$ccompare :: ContextInfo -> ContextInfo -> Ordering
External instance of the constraint type Ord Span
External instance of the constraint type Ord Span
External instance of the constraint type forall a. Ord a => Ord (Maybe a)
External instance of the constraint type forall a. Ord a => Ord (Maybe a)
External instance of the constraint type Ord Span
Instance of class: Ord of the constraint type Ord Scope
Instance of class: Eq of the constraint type Eq ContextInfo
Instance of class: Ord of the constraint type Ord EvVarSource
Instance of class: Ord of the constraint type Ord IEType
Instance of class: Ord of the constraint type Ord RecFieldContext
Instance of class: Ord of the constraint type Ord BindType
Instance of class: Ord of the constraint type Ord DeclType
Instance of class: Ord of the constraint type Ord Scope
Instance of class: Ord of the constraint type Ord TyVarScope
Instance of class: Eq of the constraint type Eq ContextInfo
Ord)
instance Outputable ContextInfo where
ppr :: ContextInfo -> SDoc
ppr (ContextInfo
Use) = String -> SDoc
text String
"usage"
ppr (ContextInfo
MatchBind) = String -> SDoc
text String
"LHS of a match group"
ppr (IEThing IEType
x) = IEType -> SDoc
forall a. Outputable a => a -> SDoc
Instance of class: Outputable of the constraint type Outputable IEType
ppr IEType
x
ppr (ContextInfo
TyDecl) = String -> SDoc
text String
"bound in a type signature declaration"
ppr (ValBind BindType
t Scope
sc Maybe Span
sp) =
BindType -> SDoc
forall a. Outputable a => a -> SDoc
Instance of class: Outputable of the constraint type Outputable BindType
ppr BindType
t SDoc -> SDoc -> SDoc
<+> String -> SDoc
text String
"value bound with scope:" SDoc -> SDoc -> SDoc
<+> Scope -> SDoc
forall a. Outputable a => a -> SDoc
Instance of class: Outputable of the constraint type Outputable Scope
ppr Scope
sc SDoc -> SDoc -> SDoc
<+> Maybe Span -> SDoc
pprBindSpan Maybe Span
sp
ppr (PatternBind Scope
sc1 Scope
sc2 Maybe Span
sp) =
String -> SDoc
text String
"bound in a pattern with scope:"
SDoc -> SDoc -> SDoc
<+> Scope -> SDoc
forall a. Outputable a => a -> SDoc
Instance of class: Outputable of the constraint type Outputable Scope
ppr Scope
sc1 SDoc -> SDoc -> SDoc
<+> SDoc
"," SDoc -> SDoc -> SDoc
<+> Scope -> SDoc
forall a. Outputable a => a -> SDoc
Instance of class: Outputable of the constraint type Outputable Scope
ppr Scope
sc2
SDoc -> SDoc -> SDoc
<+> Maybe Span -> SDoc
pprBindSpan Maybe Span
sp
ppr (ClassTyDecl Maybe Span
sp) =
String -> SDoc
text String
"bound in a class type declaration" SDoc -> SDoc -> SDoc
<+> Maybe Span -> SDoc
pprBindSpan Maybe Span
sp
ppr (Decl DeclType
d Maybe Span
sp) =
String -> SDoc
text String
"declaration of" SDoc -> SDoc -> SDoc
<+> DeclType -> SDoc
forall a. Outputable a => a -> SDoc
Instance of class: Outputable of the constraint type Outputable DeclType
ppr DeclType
d SDoc -> SDoc -> SDoc
<+> Maybe Span -> SDoc
pprBindSpan Maybe Span
sp
ppr (TyVarBind Scope
sc1 TyVarScope
sc2) =
String -> SDoc
text String
"type variable binding with scope:"
SDoc -> SDoc -> SDoc
<+> Scope -> SDoc
forall a. Outputable a => a -> SDoc
Instance of class: Outputable of the constraint type Outputable Scope
ppr Scope
sc1 SDoc -> SDoc -> SDoc
<+> SDoc
"," SDoc -> SDoc -> SDoc
<+> TyVarScope -> SDoc
forall a. Outputable a => a -> SDoc
Instance of class: Outputable of the constraint type Outputable TyVarScope
ppr TyVarScope
sc2
ppr (RecField RecFieldContext
ctx Maybe Span
sp) =
String -> SDoc
text String
"record field" SDoc -> SDoc -> SDoc
<+> RecFieldContext -> SDoc
forall a. Outputable a => a -> SDoc
Instance of class: Outputable of the constraint type Outputable RecFieldContext
ppr RecFieldContext
ctx SDoc -> SDoc -> SDoc
<+> Maybe Span -> SDoc
pprBindSpan Maybe Span
sp
ppr (EvidenceVarBind EvVarSource
ctx Scope
sc Maybe Span
sp) =
String -> SDoc
text String
"evidence variable" SDoc -> SDoc -> SDoc
<+> EvVarSource -> SDoc
forall a. Outputable a => a -> SDoc
Instance of class: Outputable of the constraint type Outputable EvVarSource
ppr EvVarSource
ctx
SDoc -> SDoc -> SDoc
$$ SDoc
"with scope:" SDoc -> SDoc -> SDoc
<+> Scope -> SDoc
forall a. Outputable a => a -> SDoc
Instance of class: Outputable of the constraint type Outputable Scope
ppr Scope
sc
SDoc -> SDoc -> SDoc
$$ Maybe Span -> SDoc
pprBindSpan Maybe Span
sp
ppr (ContextInfo
EvidenceVarUse) =
String -> SDoc
text String
"usage of evidence variable"
pprBindSpan :: Maybe Span -> SDoc
pprBindSpan :: Maybe Span -> SDoc
pprBindSpan Maybe Span
Nothing = String -> SDoc
text String
""
pprBindSpan (Just Span
sp) = String -> SDoc
text String
"bound at:" SDoc -> SDoc -> SDoc
<+> Span -> SDoc
forall a. Outputable a => a -> SDoc
External instance of the constraint type Outputable Span
ppr Span
sp
instance Binary ContextInfo where
put_ :: BinHandle -> ContextInfo -> IO ()
put_ BinHandle
bh ContextInfo
Use = BinHandle -> Word8 -> IO ()
putByte BinHandle
bh Word8
0
put_ BinHandle
bh (IEThing IEType
t) = do
BinHandle -> Word8 -> IO ()
putByte BinHandle
bh Word8
1
BinHandle -> IEType -> IO ()
forall a. Binary a => BinHandle -> a -> IO ()
Instance of class: Binary of the constraint type Binary IEType
put_ BinHandle
bh IEType
t
put_ BinHandle
bh ContextInfo
TyDecl = BinHandle -> Word8 -> IO ()
putByte BinHandle
bh Word8
2
put_ BinHandle
bh (ValBind BindType
bt Scope
sc Maybe Span
msp) = do
BinHandle -> Word8 -> IO ()
putByte BinHandle
bh Word8
3
BinHandle -> BindType -> IO ()
forall a. Binary a => BinHandle -> a -> IO ()
Instance of class: Binary of the constraint type Binary BindType
put_ BinHandle
bh BindType
bt
BinHandle -> Scope -> IO ()
forall a. Binary a => BinHandle -> a -> IO ()
Instance of class: Binary of the constraint type Binary Scope
put_ BinHandle
bh Scope
sc
BinHandle -> Maybe Span -> IO ()
forall a. Binary a => BinHandle -> a -> IO ()
External instance of the constraint type forall a. Binary a => Binary (Maybe a)
External instance of the constraint type Binary Span
put_ BinHandle
bh Maybe Span
msp
put_ BinHandle
bh (PatternBind Scope
a Scope
b Maybe Span
c) = do
BinHandle -> Word8 -> IO ()
putByte BinHandle
bh Word8
4
BinHandle -> Scope -> IO ()
forall a. Binary a => BinHandle -> a -> IO ()
Instance of class: Binary of the constraint type Binary Scope
put_ BinHandle
bh Scope
a
BinHandle -> Scope -> IO ()
forall a. Binary a => BinHandle -> a -> IO ()
Instance of class: Binary of the constraint type Binary Scope
put_ BinHandle
bh Scope
b
BinHandle -> Maybe Span -> IO ()
forall a. Binary a => BinHandle -> a -> IO ()
External instance of the constraint type forall a. Binary a => Binary (Maybe a)
External instance of the constraint type Binary Span
put_ BinHandle
bh Maybe Span
c
put_ BinHandle
bh (ClassTyDecl Maybe Span
sp) = do
BinHandle -> Word8 -> IO ()
putByte BinHandle
bh Word8
5
BinHandle -> Maybe Span -> IO ()
forall a. Binary a => BinHandle -> a -> IO ()
External instance of the constraint type forall a. Binary a => Binary (Maybe a)
External instance of the constraint type Binary Span
put_ BinHandle
bh Maybe Span
sp
put_ BinHandle
bh (Decl DeclType
a Maybe Span
b) = do
BinHandle -> Word8 -> IO ()
putByte BinHandle
bh Word8
6
BinHandle -> DeclType -> IO ()
forall a. Binary a => BinHandle -> a -> IO ()
Instance of class: Binary of the constraint type Binary DeclType
put_ BinHandle
bh DeclType
a
BinHandle -> Maybe Span -> IO ()
forall a. Binary a => BinHandle -> a -> IO ()
External instance of the constraint type forall a. Binary a => Binary (Maybe a)
External instance of the constraint type Binary Span
put_ BinHandle
bh Maybe Span
b
put_ BinHandle
bh (TyVarBind Scope
a TyVarScope
b) = do
BinHandle -> Word8 -> IO ()
putByte BinHandle
bh Word8
7
BinHandle -> Scope -> IO ()
forall a. Binary a => BinHandle -> a -> IO ()
Instance of class: Binary of the constraint type Binary Scope
put_ BinHandle
bh Scope
a
BinHandle -> TyVarScope -> IO ()
forall a. Binary a => BinHandle -> a -> IO ()
Instance of class: Binary of the constraint type Binary TyVarScope
put_ BinHandle
bh TyVarScope
b
put_ BinHandle
bh (RecField RecFieldContext
a Maybe Span
b) = do
BinHandle -> Word8 -> IO ()
putByte BinHandle
bh Word8
8
BinHandle -> RecFieldContext -> IO ()
forall a. Binary a => BinHandle -> a -> IO ()
Instance of class: Binary of the constraint type Binary RecFieldContext
put_ BinHandle
bh RecFieldContext
a
BinHandle -> Maybe Span -> IO ()
forall a. Binary a => BinHandle -> a -> IO ()
External instance of the constraint type forall a. Binary a => Binary (Maybe a)
External instance of the constraint type Binary Span
put_ BinHandle
bh Maybe Span
b
put_ BinHandle
bh ContextInfo
MatchBind = BinHandle -> Word8 -> IO ()
putByte BinHandle
bh Word8
9
put_ BinHandle
bh (EvidenceVarBind EvVarSource
a Scope
b Maybe Span
c) = do
BinHandle -> Word8 -> IO ()
putByte BinHandle
bh Word8
10
BinHandle -> EvVarSource -> IO ()
forall a. Binary a => BinHandle -> a -> IO ()
Instance of class: Binary of the constraint type Binary EvVarSource
put_ BinHandle
bh EvVarSource
a
BinHandle -> Scope -> IO ()
forall a. Binary a => BinHandle -> a -> IO ()
Instance of class: Binary of the constraint type Binary Scope
put_ BinHandle
bh Scope
b
BinHandle -> Maybe Span -> IO ()
forall a. Binary a => BinHandle -> a -> IO ()
External instance of the constraint type forall a. Binary a => Binary (Maybe a)
External instance of the constraint type Binary Span
put_ BinHandle
bh Maybe Span
c
put_ BinHandle
bh ContextInfo
EvidenceVarUse = BinHandle -> Word8 -> IO ()
putByte BinHandle
bh Word8
11
get :: BinHandle -> IO ContextInfo
get BinHandle
bh = do
(Word8
t :: Word8) <- BinHandle -> IO Word8
forall a. Binary a => BinHandle -> IO a
External instance of the constraint type Binary Word8
get BinHandle
bh
case Word8
t of
Word8
0 -> ContextInfo -> IO ContextInfo
forall (m :: * -> *) a. Monad m => a -> m a
External instance of the constraint type Monad IO
return ContextInfo
Use
Word8
1 -> IEType -> ContextInfo
IEThing (IEType -> ContextInfo) -> IO IEType -> IO ContextInfo
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
External instance of the constraint type Functor IO
<$> BinHandle -> IO IEType
forall a. Binary a => BinHandle -> IO a
Instance of class: Binary of the constraint type Binary IEType
get BinHandle
bh
Word8
2 -> ContextInfo -> IO ContextInfo
forall (m :: * -> *) a. Monad m => a -> m a
External instance of the constraint type Monad IO
return ContextInfo
TyDecl
Word8
3 -> BindType -> Scope -> Maybe Span -> ContextInfo
ValBind (BindType -> Scope -> Maybe Span -> ContextInfo)
-> IO BindType -> IO (Scope -> Maybe Span -> ContextInfo)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
External instance of the constraint type Functor IO
<$> BinHandle -> IO BindType
forall a. Binary a => BinHandle -> IO a
Instance of class: Binary of the constraint type Binary BindType
get BinHandle
bh IO (Scope -> Maybe Span -> ContextInfo)
-> IO Scope -> IO (Maybe Span -> ContextInfo)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
External instance of the constraint type Applicative IO
<*> BinHandle -> IO Scope
forall a. Binary a => BinHandle -> IO a
Instance of class: Binary of the constraint type Binary Scope
get BinHandle
bh IO (Maybe Span -> ContextInfo) -> IO (Maybe Span) -> IO ContextInfo
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
External instance of the constraint type Applicative IO
<*> BinHandle -> IO (Maybe Span)
forall a. Binary a => BinHandle -> IO a
External instance of the constraint type forall a. Binary a => Binary (Maybe a)
External instance of the constraint type Binary Span
get BinHandle
bh
Word8
4 -> Scope -> Scope -> Maybe Span -> ContextInfo
PatternBind (Scope -> Scope -> Maybe Span -> ContextInfo)
-> IO Scope -> IO (Scope -> Maybe Span -> ContextInfo)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
External instance of the constraint type Functor IO
<$> BinHandle -> IO Scope
forall a. Binary a => BinHandle -> IO a
Instance of class: Binary of the constraint type Binary Scope
get BinHandle
bh IO (Scope -> Maybe Span -> ContextInfo)
-> IO Scope -> IO (Maybe Span -> ContextInfo)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
External instance of the constraint type Applicative IO
<*> BinHandle -> IO Scope
forall a. Binary a => BinHandle -> IO a
Instance of class: Binary of the constraint type Binary Scope
get BinHandle
bh IO (Maybe Span -> ContextInfo) -> IO (Maybe Span) -> IO ContextInfo
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
External instance of the constraint type Applicative IO
<*> BinHandle -> IO (Maybe Span)
forall a. Binary a => BinHandle -> IO a
External instance of the constraint type forall a. Binary a => Binary (Maybe a)
External instance of the constraint type Binary Span
get BinHandle
bh
Word8
5 -> Maybe Span -> ContextInfo
ClassTyDecl (Maybe Span -> ContextInfo) -> IO (Maybe Span) -> IO ContextInfo
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
External instance of the constraint type Functor IO
<$> BinHandle -> IO (Maybe Span)
forall a. Binary a => BinHandle -> IO a
External instance of the constraint type forall a. Binary a => Binary (Maybe a)
External instance of the constraint type Binary Span
get BinHandle
bh
Word8
6 -> DeclType -> Maybe Span -> ContextInfo
Decl (DeclType -> Maybe Span -> ContextInfo)
-> IO DeclType -> IO (Maybe Span -> ContextInfo)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
External instance of the constraint type Functor IO
<$> BinHandle -> IO DeclType
forall a. Binary a => BinHandle -> IO a
Instance of class: Binary of the constraint type Binary DeclType
get BinHandle
bh IO (Maybe Span -> ContextInfo) -> IO (Maybe Span) -> IO ContextInfo
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
External instance of the constraint type Applicative IO
<*> BinHandle -> IO (Maybe Span)
forall a. Binary a => BinHandle -> IO a
External instance of the constraint type forall a. Binary a => Binary (Maybe a)
External instance of the constraint type Binary Span
get BinHandle
bh
Word8
7 -> Scope -> TyVarScope -> ContextInfo
TyVarBind (Scope -> TyVarScope -> ContextInfo)
-> IO Scope -> IO (TyVarScope -> ContextInfo)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
External instance of the constraint type Functor IO
<$> BinHandle -> IO Scope
forall a. Binary a => BinHandle -> IO a
Instance of class: Binary of the constraint type Binary Scope
get BinHandle
bh IO (TyVarScope -> ContextInfo) -> IO TyVarScope -> IO ContextInfo
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
External instance of the constraint type Applicative IO
<*> BinHandle -> IO TyVarScope
forall a. Binary a => BinHandle -> IO a
Instance of class: Binary of the constraint type Binary TyVarScope
get BinHandle
bh
Word8
8 -> RecFieldContext -> Maybe Span -> ContextInfo
RecField (RecFieldContext -> Maybe Span -> ContextInfo)
-> IO RecFieldContext -> IO (Maybe Span -> ContextInfo)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
External instance of the constraint type Functor IO
<$> BinHandle -> IO RecFieldContext
forall a. Binary a => BinHandle -> IO a
Instance of class: Binary of the constraint type Binary RecFieldContext
get BinHandle
bh IO (Maybe Span -> ContextInfo) -> IO (Maybe Span) -> IO ContextInfo
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
External instance of the constraint type Applicative IO
<*> BinHandle -> IO (Maybe Span)
forall a. Binary a => BinHandle -> IO a
External instance of the constraint type forall a. Binary a => Binary (Maybe a)
External instance of the constraint type Binary Span
get BinHandle
bh
Word8
9 -> ContextInfo -> IO ContextInfo
forall (m :: * -> *) a. Monad m => a -> m a
External instance of the constraint type Monad IO
return ContextInfo
MatchBind
Word8
10 -> EvVarSource -> Scope -> Maybe Span -> ContextInfo
EvidenceVarBind (EvVarSource -> Scope -> Maybe Span -> ContextInfo)
-> IO EvVarSource -> IO (Scope -> Maybe Span -> ContextInfo)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
External instance of the constraint type Functor IO
<$> BinHandle -> IO EvVarSource
forall a. Binary a => BinHandle -> IO a
Instance of class: Binary of the constraint type Binary EvVarSource
get BinHandle
bh IO (Scope -> Maybe Span -> ContextInfo)
-> IO Scope -> IO (Maybe Span -> ContextInfo)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
External instance of the constraint type Applicative IO
<*> BinHandle -> IO Scope
forall a. Binary a => BinHandle -> IO a
Instance of class: Binary of the constraint type Binary Scope
get BinHandle
bh IO (Maybe Span -> ContextInfo) -> IO (Maybe Span) -> IO ContextInfo
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
External instance of the constraint type Applicative IO
<*> BinHandle -> IO (Maybe Span)
forall a. Binary a => BinHandle -> IO a
External instance of the constraint type forall a. Binary a => Binary (Maybe a)
External instance of the constraint type Binary Span
get BinHandle
bh
Word8
11 -> ContextInfo -> IO ContextInfo
forall (m :: * -> *) a. Monad m => a -> m a
External instance of the constraint type Monad IO
return ContextInfo
EvidenceVarUse
Word8
_ -> String -> IO ContextInfo
forall a. String -> a
panic String
"Binary ContextInfo: invalid tag"
data EvVarSource
= EvPatternBind
| EvSigBind
| EvWrapperBind
| EvImplicitBind
| EvInstBind { EvVarSource -> Bool
isSuperInst :: Bool, EvVarSource -> Name
cls :: Name }
| EvLetBind EvBindDeps
deriving (EvVarSource -> EvVarSource -> Bool
(EvVarSource -> EvVarSource -> Bool)
-> (EvVarSource -> EvVarSource -> Bool) -> Eq EvVarSource
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: EvVarSource -> EvVarSource -> Bool
$c/= :: EvVarSource -> EvVarSource -> Bool
== :: EvVarSource -> EvVarSource -> Bool
$c== :: EvVarSource -> EvVarSource -> Bool
External instance of the constraint type Eq Bool
External instance of the constraint type Eq Name
Instance of class: Eq of the constraint type Eq EvBindDeps
Eq,Eq EvVarSource
Eq EvVarSource
-> (EvVarSource -> EvVarSource -> Ordering)
-> (EvVarSource -> EvVarSource -> Bool)
-> (EvVarSource -> EvVarSource -> Bool)
-> (EvVarSource -> EvVarSource -> Bool)
-> (EvVarSource -> EvVarSource -> Bool)
-> (EvVarSource -> EvVarSource -> EvVarSource)
-> (EvVarSource -> EvVarSource -> EvVarSource)
-> Ord EvVarSource
EvVarSource -> EvVarSource -> Bool
EvVarSource -> EvVarSource -> Ordering
EvVarSource -> EvVarSource -> EvVarSource
forall a.
Eq a
-> (a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
min :: EvVarSource -> EvVarSource -> EvVarSource
$cmin :: EvVarSource -> EvVarSource -> EvVarSource
max :: EvVarSource -> EvVarSource -> EvVarSource
$cmax :: EvVarSource -> EvVarSource -> EvVarSource
>= :: EvVarSource -> EvVarSource -> Bool
$c>= :: EvVarSource -> EvVarSource -> Bool
> :: EvVarSource -> EvVarSource -> Bool
$c> :: EvVarSource -> EvVarSource -> Bool
<= :: EvVarSource -> EvVarSource -> Bool
$c<= :: EvVarSource -> EvVarSource -> Bool
< :: EvVarSource -> EvVarSource -> Bool
$c< :: EvVarSource -> EvVarSource -> Bool
compare :: EvVarSource -> EvVarSource -> Ordering
$ccompare :: EvVarSource -> EvVarSource -> Ordering
External instance of the constraint type Ord Bool
Instance of class: Eq of the constraint type Eq EvVarSource
External instance of the constraint type Ord Name
Instance of class: Ord of the constraint type Ord EvBindDeps
Instance of class: Eq of the constraint type Eq EvVarSource
Ord)
instance Binary EvVarSource where
put_ :: BinHandle -> EvVarSource -> IO ()
put_ BinHandle
bh EvVarSource
EvPatternBind = BinHandle -> Word8 -> IO ()
putByte BinHandle
bh Word8
0
put_ BinHandle
bh EvVarSource
EvSigBind = BinHandle -> Word8 -> IO ()
putByte BinHandle
bh Word8
1
put_ BinHandle
bh EvVarSource
EvWrapperBind = BinHandle -> Word8 -> IO ()
putByte BinHandle
bh Word8
2
put_ BinHandle
bh EvVarSource
EvImplicitBind = BinHandle -> Word8 -> IO ()
putByte BinHandle
bh Word8
3
put_ BinHandle
bh (EvInstBind Bool
b Name
cls) = do
BinHandle -> Word8 -> IO ()
putByte BinHandle
bh Word8
4
BinHandle -> Bool -> IO ()
forall a. Binary a => BinHandle -> a -> IO ()
External instance of the constraint type Binary Bool
put_ BinHandle
bh Bool
b
BinHandle -> Name -> IO ()
forall a. Binary a => BinHandle -> a -> IO ()
External instance of the constraint type Binary Name
put_ BinHandle
bh Name
cls
put_ BinHandle
bh (EvLetBind EvBindDeps
deps) = do
BinHandle -> Word8 -> IO ()
putByte BinHandle
bh Word8
5
BinHandle -> EvBindDeps -> IO ()
forall a. Binary a => BinHandle -> a -> IO ()
Instance of class: Binary of the constraint type Binary EvBindDeps
put_ BinHandle
bh EvBindDeps
deps
get :: BinHandle -> IO EvVarSource
get BinHandle
bh = do
(Word8
t :: Word8) <- BinHandle -> IO Word8
forall a. Binary a => BinHandle -> IO a
External instance of the constraint type Binary Word8
get BinHandle
bh
case Word8
t of
Word8
0 -> EvVarSource -> IO EvVarSource
forall (f :: * -> *) a. Applicative f => a -> f a
External instance of the constraint type Applicative IO
pure EvVarSource
EvPatternBind
Word8
1 -> EvVarSource -> IO EvVarSource
forall (f :: * -> *) a. Applicative f => a -> f a
External instance of the constraint type Applicative IO
pure EvVarSource
EvSigBind
Word8
2 -> EvVarSource -> IO EvVarSource
forall (f :: * -> *) a. Applicative f => a -> f a
External instance of the constraint type Applicative IO
pure EvVarSource
EvWrapperBind
Word8
3 -> EvVarSource -> IO EvVarSource
forall (f :: * -> *) a. Applicative f => a -> f a
External instance of the constraint type Applicative IO
pure EvVarSource
EvImplicitBind
Word8
4 -> Bool -> Name -> EvVarSource
EvInstBind (Bool -> Name -> EvVarSource)
-> IO Bool -> IO (Name -> EvVarSource)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
External instance of the constraint type Functor IO
<$> BinHandle -> IO Bool
forall a. Binary a => BinHandle -> IO a
External instance of the constraint type Binary Bool
get BinHandle
bh IO (Name -> EvVarSource) -> IO Name -> IO EvVarSource
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
External instance of the constraint type Applicative IO
<*> BinHandle -> IO Name
forall a. Binary a => BinHandle -> IO a
External instance of the constraint type Binary Name
get BinHandle
bh
Word8
5 -> EvBindDeps -> EvVarSource
EvLetBind (EvBindDeps -> EvVarSource) -> IO EvBindDeps -> IO EvVarSource
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
External instance of the constraint type Functor IO
<$> BinHandle -> IO EvBindDeps
forall a. Binary a => BinHandle -> IO a
Instance of class: Binary of the constraint type Binary EvBindDeps
get BinHandle
bh
Word8
_ -> String -> IO EvVarSource
forall a. String -> a
panic String
"Binary EvVarSource: invalid tag"
instance Outputable EvVarSource where
ppr :: EvVarSource -> SDoc
ppr EvVarSource
EvPatternBind = String -> SDoc
text String
"bound by a pattern"
ppr EvVarSource
EvSigBind = String -> SDoc
text String
"bound by a type signature"
ppr EvVarSource
EvWrapperBind = String -> SDoc
text String
"bound by a HsWrapper"
ppr EvVarSource
EvImplicitBind = String -> SDoc
text String
"bound by an implicit variable binding"
ppr (EvInstBind Bool
False Name
cls) = String -> SDoc
text String
"bound by an instance of class" SDoc -> SDoc -> SDoc
<+> Name -> SDoc
forall a. Outputable a => a -> SDoc
External instance of the constraint type Outputable Name
ppr Name
cls
ppr (EvInstBind Bool
True Name
cls) = String -> SDoc
text String
"bound due to a superclass of " SDoc -> SDoc -> SDoc
<+> Name -> SDoc
forall a. Outputable a => a -> SDoc
External instance of the constraint type Outputable Name
ppr Name
cls
ppr (EvLetBind EvBindDeps
deps) = String -> SDoc
text String
"bound by a let, depending on:" SDoc -> SDoc -> SDoc
<+> EvBindDeps -> SDoc
forall a. Outputable a => a -> SDoc
Instance of class: Outputable of the constraint type Outputable EvBindDeps
ppr EvBindDeps
deps
newtype EvBindDeps = EvBindDeps { EvBindDeps -> [Name]
getEvBindDeps :: [Name] }
deriving Rational -> EvBindDeps -> SDoc
EvBindDeps -> SDoc
(EvBindDeps -> SDoc)
-> (Rational -> EvBindDeps -> SDoc) -> Outputable EvBindDeps
forall a. (a -> SDoc) -> (Rational -> a -> SDoc) -> Outputable a
pprPrec :: Rational -> EvBindDeps -> SDoc
$cpprPrec :: Rational -> EvBindDeps -> SDoc
ppr :: EvBindDeps -> SDoc
$cppr :: EvBindDeps -> SDoc
External instance of the constraint type forall a. Outputable a => Outputable [a]
External instance of the constraint type Outputable Name
Outputable
instance Eq EvBindDeps where
== :: EvBindDeps -> EvBindDeps -> Bool
(==) = ([Name] -> [Name] -> Bool) -> EvBindDeps -> EvBindDeps -> Bool
coerce ([HieName] -> [HieName] -> Bool
forall a. Eq a => a -> a -> Bool
External instance of the constraint type forall a. Eq a => Eq [a]
Instance of class: Eq of the constraint type Eq HieName
(==) ([HieName] -> [HieName] -> Bool)
-> ([Name] -> [HieName]) -> [Name] -> [Name] -> Bool
forall b c a. (b -> b -> c) -> (a -> b) -> a -> a -> c
`on` (Name -> HieName) -> [Name] -> [HieName]
forall a b. (a -> b) -> [a] -> [b]
map Name -> HieName
toHieName)
instance Ord EvBindDeps where
compare :: EvBindDeps -> EvBindDeps -> Ordering
compare = ([Name] -> [Name] -> Ordering)
-> EvBindDeps -> EvBindDeps -> Ordering
coerce ([HieName] -> [HieName] -> Ordering
forall a. Ord a => a -> a -> Ordering
External instance of the constraint type forall a. Ord a => Ord [a]
Instance of class: Ord of the constraint type Ord HieName
compare ([HieName] -> [HieName] -> Ordering)
-> ([Name] -> [HieName]) -> [Name] -> [Name] -> Ordering
forall b c a. (b -> b -> c) -> (a -> b) -> a -> a -> c
`on` (Name -> HieName) -> [Name] -> [HieName]
forall a b. (a -> b) -> [a] -> [b]
map Name -> HieName
toHieName)
instance Binary EvBindDeps where
put_ :: BinHandle -> EvBindDeps -> IO ()
put_ BinHandle
bh (EvBindDeps [Name]
xs) = BinHandle -> [Name] -> IO ()
forall a. Binary a => BinHandle -> a -> IO ()
External instance of the constraint type forall a. Binary a => Binary [a]
External instance of the constraint type Binary Name
put_ BinHandle
bh [Name]
xs
get :: BinHandle -> IO EvBindDeps
get BinHandle
bh = [Name] -> EvBindDeps
EvBindDeps ([Name] -> EvBindDeps) -> IO [Name] -> IO EvBindDeps
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
External instance of the constraint type Functor IO
<$> BinHandle -> IO [Name]
forall a. Binary a => BinHandle -> IO a
External instance of the constraint type forall a. Binary a => Binary [a]
External instance of the constraint type Binary Name
get BinHandle
bh
data IEType
= Import
| ImportAs
| ImportHiding
| Export
deriving (IEType -> IEType -> Bool
(IEType -> IEType -> Bool)
-> (IEType -> IEType -> Bool) -> Eq IEType
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: IEType -> IEType -> Bool
$c/= :: IEType -> IEType -> Bool
== :: IEType -> IEType -> Bool
$c== :: IEType -> IEType -> Bool
Eq, TypeIndex -> IEType
IEType -> TypeIndex
IEType -> [IEType]
IEType -> IEType
IEType -> IEType -> [IEType]
IEType -> IEType -> IEType -> [IEType]
(IEType -> IEType)
-> (IEType -> IEType)
-> (TypeIndex -> IEType)
-> (IEType -> TypeIndex)
-> (IEType -> [IEType])
-> (IEType -> IEType -> [IEType])
-> (IEType -> IEType -> [IEType])
-> (IEType -> IEType -> IEType -> [IEType])
-> Enum IEType
forall a.
(a -> a)
-> (a -> a)
-> (TypeIndex -> a)
-> (a -> TypeIndex)
-> (a -> [a])
-> (a -> a -> [a])
-> (a -> a -> [a])
-> (a -> a -> a -> [a])
-> Enum a
enumFromThenTo :: IEType -> IEType -> IEType -> [IEType]
$cenumFromThenTo :: IEType -> IEType -> IEType -> [IEType]
enumFromTo :: IEType -> IEType -> [IEType]
$cenumFromTo :: IEType -> IEType -> [IEType]
enumFromThen :: IEType -> IEType -> [IEType]
$cenumFromThen :: IEType -> IEType -> [IEType]
enumFrom :: IEType -> [IEType]
$cenumFrom :: IEType -> [IEType]
fromEnum :: IEType -> TypeIndex
$cfromEnum :: IEType -> TypeIndex
toEnum :: TypeIndex -> IEType
$ctoEnum :: TypeIndex -> IEType
pred :: IEType -> IEType
$cpred :: IEType -> IEType
succ :: IEType -> IEType
$csucc :: IEType -> IEType
External instance of the constraint type Show TypeIndex
External instance of the constraint type forall a. (a ~ Char) => IsString [a]
External instance of the constraint type Ord TypeIndex
External instance of the constraint type Enum TypeIndex
External instance of the constraint type Show TypeIndex
External instance of the constraint type forall a. (a ~ Char) => IsString [a]
External instance of the constraint type Ord TypeIndex
External instance of the constraint type Num TypeIndex
External instance of the constraint type Eq TypeIndex
Enum, Eq IEType
Eq IEType
-> (IEType -> IEType -> Ordering)
-> (IEType -> IEType -> Bool)
-> (IEType -> IEType -> Bool)
-> (IEType -> IEType -> Bool)
-> (IEType -> IEType -> Bool)
-> (IEType -> IEType -> IEType)
-> (IEType -> IEType -> IEType)
-> Ord IEType
IEType -> IEType -> Bool
IEType -> IEType -> Ordering
IEType -> IEType -> IEType
forall a.
Eq a
-> (a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
min :: IEType -> IEType -> IEType
$cmin :: IEType -> IEType -> IEType
max :: IEType -> IEType -> IEType
$cmax :: IEType -> IEType -> IEType
>= :: IEType -> IEType -> Bool
$c>= :: IEType -> IEType -> Bool
> :: IEType -> IEType -> Bool
$c> :: IEType -> IEType -> Bool
<= :: IEType -> IEType -> Bool
$c<= :: IEType -> IEType -> Bool
< :: IEType -> IEType -> Bool
$c< :: IEType -> IEType -> Bool
compare :: IEType -> IEType -> Ordering
$ccompare :: IEType -> IEType -> Ordering
Instance of class: Eq of the constraint type Eq IEType
Instance of class: Ord of the constraint type Ord IEType
Instance of class: Eq of the constraint type Eq IEType
Ord)
instance Outputable IEType where
ppr :: IEType -> SDoc
ppr IEType
Import = String -> SDoc
text String
"import"
ppr IEType
ImportAs = String -> SDoc
text String
"import as"
ppr IEType
ImportHiding = String -> SDoc
text String
"import hiding"
ppr IEType
Export = String -> SDoc
text String
"export"
instance Binary IEType where
put_ :: BinHandle -> IEType -> IO ()
put_ BinHandle
bh IEType
b = BinHandle -> Word8 -> IO ()
putByte BinHandle
bh (TypeIndex -> Word8
forall a b. (Integral a, Num b) => a -> b
External instance of the constraint type Num Word8
External instance of the constraint type Integral TypeIndex
fromIntegral (IEType -> TypeIndex
forall a. Enum a => a -> TypeIndex
Instance of class: Enum of the constraint type Enum IEType
fromEnum IEType
b))
get :: BinHandle -> IO IEType
get BinHandle
bh = do Word8
x <- BinHandle -> IO Word8
getByte BinHandle
bh; IEType -> IO IEType
forall (f :: * -> *) a. Applicative f => a -> f a
External instance of the constraint type Applicative IO
pure (IEType -> IO IEType) -> IEType -> IO IEType
forall a b. (a -> b) -> a -> b
$! (TypeIndex -> IEType
forall a. Enum a => TypeIndex -> a
Instance of class: Enum of the constraint type Enum IEType
toEnum (Word8 -> TypeIndex
forall a b. (Integral a, Num b) => a -> b
External instance of the constraint type Num TypeIndex
External instance of the constraint type Integral Word8
fromIntegral Word8
x))
data RecFieldContext
= RecFieldDecl
| RecFieldAssign
| RecFieldMatch
| RecFieldOcc
deriving (RecFieldContext -> RecFieldContext -> Bool
(RecFieldContext -> RecFieldContext -> Bool)
-> (RecFieldContext -> RecFieldContext -> Bool)
-> Eq RecFieldContext
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: RecFieldContext -> RecFieldContext -> Bool
$c/= :: RecFieldContext -> RecFieldContext -> Bool
== :: RecFieldContext -> RecFieldContext -> Bool
$c== :: RecFieldContext -> RecFieldContext -> Bool
Eq, TypeIndex -> RecFieldContext
RecFieldContext -> TypeIndex
RecFieldContext -> [RecFieldContext]
RecFieldContext -> RecFieldContext
RecFieldContext -> RecFieldContext -> [RecFieldContext]
RecFieldContext
-> RecFieldContext -> RecFieldContext -> [RecFieldContext]
(RecFieldContext -> RecFieldContext)
-> (RecFieldContext -> RecFieldContext)
-> (TypeIndex -> RecFieldContext)
-> (RecFieldContext -> TypeIndex)
-> (RecFieldContext -> [RecFieldContext])
-> (RecFieldContext -> RecFieldContext -> [RecFieldContext])
-> (RecFieldContext -> RecFieldContext -> [RecFieldContext])
-> (RecFieldContext
-> RecFieldContext -> RecFieldContext -> [RecFieldContext])
-> Enum RecFieldContext
forall a.
(a -> a)
-> (a -> a)
-> (TypeIndex -> a)
-> (a -> TypeIndex)
-> (a -> [a])
-> (a -> a -> [a])
-> (a -> a -> [a])
-> (a -> a -> a -> [a])
-> Enum a
enumFromThenTo :: RecFieldContext
-> RecFieldContext -> RecFieldContext -> [RecFieldContext]
$cenumFromThenTo :: RecFieldContext
-> RecFieldContext -> RecFieldContext -> [RecFieldContext]
enumFromTo :: RecFieldContext -> RecFieldContext -> [RecFieldContext]
$cenumFromTo :: RecFieldContext -> RecFieldContext -> [RecFieldContext]
enumFromThen :: RecFieldContext -> RecFieldContext -> [RecFieldContext]
$cenumFromThen :: RecFieldContext -> RecFieldContext -> [RecFieldContext]
enumFrom :: RecFieldContext -> [RecFieldContext]
$cenumFrom :: RecFieldContext -> [RecFieldContext]
fromEnum :: RecFieldContext -> TypeIndex
$cfromEnum :: RecFieldContext -> TypeIndex
toEnum :: TypeIndex -> RecFieldContext
$ctoEnum :: TypeIndex -> RecFieldContext
pred :: RecFieldContext -> RecFieldContext
$cpred :: RecFieldContext -> RecFieldContext
succ :: RecFieldContext -> RecFieldContext
$csucc :: RecFieldContext -> RecFieldContext
External instance of the constraint type Show TypeIndex
External instance of the constraint type forall a. (a ~ Char) => IsString [a]
External instance of the constraint type Ord TypeIndex
External instance of the constraint type Enum TypeIndex
External instance of the constraint type Show TypeIndex
External instance of the constraint type forall a. (a ~ Char) => IsString [a]
External instance of the constraint type Ord TypeIndex
External instance of the constraint type Num TypeIndex
External instance of the constraint type Eq TypeIndex
Enum, Eq RecFieldContext
Eq RecFieldContext
-> (RecFieldContext -> RecFieldContext -> Ordering)
-> (RecFieldContext -> RecFieldContext -> Bool)
-> (RecFieldContext -> RecFieldContext -> Bool)
-> (RecFieldContext -> RecFieldContext -> Bool)
-> (RecFieldContext -> RecFieldContext -> Bool)
-> (RecFieldContext -> RecFieldContext -> RecFieldContext)
-> (RecFieldContext -> RecFieldContext -> RecFieldContext)
-> Ord RecFieldContext
RecFieldContext -> RecFieldContext -> Bool
RecFieldContext -> RecFieldContext -> Ordering
RecFieldContext -> RecFieldContext -> RecFieldContext
forall a.
Eq a
-> (a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
min :: RecFieldContext -> RecFieldContext -> RecFieldContext
$cmin :: RecFieldContext -> RecFieldContext -> RecFieldContext
max :: RecFieldContext -> RecFieldContext -> RecFieldContext
$cmax :: RecFieldContext -> RecFieldContext -> RecFieldContext
>= :: RecFieldContext -> RecFieldContext -> Bool
$c>= :: RecFieldContext -> RecFieldContext -> Bool
> :: RecFieldContext -> RecFieldContext -> Bool
$c> :: RecFieldContext -> RecFieldContext -> Bool
<= :: RecFieldContext -> RecFieldContext -> Bool
$c<= :: RecFieldContext -> RecFieldContext -> Bool
< :: RecFieldContext -> RecFieldContext -> Bool
$c< :: RecFieldContext -> RecFieldContext -> Bool
compare :: RecFieldContext -> RecFieldContext -> Ordering
$ccompare :: RecFieldContext -> RecFieldContext -> Ordering
Instance of class: Eq of the constraint type Eq RecFieldContext
Instance of class: Ord of the constraint type Ord RecFieldContext
Instance of class: Eq of the constraint type Eq RecFieldContext
Ord)
instance Outputable RecFieldContext where
ppr :: RecFieldContext -> SDoc
ppr RecFieldContext
RecFieldDecl = String -> SDoc
text String
"declaration"
ppr RecFieldContext
RecFieldAssign = String -> SDoc
text String
"assignment"
ppr RecFieldContext
RecFieldMatch = String -> SDoc
text String
"pattern match"
ppr RecFieldContext
RecFieldOcc = String -> SDoc
text String
"occurence"
instance Binary RecFieldContext where
put_ :: BinHandle -> RecFieldContext -> IO ()
put_ BinHandle
bh RecFieldContext
b = BinHandle -> Word8 -> IO ()
putByte BinHandle
bh (TypeIndex -> Word8
forall a b. (Integral a, Num b) => a -> b
External instance of the constraint type Num Word8
External instance of the constraint type Integral TypeIndex
fromIntegral (RecFieldContext -> TypeIndex
forall a. Enum a => a -> TypeIndex
Instance of class: Enum of the constraint type Enum RecFieldContext
fromEnum RecFieldContext
b))
get :: BinHandle -> IO RecFieldContext
get BinHandle
bh = do Word8
x <- BinHandle -> IO Word8
getByte BinHandle
bh; RecFieldContext -> IO RecFieldContext
forall (f :: * -> *) a. Applicative f => a -> f a
External instance of the constraint type Applicative IO
pure (RecFieldContext -> IO RecFieldContext)
-> RecFieldContext -> IO RecFieldContext
forall a b. (a -> b) -> a -> b
$! (TypeIndex -> RecFieldContext
forall a. Enum a => TypeIndex -> a
Instance of class: Enum of the constraint type Enum RecFieldContext
toEnum (Word8 -> TypeIndex
forall a b. (Integral a, Num b) => a -> b
External instance of the constraint type Num TypeIndex
External instance of the constraint type Integral Word8
fromIntegral Word8
x))
data BindType
= RegularBind
| InstanceBind
deriving (BindType -> BindType -> Bool
(BindType -> BindType -> Bool)
-> (BindType -> BindType -> Bool) -> Eq BindType
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: BindType -> BindType -> Bool
$c/= :: BindType -> BindType -> Bool
== :: BindType -> BindType -> Bool
$c== :: BindType -> BindType -> Bool
Eq, Eq BindType
Eq BindType
-> (BindType -> BindType -> Ordering)
-> (BindType -> BindType -> Bool)
-> (BindType -> BindType -> Bool)
-> (BindType -> BindType -> Bool)
-> (BindType -> BindType -> Bool)
-> (BindType -> BindType -> BindType)
-> (BindType -> BindType -> BindType)
-> Ord BindType
BindType -> BindType -> Bool
BindType -> BindType -> Ordering
BindType -> BindType -> BindType
forall a.
Eq a
-> (a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
min :: BindType -> BindType -> BindType
$cmin :: BindType -> BindType -> BindType
max :: BindType -> BindType -> BindType
$cmax :: BindType -> BindType -> BindType
>= :: BindType -> BindType -> Bool
$c>= :: BindType -> BindType -> Bool
> :: BindType -> BindType -> Bool
$c> :: BindType -> BindType -> Bool
<= :: BindType -> BindType -> Bool
$c<= :: BindType -> BindType -> Bool
< :: BindType -> BindType -> Bool
$c< :: BindType -> BindType -> Bool
compare :: BindType -> BindType -> Ordering
$ccompare :: BindType -> BindType -> Ordering
Instance of class: Eq of the constraint type Eq BindType
Instance of class: Ord of the constraint type Ord BindType
Instance of class: Eq of the constraint type Eq BindType
Ord, TypeIndex -> BindType
BindType -> TypeIndex
BindType -> [BindType]
BindType -> BindType
BindType -> BindType -> [BindType]
BindType -> BindType -> BindType -> [BindType]
(BindType -> BindType)
-> (BindType -> BindType)
-> (TypeIndex -> BindType)
-> (BindType -> TypeIndex)
-> (BindType -> [BindType])
-> (BindType -> BindType -> [BindType])
-> (BindType -> BindType -> [BindType])
-> (BindType -> BindType -> BindType -> [BindType])
-> Enum BindType
forall a.
(a -> a)
-> (a -> a)
-> (TypeIndex -> a)
-> (a -> TypeIndex)
-> (a -> [a])
-> (a -> a -> [a])
-> (a -> a -> [a])
-> (a -> a -> a -> [a])
-> Enum a
enumFromThenTo :: BindType -> BindType -> BindType -> [BindType]
$cenumFromThenTo :: BindType -> BindType -> BindType -> [BindType]
enumFromTo :: BindType -> BindType -> [BindType]
$cenumFromTo :: BindType -> BindType -> [BindType]
enumFromThen :: BindType -> BindType -> [BindType]
$cenumFromThen :: BindType -> BindType -> [BindType]
enumFrom :: BindType -> [BindType]
$cenumFrom :: BindType -> [BindType]
fromEnum :: BindType -> TypeIndex
$cfromEnum :: BindType -> TypeIndex
toEnum :: TypeIndex -> BindType
$ctoEnum :: TypeIndex -> BindType
pred :: BindType -> BindType
$cpred :: BindType -> BindType
succ :: BindType -> BindType
$csucc :: BindType -> BindType
External instance of the constraint type Show TypeIndex
External instance of the constraint type forall a. (a ~ Char) => IsString [a]
External instance of the constraint type Ord TypeIndex
External instance of the constraint type Enum TypeIndex
External instance of the constraint type Show TypeIndex
External instance of the constraint type forall a. (a ~ Char) => IsString [a]
External instance of the constraint type Ord TypeIndex
External instance of the constraint type Num TypeIndex
External instance of the constraint type Eq TypeIndex
Enum)
instance Outputable BindType where
ppr :: BindType -> SDoc
ppr BindType
RegularBind = SDoc
"regular"
ppr BindType
InstanceBind = SDoc
"instance"
instance Binary BindType where
put_ :: BinHandle -> BindType -> IO ()
put_ BinHandle
bh BindType
b = BinHandle -> Word8 -> IO ()
putByte BinHandle
bh (TypeIndex -> Word8
forall a b. (Integral a, Num b) => a -> b
External instance of the constraint type Num Word8
External instance of the constraint type Integral TypeIndex
fromIntegral (BindType -> TypeIndex
forall a. Enum a => a -> TypeIndex
Instance of class: Enum of the constraint type Enum BindType
fromEnum BindType
b))
get :: BinHandle -> IO BindType
get BinHandle
bh = do Word8
x <- BinHandle -> IO Word8
getByte BinHandle
bh; BindType -> IO BindType
forall (f :: * -> *) a. Applicative f => a -> f a
External instance of the constraint type Applicative IO
pure (BindType -> IO BindType) -> BindType -> IO BindType
forall a b. (a -> b) -> a -> b
$! (TypeIndex -> BindType
forall a. Enum a => TypeIndex -> a
Instance of class: Enum of the constraint type Enum BindType
toEnum (Word8 -> TypeIndex
forall a b. (Integral a, Num b) => a -> b
External instance of the constraint type Num TypeIndex
External instance of the constraint type Integral Word8
fromIntegral Word8
x))
data DeclType
= FamDec
| SynDec
| DataDec
| ConDec
| PatSynDec
| ClassDec
| InstDec
deriving (DeclType -> DeclType -> Bool
(DeclType -> DeclType -> Bool)
-> (DeclType -> DeclType -> Bool) -> Eq DeclType
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: DeclType -> DeclType -> Bool
$c/= :: DeclType -> DeclType -> Bool
== :: DeclType -> DeclType -> Bool
$c== :: DeclType -> DeclType -> Bool
Eq, Eq DeclType
Eq DeclType
-> (DeclType -> DeclType -> Ordering)
-> (DeclType -> DeclType -> Bool)
-> (DeclType -> DeclType -> Bool)
-> (DeclType -> DeclType -> Bool)
-> (DeclType -> DeclType -> Bool)
-> (DeclType -> DeclType -> DeclType)
-> (DeclType -> DeclType -> DeclType)
-> Ord DeclType
DeclType -> DeclType -> Bool
DeclType -> DeclType -> Ordering
DeclType -> DeclType -> DeclType
forall a.
Eq a
-> (a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
min :: DeclType -> DeclType -> DeclType
$cmin :: DeclType -> DeclType -> DeclType
max :: DeclType -> DeclType -> DeclType
$cmax :: DeclType -> DeclType -> DeclType
>= :: DeclType -> DeclType -> Bool
$c>= :: DeclType -> DeclType -> Bool
> :: DeclType -> DeclType -> Bool
$c> :: DeclType -> DeclType -> Bool
<= :: DeclType -> DeclType -> Bool
$c<= :: DeclType -> DeclType -> Bool
< :: DeclType -> DeclType -> Bool
$c< :: DeclType -> DeclType -> Bool
compare :: DeclType -> DeclType -> Ordering
$ccompare :: DeclType -> DeclType -> Ordering
Instance of class: Eq of the constraint type Eq DeclType
Instance of class: Ord of the constraint type Ord DeclType
Instance of class: Eq of the constraint type Eq DeclType
Ord, TypeIndex -> DeclType
DeclType -> TypeIndex
DeclType -> [DeclType]
DeclType -> DeclType
DeclType -> DeclType -> [DeclType]
DeclType -> DeclType -> DeclType -> [DeclType]
(DeclType -> DeclType)
-> (DeclType -> DeclType)
-> (TypeIndex -> DeclType)
-> (DeclType -> TypeIndex)
-> (DeclType -> [DeclType])
-> (DeclType -> DeclType -> [DeclType])
-> (DeclType -> DeclType -> [DeclType])
-> (DeclType -> DeclType -> DeclType -> [DeclType])
-> Enum DeclType
forall a.
(a -> a)
-> (a -> a)
-> (TypeIndex -> a)
-> (a -> TypeIndex)
-> (a -> [a])
-> (a -> a -> [a])
-> (a -> a -> [a])
-> (a -> a -> a -> [a])
-> Enum a
enumFromThenTo :: DeclType -> DeclType -> DeclType -> [DeclType]
$cenumFromThenTo :: DeclType -> DeclType -> DeclType -> [DeclType]
enumFromTo :: DeclType -> DeclType -> [DeclType]
$cenumFromTo :: DeclType -> DeclType -> [DeclType]
enumFromThen :: DeclType -> DeclType -> [DeclType]
$cenumFromThen :: DeclType -> DeclType -> [DeclType]
enumFrom :: DeclType -> [DeclType]
$cenumFrom :: DeclType -> [DeclType]
fromEnum :: DeclType -> TypeIndex
$cfromEnum :: DeclType -> TypeIndex
toEnum :: TypeIndex -> DeclType
$ctoEnum :: TypeIndex -> DeclType
pred :: DeclType -> DeclType
$cpred :: DeclType -> DeclType
succ :: DeclType -> DeclType
$csucc :: DeclType -> DeclType
External instance of the constraint type Show TypeIndex
External instance of the constraint type forall a. (a ~ Char) => IsString [a]
External instance of the constraint type Ord TypeIndex
External instance of the constraint type Enum TypeIndex
External instance of the constraint type Show TypeIndex
External instance of the constraint type forall a. (a ~ Char) => IsString [a]
External instance of the constraint type Ord TypeIndex
External instance of the constraint type Num TypeIndex
External instance of the constraint type Eq TypeIndex
Enum)
instance Outputable DeclType where
ppr :: DeclType -> SDoc
ppr DeclType
FamDec = String -> SDoc
text String
"type or data family"
ppr DeclType
SynDec = String -> SDoc
text String
"type synonym"
ppr DeclType
DataDec = String -> SDoc
text String
"data"
ppr DeclType
ConDec = String -> SDoc
text String
"constructor"
ppr DeclType
PatSynDec = String -> SDoc
text String
"pattern synonym"
ppr DeclType
ClassDec = String -> SDoc
text String
"class"
ppr DeclType
InstDec = String -> SDoc
text String
"instance"
instance Binary DeclType where
put_ :: BinHandle -> DeclType -> IO ()
put_ BinHandle
bh DeclType
b = BinHandle -> Word8 -> IO ()
putByte BinHandle
bh (TypeIndex -> Word8
forall a b. (Integral a, Num b) => a -> b
External instance of the constraint type Num Word8
External instance of the constraint type Integral TypeIndex
fromIntegral (DeclType -> TypeIndex
forall a. Enum a => a -> TypeIndex
Instance of class: Enum of the constraint type Enum DeclType
fromEnum DeclType
b))
get :: BinHandle -> IO DeclType
get BinHandle
bh = do Word8
x <- BinHandle -> IO Word8
getByte BinHandle
bh; DeclType -> IO DeclType
forall (f :: * -> *) a. Applicative f => a -> f a
External instance of the constraint type Applicative IO
pure (DeclType -> IO DeclType) -> DeclType -> IO DeclType
forall a b. (a -> b) -> a -> b
$! (TypeIndex -> DeclType
forall a. Enum a => TypeIndex -> a
Instance of class: Enum of the constraint type Enum DeclType
toEnum (Word8 -> TypeIndex
forall a b. (Integral a, Num b) => a -> b
External instance of the constraint type Num TypeIndex
External instance of the constraint type Integral Word8
fromIntegral Word8
x))
data Scope
= NoScope
| LocalScope Span
| ModuleScope
deriving (Scope -> Scope -> Bool
(Scope -> Scope -> Bool) -> (Scope -> Scope -> Bool) -> Eq Scope
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: Scope -> Scope -> Bool
$c/= :: Scope -> Scope -> Bool
== :: Scope -> Scope -> Bool
$c== :: Scope -> Scope -> Bool
External instance of the constraint type Eq Span
Eq, Eq Scope
Eq Scope
-> (Scope -> Scope -> Ordering)
-> (Scope -> Scope -> Bool)
-> (Scope -> Scope -> Bool)
-> (Scope -> Scope -> Bool)
-> (Scope -> Scope -> Bool)
-> (Scope -> Scope -> Scope)
-> (Scope -> Scope -> Scope)
-> Ord Scope
Scope -> Scope -> Bool
Scope -> Scope -> Ordering
Scope -> Scope -> Scope
forall a.
Eq a
-> (a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
min :: Scope -> Scope -> Scope
$cmin :: Scope -> Scope -> Scope
max :: Scope -> Scope -> Scope
$cmax :: Scope -> Scope -> Scope
>= :: Scope -> Scope -> Bool
$c>= :: Scope -> Scope -> Bool
> :: Scope -> Scope -> Bool
$c> :: Scope -> Scope -> Bool
<= :: Scope -> Scope -> Bool
$c<= :: Scope -> Scope -> Bool
< :: Scope -> Scope -> Bool
$c< :: Scope -> Scope -> Bool
compare :: Scope -> Scope -> Ordering
$ccompare :: Scope -> Scope -> Ordering
Instance of class: Eq of the constraint type Eq Scope
External instance of the constraint type Ord Span
Instance of class: Ord of the constraint type Ord Scope
Instance of class: Eq of the constraint type Eq Scope
Ord, Typeable, Typeable Scope
DataType
Constr
Typeable Scope
-> (forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> Scope -> c Scope)
-> (forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c Scope)
-> (Scope -> Constr)
-> (Scope -> DataType)
-> (forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c Scope))
-> (forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Scope))
-> ((forall b. Data b => b -> b) -> Scope -> Scope)
-> (forall r r'.
(r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Scope -> r)
-> (forall r r'.
(r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Scope -> r)
-> (forall u. (forall d. Data d => d -> u) -> Scope -> [u])
-> (forall u.
TypeIndex -> (forall d. Data d => d -> u) -> Scope -> u)
-> (forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> Scope -> m Scope)
-> (forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> Scope -> m Scope)
-> (forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> Scope -> m Scope)
-> Data Scope
Scope -> DataType
Scope -> Constr
(forall b. Data b => b -> b) -> Scope -> Scope
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> Scope -> c Scope
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c Scope
forall a.
Typeable a
-> (forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> a -> c a)
-> (forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c a)
-> (a -> Constr)
-> (a -> DataType)
-> (forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c a))
-> (forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c a))
-> ((forall b. Data b => b -> b) -> a -> a)
-> (forall r r'.
(r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> a -> r)
-> (forall r r'.
(r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> a -> r)
-> (forall u. (forall d. Data d => d -> u) -> a -> [u])
-> (forall u. TypeIndex -> (forall d. Data d => d -> u) -> a -> u)
-> (forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> a -> m a)
-> (forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> a -> m a)
-> (forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> a -> m a)
-> Data a
forall u. TypeIndex -> (forall d. Data d => d -> u) -> Scope -> u
forall u. (forall d. Data d => d -> u) -> Scope -> [u]
forall r r'.
(r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Scope -> r
forall r r'.
(r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Scope -> r
forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> Scope -> m Scope
forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> Scope -> m Scope
forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c Scope
forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> Scope -> c Scope
forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c Scope)
forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Scope)
$cModuleScope :: Constr
$cLocalScope :: Constr
$cNoScope :: Constr
$tScope :: DataType
gmapMo :: (forall d. Data d => d -> m d) -> Scope -> m Scope
$cgmapMo :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> Scope -> m Scope
gmapMp :: (forall d. Data d => d -> m d) -> Scope -> m Scope
$cgmapMp :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> Scope -> m Scope
gmapM :: (forall d. Data d => d -> m d) -> Scope -> m Scope
$cgmapM :: forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> Scope -> m Scope
gmapQi :: TypeIndex -> (forall d. Data d => d -> u) -> Scope -> u
$cgmapQi :: forall u. TypeIndex -> (forall d. Data d => d -> u) -> Scope -> u
gmapQ :: (forall d. Data d => d -> u) -> Scope -> [u]
$cgmapQ :: forall u. (forall d. Data d => d -> u) -> Scope -> [u]
gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Scope -> r
$cgmapQr :: forall r r'.
(r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Scope -> r
gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Scope -> r
$cgmapQl :: forall r r'.
(r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Scope -> r
gmapT :: (forall b. Data b => b -> b) -> Scope -> Scope
$cgmapT :: (forall b. Data b => b -> b) -> Scope -> Scope
dataCast2 :: (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Scope)
$cdataCast2 :: forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Scope)
dataCast1 :: (forall d. Data d => c (t d)) -> Maybe (c Scope)
$cdataCast1 :: forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c Scope)
dataTypeOf :: Scope -> DataType
$cdataTypeOf :: Scope -> DataType
toConstr :: Scope -> Constr
$ctoConstr :: Scope -> Constr
gunfold :: (forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c Scope
$cgunfold :: forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c Scope
gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> Scope -> c Scope
$cgfoldl :: forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> Scope -> c Scope
External instance of the constraint type Data Span
Data)
instance Outputable Scope where
ppr :: Scope -> SDoc
ppr Scope
NoScope = String -> SDoc
text String
"NoScope"
ppr (LocalScope Span
sp) = String -> SDoc
text String
"LocalScope" SDoc -> SDoc -> SDoc
<+> Span -> SDoc
forall a. Outputable a => a -> SDoc
External instance of the constraint type Outputable Span
ppr Span
sp
ppr Scope
ModuleScope = String -> SDoc
text String
"ModuleScope"
instance Binary Scope where
put_ :: BinHandle -> Scope -> IO ()
put_ BinHandle
bh Scope
NoScope = BinHandle -> Word8 -> IO ()
putByte BinHandle
bh Word8
0
put_ BinHandle
bh (LocalScope Span
span) = do
BinHandle -> Word8 -> IO ()
putByte BinHandle
bh Word8
1
BinHandle -> Span -> IO ()
forall a. Binary a => BinHandle -> a -> IO ()
External instance of the constraint type Binary Span
put_ BinHandle
bh Span
span
put_ BinHandle
bh Scope
ModuleScope = BinHandle -> Word8 -> IO ()
putByte BinHandle
bh Word8
2
get :: BinHandle -> IO Scope
get BinHandle
bh = do
(Word8
t :: Word8) <- BinHandle -> IO Word8
forall a. Binary a => BinHandle -> IO a
External instance of the constraint type Binary Word8
get BinHandle
bh
case Word8
t of
Word8
0 -> Scope -> IO Scope
forall (m :: * -> *) a. Monad m => a -> m a
External instance of the constraint type Monad IO
return Scope
NoScope
Word8
1 -> Span -> Scope
LocalScope (Span -> Scope) -> IO Span -> IO Scope
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
External instance of the constraint type Functor IO
<$> BinHandle -> IO Span
forall a. Binary a => BinHandle -> IO a
External instance of the constraint type Binary Span
get BinHandle
bh
Word8
2 -> Scope -> IO Scope
forall (m :: * -> *) a. Monad m => a -> m a
External instance of the constraint type Monad IO
return Scope
ModuleScope
Word8
_ -> String -> IO Scope
forall a. String -> a
panic String
"Binary Scope: invalid tag"
data TyVarScope
= ResolvedScopes [Scope]
| UnresolvedScope
[Name]
(Maybe Span)
deriving (TyVarScope -> TyVarScope -> Bool
(TyVarScope -> TyVarScope -> Bool)
-> (TyVarScope -> TyVarScope -> Bool) -> Eq TyVarScope
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: TyVarScope -> TyVarScope -> Bool
$c/= :: TyVarScope -> TyVarScope -> Bool
== :: TyVarScope -> TyVarScope -> Bool
$c== :: TyVarScope -> TyVarScope -> Bool
External instance of the constraint type Eq Span
External instance of the constraint type Eq Name
Instance of class: Eq of the constraint type Eq Scope
External instance of the constraint type Eq Span
External instance of the constraint type forall a. Eq a => Eq (Maybe a)
External instance of the constraint type forall a. Eq a => Eq [a]
External instance of the constraint type Eq Name
Instance of class: Eq of the constraint type Eq Scope
Eq, Eq TyVarScope
Eq TyVarScope
-> (TyVarScope -> TyVarScope -> Ordering)
-> (TyVarScope -> TyVarScope -> Bool)
-> (TyVarScope -> TyVarScope -> Bool)
-> (TyVarScope -> TyVarScope -> Bool)
-> (TyVarScope -> TyVarScope -> Bool)
-> (TyVarScope -> TyVarScope -> TyVarScope)
-> (TyVarScope -> TyVarScope -> TyVarScope)
-> Ord TyVarScope
TyVarScope -> TyVarScope -> Bool
TyVarScope -> TyVarScope -> Ordering
TyVarScope -> TyVarScope -> TyVarScope
forall a.
Eq a
-> (a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
min :: TyVarScope -> TyVarScope -> TyVarScope
$cmin :: TyVarScope -> TyVarScope -> TyVarScope
max :: TyVarScope -> TyVarScope -> TyVarScope
$cmax :: TyVarScope -> TyVarScope -> TyVarScope
>= :: TyVarScope -> TyVarScope -> Bool
$c>= :: TyVarScope -> TyVarScope -> Bool
> :: TyVarScope -> TyVarScope -> Bool
$c> :: TyVarScope -> TyVarScope -> Bool
<= :: TyVarScope -> TyVarScope -> Bool
$c<= :: TyVarScope -> TyVarScope -> Bool
< :: TyVarScope -> TyVarScope -> Bool
$c< :: TyVarScope -> TyVarScope -> Bool
compare :: TyVarScope -> TyVarScope -> Ordering
$ccompare :: TyVarScope -> TyVarScope -> Ordering
External instance of the constraint type Ord Span
External instance of the constraint type Ord Name
Instance of class: Ord of the constraint type Ord Scope
External instance of the constraint type Ord Span
External instance of the constraint type Ord Name
Instance of class: Ord of the constraint type Ord Scope
Instance of class: Eq of the constraint type Eq TyVarScope
External instance of the constraint type forall a. Ord a => Ord [a]
External instance of the constraint type Ord Span
External instance of the constraint type forall a. Ord a => Ord (Maybe a)
External instance of the constraint type Ord Name
Instance of class: Ord of the constraint type Ord Scope
Instance of class: Ord of the constraint type Ord TyVarScope
Instance of class: Eq of the constraint type Eq TyVarScope
Ord)
instance Outputable TyVarScope where
ppr :: TyVarScope -> SDoc
ppr (ResolvedScopes [Scope]
xs) =
String -> SDoc
text String
"type variable scopes:" SDoc -> SDoc -> SDoc
<+> [SDoc] -> SDoc
hsep (SDoc -> [SDoc] -> [SDoc]
punctuate SDoc
", " ([SDoc] -> [SDoc]) -> [SDoc] -> [SDoc]
forall a b. (a -> b) -> a -> b
$ (Scope -> SDoc) -> [Scope] -> [SDoc]
forall a b. (a -> b) -> [a] -> [b]
map Scope -> SDoc
forall a. Outputable a => a -> SDoc
Instance of class: Outputable of the constraint type Outputable Scope
ppr [Scope]
xs)
ppr (UnresolvedScope [Name]
ns Maybe Span
sp) =
String -> SDoc
text String
"unresolved type variable scope for name" SDoc -> SDoc -> SDoc
O.<> [Name] -> SDoc
forall a. [a] -> SDoc
plural [Name]
ns
SDoc -> SDoc -> SDoc
<+> Maybe Span -> SDoc
pprBindSpan Maybe Span
sp
instance Binary TyVarScope where
put_ :: BinHandle -> TyVarScope -> IO ()
put_ BinHandle
bh (ResolvedScopes [Scope]
xs) = do
BinHandle -> Word8 -> IO ()
putByte BinHandle
bh Word8
0
BinHandle -> [Scope] -> IO ()
forall a. Binary a => BinHandle -> a -> IO ()
External instance of the constraint type forall a. Binary a => Binary [a]
Instance of class: Binary of the constraint type Binary Scope
put_ BinHandle
bh [Scope]
xs
put_ BinHandle
bh (UnresolvedScope [Name]
ns Maybe Span
span) = do
BinHandle -> Word8 -> IO ()
putByte BinHandle
bh Word8
1
BinHandle -> [Name] -> IO ()
forall a. Binary a => BinHandle -> a -> IO ()
External instance of the constraint type forall a. Binary a => Binary [a]
External instance of the constraint type Binary Name
put_ BinHandle
bh [Name]
ns
BinHandle -> Maybe Span -> IO ()
forall a. Binary a => BinHandle -> a -> IO ()
External instance of the constraint type forall a. Binary a => Binary (Maybe a)
External instance of the constraint type Binary Span
put_ BinHandle
bh Maybe Span
span
get :: BinHandle -> IO TyVarScope
get BinHandle
bh = do
(Word8
t :: Word8) <- BinHandle -> IO Word8
forall a. Binary a => BinHandle -> IO a
External instance of the constraint type Binary Word8
get BinHandle
bh
case Word8
t of
Word8
0 -> [Scope] -> TyVarScope
ResolvedScopes ([Scope] -> TyVarScope) -> IO [Scope] -> IO TyVarScope
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
External instance of the constraint type Functor IO
<$> BinHandle -> IO [Scope]
forall a. Binary a => BinHandle -> IO a
External instance of the constraint type forall a. Binary a => Binary [a]
Instance of class: Binary of the constraint type Binary Scope
get BinHandle
bh
Word8
1 -> [Name] -> Maybe Span -> TyVarScope
UnresolvedScope ([Name] -> Maybe Span -> TyVarScope)
-> IO [Name] -> IO (Maybe Span -> TyVarScope)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
External instance of the constraint type Functor IO
<$> BinHandle -> IO [Name]
forall a. Binary a => BinHandle -> IO a
External instance of the constraint type forall a. Binary a => Binary [a]
External instance of the constraint type Binary Name
get BinHandle
bh IO (Maybe Span -> TyVarScope) -> IO (Maybe Span) -> IO TyVarScope
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
External instance of the constraint type Applicative IO
<*> BinHandle -> IO (Maybe Span)
forall a. Binary a => BinHandle -> IO a
External instance of the constraint type forall a. Binary a => Binary (Maybe a)
External instance of the constraint type Binary Span
get BinHandle
bh
Word8
_ -> String -> IO TyVarScope
forall a. String -> a
panic String
"Binary TyVarScope: invalid tag"
data HieName
= ExternalName !Module !OccName !SrcSpan
| LocalName !OccName !SrcSpan
| KnownKeyName !Unique
deriving (HieName -> HieName -> Bool
(HieName -> HieName -> Bool)
-> (HieName -> HieName -> Bool) -> Eq HieName
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: HieName -> HieName -> Bool
$c/= :: HieName -> HieName -> Bool
== :: HieName -> HieName -> Bool
$c== :: HieName -> HieName -> Bool
External instance of the constraint type Eq (GenUnit UnitId)
External instance of the constraint type Eq Unique
External instance of the constraint type Eq SrcSpan
External instance of the constraint type Eq SrcSpan
External instance of the constraint type Eq OccName
External instance of the constraint type Eq OccName
External instance of the constraint type Eq (GenUnit UnitId)
External instance of the constraint type forall unit. Eq unit => Eq (GenModule unit)
Eq)
instance Ord HieName where
compare :: HieName -> HieName -> Ordering
compare (ExternalName Module
a OccName
b SrcSpan
c) (ExternalName Module
d OccName
e SrcSpan
f) = (Module, OccName) -> (Module, OccName) -> Ordering
forall a. Ord a => a -> a -> Ordering
External instance of the constraint type forall a b. (Ord a, Ord b) => Ord (a, b)
External instance of the constraint type forall unit. Ord unit => Ord (GenModule unit)
External instance of the constraint type Ord (GenUnit UnitId)
External instance of the constraint type Ord OccName
compare (Module
a,OccName
b) (Module
d,OccName
e) Ordering -> Ordering -> Ordering
`thenCmp` SrcSpan -> SrcSpan -> Ordering
leftmost_smallest SrcSpan
c SrcSpan
f
compare (LocalName OccName
a SrcSpan
b) (LocalName OccName
c SrcSpan
d) = OccName -> OccName -> Ordering
forall a. Ord a => a -> a -> Ordering
External instance of the constraint type Ord OccName
compare OccName
a OccName
c Ordering -> Ordering -> Ordering
`thenCmp` SrcSpan -> SrcSpan -> Ordering
leftmost_smallest SrcSpan
b SrcSpan
d
compare (KnownKeyName Unique
a) (KnownKeyName Unique
b) = Unique -> Unique -> Ordering
nonDetCmpUnique Unique
a Unique
b
compare ExternalName{} HieName
_ = Ordering
LT
compare LocalName{} ExternalName{} = Ordering
GT
compare LocalName{} HieName
_ = Ordering
LT
compare KnownKeyName{} HieName
_ = Ordering
GT
instance Outputable HieName where
ppr :: HieName -> SDoc
ppr (ExternalName Module
m OccName
n SrcSpan
sp) = String -> SDoc
text String
"ExternalName" SDoc -> SDoc -> SDoc
<+> Module -> SDoc
forall a. Outputable a => a -> SDoc
External instance of the constraint type Outputable Module
ppr Module
m SDoc -> SDoc -> SDoc
<+> OccName -> SDoc
forall a. Outputable a => a -> SDoc
External instance of the constraint type Outputable OccName
ppr OccName
n SDoc -> SDoc -> SDoc
<+> SrcSpan -> SDoc
forall a. Outputable a => a -> SDoc
External instance of the constraint type Outputable SrcSpan
ppr SrcSpan
sp
ppr (LocalName OccName
n SrcSpan
sp) = String -> SDoc
text String
"LocalName" SDoc -> SDoc -> SDoc
<+> OccName -> SDoc
forall a. Outputable a => a -> SDoc
External instance of the constraint type Outputable OccName
ppr OccName
n SDoc -> SDoc -> SDoc
<+> SrcSpan -> SDoc
forall a. Outputable a => a -> SDoc
External instance of the constraint type Outputable SrcSpan
ppr SrcSpan
sp
ppr (KnownKeyName Unique
u) = String -> SDoc
text String
"KnownKeyName" SDoc -> SDoc -> SDoc
<+> Unique -> SDoc
forall a. Outputable a => a -> SDoc
External instance of the constraint type Outputable Unique
ppr Unique
u
hieNameOcc :: HieName -> OccName
hieNameOcc :: HieName -> OccName
hieNameOcc (ExternalName Module
_ OccName
occ SrcSpan
_) = OccName
occ
hieNameOcc (LocalName OccName
occ SrcSpan
_) = OccName
occ
hieNameOcc (KnownKeyName Unique
u) =
case Unique -> Maybe Name
lookupKnownKeyName Unique
u of
Just Name
n -> Name -> OccName
nameOccName Name
n
Maybe Name
Nothing -> String -> SDoc -> OccName
forall a. HasCallStack => String -> SDoc -> a
pprPanic String
"hieNameOcc:unknown known-key unique"
((Char, TypeIndex) -> SDoc
forall a. Outputable a => a -> SDoc
External instance of the constraint type forall a b. (Outputable a, Outputable b) => Outputable (a, b)
External instance of the constraint type Outputable Char
External instance of the constraint type Outputable TypeIndex
ppr (Unique -> (Char, TypeIndex)
unpkUnique Unique
u))
toHieName :: Name -> HieName
toHieName :: Name -> HieName
toHieName Name
name
| Name -> Bool
isKnownKeyName Name
name = Unique -> HieName
KnownKeyName (Name -> Unique
nameUnique Name
name)
| Name -> Bool
isExternalName Name
name = Module -> OccName -> SrcSpan -> HieName
ExternalName (HasDebugCallStack => Name -> Module
Name -> Module
External instance of the constraint type HasDebugCallStack
nameModule Name
name)
(Name -> OccName
nameOccName Name
name)
(Name -> SrcSpan
nameSrcSpan Name
name)
| Bool
otherwise = OccName -> SrcSpan -> HieName
LocalName (Name -> OccName
nameOccName Name
name) (Name -> SrcSpan
nameSrcSpan Name
name)