{-# LANGUAGE DeriveTraversable #-}
{-# LANGUAGE DeriveDataTypeable #-}
{-# LANGUAGE TypeSynonymInstances #-}
{-# LANGUAGE FlexibleInstances #-}
{-# LANGUAGE ScopedTypeVariables #-}
module HieTypes where
import GhcPrelude
import Config
import Binary
import FastString ( FastString )
import IfaceType
import Module ( ModuleName, Module )
import Name ( Name )
import Outputable hiding ( (<>) )
import SrcLoc ( RealSrcSpan )
import Avail
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 ( (<|>) )
type Span = RealSrcSpan
hieVersion :: Integer
hieVersion :: Integer
hieVersion = String -> Integer
forall a. Read a => String -> a
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 Int HieTypeFlat
hie_types :: A.Array TypeIndex HieTypeFlat
, HieFile -> HieASTs Int
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 ()
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 ()
put_ BinHandle
bh (Module -> IO ()) -> Module -> IO ()
forall a b. (a -> b) -> a -> b
$ HieFile -> Module
hie_module HieFile
hf
BinHandle -> Array Int HieTypeFlat -> IO ()
forall a. Binary a => BinHandle -> a -> IO ()
put_ BinHandle
bh (Array Int HieTypeFlat -> IO ()) -> Array Int HieTypeFlat -> IO ()
forall a b. (a -> b) -> a -> b
$ HieFile -> Array Int HieTypeFlat
hie_types HieFile
hf
BinHandle -> HieASTs Int -> IO ()
forall a. Binary a => BinHandle -> a -> IO ()
put_ BinHandle
bh (HieASTs Int -> IO ()) -> HieASTs Int -> IO ()
forall a b. (a -> b) -> a -> b
$ HieFile -> HieASTs Int
hie_asts HieFile
hf
BinHandle -> [AvailInfo] -> IO ()
forall a. Binary a => BinHandle -> a -> IO ()
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 ()
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 Int HieTypeFlat
-> HieASTs Int
-> [AvailInfo]
-> ByteString
-> HieFile
HieFile
(String
-> Module
-> Array Int HieTypeFlat
-> HieASTs Int
-> [AvailInfo]
-> ByteString
-> HieFile)
-> IO String
-> IO
(Module
-> Array Int HieTypeFlat
-> HieASTs Int
-> [AvailInfo]
-> ByteString
-> HieFile)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> BinHandle -> IO String
forall a. Binary a => BinHandle -> IO a
get BinHandle
bh
IO
(Module
-> Array Int HieTypeFlat
-> HieASTs Int
-> [AvailInfo]
-> ByteString
-> HieFile)
-> IO Module
-> IO
(Array Int HieTypeFlat
-> HieASTs Int -> [AvailInfo] -> ByteString -> HieFile)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> BinHandle -> IO Module
forall a. Binary a => BinHandle -> IO a
get BinHandle
bh
IO
(Array Int HieTypeFlat
-> HieASTs Int -> [AvailInfo] -> ByteString -> HieFile)
-> IO (Array Int HieTypeFlat)
-> IO (HieASTs Int -> [AvailInfo] -> ByteString -> HieFile)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> BinHandle -> IO (Array Int HieTypeFlat)
forall a. Binary a => BinHandle -> IO a
get BinHandle
bh
IO (HieASTs Int -> [AvailInfo] -> ByteString -> HieFile)
-> IO (HieASTs Int) -> IO ([AvailInfo] -> ByteString -> HieFile)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> BinHandle -> IO (HieASTs Int)
forall a. Binary a => BinHandle -> IO a
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
<*> BinHandle -> IO [AvailInfo]
forall a. Binary a => BinHandle -> IO a
get BinHandle
bh
IO (ByteString -> HieFile) -> IO ByteString -> IO HieFile
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> BinHandle -> IO ByteString
forall a. Binary a => BinHandle -> IO a
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
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 -> Int)
-> (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 -> Int
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 -> Int)
-> (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 -> Int
$clength :: forall a. HieType a -> Int
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
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)
$cp2Traversable :: Foldable HieType
$cp1Traversable :: Functor 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
Eq)
type HieTypeFlat = HieType TypeIndex
newtype HieTypeFix = Roll (HieType (HieTypeFix))
instance Binary (HieType TypeIndex) where
put_ :: BinHandle -> HieTypeFlat -> 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 ()
put_ BinHandle
bh Name
n
put_ BinHandle
bh (HAppTy Int
a HieArgs Int
b) = do
BinHandle -> Word8 -> IO ()
putByte BinHandle
bh Word8
1
BinHandle -> Int -> IO ()
forall a. Binary a => BinHandle -> a -> IO ()
put_ BinHandle
bh Int
a
BinHandle -> HieArgs Int -> IO ()
forall a. Binary a => BinHandle -> a -> IO ()
put_ BinHandle
bh HieArgs Int
b
put_ BinHandle
bh (HTyConApp IfaceTyCon
n HieArgs Int
xs) = do
BinHandle -> Word8 -> IO ()
putByte BinHandle
bh Word8
2
BinHandle -> IfaceTyCon -> IO ()
forall a. Binary a => BinHandle -> a -> IO ()
put_ BinHandle
bh IfaceTyCon
n
BinHandle -> HieArgs Int -> IO ()
forall a. Binary a => BinHandle -> a -> IO ()
put_ BinHandle
bh HieArgs Int
xs
put_ BinHandle
bh (HForAllTy ((Name, Int), ArgFlag)
bndr Int
a) = do
BinHandle -> Word8 -> IO ()
putByte BinHandle
bh Word8
3
BinHandle -> ((Name, Int), ArgFlag) -> IO ()
forall a. Binary a => BinHandle -> a -> IO ()
put_ BinHandle
bh ((Name, Int), ArgFlag)
bndr
BinHandle -> Int -> IO ()
forall a. Binary a => BinHandle -> a -> IO ()
put_ BinHandle
bh Int
a
put_ BinHandle
bh (HFunTy Int
a Int
b) = do
BinHandle -> Word8 -> IO ()
putByte BinHandle
bh Word8
4
BinHandle -> Int -> IO ()
forall a. Binary a => BinHandle -> a -> IO ()
put_ BinHandle
bh Int
a
BinHandle -> Int -> IO ()
forall a. Binary a => BinHandle -> a -> IO ()
put_ BinHandle
bh Int
b
put_ BinHandle
bh (HQualTy Int
a Int
b) = do
BinHandle -> Word8 -> IO ()
putByte BinHandle
bh Word8
5
BinHandle -> Int -> IO ()
forall a. Binary a => BinHandle -> a -> IO ()
put_ BinHandle
bh Int
a
BinHandle -> Int -> IO ()
forall a. Binary a => BinHandle -> a -> IO ()
put_ BinHandle
bh Int
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 ()
put_ BinHandle
bh IfaceTyLit
l
put_ BinHandle
bh (HCastTy Int
a) = do
BinHandle -> Word8 -> IO ()
putByte BinHandle
bh Word8
7
BinHandle -> Int -> IO ()
forall a. Binary a => BinHandle -> a -> IO ()
put_ BinHandle
bh Int
a
put_ BinHandle
bh (HieTypeFlat
HCoercionTy) = BinHandle -> Word8 -> IO ()
putByte BinHandle
bh Word8
8
get :: BinHandle -> IO HieTypeFlat
get BinHandle
bh = do
(Word8
t :: Word8) <- BinHandle -> IO Word8
forall a. Binary a => BinHandle -> IO a
get BinHandle
bh
case Word8
t of
Word8
0 -> Name -> HieTypeFlat
forall a. Name -> HieType a
HTyVarTy (Name -> HieTypeFlat) -> IO Name -> IO HieTypeFlat
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> BinHandle -> IO Name
forall a. Binary a => BinHandle -> IO a
get BinHandle
bh
Word8
1 -> Int -> HieArgs Int -> HieTypeFlat
forall a. a -> HieArgs a -> HieType a
HAppTy (Int -> HieArgs Int -> HieTypeFlat)
-> IO Int -> IO (HieArgs Int -> HieTypeFlat)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> BinHandle -> IO Int
forall a. Binary a => BinHandle -> IO a
get BinHandle
bh IO (HieArgs Int -> HieTypeFlat)
-> IO (HieArgs Int) -> IO HieTypeFlat
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> BinHandle -> IO (HieArgs Int)
forall a. Binary a => BinHandle -> IO a
get BinHandle
bh
Word8
2 -> IfaceTyCon -> HieArgs Int -> HieTypeFlat
forall a. IfaceTyCon -> HieArgs a -> HieType a
HTyConApp (IfaceTyCon -> HieArgs Int -> HieTypeFlat)
-> IO IfaceTyCon -> IO (HieArgs Int -> HieTypeFlat)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> BinHandle -> IO IfaceTyCon
forall a. Binary a => BinHandle -> IO a
get BinHandle
bh IO (HieArgs Int -> HieTypeFlat)
-> IO (HieArgs Int) -> IO HieTypeFlat
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> BinHandle -> IO (HieArgs Int)
forall a. Binary a => BinHandle -> IO a
get BinHandle
bh
Word8
3 -> ((Name, Int), ArgFlag) -> Int -> HieTypeFlat
forall a. ((Name, a), ArgFlag) -> a -> HieType a
HForAllTy (((Name, Int), ArgFlag) -> Int -> HieTypeFlat)
-> IO ((Name, Int), ArgFlag) -> IO (Int -> HieTypeFlat)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> BinHandle -> IO ((Name, Int), ArgFlag)
forall a. Binary a => BinHandle -> IO a
get BinHandle
bh IO (Int -> HieTypeFlat) -> IO Int -> IO HieTypeFlat
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> BinHandle -> IO Int
forall a. Binary a => BinHandle -> IO a
get BinHandle
bh
Word8
4 -> Int -> Int -> HieTypeFlat
forall a. a -> a -> HieType a
HFunTy (Int -> Int -> HieTypeFlat) -> IO Int -> IO (Int -> HieTypeFlat)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> BinHandle -> IO Int
forall a. Binary a => BinHandle -> IO a
get BinHandle
bh IO (Int -> HieTypeFlat) -> IO Int -> IO HieTypeFlat
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> BinHandle -> IO Int
forall a. Binary a => BinHandle -> IO a
get BinHandle
bh
Word8
5 -> Int -> Int -> HieTypeFlat
forall a. a -> a -> HieType a
HQualTy (Int -> Int -> HieTypeFlat) -> IO Int -> IO (Int -> HieTypeFlat)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> BinHandle -> IO Int
forall a. Binary a => BinHandle -> IO a
get BinHandle
bh IO (Int -> HieTypeFlat) -> IO Int -> IO HieTypeFlat
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> BinHandle -> IO Int
forall a. Binary a => BinHandle -> IO a
get BinHandle
bh
Word8
6 -> IfaceTyLit -> HieTypeFlat
forall a. IfaceTyLit -> HieType a
HLitTy (IfaceTyLit -> HieTypeFlat) -> IO IfaceTyLit -> IO HieTypeFlat
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> BinHandle -> IO IfaceTyLit
forall a. Binary a => BinHandle -> IO a
get BinHandle
bh
Word8
7 -> Int -> HieTypeFlat
forall a. a -> HieType a
HCastTy (Int -> HieTypeFlat) -> IO Int -> IO HieTypeFlat
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> BinHandle -> IO Int
forall a. Binary a => BinHandle -> IO a
get BinHandle
bh
Word8
8 -> HieTypeFlat -> IO HieTypeFlat
forall (m :: * -> *) a. Monad m => a -> m a
return HieTypeFlat
forall a. HieType a
HCoercionTy
Word8
_ -> String -> IO HieTypeFlat
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
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 -> Int)
-> (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 -> Int
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 -> Int)
-> (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 -> Int
$clength :: forall a. HieArgs a -> Int
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
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)
$cp2Traversable :: Foldable HieArgs
$cp1Traversable :: Functor 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
Eq)
instance Binary (HieArgs TypeIndex) where
put_ :: BinHandle -> HieArgs Int -> IO ()
put_ BinHandle
bh (HieArgs [(Bool, Int)]
xs) = BinHandle -> [(Bool, Int)] -> IO ()
forall a. Binary a => BinHandle -> a -> IO ()
put_ BinHandle
bh [(Bool, Int)]
xs
get :: BinHandle -> IO (HieArgs Int)
get BinHandle
bh = [(Bool, Int)] -> HieArgs Int
forall a. [(Bool, a)] -> HieArgs a
HieArgs ([(Bool, Int)] -> HieArgs Int)
-> IO [(Bool, Int)] -> IO (HieArgs Int)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> BinHandle -> IO [(Bool, Int)]
forall a. Binary a => BinHandle -> IO a
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
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 -> Int)
-> (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 -> Int
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 -> Int)
-> (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 -> Int
$clength :: forall a. HieASTs a -> Int
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
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)
$cp2Traversable :: Foldable HieASTs
$cp1Traversable :: Functor HieASTs
Traversable)
instance Binary (HieASTs TypeIndex) where
put_ :: BinHandle -> HieASTs Int -> IO ()
put_ BinHandle
bh HieASTs Int
asts = BinHandle -> [(FastString, HieAST Int)] -> IO ()
forall a. Binary a => BinHandle -> a -> IO ()
put_ BinHandle
bh ([(FastString, HieAST Int)] -> IO ())
-> [(FastString, HieAST Int)] -> IO ()
forall a b. (a -> b) -> a -> b
$ Map FastString (HieAST Int) -> [(FastString, HieAST Int)]
forall k a. Map k a -> [(k, a)]
M.toAscList (Map FastString (HieAST Int) -> [(FastString, HieAST Int)])
-> Map FastString (HieAST Int) -> [(FastString, HieAST Int)]
forall a b. (a -> b) -> a -> b
$ HieASTs Int -> Map FastString (HieAST Int)
forall a. HieASTs a -> Map FastString (HieAST a)
getAsts HieASTs Int
asts
get :: BinHandle -> IO (HieASTs Int)
get BinHandle
bh = Map FastString (HieAST Int) -> HieASTs Int
forall a. Map FastString (HieAST a) -> HieASTs a
HieASTs (Map FastString (HieAST Int) -> HieASTs Int)
-> IO (Map FastString (HieAST Int)) -> IO (HieASTs Int)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> ([(FastString, HieAST Int)] -> Map FastString (HieAST Int))
-> IO [(FastString, HieAST Int)]
-> IO (Map FastString (HieAST Int))
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap [(FastString, HieAST Int)] -> Map FastString (HieAST Int)
forall k a. [(k, a)] -> Map k a
M.fromDistinctAscList (BinHandle -> IO [(FastString, HieAST Int)]
forall a. Binary a => BinHandle -> IO a
get BinHandle
bh)
data HieAST a =
Node
{ HieAST a -> NodeInfo a
nodeInfo :: NodeInfo 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
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 -> Int)
-> (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 -> Int
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 -> Int)
-> (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 -> Int
$clength :: forall a. HieAST a -> Int
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
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)
$cp2Traversable :: Foldable HieAST
$cp1Traversable :: Functor HieAST
Traversable)
instance Binary (HieAST TypeIndex) where
put_ :: BinHandle -> HieAST Int -> IO ()
put_ BinHandle
bh HieAST Int
ast = do
BinHandle -> NodeInfo Int -> IO ()
forall a. Binary a => BinHandle -> a -> IO ()
put_ BinHandle
bh (NodeInfo Int -> IO ()) -> NodeInfo Int -> IO ()
forall a b. (a -> b) -> a -> b
$ HieAST Int -> NodeInfo Int
forall a. HieAST a -> NodeInfo a
nodeInfo HieAST Int
ast
BinHandle -> Span -> IO ()
forall a. Binary a => BinHandle -> a -> IO ()
put_ BinHandle
bh (Span -> IO ()) -> Span -> IO ()
forall a b. (a -> b) -> a -> b
$ HieAST Int -> Span
forall a. HieAST a -> Span
nodeSpan HieAST Int
ast
BinHandle -> [HieAST Int] -> IO ()
forall a. Binary a => BinHandle -> a -> IO ()
put_ BinHandle
bh ([HieAST Int] -> IO ()) -> [HieAST Int] -> IO ()
forall a b. (a -> b) -> a -> b
$ HieAST Int -> [HieAST Int]
forall a. HieAST a -> [HieAST a]
nodeChildren HieAST Int
ast
get :: BinHandle -> IO (HieAST Int)
get BinHandle
bh = NodeInfo Int -> Span -> [HieAST Int] -> HieAST Int
forall a. NodeInfo a -> Span -> [HieAST a] -> HieAST a
Node
(NodeInfo Int -> Span -> [HieAST Int] -> HieAST Int)
-> IO (NodeInfo Int) -> IO (Span -> [HieAST Int] -> HieAST Int)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> BinHandle -> IO (NodeInfo Int)
forall a. Binary a => BinHandle -> IO a
get BinHandle
bh
IO (Span -> [HieAST Int] -> HieAST Int)
-> IO Span -> IO ([HieAST Int] -> HieAST Int)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> BinHandle -> IO Span
forall a. Binary a => BinHandle -> IO a
get BinHandle
bh
IO ([HieAST Int] -> HieAST Int)
-> IO [HieAST Int] -> IO (HieAST Int)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> BinHandle -> IO [HieAST Int]
forall a. Binary a => BinHandle -> IO a
get BinHandle
bh
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
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 -> Int)
-> (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 -> Int
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 -> Int)
-> (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 -> Int
$clength :: forall a. NodeInfo a -> Int
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
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)
$cp2Traversable :: Foldable NodeInfo
$cp1Traversable :: Functor NodeInfo
Traversable)
instance Binary (NodeInfo TypeIndex) where
put_ :: BinHandle -> NodeInfo Int -> IO ()
put_ BinHandle
bh NodeInfo Int
ni = do
BinHandle -> [(FastString, FastString)] -> IO ()
forall a. Binary a => BinHandle -> a -> IO ()
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 Int -> Set (FastString, FastString)
forall a. NodeInfo a -> Set (FastString, FastString)
nodeAnnotations NodeInfo Int
ni
BinHandle -> [Int] -> IO ()
forall a. Binary a => BinHandle -> a -> IO ()
put_ BinHandle
bh ([Int] -> IO ()) -> [Int] -> IO ()
forall a b. (a -> b) -> a -> b
$ NodeInfo Int -> [Int]
forall a. NodeInfo a -> [a]
nodeType NodeInfo Int
ni
BinHandle -> [(Identifier, IdentifierDetails Int)] -> IO ()
forall a. Binary a => BinHandle -> a -> IO ()
put_ BinHandle
bh ([(Identifier, IdentifierDetails Int)] -> IO ())
-> [(Identifier, IdentifierDetails Int)] -> IO ()
forall a b. (a -> b) -> a -> b
$ Map Identifier (IdentifierDetails Int)
-> [(Identifier, IdentifierDetails Int)]
forall k a. Map k a -> [(k, a)]
M.toList (Map Identifier (IdentifierDetails Int)
-> [(Identifier, IdentifierDetails Int)])
-> Map Identifier (IdentifierDetails Int)
-> [(Identifier, IdentifierDetails Int)]
forall a b. (a -> b) -> a -> b
$ NodeInfo Int -> Map Identifier (IdentifierDetails Int)
forall a. NodeInfo a -> NodeIdentifiers a
nodeIdentifiers NodeInfo Int
ni
get :: BinHandle -> IO (NodeInfo Int)
get BinHandle
bh = Set (FastString, FastString)
-> [Int] -> Map Identifier (IdentifierDetails Int) -> NodeInfo Int
forall a.
Set (FastString, FastString)
-> [a] -> NodeIdentifiers a -> NodeInfo a
NodeInfo
(Set (FastString, FastString)
-> [Int] -> Map Identifier (IdentifierDetails Int) -> NodeInfo Int)
-> IO (Set (FastString, FastString))
-> IO
([Int] -> Map Identifier (IdentifierDetails Int) -> NodeInfo Int)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> ([(FastString, FastString)] -> Set (FastString, FastString))
-> IO [(FastString, FastString)]
-> IO (Set (FastString, FastString))
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap ([(FastString, FastString)] -> Set (FastString, FastString)
forall a. [a] -> Set a
S.fromDistinctAscList) (BinHandle -> IO [(FastString, FastString)]
forall a. Binary a => BinHandle -> IO a
get BinHandle
bh)
IO
([Int] -> Map Identifier (IdentifierDetails Int) -> NodeInfo Int)
-> IO [Int]
-> IO (Map Identifier (IdentifierDetails Int) -> NodeInfo Int)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> BinHandle -> IO [Int]
forall a. Binary a => BinHandle -> IO a
get BinHandle
bh
IO (Map Identifier (IdentifierDetails Int) -> NodeInfo Int)
-> IO (Map Identifier (IdentifierDetails Int)) -> IO (NodeInfo Int)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> ([(Identifier, IdentifierDetails Int)]
-> Map Identifier (IdentifierDetails Int))
-> IO [(Identifier, IdentifierDetails Int)]
-> IO (Map Identifier (IdentifierDetails Int))
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap ([(Identifier, IdentifierDetails Int)]
-> Map Identifier (IdentifierDetails Int)
forall k a. Ord k => [(k, a)] -> Map k a
M.fromList) (BinHandle -> IO [(Identifier, IdentifierDetails Int)]
forall a. Binary a => BinHandle -> IO a
get BinHandle
bh)
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
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
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 -> Int)
-> (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 -> Int
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 -> Int)
-> (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 -> Int
$clength :: forall a. IdentifierDetails a -> Int
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
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)
$cp2Traversable :: Foldable IdentifierDetails
$cp1Traversable :: Functor IdentifierDetails
Traversable)
instance Outputable a => Outputable (IdentifierDetails a) where
ppr :: IdentifierDetails a -> SDoc
ppr IdentifierDetails a
x = String -> SDoc
text String
"IdentifierDetails" SDoc -> SDoc -> SDoc
<+> Maybe a -> SDoc
forall a. Outputable a => a -> SDoc
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
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
<|> 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
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 Int -> IO ()
put_ BinHandle
bh IdentifierDetails Int
dets = do
BinHandle -> Maybe Int -> IO ()
forall a. Binary a => BinHandle -> a -> IO ()
put_ BinHandle
bh (Maybe Int -> IO ()) -> Maybe Int -> IO ()
forall a b. (a -> b) -> a -> b
$ IdentifierDetails Int -> Maybe Int
forall a. IdentifierDetails a -> Maybe a
identType IdentifierDetails Int
dets
BinHandle -> [ContextInfo] -> IO ()
forall a. Binary a => BinHandle -> a -> IO ()
put_ BinHandle
bh ([ContextInfo] -> IO ()) -> [ContextInfo] -> IO ()
forall a b. (a -> b) -> a -> b
$ Set ContextInfo -> [ContextInfo]
forall a. Set a -> [a]
S.toAscList (Set ContextInfo -> [ContextInfo])
-> Set ContextInfo -> [ContextInfo]
forall a b. (a -> b) -> a -> b
$ IdentifierDetails Int -> Set ContextInfo
forall a. IdentifierDetails a -> Set ContextInfo
identInfo IdentifierDetails Int
dets
get :: BinHandle -> IO (IdentifierDetails Int)
get BinHandle
bh = Maybe Int -> Set ContextInfo -> IdentifierDetails Int
forall a. Maybe a -> Set ContextInfo -> IdentifierDetails a
IdentifierDetails
(Maybe Int -> Set ContextInfo -> IdentifierDetails Int)
-> IO (Maybe Int) -> IO (Set ContextInfo -> IdentifierDetails Int)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> BinHandle -> IO (Maybe Int)
forall a. Binary a => BinHandle -> IO a
get BinHandle
bh
IO (Set ContextInfo -> IdentifierDetails Int)
-> IO (Set ContextInfo) -> IO (IdentifierDetails Int)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> ([ContextInfo] -> Set ContextInfo)
-> IO [ContextInfo] -> IO (Set ContextInfo)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap ([ContextInfo] -> Set ContextInfo
forall a. [a] -> Set a
S.fromDistinctAscList) (BinHandle -> IO [ContextInfo]
forall a. Binary a => BinHandle -> IO a
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)
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
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
$cp1Ord :: Eq ContextInfo
Ord, Int -> ContextInfo -> String -> String
[ContextInfo] -> String -> String
ContextInfo -> String
(Int -> ContextInfo -> String -> String)
-> (ContextInfo -> String)
-> ([ContextInfo] -> String -> String)
-> Show ContextInfo
forall a.
(Int -> a -> String -> String)
-> (a -> String) -> ([a] -> String -> String) -> Show a
showList :: [ContextInfo] -> String -> String
$cshowList :: [ContextInfo] -> String -> String
show :: ContextInfo -> String
$cshow :: ContextInfo -> String
showsPrec :: Int -> ContextInfo -> String -> String
$cshowsPrec :: Int -> ContextInfo -> String -> String
Show)
instance Outputable ContextInfo where
ppr :: ContextInfo -> SDoc
ppr = String -> SDoc
text (String -> SDoc) -> (ContextInfo -> String) -> ContextInfo -> SDoc
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ContextInfo -> String
forall a. Show a => a -> String
show
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 ()
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 ()
put_ BinHandle
bh BindType
bt
BinHandle -> Scope -> IO ()
forall a. Binary a => BinHandle -> a -> IO ()
put_ BinHandle
bh Scope
sc
BinHandle -> Maybe Span -> IO ()
forall a. Binary a => BinHandle -> a -> IO ()
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 ()
put_ BinHandle
bh Scope
a
BinHandle -> Scope -> IO ()
forall a. Binary a => BinHandle -> a -> IO ()
put_ BinHandle
bh Scope
b
BinHandle -> Maybe Span -> IO ()
forall a. Binary a => BinHandle -> a -> IO ()
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 ()
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 ()
put_ BinHandle
bh DeclType
a
BinHandle -> Maybe Span -> IO ()
forall a. Binary a => BinHandle -> a -> IO ()
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 ()
put_ BinHandle
bh Scope
a
BinHandle -> TyVarScope -> IO ()
forall a. Binary a => BinHandle -> a -> IO ()
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 ()
put_ BinHandle
bh RecFieldContext
a
BinHandle -> Maybe Span -> IO ()
forall a. Binary a => BinHandle -> a -> IO ()
put_ BinHandle
bh Maybe Span
b
put_ BinHandle
bh ContextInfo
MatchBind = BinHandle -> Word8 -> IO ()
putByte BinHandle
bh Word8
9
get :: BinHandle -> IO ContextInfo
get BinHandle
bh = do
(Word8
t :: Word8) <- BinHandle -> IO Word8
forall a. Binary a => BinHandle -> IO a
get BinHandle
bh
case Word8
t of
Word8
0 -> ContextInfo -> IO ContextInfo
forall (m :: * -> *) a. Monad m => a -> m a
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
<$> BinHandle -> IO IEType
forall a. Binary a => BinHandle -> IO a
get BinHandle
bh
Word8
2 -> ContextInfo -> IO ContextInfo
forall (m :: * -> *) a. Monad m => a -> m a
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
<$> BinHandle -> IO BindType
forall a. Binary a => BinHandle -> IO a
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
<*> BinHandle -> IO Scope
forall a. Binary a => BinHandle -> IO a
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
<*> BinHandle -> IO (Maybe Span)
forall a. Binary a => BinHandle -> IO a
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
<$> BinHandle -> IO Scope
forall a. Binary a => BinHandle -> IO a
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
<*> BinHandle -> IO Scope
forall a. Binary a => BinHandle -> IO a
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
<*> BinHandle -> IO (Maybe Span)
forall a. Binary a => BinHandle -> IO a
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
<$> BinHandle -> IO (Maybe Span)
forall a. Binary a => BinHandle -> IO a
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
<$> BinHandle -> IO DeclType
forall a. Binary a => BinHandle -> IO a
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
<*> BinHandle -> IO (Maybe Span)
forall a. Binary a => BinHandle -> IO a
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
<$> BinHandle -> IO Scope
forall a. Binary a => BinHandle -> IO a
get BinHandle
bh IO (TyVarScope -> ContextInfo) -> IO TyVarScope -> IO ContextInfo
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> BinHandle -> IO TyVarScope
forall a. Binary a => BinHandle -> IO a
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
<$> BinHandle -> IO RecFieldContext
forall a. Binary a => BinHandle -> IO a
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
<*> BinHandle -> IO (Maybe Span)
forall a. Binary a => BinHandle -> IO a
get BinHandle
bh
Word8
9 -> ContextInfo -> IO ContextInfo
forall (m :: * -> *) a. Monad m => a -> m a
return ContextInfo
MatchBind
Word8
_ -> String -> IO ContextInfo
forall a. String -> a
panic String
"Binary ContextInfo: invalid tag"
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, Int -> IEType
IEType -> Int
IEType -> [IEType]
IEType -> IEType
IEType -> IEType -> [IEType]
IEType -> IEType -> IEType -> [IEType]
(IEType -> IEType)
-> (IEType -> IEType)
-> (Int -> IEType)
-> (IEType -> Int)
-> (IEType -> [IEType])
-> (IEType -> IEType -> [IEType])
-> (IEType -> IEType -> [IEType])
-> (IEType -> IEType -> IEType -> [IEType])
-> Enum IEType
forall a.
(a -> a)
-> (a -> a)
-> (Int -> a)
-> (a -> Int)
-> (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 -> Int
$cfromEnum :: IEType -> Int
toEnum :: Int -> IEType
$ctoEnum :: Int -> IEType
pred :: IEType -> IEType
$cpred :: IEType -> IEType
succ :: IEType -> IEType
$csucc :: IEType -> IEType
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
$cp1Ord :: Eq IEType
Ord, Int -> IEType -> String -> String
[IEType] -> String -> String
IEType -> String
(Int -> IEType -> String -> String)
-> (IEType -> String)
-> ([IEType] -> String -> String)
-> Show IEType
forall a.
(Int -> a -> String -> String)
-> (a -> String) -> ([a] -> String -> String) -> Show a
showList :: [IEType] -> String -> String
$cshowList :: [IEType] -> String -> String
show :: IEType -> String
$cshow :: IEType -> String
showsPrec :: Int -> IEType -> String -> String
$cshowsPrec :: Int -> IEType -> String -> String
Show)
instance Binary IEType where
put_ :: BinHandle -> IEType -> IO ()
put_ BinHandle
bh IEType
b = BinHandle -> Word8 -> IO ()
putByte BinHandle
bh (Int -> Word8
forall a b. (Integral a, Num b) => a -> b
fromIntegral (IEType -> Int
forall a. Enum a => a -> Int
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
pure (IEType -> IO IEType) -> IEType -> IO IEType
forall a b. (a -> b) -> a -> b
$! (Int -> IEType
forall a. Enum a => Int -> a
toEnum (Word8 -> Int
forall a b. (Integral a, Num b) => a -> b
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, Int -> RecFieldContext
RecFieldContext -> Int
RecFieldContext -> [RecFieldContext]
RecFieldContext -> RecFieldContext
RecFieldContext -> RecFieldContext -> [RecFieldContext]
RecFieldContext
-> RecFieldContext -> RecFieldContext -> [RecFieldContext]
(RecFieldContext -> RecFieldContext)
-> (RecFieldContext -> RecFieldContext)
-> (Int -> RecFieldContext)
-> (RecFieldContext -> Int)
-> (RecFieldContext -> [RecFieldContext])
-> (RecFieldContext -> RecFieldContext -> [RecFieldContext])
-> (RecFieldContext -> RecFieldContext -> [RecFieldContext])
-> (RecFieldContext
-> RecFieldContext -> RecFieldContext -> [RecFieldContext])
-> Enum RecFieldContext
forall a.
(a -> a)
-> (a -> a)
-> (Int -> a)
-> (a -> Int)
-> (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 -> Int
$cfromEnum :: RecFieldContext -> Int
toEnum :: Int -> RecFieldContext
$ctoEnum :: Int -> RecFieldContext
pred :: RecFieldContext -> RecFieldContext
$cpred :: RecFieldContext -> RecFieldContext
succ :: RecFieldContext -> RecFieldContext
$csucc :: RecFieldContext -> RecFieldContext
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
$cp1Ord :: Eq RecFieldContext
Ord, Int -> RecFieldContext -> String -> String
[RecFieldContext] -> String -> String
RecFieldContext -> String
(Int -> RecFieldContext -> String -> String)
-> (RecFieldContext -> String)
-> ([RecFieldContext] -> String -> String)
-> Show RecFieldContext
forall a.
(Int -> a -> String -> String)
-> (a -> String) -> ([a] -> String -> String) -> Show a
showList :: [RecFieldContext] -> String -> String
$cshowList :: [RecFieldContext] -> String -> String
show :: RecFieldContext -> String
$cshow :: RecFieldContext -> String
showsPrec :: Int -> RecFieldContext -> String -> String
$cshowsPrec :: Int -> RecFieldContext -> String -> String
Show)
instance Binary RecFieldContext where
put_ :: BinHandle -> RecFieldContext -> IO ()
put_ BinHandle
bh RecFieldContext
b = BinHandle -> Word8 -> IO ()
putByte BinHandle
bh (Int -> Word8
forall a b. (Integral a, Num b) => a -> b
fromIntegral (RecFieldContext -> Int
forall a. Enum a => a -> Int
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
pure (RecFieldContext -> IO RecFieldContext)
-> RecFieldContext -> IO RecFieldContext
forall a b. (a -> b) -> a -> b
$! (Int -> RecFieldContext
forall a. Enum a => Int -> a
toEnum (Word8 -> Int
forall a b. (Integral a, Num b) => a -> b
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
$cp1Ord :: Eq BindType
Ord, Int -> BindType -> String -> String
[BindType] -> String -> String
BindType -> String
(Int -> BindType -> String -> String)
-> (BindType -> String)
-> ([BindType] -> String -> String)
-> Show BindType
forall a.
(Int -> a -> String -> String)
-> (a -> String) -> ([a] -> String -> String) -> Show a
showList :: [BindType] -> String -> String
$cshowList :: [BindType] -> String -> String
show :: BindType -> String
$cshow :: BindType -> String
showsPrec :: Int -> BindType -> String -> String
$cshowsPrec :: Int -> BindType -> String -> String
Show, Int -> BindType
BindType -> Int
BindType -> [BindType]
BindType -> BindType
BindType -> BindType -> [BindType]
BindType -> BindType -> BindType -> [BindType]
(BindType -> BindType)
-> (BindType -> BindType)
-> (Int -> BindType)
-> (BindType -> Int)
-> (BindType -> [BindType])
-> (BindType -> BindType -> [BindType])
-> (BindType -> BindType -> [BindType])
-> (BindType -> BindType -> BindType -> [BindType])
-> Enum BindType
forall a.
(a -> a)
-> (a -> a)
-> (Int -> a)
-> (a -> Int)
-> (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 -> Int
$cfromEnum :: BindType -> Int
toEnum :: Int -> BindType
$ctoEnum :: Int -> BindType
pred :: BindType -> BindType
$cpred :: BindType -> BindType
succ :: BindType -> BindType
$csucc :: BindType -> BindType
Enum)
instance Binary BindType where
put_ :: BinHandle -> BindType -> IO ()
put_ BinHandle
bh BindType
b = BinHandle -> Word8 -> IO ()
putByte BinHandle
bh (Int -> Word8
forall a b. (Integral a, Num b) => a -> b
fromIntegral (BindType -> Int
forall a. Enum a => a -> Int
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
pure (BindType -> IO BindType) -> BindType -> IO BindType
forall a b. (a -> b) -> a -> b
$! (Int -> BindType
forall a. Enum a => Int -> a
toEnum (Word8 -> Int
forall a b. (Integral a, Num b) => a -> b
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
$cp1Ord :: Eq DeclType
Ord, Int -> DeclType -> String -> String
[DeclType] -> String -> String
DeclType -> String
(Int -> DeclType -> String -> String)
-> (DeclType -> String)
-> ([DeclType] -> String -> String)
-> Show DeclType
forall a.
(Int -> a -> String -> String)
-> (a -> String) -> ([a] -> String -> String) -> Show a
showList :: [DeclType] -> String -> String
$cshowList :: [DeclType] -> String -> String
show :: DeclType -> String
$cshow :: DeclType -> String
showsPrec :: Int -> DeclType -> String -> String
$cshowsPrec :: Int -> DeclType -> String -> String
Show, Int -> DeclType
DeclType -> Int
DeclType -> [DeclType]
DeclType -> DeclType
DeclType -> DeclType -> [DeclType]
DeclType -> DeclType -> DeclType -> [DeclType]
(DeclType -> DeclType)
-> (DeclType -> DeclType)
-> (Int -> DeclType)
-> (DeclType -> Int)
-> (DeclType -> [DeclType])
-> (DeclType -> DeclType -> [DeclType])
-> (DeclType -> DeclType -> [DeclType])
-> (DeclType -> DeclType -> DeclType -> [DeclType])
-> Enum DeclType
forall a.
(a -> a)
-> (a -> a)
-> (Int -> a)
-> (a -> Int)
-> (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 -> Int
$cfromEnum :: DeclType -> Int
toEnum :: Int -> DeclType
$ctoEnum :: Int -> DeclType
pred :: DeclType -> DeclType
$cpred :: DeclType -> DeclType
succ :: DeclType -> DeclType
$csucc :: DeclType -> DeclType
Enum)
instance Binary DeclType where
put_ :: BinHandle -> DeclType -> IO ()
put_ BinHandle
bh DeclType
b = BinHandle -> Word8 -> IO ()
putByte BinHandle
bh (Int -> Word8
forall a b. (Integral a, Num b) => a -> b
fromIntegral (DeclType -> Int
forall a. Enum a => a -> Int
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
pure (DeclType -> IO DeclType) -> DeclType -> IO DeclType
forall a b. (a -> b) -> a -> b
$! (Int -> DeclType
forall a. Enum a => Int -> a
toEnum (Word8 -> Int
forall a b. (Integral a, Num b) => a -> b
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
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
$cp1Ord :: Eq Scope
Ord, Int -> Scope -> String -> String
[Scope] -> String -> String
Scope -> String
(Int -> Scope -> String -> String)
-> (Scope -> String) -> ([Scope] -> String -> String) -> Show Scope
forall a.
(Int -> a -> String -> String)
-> (a -> String) -> ([a] -> String -> String) -> Show a
showList :: [Scope] -> String -> String
$cshowList :: [Scope] -> String -> String
show :: Scope -> String
$cshow :: Scope -> String
showsPrec :: Int -> Scope -> String -> String
$cshowsPrec :: Int -> Scope -> String -> String
Show, 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. Int -> (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. Int -> (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. Int -> (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 :: Int -> (forall d. Data d => d -> u) -> Scope -> u
$cgmapQi :: forall u. Int -> (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
$cp1Data :: Typeable Scope
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
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 ()
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
get BinHandle
bh
case Word8
t of
Word8
0 -> Scope -> IO Scope
forall (m :: * -> *) a. Monad m => a -> m a
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
<$> BinHandle -> IO Span
forall a. Binary a => BinHandle -> IO a
get BinHandle
bh
Word8
2 -> Scope -> IO Scope
forall (m :: * -> *) a. Monad m => a -> m a
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
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
$cp1Ord :: Eq TyVarScope
Ord)
instance Show TyVarScope where
show :: TyVarScope -> String
show (ResolvedScopes [Scope]
sc) = [Scope] -> String
forall a. Show a => a -> String
show [Scope]
sc
show TyVarScope
_ = String -> String
forall a. HasCallStack => String -> a
error String
"UnresolvedScope"
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 ()
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 ()
put_ BinHandle
bh [Name]
ns
BinHandle -> Maybe Span -> IO ()
forall a. Binary a => BinHandle -> a -> IO ()
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
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
<$> BinHandle -> IO [Scope]
forall a. Binary a => BinHandle -> IO a
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
<$> BinHandle -> IO [Name]
forall a. Binary a => BinHandle -> IO a
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
<*> BinHandle -> IO (Maybe Span)
forall a. Binary a => BinHandle -> IO a
get BinHandle
bh
Word8
_ -> String -> IO TyVarScope
forall a. String -> a
panic String
"Binary TyVarScope: invalid tag"