{-# LANGUAGE DeriveDataTypeable         #-}
{-# LANGUAGE DeriveTraversable          #-}
{-# LANGUAGE FlexibleInstances          #-}
{-# LANGUAGE GeneralizedNewtypeDeriving #-}
{-# LANGUAGE OverloadedStrings          #-}
{-# LANGUAGE PatternSynonyms            #-}
{-# LANGUAGE ScopedTypeVariables        #-}

{-
Types for the .hie file format are defined here.

For more information see https://gitlab.haskell.org/ghc/ghc/wikis/hie-files
-}

module GHC.Iface.Ext.Types where

import GHC.Prelude

import GHC.Settings.Config
import GHC.Utils.Binary
import GHC.Data.FastString
import GHC.Builtin.Utils
import GHC.Iface.Type
import GHC.Unit.Module            ( ModuleName, Module )
import GHC.Types.Name
import GHC.Utils.Outputable hiding ( (<>) )
import GHC.Types.SrcLoc
import GHC.Types.Avail
import GHC.Types.Unique
import qualified GHC.Utils.Outputable as O ( (<>) )
import GHC.Utils.Misc
import GHC.Utils.Panic

import qualified Data.Array as A
import qualified Data.Map as M
import qualified Data.Set as S
import Data.ByteString            ( ByteString )
import Data.Data                  ( Typeable, Data )
import Data.Semigroup             ( Semigroup(..) )
import Data.Word                  ( Word8 )
import Control.Applicative        ( (<|>) )
import Data.Coerce                ( coerce  )
import Data.Function              ( on )

type Span = RealSrcSpan

-- | Current version of @.hie@ files
hieVersion :: Integer
hieVersion :: Integer
hieVersion = forall a. Read a => String -> a
read (String
cProjectVersionInt forall a. [a] -> [a] -> [a]
++ String
cProjectPatchLevel) :: Integer

{- |
GHC builds up a wealth of information about Haskell source as it compiles it.
@.hie@ files are a way of persisting some of this information to disk so that
external tools that need to work with haskell source don't need to parse,
typecheck, and rename all over again. These files contain:

  * a simplified AST

       * nodes are annotated with source positions and types
       * identifiers are annotated with scope information

  * the raw bytes of the initial Haskell source

Besides saving compilation cycles, @.hie@ files also offer a more stable
interface than the GHC API.
-}
data HieFile = HieFile
    { HieFile -> String
hie_hs_file :: FilePath
    -- ^ Initial Haskell source file path

    , HieFile -> Module
hie_module :: Module
    -- ^ The module this HIE file is for

    , HieFile -> Array TypeIndex (HieType TypeIndex)
hie_types :: A.Array TypeIndex HieTypeFlat
    -- ^ Types referenced in the 'hie_asts'.
    --
    -- See Note [Efficient serialization of redundant type info]

    , HieFile -> HieASTs TypeIndex
hie_asts :: HieASTs TypeIndex
    -- ^ Type-annotated abstract syntax trees

    , HieFile -> [AvailInfo]
hie_exports :: [AvailInfo]
    -- ^ The names that this module exports

    , HieFile -> ByteString
hie_hs_src :: ByteString
    -- ^ Raw bytes of the initial Haskell source
    }
instance Binary HieFile where
  put_ :: BinHandle -> HieFile -> IO ()
put_ BinHandle
bh HieFile
hf = do
    forall a. Binary a => BinHandle -> a -> IO ()
put_ BinHandle
bh forall a b. (a -> b) -> a -> b
$ HieFile -> String
hie_hs_file HieFile
hf
    forall a. Binary a => BinHandle -> a -> IO ()
put_ BinHandle
bh forall a b. (a -> b) -> a -> b
$ HieFile -> Module
hie_module HieFile
hf
    forall a. Binary a => BinHandle -> a -> IO ()
put_ BinHandle
bh forall a b. (a -> b) -> a -> b
$ HieFile -> Array TypeIndex (HieType TypeIndex)
hie_types HieFile
hf
    forall a. Binary a => BinHandle -> a -> IO ()
put_ BinHandle
bh forall a b. (a -> b) -> a -> b
$ HieFile -> HieASTs TypeIndex
hie_asts HieFile
hf
    forall a. Binary a => BinHandle -> a -> IO ()
put_ BinHandle
bh forall a b. (a -> b) -> a -> b
$ HieFile -> [AvailInfo]
hie_exports HieFile
hf
    forall a. Binary a => BinHandle -> a -> IO ()
put_ BinHandle
bh forall a b. (a -> b) -> a -> b
$ HieFile -> ByteString
hie_hs_src HieFile
hf

  get :: BinHandle -> IO HieFile
get BinHandle
bh = String
-> Module
-> Array TypeIndex (HieType TypeIndex)
-> HieASTs TypeIndex
-> [AvailInfo]
-> ByteString
-> HieFile
HieFile
    forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> forall a. Binary a => BinHandle -> IO a
get BinHandle
bh
    forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> forall a. Binary a => BinHandle -> IO a
get BinHandle
bh
    forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> forall a. Binary a => BinHandle -> IO a
get BinHandle
bh
    forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> forall a. Binary a => BinHandle -> IO a
get BinHandle
bh
    forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> forall a. Binary a => BinHandle -> IO a
get BinHandle
bh
    forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> forall a. Binary a => BinHandle -> IO a
get BinHandle
bh


{-
Note [Efficient serialization of redundant type info]
~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~

The type information in .hie files is highly repetitive and redundant. For
example, consider the expression

    const True 'a'

There is a lot of shared structure between the types of subterms:

  * const True 'a' ::                 Bool
  * const True     ::         Char -> Bool
  * const          :: Bool -> Char -> Bool

Since all 3 of these types need to be stored in the .hie file, it is worth
making an effort to deduplicate this shared structure. The trick is to define
a new data type that is a flattened version of 'Type':

    data HieType a = HAppTy a a  -- data Type = AppTy Type Type
                   | HFunTy a a  --           | FunTy Type Type
                   | ...

    type TypeIndex = Int

Types in the final AST are stored in an 'A.Array TypeIndex (HieType TypeIndex)',
where the 'TypeIndex's in the 'HieType' are references to other elements of the
array. Types recovered from GHC are deduplicated and stored in this compressed
form with sharing of subtrees.
-}

type TypeIndex = Int

-- | A flattened version of 'Type'.
--
-- See Note [Efficient serialization of redundant type info]
data HieType a
  = HTyVarTy Name
  | HAppTy a (HieArgs a)
  | HTyConApp IfaceTyCon (HieArgs a)
  | HForAllTy ((Name, a),ArgFlag) a
  | HFunTy a a a
  | HQualTy a a           -- ^ type with constraint: @t1 => t2@ (see 'IfaceDFunTy')
  | HLitTy IfaceTyLit
  | HCastTy a
  | HCoercionTy
    deriving (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
<$ :: forall a b. a -> HieType b -> HieType a
$c<$ :: forall a b. a -> HieType b -> HieType a
fmap :: forall a b. (a -> b) -> HieType a -> HieType b
$cfmap :: forall a b. (a -> b) -> HieType a -> HieType b
Functor, forall a. Eq a => a -> HieType a -> Bool
forall a. Num a => HieType a -> a
forall a. Ord a => HieType a -> a
forall m. Monoid m => HieType m -> m
forall a. HieType a -> Bool
forall a. HieType a -> TypeIndex
forall a. HieType a -> [a]
forall a. (a -> a -> a) -> HieType a -> a
forall m a. Monoid m => (a -> m) -> HieType a -> m
forall b a. (b -> a -> b) -> b -> HieType a -> b
forall a b. (a -> b -> b) -> b -> HieType a -> b
forall (t :: * -> *).
(forall m. Monoid m => t m -> m)
-> (forall m a. Monoid m => (a -> m) -> t a -> m)
-> (forall m a. Monoid m => (a -> m) -> t a -> m)
-> (forall a b. (a -> b -> b) -> b -> t a -> b)
-> (forall a b. (a -> b -> b) -> b -> t a -> b)
-> (forall b a. (b -> a -> b) -> b -> t a -> b)
-> (forall b a. (b -> a -> b) -> b -> t a -> b)
-> (forall a. (a -> a -> a) -> t a -> a)
-> (forall a. (a -> a -> a) -> t a -> a)
-> (forall a. t a -> [a])
-> (forall a. t a -> Bool)
-> (forall a. t a -> TypeIndex)
-> (forall a. Eq a => a -> t a -> Bool)
-> (forall a. Ord a => t a -> a)
-> (forall a. Ord a => t a -> a)
-> (forall a. Num a => t a -> a)
-> (forall a. Num a => t a -> a)
-> Foldable t
product :: forall a. Num a => HieType a -> a
$cproduct :: forall a. Num a => HieType a -> a
sum :: forall a. Num a => HieType a -> a
$csum :: forall a. Num a => HieType a -> a
minimum :: forall a. Ord a => HieType a -> a
$cminimum :: forall a. Ord a => HieType a -> a
maximum :: forall a. Ord a => HieType a -> a
$cmaximum :: forall a. Ord a => HieType a -> a
elem :: forall a. Eq a => a -> HieType a -> Bool
$celem :: forall a. Eq a => a -> HieType a -> Bool
length :: forall a. HieType a -> TypeIndex
$clength :: forall a. HieType a -> TypeIndex
null :: forall a. HieType a -> Bool
$cnull :: forall a. HieType a -> Bool
toList :: forall a. HieType a -> [a]
$ctoList :: forall a. HieType a -> [a]
foldl1 :: forall a. (a -> a -> a) -> HieType a -> a
$cfoldl1 :: forall a. (a -> a -> a) -> HieType a -> a
foldr1 :: forall a. (a -> a -> a) -> HieType a -> a
$cfoldr1 :: forall a. (a -> a -> a) -> HieType a -> a
foldl' :: forall b a. (b -> a -> b) -> b -> HieType a -> b
$cfoldl' :: forall b a. (b -> a -> b) -> b -> HieType a -> b
foldl :: forall b a. (b -> a -> b) -> b -> HieType a -> b
$cfoldl :: forall b a. (b -> a -> b) -> b -> HieType a -> b
foldr' :: forall a b. (a -> b -> b) -> b -> HieType a -> b
$cfoldr' :: forall a b. (a -> b -> b) -> b -> HieType a -> b
foldr :: forall a b. (a -> b -> b) -> b -> HieType a -> b
$cfoldr :: forall a b. (a -> b -> b) -> b -> HieType a -> b
foldMap' :: forall m a. Monoid m => (a -> m) -> HieType a -> m
$cfoldMap' :: forall m a. Monoid m => (a -> m) -> HieType a -> m
foldMap :: forall m a. Monoid m => (a -> m) -> HieType a -> m
$cfoldMap :: forall m a. Monoid m => (a -> m) -> HieType a -> m
fold :: forall m. Monoid m => HieType m -> m
$cfold :: forall m. Monoid m => HieType m -> m
Foldable, Functor HieType
Foldable HieType
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 :: forall (m :: * -> *) a. Monad m => HieType (m a) -> m (HieType a)
$csequence :: forall (m :: * -> *) a. Monad m => HieType (m a) -> m (HieType a)
mapM :: forall (m :: * -> *) a b.
Monad m =>
(a -> m b) -> HieType a -> m (HieType b)
$cmapM :: forall (m :: * -> *) a b.
Monad m =>
(a -> m b) -> HieType a -> m (HieType b)
sequenceA :: forall (f :: * -> *) a.
Applicative f =>
HieType (f a) -> f (HieType a)
$csequenceA :: forall (f :: * -> *) a.
Applicative f =>
HieType (f a) -> f (HieType a)
traverse :: forall (f :: * -> *) a b.
Applicative f =>
(a -> f b) -> HieType a -> f (HieType b)
$ctraverse :: forall (f :: * -> *) a b.
Applicative f =>
(a -> f b) -> HieType a -> f (HieType b)
Traversable, HieType a -> HieType a -> Bool
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

-- | Roughly isomorphic to the original core 'Type'.
newtype HieTypeFix = Roll (HieType (HieTypeFix))

instance Binary (HieType TypeIndex) where
  put_ :: BinHandle -> HieType TypeIndex -> IO ()
put_ BinHandle
bh (HTyVarTy Name
n) = do
    BinHandle -> Word8 -> IO ()
putByte BinHandle
bh Word8
0
    forall a. Binary a => BinHandle -> a -> IO ()
put_ BinHandle
bh Name
n
  put_ BinHandle
bh (HAppTy TypeIndex
a HieArgs TypeIndex
b) = do
    BinHandle -> Word8 -> IO ()
putByte BinHandle
bh Word8
1
    forall a. Binary a => BinHandle -> a -> IO ()
put_ BinHandle
bh TypeIndex
a
    forall a. Binary a => BinHandle -> a -> IO ()
put_ BinHandle
bh HieArgs TypeIndex
b
  put_ BinHandle
bh (HTyConApp IfaceTyCon
n HieArgs TypeIndex
xs) = do
    BinHandle -> Word8 -> IO ()
putByte BinHandle
bh Word8
2
    forall a. Binary a => BinHandle -> a -> IO ()
put_ BinHandle
bh IfaceTyCon
n
    forall a. Binary a => BinHandle -> a -> IO ()
put_ BinHandle
bh HieArgs TypeIndex
xs
  put_ BinHandle
bh (HForAllTy ((Name, TypeIndex), ArgFlag)
bndr TypeIndex
a) = do
    BinHandle -> Word8 -> IO ()
putByte BinHandle
bh Word8
3
    forall a. Binary a => BinHandle -> a -> IO ()
put_ BinHandle
bh ((Name, TypeIndex), ArgFlag)
bndr
    forall a. Binary a => BinHandle -> a -> IO ()
put_ BinHandle
bh TypeIndex
a
  put_ BinHandle
bh (HFunTy TypeIndex
w TypeIndex
a TypeIndex
b) = do
    BinHandle -> Word8 -> IO ()
putByte BinHandle
bh Word8
4
    forall a. Binary a => BinHandle -> a -> IO ()
put_ BinHandle
bh TypeIndex
w
    forall a. Binary a => BinHandle -> a -> IO ()
put_ BinHandle
bh TypeIndex
a
    forall a. Binary a => BinHandle -> a -> IO ()
put_ BinHandle
bh TypeIndex
b
  put_ BinHandle
bh (HQualTy TypeIndex
a TypeIndex
b) = do
    BinHandle -> Word8 -> IO ()
putByte BinHandle
bh Word8
5
    forall a. Binary a => BinHandle -> a -> IO ()
put_ BinHandle
bh TypeIndex
a
    forall a. Binary a => BinHandle -> a -> IO ()
put_ BinHandle
bh TypeIndex
b
  put_ BinHandle
bh (HLitTy IfaceTyLit
l) = do
    BinHandle -> Word8 -> IO ()
putByte BinHandle
bh Word8
6
    forall a. Binary a => BinHandle -> a -> IO ()
put_ BinHandle
bh IfaceTyLit
l
  put_ BinHandle
bh (HCastTy TypeIndex
a) = do
    BinHandle -> Word8 -> IO ()
putByte BinHandle
bh Word8
7
    forall a. Binary a => BinHandle -> a -> IO ()
put_ BinHandle
bh TypeIndex
a
  put_ BinHandle
bh (HieType TypeIndex
HCoercionTy) = BinHandle -> Word8 -> IO ()
putByte BinHandle
bh Word8
8

  get :: BinHandle -> IO (HieType TypeIndex)
get BinHandle
bh = do
    (Word8
t :: Word8) <- forall a. Binary a => BinHandle -> IO a
get BinHandle
bh
    case Word8
t of
      Word8
0 -> forall a. Name -> HieType a
HTyVarTy forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> forall a. Binary a => BinHandle -> IO a
get BinHandle
bh
      Word8
1 -> forall a. a -> HieArgs a -> HieType a
HAppTy forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> forall a. Binary a => BinHandle -> IO a
get BinHandle
bh forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> forall a. Binary a => BinHandle -> IO a
get BinHandle
bh
      Word8
2 -> forall a. IfaceTyCon -> HieArgs a -> HieType a
HTyConApp forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> forall a. Binary a => BinHandle -> IO a
get BinHandle
bh forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> forall a. Binary a => BinHandle -> IO a
get BinHandle
bh
      Word8
3 -> forall a. ((Name, a), ArgFlag) -> a -> HieType a
HForAllTy forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> forall a. Binary a => BinHandle -> IO a
get BinHandle
bh forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> forall a. Binary a => BinHandle -> IO a
get BinHandle
bh
      Word8
4 -> forall a. a -> a -> a -> HieType a
HFunTy forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> forall a. Binary a => BinHandle -> IO a
get BinHandle
bh forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> forall a. Binary a => BinHandle -> IO a
get BinHandle
bh forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> forall a. Binary a => BinHandle -> IO a
get BinHandle
bh
      Word8
5 -> forall a. a -> a -> HieType a
HQualTy forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> forall a. Binary a => BinHandle -> IO a
get BinHandle
bh forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> forall a. Binary a => BinHandle -> IO a
get BinHandle
bh
      Word8
6 -> forall a. IfaceTyLit -> HieType a
HLitTy forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> forall a. Binary a => BinHandle -> IO a
get BinHandle
bh
      Word8
7 -> forall a. a -> HieType a
HCastTy forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> forall a. Binary a => BinHandle -> IO a
get BinHandle
bh
      Word8
8 -> forall (m :: * -> *) a. Monad m => a -> m a
return forall a. HieType a
HCoercionTy
      Word8
_ -> forall a. String -> a
panic String
"Binary (HieArgs Int): invalid tag"


-- | A list of type arguments along with their respective visibilities (ie. is
-- this an argument that would return 'True' for 'isVisibleArgFlag'?).
newtype HieArgs a = HieArgs [(Bool,a)]
  deriving (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
<$ :: forall a b. a -> HieArgs b -> HieArgs a
$c<$ :: forall a b. a -> HieArgs b -> HieArgs a
fmap :: forall a b. (a -> b) -> HieArgs a -> HieArgs b
$cfmap :: forall a b. (a -> b) -> HieArgs a -> HieArgs b
Functor, forall a. Eq a => a -> HieArgs a -> Bool
forall a. Num a => HieArgs a -> a
forall a. Ord a => HieArgs a -> a
forall m. Monoid m => HieArgs m -> m
forall a. HieArgs a -> Bool
forall a. HieArgs a -> TypeIndex
forall a. HieArgs a -> [a]
forall a. (a -> a -> a) -> HieArgs a -> a
forall m a. Monoid m => (a -> m) -> HieArgs a -> m
forall b a. (b -> a -> b) -> b -> HieArgs a -> b
forall a b. (a -> b -> b) -> b -> HieArgs a -> b
forall (t :: * -> *).
(forall m. Monoid m => t m -> m)
-> (forall m a. Monoid m => (a -> m) -> t a -> m)
-> (forall m a. Monoid m => (a -> m) -> t a -> m)
-> (forall a b. (a -> b -> b) -> b -> t a -> b)
-> (forall a b. (a -> b -> b) -> b -> t a -> b)
-> (forall b a. (b -> a -> b) -> b -> t a -> b)
-> (forall b a. (b -> a -> b) -> b -> t a -> b)
-> (forall a. (a -> a -> a) -> t a -> a)
-> (forall a. (a -> a -> a) -> t a -> a)
-> (forall a. t a -> [a])
-> (forall a. t a -> Bool)
-> (forall a. t a -> TypeIndex)
-> (forall a. Eq a => a -> t a -> Bool)
-> (forall a. Ord a => t a -> a)
-> (forall a. Ord a => t a -> a)
-> (forall a. Num a => t a -> a)
-> (forall a. Num a => t a -> a)
-> Foldable t
product :: forall a. Num a => HieArgs a -> a
$cproduct :: forall a. Num a => HieArgs a -> a
sum :: forall a. Num a => HieArgs a -> a
$csum :: forall a. Num a => HieArgs a -> a
minimum :: forall a. Ord a => HieArgs a -> a
$cminimum :: forall a. Ord a => HieArgs a -> a
maximum :: forall a. Ord a => HieArgs a -> a
$cmaximum :: forall a. Ord a => HieArgs a -> a
elem :: forall a. Eq a => a -> HieArgs a -> Bool
$celem :: forall a. Eq a => a -> HieArgs a -> Bool
length :: forall a. HieArgs a -> TypeIndex
$clength :: forall a. HieArgs a -> TypeIndex
null :: forall a. HieArgs a -> Bool
$cnull :: forall a. HieArgs a -> Bool
toList :: forall a. HieArgs a -> [a]
$ctoList :: forall a. HieArgs a -> [a]
foldl1 :: forall a. (a -> a -> a) -> HieArgs a -> a
$cfoldl1 :: forall a. (a -> a -> a) -> HieArgs a -> a
foldr1 :: forall a. (a -> a -> a) -> HieArgs a -> a
$cfoldr1 :: forall a. (a -> a -> a) -> HieArgs a -> a
foldl' :: forall b a. (b -> a -> b) -> b -> HieArgs a -> b
$cfoldl' :: forall b a. (b -> a -> b) -> b -> HieArgs a -> b
foldl :: forall b a. (b -> a -> b) -> b -> HieArgs a -> b
$cfoldl :: forall b a. (b -> a -> b) -> b -> HieArgs a -> b
foldr' :: forall a b. (a -> b -> b) -> b -> HieArgs a -> b
$cfoldr' :: forall a b. (a -> b -> b) -> b -> HieArgs a -> b
foldr :: forall a b. (a -> b -> b) -> b -> HieArgs a -> b
$cfoldr :: forall a b. (a -> b -> b) -> b -> HieArgs a -> b
foldMap' :: forall m a. Monoid m => (a -> m) -> HieArgs a -> m
$cfoldMap' :: forall m a. Monoid m => (a -> m) -> HieArgs a -> m
foldMap :: forall m a. Monoid m => (a -> m) -> HieArgs a -> m
$cfoldMap :: forall m a. Monoid m => (a -> m) -> HieArgs a -> m
fold :: forall m. Monoid m => HieArgs m -> m
$cfold :: forall m. Monoid m => HieArgs m -> m
Foldable, Functor HieArgs
Foldable HieArgs
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 :: forall (m :: * -> *) a. Monad m => HieArgs (m a) -> m (HieArgs a)
$csequence :: forall (m :: * -> *) a. Monad m => HieArgs (m a) -> m (HieArgs a)
mapM :: forall (m :: * -> *) a b.
Monad m =>
(a -> m b) -> HieArgs a -> m (HieArgs b)
$cmapM :: forall (m :: * -> *) a b.
Monad m =>
(a -> m b) -> HieArgs a -> m (HieArgs b)
sequenceA :: forall (f :: * -> *) a.
Applicative f =>
HieArgs (f a) -> f (HieArgs a)
$csequenceA :: forall (f :: * -> *) a.
Applicative f =>
HieArgs (f a) -> f (HieArgs a)
traverse :: forall (f :: * -> *) a b.
Applicative f =>
(a -> f b) -> HieArgs a -> f (HieArgs b)
$ctraverse :: forall (f :: * -> *) a b.
Applicative f =>
(a -> f b) -> HieArgs a -> f (HieArgs b)
Traversable, HieArgs a -> HieArgs a -> Bool
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 TypeIndex -> IO ()
put_ BinHandle
bh (HieArgs [(Bool, TypeIndex)]
xs) = forall a. Binary a => BinHandle -> a -> IO ()
put_ BinHandle
bh [(Bool, TypeIndex)]
xs
  get :: BinHandle -> IO (HieArgs TypeIndex)
get BinHandle
bh = forall a. [(Bool, a)] -> HieArgs a
HieArgs forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> forall a. Binary a => BinHandle -> IO a
get BinHandle
bh


-- A HiePath is just a lexical FastString. We use a lexical FastString to avoid
-- non-determinism when printing or storing HieASTs which are sorted by their
-- HiePath.
type HiePath = LexicalFastString

{-# COMPLETE HiePath #-}
pattern HiePath :: FastString -> HiePath
pattern $mHiePath :: forall {r}. HiePath -> (FastString -> r) -> ((# #) -> r) -> r
$bHiePath :: FastString -> HiePath
HiePath fs = LexicalFastString fs

-- | Mapping from filepaths to the corresponding AST
newtype HieASTs a = HieASTs { forall a. HieASTs a -> Map HiePath (HieAST a)
getAsts :: M.Map HiePath (HieAST a) }
  deriving (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
<$ :: forall a b. a -> HieASTs b -> HieASTs a
$c<$ :: forall a b. a -> HieASTs b -> HieASTs a
fmap :: forall a b. (a -> b) -> HieASTs a -> HieASTs b
$cfmap :: forall a b. (a -> b) -> HieASTs a -> HieASTs b
Functor, forall a. Eq a => a -> HieASTs a -> Bool
forall a. Num a => HieASTs a -> a
forall a. Ord a => HieASTs a -> a
forall m. Monoid m => HieASTs m -> m
forall a. HieASTs a -> Bool
forall a. HieASTs a -> TypeIndex
forall a. HieASTs a -> [a]
forall a. (a -> a -> a) -> HieASTs a -> a
forall m a. Monoid m => (a -> m) -> HieASTs a -> m
forall b a. (b -> a -> b) -> b -> HieASTs a -> b
forall a b. (a -> b -> b) -> b -> HieASTs a -> b
forall (t :: * -> *).
(forall m. Monoid m => t m -> m)
-> (forall m a. Monoid m => (a -> m) -> t a -> m)
-> (forall m a. Monoid m => (a -> m) -> t a -> m)
-> (forall a b. (a -> b -> b) -> b -> t a -> b)
-> (forall a b. (a -> b -> b) -> b -> t a -> b)
-> (forall b a. (b -> a -> b) -> b -> t a -> b)
-> (forall b a. (b -> a -> b) -> b -> t a -> b)
-> (forall a. (a -> a -> a) -> t a -> a)
-> (forall a. (a -> a -> a) -> t a -> a)
-> (forall a. t a -> [a])
-> (forall a. t a -> Bool)
-> (forall a. t a -> TypeIndex)
-> (forall a. Eq a => a -> t a -> Bool)
-> (forall a. Ord a => t a -> a)
-> (forall a. Ord a => t a -> a)
-> (forall a. Num a => t a -> a)
-> (forall a. Num a => t a -> a)
-> Foldable t
product :: forall a. Num a => HieASTs a -> a
$cproduct :: forall a. Num a => HieASTs a -> a
sum :: forall a. Num a => HieASTs a -> a
$csum :: forall a. Num a => HieASTs a -> a
minimum :: forall a. Ord a => HieASTs a -> a
$cminimum :: forall a. Ord a => HieASTs a -> a
maximum :: forall a. Ord a => HieASTs a -> a
$cmaximum :: forall a. Ord a => HieASTs a -> a
elem :: forall a. Eq a => a -> HieASTs a -> Bool
$celem :: forall a. Eq a => a -> HieASTs a -> Bool
length :: forall a. HieASTs a -> TypeIndex
$clength :: forall a. HieASTs a -> TypeIndex
null :: forall a. HieASTs a -> Bool
$cnull :: forall a. HieASTs a -> Bool
toList :: forall a. HieASTs a -> [a]
$ctoList :: forall a. HieASTs a -> [a]
foldl1 :: forall a. (a -> a -> a) -> HieASTs a -> a
$cfoldl1 :: forall a. (a -> a -> a) -> HieASTs a -> a
foldr1 :: forall a. (a -> a -> a) -> HieASTs a -> a
$cfoldr1 :: forall a. (a -> a -> a) -> HieASTs a -> a
foldl' :: forall b a. (b -> a -> b) -> b -> HieASTs a -> b
$cfoldl' :: forall b a. (b -> a -> b) -> b -> HieASTs a -> b
foldl :: forall b a. (b -> a -> b) -> b -> HieASTs a -> b
$cfoldl :: forall b a. (b -> a -> b) -> b -> HieASTs a -> b
foldr' :: forall a b. (a -> b -> b) -> b -> HieASTs a -> b
$cfoldr' :: forall a b. (a -> b -> b) -> b -> HieASTs a -> b
foldr :: forall a b. (a -> b -> b) -> b -> HieASTs a -> b
$cfoldr :: forall a b. (a -> b -> b) -> b -> HieASTs a -> b
foldMap' :: forall m a. Monoid m => (a -> m) -> HieASTs a -> m
$cfoldMap' :: forall m a. Monoid m => (a -> m) -> HieASTs a -> m
foldMap :: forall m a. Monoid m => (a -> m) -> HieASTs a -> m
$cfoldMap :: forall m a. Monoid m => (a -> m) -> HieASTs a -> m
fold :: forall m. Monoid m => HieASTs m -> m
$cfold :: forall m. Monoid m => HieASTs m -> m
Foldable, Functor HieASTs
Foldable HieASTs
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 :: forall (m :: * -> *) a. Monad m => HieASTs (m a) -> m (HieASTs a)
$csequence :: forall (m :: * -> *) a. Monad m => HieASTs (m a) -> m (HieASTs a)
mapM :: forall (m :: * -> *) a b.
Monad m =>
(a -> m b) -> HieASTs a -> m (HieASTs b)
$cmapM :: forall (m :: * -> *) a b.
Monad m =>
(a -> m b) -> HieASTs a -> m (HieASTs b)
sequenceA :: forall (f :: * -> *) a.
Applicative f =>
HieASTs (f a) -> f (HieASTs a)
$csequenceA :: forall (f :: * -> *) a.
Applicative f =>
HieASTs (f a) -> f (HieASTs a)
traverse :: forall (f :: * -> *) a b.
Applicative f =>
(a -> f b) -> HieASTs a -> f (HieASTs b)
$ctraverse :: forall (f :: * -> *) a b.
Applicative f =>
(a -> f b) -> HieASTs a -> f (HieASTs b)
Traversable)

instance Binary (HieASTs TypeIndex) where
  put_ :: BinHandle -> HieASTs TypeIndex -> IO ()
put_ BinHandle
bh HieASTs TypeIndex
asts = forall a. Binary a => BinHandle -> a -> IO ()
put_ BinHandle
bh forall a b. (a -> b) -> a -> b
$ forall k a. Map k a -> [(k, a)]
M.toAscList forall a b. (a -> b) -> a -> b
$ forall a. HieASTs a -> Map HiePath (HieAST a)
getAsts HieASTs TypeIndex
asts
  get :: BinHandle -> IO (HieASTs TypeIndex)
get BinHandle
bh = forall a. Map HiePath (HieAST a) -> HieASTs a
HieASTs forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap forall k a. [(k, a)] -> Map k a
M.fromDistinctAscList (forall a. Binary a => BinHandle -> IO a
get BinHandle
bh)

instance Outputable a => Outputable (HieASTs a) where
  ppr :: HieASTs a -> SDoc
ppr (HieASTs Map HiePath (HieAST a)
asts) = forall k a b. (k -> a -> b -> b) -> b -> Map k a -> b
M.foldrWithKey forall {a} {a}.
(Outputable a, Outputable a) =>
a -> a -> SDoc -> SDoc
go SDoc
"" Map HiePath (HieAST a)
asts
    where
      go :: a -> a -> SDoc -> SDoc
go a
k a
a SDoc
rest = [SDoc] -> SDoc
vcat forall a b. (a -> b) -> a -> b
$
        [ SDoc
"File: " SDoc -> SDoc -> SDoc
O.<> forall a. Outputable a => a -> SDoc
ppr a
k
        , forall a. Outputable a => a -> SDoc
ppr a
a
        , SDoc
rest
        ]

data HieAST a =
  Node
    { forall a. HieAST a -> SourcedNodeInfo a
sourcedNodeInfo :: SourcedNodeInfo a
    , forall a. HieAST a -> Span
nodeSpan :: Span
    , forall a. HieAST a -> [HieAST a]
nodeChildren :: [HieAST a]
    } deriving (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
<$ :: forall a b. a -> HieAST b -> HieAST a
$c<$ :: forall a b. a -> HieAST b -> HieAST a
fmap :: forall a b. (a -> b) -> HieAST a -> HieAST b
$cfmap :: forall a b. (a -> b) -> HieAST a -> HieAST b
Functor, forall a. Eq a => a -> HieAST a -> Bool
forall a. Num a => HieAST a -> a
forall a. Ord a => HieAST a -> a
forall m. Monoid m => HieAST m -> m
forall a. HieAST a -> Bool
forall a. HieAST a -> TypeIndex
forall a. HieAST a -> [a]
forall a. (a -> a -> a) -> HieAST a -> a
forall m a. Monoid m => (a -> m) -> HieAST a -> m
forall b a. (b -> a -> b) -> b -> HieAST a -> b
forall a b. (a -> b -> b) -> b -> HieAST a -> b
forall (t :: * -> *).
(forall m. Monoid m => t m -> m)
-> (forall m a. Monoid m => (a -> m) -> t a -> m)
-> (forall m a. Monoid m => (a -> m) -> t a -> m)
-> (forall a b. (a -> b -> b) -> b -> t a -> b)
-> (forall a b. (a -> b -> b) -> b -> t a -> b)
-> (forall b a. (b -> a -> b) -> b -> t a -> b)
-> (forall b a. (b -> a -> b) -> b -> t a -> b)
-> (forall a. (a -> a -> a) -> t a -> a)
-> (forall a. (a -> a -> a) -> t a -> a)
-> (forall a. t a -> [a])
-> (forall a. t a -> Bool)
-> (forall a. t a -> TypeIndex)
-> (forall a. Eq a => a -> t a -> Bool)
-> (forall a. Ord a => t a -> a)
-> (forall a. Ord a => t a -> a)
-> (forall a. Num a => t a -> a)
-> (forall a. Num a => t a -> a)
-> Foldable t
product :: forall a. Num a => HieAST a -> a
$cproduct :: forall a. Num a => HieAST a -> a
sum :: forall a. Num a => HieAST a -> a
$csum :: forall a. Num a => HieAST a -> a
minimum :: forall a. Ord a => HieAST a -> a
$cminimum :: forall a. Ord a => HieAST a -> a
maximum :: forall a. Ord a => HieAST a -> a
$cmaximum :: forall a. Ord a => HieAST a -> a
elem :: forall a. Eq a => a -> HieAST a -> Bool
$celem :: forall a. Eq a => a -> HieAST a -> Bool
length :: forall a. HieAST a -> TypeIndex
$clength :: forall a. HieAST a -> TypeIndex
null :: forall a. HieAST a -> Bool
$cnull :: forall a. HieAST a -> Bool
toList :: forall a. HieAST a -> [a]
$ctoList :: forall a. HieAST a -> [a]
foldl1 :: forall a. (a -> a -> a) -> HieAST a -> a
$cfoldl1 :: forall a. (a -> a -> a) -> HieAST a -> a
foldr1 :: forall a. (a -> a -> a) -> HieAST a -> a
$cfoldr1 :: forall a. (a -> a -> a) -> HieAST a -> a
foldl' :: forall b a. (b -> a -> b) -> b -> HieAST a -> b
$cfoldl' :: forall b a. (b -> a -> b) -> b -> HieAST a -> b
foldl :: forall b a. (b -> a -> b) -> b -> HieAST a -> b
$cfoldl :: forall b a. (b -> a -> b) -> b -> HieAST a -> b
foldr' :: forall a b. (a -> b -> b) -> b -> HieAST a -> b
$cfoldr' :: forall a b. (a -> b -> b) -> b -> HieAST a -> b
foldr :: forall a b. (a -> b -> b) -> b -> HieAST a -> b
$cfoldr :: forall a b. (a -> b -> b) -> b -> HieAST a -> b
foldMap' :: forall m a. Monoid m => (a -> m) -> HieAST a -> m
$cfoldMap' :: forall m a. Monoid m => (a -> m) -> HieAST a -> m
foldMap :: forall m a. Monoid m => (a -> m) -> HieAST a -> m
$cfoldMap :: forall m a. Monoid m => (a -> m) -> HieAST a -> m
fold :: forall m. Monoid m => HieAST m -> m
$cfold :: forall m. Monoid m => HieAST m -> m
Foldable, Functor HieAST
Foldable HieAST
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 :: forall (m :: * -> *) a. Monad m => HieAST (m a) -> m (HieAST a)
$csequence :: forall (m :: * -> *) a. Monad m => HieAST (m a) -> m (HieAST a)
mapM :: forall (m :: * -> *) a b.
Monad m =>
(a -> m b) -> HieAST a -> m (HieAST b)
$cmapM :: forall (m :: * -> *) a b.
Monad m =>
(a -> m b) -> HieAST a -> m (HieAST b)
sequenceA :: forall (f :: * -> *) a.
Applicative f =>
HieAST (f a) -> f (HieAST a)
$csequenceA :: forall (f :: * -> *) a.
Applicative f =>
HieAST (f a) -> f (HieAST a)
traverse :: forall (f :: * -> *) a b.
Applicative f =>
(a -> f b) -> HieAST a -> f (HieAST b)
$ctraverse :: forall (f :: * -> *) a b.
Applicative f =>
(a -> f b) -> HieAST a -> f (HieAST b)
Traversable)

instance Binary (HieAST TypeIndex) where
  put_ :: BinHandle -> HieAST TypeIndex -> IO ()
put_ BinHandle
bh HieAST TypeIndex
ast = do
    forall a. Binary a => BinHandle -> a -> IO ()
put_ BinHandle
bh forall a b. (a -> b) -> a -> b
$ forall a. HieAST a -> SourcedNodeInfo a
sourcedNodeInfo HieAST TypeIndex
ast
    forall a. Binary a => BinHandle -> a -> IO ()
put_ BinHandle
bh forall a b. (a -> b) -> a -> b
$ forall a. HieAST a -> Span
nodeSpan HieAST TypeIndex
ast
    forall a. Binary a => BinHandle -> a -> IO ()
put_ BinHandle
bh forall a b. (a -> b) -> a -> b
$ forall a. HieAST a -> [HieAST a]
nodeChildren HieAST TypeIndex
ast

  get :: BinHandle -> IO (HieAST TypeIndex)
get BinHandle
bh = forall a. SourcedNodeInfo a -> Span -> [HieAST a] -> HieAST a
Node
    forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> forall a. Binary a => BinHandle -> IO a
get BinHandle
bh
    forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> forall a. Binary a => BinHandle -> IO a
get BinHandle
bh
    forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> forall a. Binary a => BinHandle -> IO a
get BinHandle
bh

instance Outputable a => Outputable (HieAST a) where
  ppr :: HieAST a -> SDoc
ppr (Node SourcedNodeInfo a
ni Span
sp [HieAST a]
ch) = SDoc -> TypeIndex -> SDoc -> SDoc
hang SDoc
header TypeIndex
2 SDoc
rest
    where
      header :: SDoc
header = String -> SDoc
text String
"Node@" SDoc -> SDoc -> SDoc
O.<> forall a. Outputable a => a -> SDoc
ppr Span
sp SDoc -> SDoc -> SDoc
O.<> SDoc
":" SDoc -> SDoc -> SDoc
<+> forall a. Outputable a => a -> SDoc
ppr SourcedNodeInfo a
ni
      rest :: SDoc
rest = [SDoc] -> SDoc
vcat (forall a b. (a -> b) -> [a] -> [b]
map forall a. Outputable a => a -> SDoc
ppr [HieAST a]
ch)


-- | NodeInfos grouped by source
newtype SourcedNodeInfo a = SourcedNodeInfo { forall a. SourcedNodeInfo a -> Map NodeOrigin (NodeInfo a)
getSourcedNodeInfo :: (M.Map NodeOrigin (NodeInfo a)) }
  deriving (forall a b. a -> SourcedNodeInfo b -> SourcedNodeInfo a
forall a b. (a -> b) -> SourcedNodeInfo a -> SourcedNodeInfo b
forall (f :: * -> *).
(forall a b. (a -> b) -> f a -> f b)
-> (forall a b. a -> f b -> f a) -> Functor f
<$ :: forall a b. a -> SourcedNodeInfo b -> SourcedNodeInfo a
$c<$ :: forall a b. a -> SourcedNodeInfo b -> SourcedNodeInfo a
fmap :: forall a b. (a -> b) -> SourcedNodeInfo a -> SourcedNodeInfo b
$cfmap :: forall a b. (a -> b) -> SourcedNodeInfo a -> SourcedNodeInfo b
Functor, forall a. Eq a => a -> SourcedNodeInfo a -> Bool
forall a. Num a => SourcedNodeInfo a -> a
forall a. Ord a => SourcedNodeInfo a -> a
forall m. Monoid m => SourcedNodeInfo m -> m
forall a. SourcedNodeInfo a -> Bool
forall a. SourcedNodeInfo a -> TypeIndex
forall a. SourcedNodeInfo a -> [a]
forall a. (a -> a -> a) -> SourcedNodeInfo a -> a
forall m a. Monoid m => (a -> m) -> SourcedNodeInfo a -> m
forall b a. (b -> a -> b) -> b -> SourcedNodeInfo a -> b
forall a b. (a -> b -> b) -> b -> SourcedNodeInfo a -> b
forall (t :: * -> *).
(forall m. Monoid m => t m -> m)
-> (forall m a. Monoid m => (a -> m) -> t a -> m)
-> (forall m a. Monoid m => (a -> m) -> t a -> m)
-> (forall a b. (a -> b -> b) -> b -> t a -> b)
-> (forall a b. (a -> b -> b) -> b -> t a -> b)
-> (forall b a. (b -> a -> b) -> b -> t a -> b)
-> (forall b a. (b -> a -> b) -> b -> t a -> b)
-> (forall a. (a -> a -> a) -> t a -> a)
-> (forall a. (a -> a -> a) -> t a -> a)
-> (forall a. t a -> [a])
-> (forall a. t a -> Bool)
-> (forall a. t a -> TypeIndex)
-> (forall a. Eq a => a -> t a -> Bool)
-> (forall a. Ord a => t a -> a)
-> (forall a. Ord a => t a -> a)
-> (forall a. Num a => t a -> a)
-> (forall a. Num a => t a -> a)
-> Foldable t
product :: forall a. Num a => SourcedNodeInfo a -> a
$cproduct :: forall a. Num a => SourcedNodeInfo a -> a
sum :: forall a. Num a => SourcedNodeInfo a -> a
$csum :: forall a. Num a => SourcedNodeInfo a -> a
minimum :: forall a. Ord a => SourcedNodeInfo a -> a
$cminimum :: forall a. Ord a => SourcedNodeInfo a -> a
maximum :: forall a. Ord a => SourcedNodeInfo a -> a
$cmaximum :: forall a. Ord a => SourcedNodeInfo a -> a
elem :: forall a. Eq a => a -> SourcedNodeInfo a -> Bool
$celem :: forall a. Eq a => a -> SourcedNodeInfo a -> Bool
length :: forall a. SourcedNodeInfo a -> TypeIndex
$clength :: forall a. SourcedNodeInfo a -> TypeIndex
null :: forall a. SourcedNodeInfo a -> Bool
$cnull :: forall a. SourcedNodeInfo a -> Bool
toList :: forall a. SourcedNodeInfo a -> [a]
$ctoList :: forall a. SourcedNodeInfo a -> [a]
foldl1 :: forall a. (a -> a -> a) -> SourcedNodeInfo a -> a
$cfoldl1 :: forall a. (a -> a -> a) -> SourcedNodeInfo a -> a
foldr1 :: forall a. (a -> a -> a) -> SourcedNodeInfo a -> a
$cfoldr1 :: forall a. (a -> a -> a) -> SourcedNodeInfo a -> a
foldl' :: forall b a. (b -> a -> b) -> b -> SourcedNodeInfo a -> b
$cfoldl' :: forall b a. (b -> a -> b) -> b -> SourcedNodeInfo a -> b
foldl :: forall b a. (b -> a -> b) -> b -> SourcedNodeInfo a -> b
$cfoldl :: forall b a. (b -> a -> b) -> b -> SourcedNodeInfo a -> b
foldr' :: forall a b. (a -> b -> b) -> b -> SourcedNodeInfo a -> b
$cfoldr' :: forall a b. (a -> b -> b) -> b -> SourcedNodeInfo a -> b
foldr :: forall a b. (a -> b -> b) -> b -> SourcedNodeInfo a -> b
$cfoldr :: forall a b. (a -> b -> b) -> b -> SourcedNodeInfo a -> b
foldMap' :: forall m a. Monoid m => (a -> m) -> SourcedNodeInfo a -> m
$cfoldMap' :: forall m a. Monoid m => (a -> m) -> SourcedNodeInfo a -> m
foldMap :: forall m a. Monoid m => (a -> m) -> SourcedNodeInfo a -> m
$cfoldMap :: forall m a. Monoid m => (a -> m) -> SourcedNodeInfo a -> m
fold :: forall m. Monoid m => SourcedNodeInfo m -> m
$cfold :: forall m. Monoid m => SourcedNodeInfo m -> m
Foldable, Functor SourcedNodeInfo
Foldable SourcedNodeInfo
forall (t :: * -> *).
Functor t
-> Foldable t
-> (forall (f :: * -> *) a b.
    Applicative f =>
    (a -> f b) -> t a -> f (t b))
-> (forall (f :: * -> *) a. Applicative f => t (f a) -> f (t a))
-> (forall (m :: * -> *) a b.
    Monad m =>
    (a -> m b) -> t a -> m (t b))
-> (forall (m :: * -> *) a. Monad m => t (m a) -> m (t a))
-> Traversable t
forall (m :: * -> *) a.
Monad m =>
SourcedNodeInfo (m a) -> m (SourcedNodeInfo a)
forall (f :: * -> *) a.
Applicative f =>
SourcedNodeInfo (f a) -> f (SourcedNodeInfo a)
forall (m :: * -> *) a b.
Monad m =>
(a -> m b) -> SourcedNodeInfo a -> m (SourcedNodeInfo b)
forall (f :: * -> *) a b.
Applicative f =>
(a -> f b) -> SourcedNodeInfo a -> f (SourcedNodeInfo b)
sequence :: forall (m :: * -> *) a.
Monad m =>
SourcedNodeInfo (m a) -> m (SourcedNodeInfo a)
$csequence :: forall (m :: * -> *) a.
Monad m =>
SourcedNodeInfo (m a) -> m (SourcedNodeInfo a)
mapM :: forall (m :: * -> *) a b.
Monad m =>
(a -> m b) -> SourcedNodeInfo a -> m (SourcedNodeInfo b)
$cmapM :: forall (m :: * -> *) a b.
Monad m =>
(a -> m b) -> SourcedNodeInfo a -> m (SourcedNodeInfo b)
sequenceA :: forall (f :: * -> *) a.
Applicative f =>
SourcedNodeInfo (f a) -> f (SourcedNodeInfo a)
$csequenceA :: forall (f :: * -> *) a.
Applicative f =>
SourcedNodeInfo (f a) -> f (SourcedNodeInfo a)
traverse :: forall (f :: * -> *) a b.
Applicative f =>
(a -> f b) -> SourcedNodeInfo a -> f (SourcedNodeInfo b)
$ctraverse :: forall (f :: * -> *) a b.
Applicative f =>
(a -> f b) -> SourcedNodeInfo a -> f (SourcedNodeInfo b)
Traversable)

instance Binary (SourcedNodeInfo TypeIndex) where
  put_ :: BinHandle -> SourcedNodeInfo TypeIndex -> IO ()
put_ BinHandle
bh SourcedNodeInfo TypeIndex
asts = forall a. Binary a => BinHandle -> a -> IO ()
put_ BinHandle
bh forall a b. (a -> b) -> a -> b
$ forall k a. Map k a -> [(k, a)]
M.toAscList forall a b. (a -> b) -> a -> b
$ forall a. SourcedNodeInfo a -> Map NodeOrigin (NodeInfo a)
getSourcedNodeInfo SourcedNodeInfo TypeIndex
asts
  get :: BinHandle -> IO (SourcedNodeInfo TypeIndex)
get BinHandle
bh = forall a. Map NodeOrigin (NodeInfo a) -> SourcedNodeInfo a
SourcedNodeInfo forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap forall k a. [(k, a)] -> Map k a
M.fromDistinctAscList (forall a. Binary a => BinHandle -> IO a
get BinHandle
bh)

instance Outputable a => Outputable (SourcedNodeInfo a) where
  ppr :: SourcedNodeInfo a -> SDoc
ppr (SourcedNodeInfo Map NodeOrigin (NodeInfo a)
asts) = forall k a b. (k -> a -> b -> b) -> b -> Map k a -> b
M.foldrWithKey forall {a} {a}.
(Outputable a, Outputable a) =>
a -> a -> SDoc -> SDoc
go SDoc
"" Map NodeOrigin (NodeInfo a)
asts
    where
      go :: a -> a -> SDoc -> SDoc
go a
k a
a SDoc
rest = [SDoc] -> SDoc
vcat forall a b. (a -> b) -> a -> b
$
        [ SDoc
"Source: " SDoc -> SDoc -> SDoc
O.<> forall a. Outputable a => a -> SDoc
ppr a
k
        , forall a. Outputable a => a -> SDoc
ppr a
a
        , SDoc
rest
        ]

-- | Source of node info
data NodeOrigin
  = SourceInfo
  | GeneratedInfo
    deriving (NodeOrigin -> NodeOrigin -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: NodeOrigin -> NodeOrigin -> Bool
$c/= :: NodeOrigin -> NodeOrigin -> Bool
== :: NodeOrigin -> NodeOrigin -> Bool
$c== :: NodeOrigin -> NodeOrigin -> Bool
Eq, TypeIndex -> NodeOrigin
NodeOrigin -> TypeIndex
NodeOrigin -> [NodeOrigin]
NodeOrigin -> NodeOrigin
NodeOrigin -> NodeOrigin -> [NodeOrigin]
NodeOrigin -> NodeOrigin -> NodeOrigin -> [NodeOrigin]
forall a.
(a -> a)
-> (a -> a)
-> (TypeIndex -> a)
-> (a -> TypeIndex)
-> (a -> [a])
-> (a -> a -> [a])
-> (a -> a -> [a])
-> (a -> a -> a -> [a])
-> Enum a
enumFromThenTo :: NodeOrigin -> NodeOrigin -> NodeOrigin -> [NodeOrigin]
$cenumFromThenTo :: NodeOrigin -> NodeOrigin -> NodeOrigin -> [NodeOrigin]
enumFromTo :: NodeOrigin -> NodeOrigin -> [NodeOrigin]
$cenumFromTo :: NodeOrigin -> NodeOrigin -> [NodeOrigin]
enumFromThen :: NodeOrigin -> NodeOrigin -> [NodeOrigin]
$cenumFromThen :: NodeOrigin -> NodeOrigin -> [NodeOrigin]
enumFrom :: NodeOrigin -> [NodeOrigin]
$cenumFrom :: NodeOrigin -> [NodeOrigin]
fromEnum :: NodeOrigin -> TypeIndex
$cfromEnum :: NodeOrigin -> TypeIndex
toEnum :: TypeIndex -> NodeOrigin
$ctoEnum :: TypeIndex -> NodeOrigin
pred :: NodeOrigin -> NodeOrigin
$cpred :: NodeOrigin -> NodeOrigin
succ :: NodeOrigin -> NodeOrigin
$csucc :: NodeOrigin -> NodeOrigin
Enum, Eq NodeOrigin
NodeOrigin -> NodeOrigin -> Bool
NodeOrigin -> NodeOrigin -> Ordering
NodeOrigin -> NodeOrigin -> NodeOrigin
forall a.
Eq a
-> (a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
min :: NodeOrigin -> NodeOrigin -> NodeOrigin
$cmin :: NodeOrigin -> NodeOrigin -> NodeOrigin
max :: NodeOrigin -> NodeOrigin -> NodeOrigin
$cmax :: NodeOrigin -> NodeOrigin -> NodeOrigin
>= :: NodeOrigin -> NodeOrigin -> Bool
$c>= :: NodeOrigin -> NodeOrigin -> Bool
> :: NodeOrigin -> NodeOrigin -> Bool
$c> :: NodeOrigin -> NodeOrigin -> Bool
<= :: NodeOrigin -> NodeOrigin -> Bool
$c<= :: NodeOrigin -> NodeOrigin -> Bool
< :: NodeOrigin -> NodeOrigin -> Bool
$c< :: NodeOrigin -> NodeOrigin -> Bool
compare :: NodeOrigin -> NodeOrigin -> Ordering
$ccompare :: NodeOrigin -> NodeOrigin -> Ordering
Ord)

instance Outputable NodeOrigin where
  ppr :: NodeOrigin -> SDoc
ppr NodeOrigin
SourceInfo = String -> SDoc
text String
"From source"
  ppr NodeOrigin
GeneratedInfo = String -> SDoc
text String
"generated by ghc"

instance Binary NodeOrigin where
  put_ :: BinHandle -> NodeOrigin -> IO ()
put_ BinHandle
bh NodeOrigin
b = BinHandle -> Word8 -> IO ()
putByte BinHandle
bh (forall a b. (Integral a, Num b) => a -> b
fromIntegral (forall a. Enum a => a -> TypeIndex
fromEnum NodeOrigin
b))
  get :: BinHandle -> IO NodeOrigin
get BinHandle
bh = do Word8
x <- BinHandle -> IO Word8
getByte BinHandle
bh; forall (f :: * -> *) a. Applicative f => a -> f a
pure forall a b. (a -> b) -> a -> b
$! (forall a. Enum a => TypeIndex -> a
toEnum (forall a b. (Integral a, Num b) => a -> b
fromIntegral Word8
x))

-- | A node annotation
data NodeAnnotation = NodeAnnotation
   { NodeAnnotation -> FastString
nodeAnnotConstr :: !FastString -- ^ name of the AST node constructor
   , NodeAnnotation -> FastString
nodeAnnotType   :: !FastString -- ^ name of the AST node Type
   }
   deriving (NodeAnnotation -> NodeAnnotation -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: NodeAnnotation -> NodeAnnotation -> Bool
$c/= :: NodeAnnotation -> NodeAnnotation -> Bool
== :: NodeAnnotation -> NodeAnnotation -> Bool
$c== :: NodeAnnotation -> NodeAnnotation -> Bool
Eq)

instance Ord NodeAnnotation where
   compare :: NodeAnnotation -> NodeAnnotation -> Ordering
compare (NodeAnnotation FastString
c0 FastString
t0) (NodeAnnotation FastString
c1 FastString
t1)
      = forall a. Monoid a => [a] -> a
mconcat [FastString -> FastString -> Ordering
uniqCompareFS FastString
c0 FastString
c1, FastString -> FastString -> Ordering
uniqCompareFS FastString
t0 FastString
t1]

instance Outputable NodeAnnotation where
   ppr :: NodeAnnotation -> SDoc
ppr (NodeAnnotation FastString
c FastString
t) = forall a. Outputable a => a -> SDoc
ppr (FastString
c,FastString
t)

instance Binary NodeAnnotation where
  put_ :: BinHandle -> NodeAnnotation -> IO ()
put_ BinHandle
bh (NodeAnnotation FastString
c FastString
t) = do
    forall a. Binary a => BinHandle -> a -> IO ()
put_ BinHandle
bh FastString
c
    forall a. Binary a => BinHandle -> a -> IO ()
put_ BinHandle
bh FastString
t
  get :: BinHandle -> IO NodeAnnotation
get BinHandle
bh = FastString -> FastString -> NodeAnnotation
NodeAnnotation
    forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> forall a. Binary a => BinHandle -> IO a
get BinHandle
bh
    forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> forall a. Binary a => BinHandle -> IO a
get BinHandle
bh

-- | The information stored in one AST node.
--
-- The type parameter exists to provide flexibility in representation of types
-- (see Note [Efficient serialization of redundant type info]).
data NodeInfo a = NodeInfo
    { forall a. NodeInfo a -> Set NodeAnnotation
nodeAnnotations :: S.Set NodeAnnotation
    -- ^ Annotations

    , forall a. NodeInfo a -> [a]
nodeType :: [a]
    -- ^ The Haskell types of this node, if any.

    , forall a. NodeInfo a -> NodeIdentifiers a
nodeIdentifiers :: NodeIdentifiers a
    -- ^ All the identifiers and their details
    } deriving (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
<$ :: forall a b. a -> NodeInfo b -> NodeInfo a
$c<$ :: forall a b. a -> NodeInfo b -> NodeInfo a
fmap :: forall a b. (a -> b) -> NodeInfo a -> NodeInfo b
$cfmap :: forall a b. (a -> b) -> NodeInfo a -> NodeInfo b
Functor, forall a. Eq a => a -> NodeInfo a -> Bool
forall a. Num a => NodeInfo a -> a
forall a. Ord a => NodeInfo a -> a
forall m. Monoid m => NodeInfo m -> m
forall a. NodeInfo a -> Bool
forall a. NodeInfo a -> TypeIndex
forall a. NodeInfo a -> [a]
forall a. (a -> a -> a) -> NodeInfo a -> a
forall m a. Monoid m => (a -> m) -> NodeInfo a -> m
forall b a. (b -> a -> b) -> b -> NodeInfo a -> b
forall a b. (a -> b -> b) -> b -> NodeInfo a -> b
forall (t :: * -> *).
(forall m. Monoid m => t m -> m)
-> (forall m a. Monoid m => (a -> m) -> t a -> m)
-> (forall m a. Monoid m => (a -> m) -> t a -> m)
-> (forall a b. (a -> b -> b) -> b -> t a -> b)
-> (forall a b. (a -> b -> b) -> b -> t a -> b)
-> (forall b a. (b -> a -> b) -> b -> t a -> b)
-> (forall b a. (b -> a -> b) -> b -> t a -> b)
-> (forall a. (a -> a -> a) -> t a -> a)
-> (forall a. (a -> a -> a) -> t a -> a)
-> (forall a. t a -> [a])
-> (forall a. t a -> Bool)
-> (forall a. t a -> TypeIndex)
-> (forall a. Eq a => a -> t a -> Bool)
-> (forall a. Ord a => t a -> a)
-> (forall a. Ord a => t a -> a)
-> (forall a. Num a => t a -> a)
-> (forall a. Num a => t a -> a)
-> Foldable t
product :: forall a. Num a => NodeInfo a -> a
$cproduct :: forall a. Num a => NodeInfo a -> a
sum :: forall a. Num a => NodeInfo a -> a
$csum :: forall a. Num a => NodeInfo a -> a
minimum :: forall a. Ord a => NodeInfo a -> a
$cminimum :: forall a. Ord a => NodeInfo a -> a
maximum :: forall a. Ord a => NodeInfo a -> a
$cmaximum :: forall a. Ord a => NodeInfo a -> a
elem :: forall a. Eq a => a -> NodeInfo a -> Bool
$celem :: forall a. Eq a => a -> NodeInfo a -> Bool
length :: forall a. NodeInfo a -> TypeIndex
$clength :: forall a. NodeInfo a -> TypeIndex
null :: forall a. NodeInfo a -> Bool
$cnull :: forall a. NodeInfo a -> Bool
toList :: forall a. NodeInfo a -> [a]
$ctoList :: forall a. NodeInfo a -> [a]
foldl1 :: forall a. (a -> a -> a) -> NodeInfo a -> a
$cfoldl1 :: forall a. (a -> a -> a) -> NodeInfo a -> a
foldr1 :: forall a. (a -> a -> a) -> NodeInfo a -> a
$cfoldr1 :: forall a. (a -> a -> a) -> NodeInfo a -> a
foldl' :: forall b a. (b -> a -> b) -> b -> NodeInfo a -> b
$cfoldl' :: forall b a. (b -> a -> b) -> b -> NodeInfo a -> b
foldl :: forall b a. (b -> a -> b) -> b -> NodeInfo a -> b
$cfoldl :: forall b a. (b -> a -> b) -> b -> NodeInfo a -> b
foldr' :: forall a b. (a -> b -> b) -> b -> NodeInfo a -> b
$cfoldr' :: forall a b. (a -> b -> b) -> b -> NodeInfo a -> b
foldr :: forall a b. (a -> b -> b) -> b -> NodeInfo a -> b
$cfoldr :: forall a b. (a -> b -> b) -> b -> NodeInfo a -> b
foldMap' :: forall m a. Monoid m => (a -> m) -> NodeInfo a -> m
$cfoldMap' :: forall m a. Monoid m => (a -> m) -> NodeInfo a -> m
foldMap :: forall m a. Monoid m => (a -> m) -> NodeInfo a -> m
$cfoldMap :: forall m a. Monoid m => (a -> m) -> NodeInfo a -> m
fold :: forall m. Monoid m => NodeInfo m -> m
$cfold :: forall m. Monoid m => NodeInfo m -> m
Foldable, Functor NodeInfo
Foldable NodeInfo
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 :: forall (m :: * -> *) a. Monad m => NodeInfo (m a) -> m (NodeInfo a)
$csequence :: forall (m :: * -> *) a. Monad m => NodeInfo (m a) -> m (NodeInfo a)
mapM :: forall (m :: * -> *) a b.
Monad m =>
(a -> m b) -> NodeInfo a -> m (NodeInfo b)
$cmapM :: forall (m :: * -> *) a b.
Monad m =>
(a -> m b) -> NodeInfo a -> m (NodeInfo b)
sequenceA :: forall (f :: * -> *) a.
Applicative f =>
NodeInfo (f a) -> f (NodeInfo a)
$csequenceA :: forall (f :: * -> *) a.
Applicative f =>
NodeInfo (f a) -> f (NodeInfo a)
traverse :: forall (f :: * -> *) a b.
Applicative f =>
(a -> f b) -> NodeInfo a -> f (NodeInfo b)
$ctraverse :: forall (f :: * -> *) a b.
Applicative f =>
(a -> f b) -> NodeInfo a -> f (NodeInfo b)
Traversable)

instance Binary (NodeInfo TypeIndex) where
  put_ :: BinHandle -> NodeInfo TypeIndex -> IO ()
put_ BinHandle
bh NodeInfo TypeIndex
ni = do
    forall a. Binary a => BinHandle -> a -> IO ()
put_ BinHandle
bh forall a b. (a -> b) -> a -> b
$ forall a. Set a -> [a]
S.toAscList forall a b. (a -> b) -> a -> b
$ forall a. NodeInfo a -> Set NodeAnnotation
nodeAnnotations NodeInfo TypeIndex
ni
    forall a. Binary a => BinHandle -> a -> IO ()
put_ BinHandle
bh forall a b. (a -> b) -> a -> b
$ forall a. NodeInfo a -> [a]
nodeType NodeInfo TypeIndex
ni
    forall a. Binary a => BinHandle -> a -> IO ()
put_ BinHandle
bh forall a b. (a -> b) -> a -> b
$ forall k a. Map k a -> [(k, a)]
M.toList forall a b. (a -> b) -> a -> b
$ forall a. NodeInfo a -> NodeIdentifiers a
nodeIdentifiers NodeInfo TypeIndex
ni
  get :: BinHandle -> IO (NodeInfo TypeIndex)
get BinHandle
bh = forall a.
Set NodeAnnotation -> [a] -> NodeIdentifiers a -> NodeInfo a
NodeInfo
    forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap (forall a. [a] -> Set a
S.fromDistinctAscList) (forall a. Binary a => BinHandle -> IO a
get BinHandle
bh)
    forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> forall a. Binary a => BinHandle -> IO a
get BinHandle
bh
    forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap (forall k a. Ord k => [(k, a)] -> Map k a
M.fromList) (forall a. Binary a => BinHandle -> IO a
get BinHandle
bh)

instance Outputable a => Outputable (NodeInfo a) where
  ppr :: NodeInfo a -> SDoc
ppr (NodeInfo Set NodeAnnotation
anns [a]
typs NodeIdentifiers a
idents) = SDoc -> SDoc
braces forall a b. (a -> b) -> a -> b
$ [SDoc] -> SDoc
fsep forall a b. (a -> b) -> a -> b
$ SDoc -> [SDoc] -> [SDoc]
punctuate SDoc
", "
    [ SDoc -> SDoc
parens (String -> SDoc
text String
"annotations:" SDoc -> SDoc -> SDoc
<+> forall a. Outputable a => a -> SDoc
ppr Set NodeAnnotation
anns)
    , SDoc -> SDoc
parens (String -> SDoc
text String
"types:" SDoc -> SDoc -> SDoc
<+> forall a. Outputable a => a -> SDoc
ppr [a]
typs)
    , SDoc -> SDoc
parens (String -> SDoc
text String
"identifier info:" SDoc -> SDoc -> SDoc
<+> forall a. Outputable a => NodeIdentifiers a -> SDoc
pprNodeIdents NodeIdentifiers a
idents)
    ]

pprNodeIdents :: Outputable a => NodeIdentifiers a -> SDoc
pprNodeIdents :: forall a. Outputable a => NodeIdentifiers a -> SDoc
pprNodeIdents NodeIdentifiers a
ni = SDoc -> SDoc
braces forall a b. (a -> b) -> a -> b
$ [SDoc] -> SDoc
fsep forall a b. (a -> b) -> a -> b
$ SDoc -> [SDoc] -> [SDoc]
punctuate SDoc
", " forall a b. (a -> b) -> a -> b
$ forall a b. (a -> b) -> [a] -> [b]
map forall {a}. Outputable a => (Identifier, a) -> SDoc
go forall a b. (a -> b) -> a -> b
$ forall k a. Map k a -> [(k, a)]
M.toList NodeIdentifiers a
ni
  where
    go :: (Identifier, a) -> SDoc
go (Identifier
i,a
id) = SDoc -> SDoc
parens forall a b. (a -> b) -> a -> b
$ [SDoc] -> SDoc
hsep forall a b. (a -> b) -> a -> b
$ SDoc -> [SDoc] -> [SDoc]
punctuate SDoc
", " [Identifier -> SDoc
pprIdentifier Identifier
i, forall a. Outputable a => a -> SDoc
ppr a
id]

pprIdentifier :: Identifier -> SDoc
pprIdentifier :: Identifier -> SDoc
pprIdentifier (Left ModuleName
mod) = String -> SDoc
text String
"module" SDoc -> SDoc -> SDoc
<+> forall a. Outputable a => a -> SDoc
ppr ModuleName
mod
pprIdentifier (Right Name
name) = String -> SDoc
text String
"name" SDoc -> SDoc -> SDoc
<+> forall a. Outputable a => a -> SDoc
ppr Name
name

type Identifier = Either ModuleName Name

type NodeIdentifiers a = M.Map Identifier (IdentifierDetails a)

-- | Information associated with every identifier
--
-- We need to include types with identifiers because sometimes multiple
-- identifiers occur in the same span(Overloaded Record Fields and so on)
data IdentifierDetails a = IdentifierDetails
  { forall a. IdentifierDetails a -> Maybe a
identType :: Maybe a
  , forall a. IdentifierDetails a -> Set ContextInfo
identInfo :: S.Set ContextInfo
  } deriving (IdentifierDetails a -> IdentifierDetails a -> Bool
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, 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
<$ :: forall a b. a -> IdentifierDetails b -> IdentifierDetails a
$c<$ :: forall a b. a -> IdentifierDetails b -> IdentifierDetails a
fmap :: forall a b. (a -> b) -> IdentifierDetails a -> IdentifierDetails b
$cfmap :: forall a b. (a -> b) -> IdentifierDetails a -> IdentifierDetails b
Functor, forall a. Eq a => a -> IdentifierDetails a -> Bool
forall a. Num a => IdentifierDetails a -> a
forall a. Ord a => IdentifierDetails a -> a
forall m. Monoid m => IdentifierDetails m -> m
forall a. IdentifierDetails a -> Bool
forall a. IdentifierDetails a -> TypeIndex
forall a. IdentifierDetails a -> [a]
forall a. (a -> a -> a) -> IdentifierDetails a -> a
forall m a. Monoid m => (a -> m) -> IdentifierDetails a -> m
forall b a. (b -> a -> b) -> b -> IdentifierDetails a -> b
forall a b. (a -> b -> b) -> b -> IdentifierDetails a -> b
forall (t :: * -> *).
(forall m. Monoid m => t m -> m)
-> (forall m a. Monoid m => (a -> m) -> t a -> m)
-> (forall m a. Monoid m => (a -> m) -> t a -> m)
-> (forall a b. (a -> b -> b) -> b -> t a -> b)
-> (forall a b. (a -> b -> b) -> b -> t a -> b)
-> (forall b a. (b -> a -> b) -> b -> t a -> b)
-> (forall b a. (b -> a -> b) -> b -> t a -> b)
-> (forall a. (a -> a -> a) -> t a -> a)
-> (forall a. (a -> a -> a) -> t a -> a)
-> (forall a. t a -> [a])
-> (forall a. t a -> Bool)
-> (forall a. t a -> TypeIndex)
-> (forall a. Eq a => a -> t a -> Bool)
-> (forall a. Ord a => t a -> a)
-> (forall a. Ord a => t a -> a)
-> (forall a. Num a => t a -> a)
-> (forall a. Num a => t a -> a)
-> Foldable t
product :: forall a. Num a => IdentifierDetails a -> a
$cproduct :: forall a. Num a => IdentifierDetails a -> a
sum :: forall a. Num a => IdentifierDetails a -> a
$csum :: forall a. Num a => IdentifierDetails a -> a
minimum :: forall a. Ord a => IdentifierDetails a -> a
$cminimum :: forall a. Ord a => IdentifierDetails a -> a
maximum :: forall a. Ord a => IdentifierDetails a -> a
$cmaximum :: forall a. Ord a => IdentifierDetails a -> a
elem :: forall a. Eq a => a -> IdentifierDetails a -> Bool
$celem :: forall a. Eq a => a -> IdentifierDetails a -> Bool
length :: forall a. IdentifierDetails a -> TypeIndex
$clength :: forall a. IdentifierDetails a -> TypeIndex
null :: forall a. IdentifierDetails a -> Bool
$cnull :: forall a. IdentifierDetails a -> Bool
toList :: forall a. IdentifierDetails a -> [a]
$ctoList :: forall a. IdentifierDetails a -> [a]
foldl1 :: forall a. (a -> a -> a) -> IdentifierDetails a -> a
$cfoldl1 :: forall a. (a -> a -> a) -> IdentifierDetails a -> a
foldr1 :: forall a. (a -> a -> a) -> IdentifierDetails a -> a
$cfoldr1 :: forall a. (a -> a -> a) -> IdentifierDetails a -> a
foldl' :: forall b a. (b -> a -> b) -> b -> IdentifierDetails a -> b
$cfoldl' :: forall b a. (b -> a -> b) -> b -> IdentifierDetails a -> b
foldl :: forall b a. (b -> a -> b) -> b -> IdentifierDetails a -> b
$cfoldl :: forall b a. (b -> a -> b) -> b -> IdentifierDetails a -> b
foldr' :: forall a b. (a -> b -> b) -> b -> IdentifierDetails a -> b
$cfoldr' :: forall a b. (a -> b -> b) -> b -> IdentifierDetails a -> b
foldr :: forall a b. (a -> b -> b) -> b -> IdentifierDetails a -> b
$cfoldr :: forall a b. (a -> b -> b) -> b -> IdentifierDetails a -> b
foldMap' :: forall m a. Monoid m => (a -> m) -> IdentifierDetails a -> m
$cfoldMap' :: forall m a. Monoid m => (a -> m) -> IdentifierDetails a -> m
foldMap :: forall m a. Monoid m => (a -> m) -> IdentifierDetails a -> m
$cfoldMap :: forall m a. Monoid m => (a -> m) -> IdentifierDetails a -> m
fold :: forall m. Monoid m => IdentifierDetails m -> m
$cfold :: forall m. Monoid m => IdentifierDetails m -> m
Foldable, Functor IdentifierDetails
Foldable IdentifierDetails
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 :: forall (m :: * -> *) a.
Monad m =>
IdentifierDetails (m a) -> m (IdentifierDetails a)
$csequence :: forall (m :: * -> *) a.
Monad m =>
IdentifierDetails (m a) -> m (IdentifierDetails a)
mapM :: forall (m :: * -> *) a b.
Monad m =>
(a -> m b) -> IdentifierDetails a -> m (IdentifierDetails b)
$cmapM :: forall (m :: * -> *) a b.
Monad m =>
(a -> m b) -> IdentifierDetails a -> m (IdentifierDetails b)
sequenceA :: forall (f :: * -> *) a.
Applicative f =>
IdentifierDetails (f a) -> f (IdentifierDetails a)
$csequenceA :: forall (f :: * -> *) a.
Applicative f =>
IdentifierDetails (f a) -> f (IdentifierDetails a)
traverse :: forall (f :: * -> *) a b.
Applicative f =>
(a -> f b) -> IdentifierDetails a -> f (IdentifierDetails b)
$ctraverse :: forall (f :: * -> *) a b.
Applicative f =>
(a -> f b) -> IdentifierDetails a -> f (IdentifierDetails b)
Traversable)

instance Outputable a => Outputable (IdentifierDetails a) where
  ppr :: IdentifierDetails a -> SDoc
ppr IdentifierDetails a
x = String -> SDoc
text String
"Details: " SDoc -> SDoc -> SDoc
<+> forall a. Outputable a => a -> SDoc
ppr (forall a. IdentifierDetails a -> Maybe a
identType IdentifierDetails a
x) SDoc -> SDoc -> SDoc
<+> forall a. Outputable a => a -> SDoc
ppr (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 = forall a. Maybe a -> Set ContextInfo -> IdentifierDetails a
IdentifierDetails (forall a. IdentifierDetails a -> Maybe a
identType IdentifierDetails a
d1 forall (f :: * -> *) a. Alternative f => f a -> f a -> f a
<|> forall a. IdentifierDetails a -> Maybe a
identType IdentifierDetails a
d2)
                               (forall a. Ord a => Set a -> Set a -> Set a
S.union (forall a. IdentifierDetails a -> Set ContextInfo
identInfo IdentifierDetails a
d1) (forall a. IdentifierDetails a -> Set ContextInfo
identInfo IdentifierDetails a
d2))

instance Monoid (IdentifierDetails a) where
  mempty :: IdentifierDetails a
mempty = forall a. Maybe a -> Set ContextInfo -> IdentifierDetails a
IdentifierDetails forall a. Maybe a
Nothing forall a. Set a
S.empty

instance Binary (IdentifierDetails TypeIndex) where
  put_ :: BinHandle -> IdentifierDetails TypeIndex -> IO ()
put_ BinHandle
bh IdentifierDetails TypeIndex
dets = do
    forall a. Binary a => BinHandle -> a -> IO ()
put_ BinHandle
bh forall a b. (a -> b) -> a -> b
$ forall a. IdentifierDetails a -> Maybe a
identType IdentifierDetails TypeIndex
dets
    forall a. Binary a => BinHandle -> a -> IO ()
put_ BinHandle
bh forall a b. (a -> b) -> a -> b
$ forall a. Set a -> [a]
S.toList forall a b. (a -> b) -> a -> b
$ forall a. IdentifierDetails a -> Set ContextInfo
identInfo IdentifierDetails TypeIndex
dets
  get :: BinHandle -> IO (IdentifierDetails TypeIndex)
get BinHandle
bh =  forall a. Maybe a -> Set ContextInfo -> IdentifierDetails a
IdentifierDetails
    forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> forall a. Binary a => BinHandle -> IO a
get BinHandle
bh
    forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap forall a. [a] -> Set a
S.fromDistinctAscList (forall a. Binary a => BinHandle -> IO a
get BinHandle
bh)


-- | Different contexts under which identifiers exist
data ContextInfo
  = Use                -- ^ regular variable
  | MatchBind
  | IEThing IEType     -- ^ import/export
  | TyDecl

  -- | Value binding
  | ValBind
      BindType     -- ^ whether or not the binding is in an instance
      Scope        -- ^ scope over which the value is bound
      (Maybe Span) -- ^ span of entire binding

  -- | Pattern binding
  --
  -- This case is tricky because the bound identifier can be used in two
  -- distinct scopes. Consider the following example (with @-XViewPatterns@)
  --
  -- @
  -- do (b, a, (a -> True)) <- bar
  --    foo a
  -- @
  --
  -- The identifier @a@ has two scopes: in the view pattern @(a -> True)@ and
  -- in the rest of the @do@-block in @foo a@.
  | PatternBind
      Scope        -- ^ scope /in the pattern/ (the variable bound can be used
                   -- further in the pattern)
      Scope        -- ^ rest of the scope outside the pattern
      (Maybe Span) -- ^ span of entire binding

  | ClassTyDecl (Maybe Span)

  -- | Declaration
  | Decl
      DeclType     -- ^ type of declaration
      (Maybe Span) -- ^ span of entire binding

  -- | Type variable
  | TyVarBind Scope TyVarScope

  -- | Record field
  | RecField RecFieldContext (Maybe Span)
  -- | Constraint/Dictionary evidence variable binding
  | EvidenceVarBind
      EvVarSource  -- ^ how did this bind come into being
      Scope        -- ^ scope over which the value is bound
      (Maybe Span) -- ^ span of the binding site

  -- | Usage of evidence variable
  | EvidenceVarUse
    deriving (ContextInfo -> ContextInfo -> Bool
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
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
Ord)

instance Outputable ContextInfo where
 ppr :: ContextInfo -> SDoc
ppr (ContextInfo
Use) = String -> SDoc
text String
"usage"
 ppr (ContextInfo
MatchBind) = String -> SDoc
text String
"LHS of a match group"
 ppr (IEThing IEType
x) = forall a. Outputable a => a -> SDoc
ppr IEType
x
 ppr (ContextInfo
TyDecl) = String -> SDoc
text String
"bound in a type signature declaration"
 ppr (ValBind BindType
t Scope
sc Maybe Span
sp) =
   forall a. Outputable a => a -> SDoc
ppr BindType
t SDoc -> SDoc -> SDoc
<+> String -> SDoc
text String
"value bound with scope:" SDoc -> SDoc -> SDoc
<+> forall a. Outputable a => a -> SDoc
ppr Scope
sc SDoc -> SDoc -> SDoc
<+> Maybe Span -> SDoc
pprBindSpan Maybe Span
sp
 ppr (PatternBind Scope
sc1 Scope
sc2 Maybe Span
sp) =
   String -> SDoc
text String
"bound in a pattern with scope:"
     SDoc -> SDoc -> SDoc
<+> forall a. Outputable a => a -> SDoc
ppr Scope
sc1 SDoc -> SDoc -> SDoc
<+> SDoc
"," SDoc -> SDoc -> SDoc
<+> forall a. Outputable a => a -> SDoc
ppr Scope
sc2
     SDoc -> SDoc -> SDoc
<+> Maybe Span -> SDoc
pprBindSpan Maybe Span
sp
 ppr (ClassTyDecl Maybe Span
sp) =
   String -> SDoc
text String
"bound in a class type declaration" SDoc -> SDoc -> SDoc
<+> Maybe Span -> SDoc
pprBindSpan Maybe Span
sp
 ppr (Decl DeclType
d Maybe Span
sp) =
   String -> SDoc
text String
"declaration of" SDoc -> SDoc -> SDoc
<+> forall a. Outputable a => a -> SDoc
ppr DeclType
d SDoc -> SDoc -> SDoc
<+> Maybe Span -> SDoc
pprBindSpan Maybe Span
sp
 ppr (TyVarBind Scope
sc1 TyVarScope
sc2) =
   String -> SDoc
text String
"type variable binding with scope:"
     SDoc -> SDoc -> SDoc
<+> forall a. Outputable a => a -> SDoc
ppr Scope
sc1 SDoc -> SDoc -> SDoc
<+> SDoc
"," SDoc -> SDoc -> SDoc
<+> forall a. Outputable a => a -> SDoc
ppr TyVarScope
sc2
 ppr (RecField RecFieldContext
ctx Maybe Span
sp) =
   String -> SDoc
text String
"record field" SDoc -> SDoc -> SDoc
<+> forall a. Outputable a => a -> SDoc
ppr RecFieldContext
ctx SDoc -> SDoc -> SDoc
<+> Maybe Span -> SDoc
pprBindSpan Maybe Span
sp
 ppr (EvidenceVarBind EvVarSource
ctx Scope
sc Maybe Span
sp) =
   String -> SDoc
text String
"evidence variable" SDoc -> SDoc -> SDoc
<+> forall a. Outputable a => a -> SDoc
ppr EvVarSource
ctx
     SDoc -> SDoc -> SDoc
$$ SDoc
"with scope:" SDoc -> SDoc -> SDoc
<+> forall a. Outputable a => a -> SDoc
ppr Scope
sc
     SDoc -> SDoc -> SDoc
$$ Maybe Span -> SDoc
pprBindSpan Maybe Span
sp
 ppr (ContextInfo
EvidenceVarUse) =
   String -> SDoc
text String
"usage of evidence variable"

pprBindSpan :: Maybe Span -> SDoc
pprBindSpan :: Maybe Span -> SDoc
pprBindSpan Maybe Span
Nothing = String -> SDoc
text String
""
pprBindSpan (Just Span
sp) = String -> SDoc
text String
"bound at:" SDoc -> SDoc -> SDoc
<+> forall a. Outputable a => a -> SDoc
ppr Span
sp

instance Binary ContextInfo where
  put_ :: BinHandle -> ContextInfo -> IO ()
put_ BinHandle
bh ContextInfo
Use = BinHandle -> Word8 -> IO ()
putByte BinHandle
bh Word8
0
  put_ BinHandle
bh (IEThing IEType
t) = do
    BinHandle -> Word8 -> IO ()
putByte BinHandle
bh Word8
1
    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
    forall a. Binary a => BinHandle -> a -> IO ()
put_ BinHandle
bh BindType
bt
    forall a. Binary a => BinHandle -> a -> IO ()
put_ BinHandle
bh Scope
sc
    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
    forall a. Binary a => BinHandle -> a -> IO ()
put_ BinHandle
bh Scope
a
    forall a. Binary a => BinHandle -> a -> IO ()
put_ BinHandle
bh Scope
b
    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
    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
    forall a. Binary a => BinHandle -> a -> IO ()
put_ BinHandle
bh DeclType
a
    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
    forall a. Binary a => BinHandle -> a -> IO ()
put_ BinHandle
bh Scope
a
    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
    forall a. Binary a => BinHandle -> a -> IO ()
put_ BinHandle
bh RecFieldContext
a
    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
  put_ BinHandle
bh (EvidenceVarBind EvVarSource
a Scope
b Maybe Span
c) = do
    BinHandle -> Word8 -> IO ()
putByte BinHandle
bh Word8
10
    forall a. Binary a => BinHandle -> a -> IO ()
put_ BinHandle
bh EvVarSource
a
    forall a. Binary a => BinHandle -> a -> IO ()
put_ BinHandle
bh Scope
b
    forall a. Binary a => BinHandle -> a -> IO ()
put_ BinHandle
bh Maybe Span
c
  put_ BinHandle
bh ContextInfo
EvidenceVarUse = BinHandle -> Word8 -> IO ()
putByte BinHandle
bh Word8
11

  get :: BinHandle -> IO ContextInfo
get BinHandle
bh = do
    (Word8
t :: Word8) <- forall a. Binary a => BinHandle -> IO a
get BinHandle
bh
    case Word8
t of
      Word8
0 -> forall (m :: * -> *) a. Monad m => a -> m a
return ContextInfo
Use
      Word8
1 -> IEType -> ContextInfo
IEThing forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> forall a. Binary a => BinHandle -> IO a
get BinHandle
bh
      Word8
2 -> forall (m :: * -> *) a. Monad m => a -> m a
return ContextInfo
TyDecl
      Word8
3 -> BindType -> Scope -> Maybe Span -> ContextInfo
ValBind forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> forall a. Binary a => BinHandle -> IO a
get BinHandle
bh forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> forall a. Binary a => BinHandle -> IO a
get BinHandle
bh forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> forall a. Binary a => BinHandle -> IO a
get BinHandle
bh
      Word8
4 -> Scope -> Scope -> Maybe Span -> ContextInfo
PatternBind forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> forall a. Binary a => BinHandle -> IO a
get BinHandle
bh forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> forall a. Binary a => BinHandle -> IO a
get BinHandle
bh forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> forall a. Binary a => BinHandle -> IO a
get BinHandle
bh
      Word8
5 -> Maybe Span -> ContextInfo
ClassTyDecl forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> forall a. Binary a => BinHandle -> IO a
get BinHandle
bh
      Word8
6 -> DeclType -> Maybe Span -> ContextInfo
Decl forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> forall a. Binary a => BinHandle -> IO a
get BinHandle
bh forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> forall a. Binary a => BinHandle -> IO a
get BinHandle
bh
      Word8
7 -> Scope -> TyVarScope -> ContextInfo
TyVarBind forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> forall a. Binary a => BinHandle -> IO a
get BinHandle
bh forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> forall a. Binary a => BinHandle -> IO a
get BinHandle
bh
      Word8
8 -> RecFieldContext -> Maybe Span -> ContextInfo
RecField forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> forall a. Binary a => BinHandle -> IO a
get BinHandle
bh forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> forall a. Binary a => BinHandle -> IO a
get BinHandle
bh
      Word8
9 -> forall (m :: * -> *) a. Monad m => a -> m a
return ContextInfo
MatchBind
      Word8
10 -> EvVarSource -> Scope -> Maybe Span -> ContextInfo
EvidenceVarBind forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> forall a. Binary a => BinHandle -> IO a
get BinHandle
bh forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> forall a. Binary a => BinHandle -> IO a
get BinHandle
bh forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> forall a. Binary a => BinHandle -> IO a
get BinHandle
bh
      Word8
11 -> forall (m :: * -> *) a. Monad m => a -> m a
return ContextInfo
EvidenceVarUse
      Word8
_ -> forall a. String -> a
panic String
"Binary ContextInfo: invalid tag"

data EvVarSource
  = EvPatternBind -- ^ bound by a pattern match
  | EvSigBind -- ^ bound by a type signature
  | EvWrapperBind -- ^ bound by a hswrapper
  | EvImplicitBind -- ^ bound by an implicit variable
  | EvInstBind { EvVarSource -> Bool
isSuperInst :: Bool, EvVarSource -> Name
cls :: Name } -- ^ Bound by some instance of given class
  | EvLetBind EvBindDeps -- ^ A direct let binding
  deriving (EvVarSource -> EvVarSource -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: EvVarSource -> EvVarSource -> Bool
$c/= :: EvVarSource -> EvVarSource -> Bool
== :: EvVarSource -> EvVarSource -> Bool
$c== :: EvVarSource -> EvVarSource -> Bool
Eq,Eq EvVarSource
EvVarSource -> EvVarSource -> Bool
EvVarSource -> EvVarSource -> Ordering
EvVarSource -> EvVarSource -> EvVarSource
forall a.
Eq a
-> (a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
min :: EvVarSource -> EvVarSource -> EvVarSource
$cmin :: EvVarSource -> EvVarSource -> EvVarSource
max :: EvVarSource -> EvVarSource -> EvVarSource
$cmax :: EvVarSource -> EvVarSource -> EvVarSource
>= :: EvVarSource -> EvVarSource -> Bool
$c>= :: EvVarSource -> EvVarSource -> Bool
> :: EvVarSource -> EvVarSource -> Bool
$c> :: EvVarSource -> EvVarSource -> Bool
<= :: EvVarSource -> EvVarSource -> Bool
$c<= :: EvVarSource -> EvVarSource -> Bool
< :: EvVarSource -> EvVarSource -> Bool
$c< :: EvVarSource -> EvVarSource -> Bool
compare :: EvVarSource -> EvVarSource -> Ordering
$ccompare :: EvVarSource -> EvVarSource -> Ordering
Ord)

instance Binary EvVarSource where
  put_ :: BinHandle -> EvVarSource -> IO ()
put_ BinHandle
bh EvVarSource
EvPatternBind = BinHandle -> Word8 -> IO ()
putByte BinHandle
bh Word8
0
  put_ BinHandle
bh EvVarSource
EvSigBind = BinHandle -> Word8 -> IO ()
putByte BinHandle
bh Word8
1
  put_ BinHandle
bh EvVarSource
EvWrapperBind = BinHandle -> Word8 -> IO ()
putByte BinHandle
bh Word8
2
  put_ BinHandle
bh EvVarSource
EvImplicitBind = BinHandle -> Word8 -> IO ()
putByte BinHandle
bh Word8
3
  put_ BinHandle
bh (EvInstBind Bool
b Name
cls) = do
    BinHandle -> Word8 -> IO ()
putByte BinHandle
bh Word8
4
    forall a. Binary a => BinHandle -> a -> IO ()
put_ BinHandle
bh Bool
b
    forall a. Binary a => BinHandle -> a -> IO ()
put_ BinHandle
bh Name
cls
  put_ BinHandle
bh (EvLetBind EvBindDeps
deps) = do
    BinHandle -> Word8 -> IO ()
putByte BinHandle
bh Word8
5
    forall a. Binary a => BinHandle -> a -> IO ()
put_ BinHandle
bh EvBindDeps
deps

  get :: BinHandle -> IO EvVarSource
get BinHandle
bh = do
    (Word8
t :: Word8) <- forall a. Binary a => BinHandle -> IO a
get BinHandle
bh
    case Word8
t of
      Word8
0 -> forall (f :: * -> *) a. Applicative f => a -> f a
pure EvVarSource
EvPatternBind
      Word8
1 -> forall (f :: * -> *) a. Applicative f => a -> f a
pure EvVarSource
EvSigBind
      Word8
2 -> forall (f :: * -> *) a. Applicative f => a -> f a
pure EvVarSource
EvWrapperBind
      Word8
3 -> forall (f :: * -> *) a. Applicative f => a -> f a
pure EvVarSource
EvImplicitBind
      Word8
4 -> Bool -> Name -> EvVarSource
EvInstBind forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> forall a. Binary a => BinHandle -> IO a
get BinHandle
bh forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> forall a. Binary a => BinHandle -> IO a
get BinHandle
bh
      Word8
5 -> EvBindDeps -> EvVarSource
EvLetBind forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> forall a. Binary a => BinHandle -> IO a
get BinHandle
bh
      Word8
_ -> forall a. String -> a
panic String
"Binary EvVarSource: invalid tag"

instance Outputable EvVarSource where
  ppr :: EvVarSource -> SDoc
ppr EvVarSource
EvPatternBind = String -> SDoc
text String
"bound by a pattern"
  ppr EvVarSource
EvSigBind = String -> SDoc
text String
"bound by a type signature"
  ppr EvVarSource
EvWrapperBind = String -> SDoc
text String
"bound by a HsWrapper"
  ppr EvVarSource
EvImplicitBind = String -> SDoc
text String
"bound by an implicit variable binding"
  ppr (EvInstBind Bool
False Name
cls) = String -> SDoc
text String
"bound by an instance of class" SDoc -> SDoc -> SDoc
<+> forall a. Outputable a => a -> SDoc
ppr Name
cls
  ppr (EvInstBind Bool
True Name
cls) = String -> SDoc
text String
"bound due to a superclass of " SDoc -> SDoc -> SDoc
<+> forall a. Outputable a => a -> SDoc
ppr Name
cls
  ppr (EvLetBind EvBindDeps
deps) = String -> SDoc
text String
"bound by a let, depending on:" SDoc -> SDoc -> SDoc
<+> forall a. Outputable a => a -> SDoc
ppr EvBindDeps
deps

-- | Eq/Ord instances compare on the converted HieName,
-- as non-exported names may have different uniques after
-- a roundtrip
newtype EvBindDeps = EvBindDeps { EvBindDeps -> [Name]
getEvBindDeps :: [Name] }
  deriving EvBindDeps -> SDoc
forall a. (a -> SDoc) -> Outputable a
ppr :: EvBindDeps -> SDoc
$cppr :: EvBindDeps -> SDoc
Outputable

instance Eq EvBindDeps where
  == :: EvBindDeps -> EvBindDeps -> Bool
(==) = coerce :: forall a b. Coercible a b => a -> b
coerce (forall a. Eq a => a -> a -> Bool
(==) forall b c a. (b -> b -> c) -> (a -> b) -> a -> a -> c
`on` forall a b. (a -> b) -> [a] -> [b]
map Name -> HieName
toHieName)

instance Ord EvBindDeps where
  compare :: EvBindDeps -> EvBindDeps -> Ordering
compare = coerce :: forall a b. Coercible a b => a -> b
coerce (forall a. Ord a => a -> a -> Ordering
compare forall b c a. (b -> b -> c) -> (a -> b) -> a -> a -> c
`on` forall a b. (a -> b) -> [a] -> [b]
map Name -> HieName
toHieName)

instance Binary EvBindDeps where
  put_ :: BinHandle -> EvBindDeps -> IO ()
put_ BinHandle
bh (EvBindDeps [Name]
xs) = forall a. Binary a => BinHandle -> a -> IO ()
put_ BinHandle
bh [Name]
xs
  get :: BinHandle -> IO EvBindDeps
get BinHandle
bh = [Name] -> EvBindDeps
EvBindDeps forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> forall a. Binary a => BinHandle -> IO a
get BinHandle
bh


-- | Types of imports and exports
data IEType
  = Import
  | ImportAs
  | ImportHiding
  | Export
    deriving (IEType -> IEType -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: IEType -> IEType -> Bool
$c/= :: IEType -> IEType -> Bool
== :: IEType -> IEType -> Bool
$c== :: IEType -> IEType -> Bool
Eq, TypeIndex -> IEType
IEType -> TypeIndex
IEType -> [IEType]
IEType -> IEType
IEType -> IEType -> [IEType]
IEType -> IEType -> IEType -> [IEType]
forall a.
(a -> a)
-> (a -> a)
-> (TypeIndex -> a)
-> (a -> TypeIndex)
-> (a -> [a])
-> (a -> a -> [a])
-> (a -> a -> [a])
-> (a -> a -> a -> [a])
-> Enum a
enumFromThenTo :: IEType -> IEType -> IEType -> [IEType]
$cenumFromThenTo :: IEType -> IEType -> IEType -> [IEType]
enumFromTo :: IEType -> IEType -> [IEType]
$cenumFromTo :: IEType -> IEType -> [IEType]
enumFromThen :: IEType -> IEType -> [IEType]
$cenumFromThen :: IEType -> IEType -> [IEType]
enumFrom :: IEType -> [IEType]
$cenumFrom :: IEType -> [IEType]
fromEnum :: IEType -> TypeIndex
$cfromEnum :: IEType -> TypeIndex
toEnum :: TypeIndex -> IEType
$ctoEnum :: TypeIndex -> IEType
pred :: IEType -> IEType
$cpred :: IEType -> IEType
succ :: IEType -> IEType
$csucc :: IEType -> IEType
Enum, Eq 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
Ord)

instance Outputable IEType where
  ppr :: IEType -> SDoc
ppr IEType
Import = String -> SDoc
text String
"import"
  ppr IEType
ImportAs = String -> SDoc
text String
"import as"
  ppr IEType
ImportHiding = String -> SDoc
text String
"import hiding"
  ppr IEType
Export = String -> SDoc
text String
"export"

instance Binary IEType where
  put_ :: BinHandle -> IEType -> IO ()
put_ BinHandle
bh IEType
b = BinHandle -> Word8 -> IO ()
putByte BinHandle
bh (forall a b. (Integral a, Num b) => a -> b
fromIntegral (forall a. Enum a => a -> TypeIndex
fromEnum IEType
b))
  get :: BinHandle -> IO IEType
get BinHandle
bh = do Word8
x <- BinHandle -> IO Word8
getByte BinHandle
bh; forall (f :: * -> *) a. Applicative f => a -> f a
pure forall a b. (a -> b) -> a -> b
$! (forall a. Enum a => TypeIndex -> a
toEnum (forall a b. (Integral a, Num b) => a -> b
fromIntegral Word8
x))


data RecFieldContext
  = RecFieldDecl
  | RecFieldAssign
  | RecFieldMatch
  | RecFieldOcc
    deriving (RecFieldContext -> RecFieldContext -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: RecFieldContext -> RecFieldContext -> Bool
$c/= :: RecFieldContext -> RecFieldContext -> Bool
== :: RecFieldContext -> RecFieldContext -> Bool
$c== :: RecFieldContext -> RecFieldContext -> Bool
Eq, TypeIndex -> RecFieldContext
RecFieldContext -> TypeIndex
RecFieldContext -> [RecFieldContext]
RecFieldContext -> RecFieldContext
RecFieldContext -> RecFieldContext -> [RecFieldContext]
RecFieldContext
-> RecFieldContext -> RecFieldContext -> [RecFieldContext]
forall a.
(a -> a)
-> (a -> a)
-> (TypeIndex -> a)
-> (a -> TypeIndex)
-> (a -> [a])
-> (a -> a -> [a])
-> (a -> a -> [a])
-> (a -> a -> a -> [a])
-> Enum a
enumFromThenTo :: RecFieldContext
-> RecFieldContext -> RecFieldContext -> [RecFieldContext]
$cenumFromThenTo :: RecFieldContext
-> RecFieldContext -> RecFieldContext -> [RecFieldContext]
enumFromTo :: RecFieldContext -> RecFieldContext -> [RecFieldContext]
$cenumFromTo :: RecFieldContext -> RecFieldContext -> [RecFieldContext]
enumFromThen :: RecFieldContext -> RecFieldContext -> [RecFieldContext]
$cenumFromThen :: RecFieldContext -> RecFieldContext -> [RecFieldContext]
enumFrom :: RecFieldContext -> [RecFieldContext]
$cenumFrom :: RecFieldContext -> [RecFieldContext]
fromEnum :: RecFieldContext -> TypeIndex
$cfromEnum :: RecFieldContext -> TypeIndex
toEnum :: TypeIndex -> RecFieldContext
$ctoEnum :: TypeIndex -> RecFieldContext
pred :: RecFieldContext -> RecFieldContext
$cpred :: RecFieldContext -> RecFieldContext
succ :: RecFieldContext -> RecFieldContext
$csucc :: RecFieldContext -> RecFieldContext
Enum, Eq 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
Ord)

instance Outputable RecFieldContext where
  ppr :: RecFieldContext -> SDoc
ppr RecFieldContext
RecFieldDecl = String -> SDoc
text String
"declaration"
  ppr RecFieldContext
RecFieldAssign = String -> SDoc
text String
"assignment"
  ppr RecFieldContext
RecFieldMatch = String -> SDoc
text String
"pattern match"
  ppr RecFieldContext
RecFieldOcc = String -> SDoc
text String
"occurence"

instance Binary RecFieldContext where
  put_ :: BinHandle -> RecFieldContext -> IO ()
put_ BinHandle
bh RecFieldContext
b = BinHandle -> Word8 -> IO ()
putByte BinHandle
bh (forall a b. (Integral a, Num b) => a -> b
fromIntegral (forall a. Enum a => a -> TypeIndex
fromEnum RecFieldContext
b))
  get :: BinHandle -> IO RecFieldContext
get BinHandle
bh = do Word8
x <- BinHandle -> IO Word8
getByte BinHandle
bh; forall (f :: * -> *) a. Applicative f => a -> f a
pure forall a b. (a -> b) -> a -> b
$! (forall a. Enum a => TypeIndex -> a
toEnum (forall a b. (Integral a, Num b) => a -> b
fromIntegral Word8
x))


data BindType
  = RegularBind
  | InstanceBind
    deriving (BindType -> BindType -> Bool
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
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
Ord, TypeIndex -> BindType
BindType -> TypeIndex
BindType -> [BindType]
BindType -> BindType
BindType -> BindType -> [BindType]
BindType -> BindType -> BindType -> [BindType]
forall a.
(a -> a)
-> (a -> a)
-> (TypeIndex -> a)
-> (a -> TypeIndex)
-> (a -> [a])
-> (a -> a -> [a])
-> (a -> a -> [a])
-> (a -> a -> a -> [a])
-> Enum a
enumFromThenTo :: BindType -> BindType -> BindType -> [BindType]
$cenumFromThenTo :: BindType -> BindType -> BindType -> [BindType]
enumFromTo :: BindType -> BindType -> [BindType]
$cenumFromTo :: BindType -> BindType -> [BindType]
enumFromThen :: BindType -> BindType -> [BindType]
$cenumFromThen :: BindType -> BindType -> [BindType]
enumFrom :: BindType -> [BindType]
$cenumFrom :: BindType -> [BindType]
fromEnum :: BindType -> TypeIndex
$cfromEnum :: BindType -> TypeIndex
toEnum :: TypeIndex -> BindType
$ctoEnum :: TypeIndex -> BindType
pred :: BindType -> BindType
$cpred :: BindType -> BindType
succ :: BindType -> BindType
$csucc :: BindType -> BindType
Enum)

instance Outputable BindType where
  ppr :: BindType -> SDoc
ppr BindType
RegularBind = SDoc
"regular"
  ppr BindType
InstanceBind = SDoc
"instance"

instance Binary BindType where
  put_ :: BinHandle -> BindType -> IO ()
put_ BinHandle
bh BindType
b = BinHandle -> Word8 -> IO ()
putByte BinHandle
bh (forall a b. (Integral a, Num b) => a -> b
fromIntegral (forall a. Enum a => a -> TypeIndex
fromEnum BindType
b))
  get :: BinHandle -> IO BindType
get BinHandle
bh = do Word8
x <- BinHandle -> IO Word8
getByte BinHandle
bh; forall (f :: * -> *) a. Applicative f => a -> f a
pure forall a b. (a -> b) -> a -> b
$! (forall a. Enum a => TypeIndex -> a
toEnum (forall a b. (Integral a, Num b) => a -> b
fromIntegral Word8
x))

data DeclType
  = FamDec     -- ^ type or data family
  | SynDec     -- ^ type synonym
  | DataDec    -- ^ data declaration
  | ConDec     -- ^ constructor declaration
  | PatSynDec  -- ^ pattern synonym
  | ClassDec   -- ^ class declaration
  | InstDec    -- ^ instance declaration
    deriving (DeclType -> DeclType -> Bool
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
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
Ord, TypeIndex -> DeclType
DeclType -> TypeIndex
DeclType -> [DeclType]
DeclType -> DeclType
DeclType -> DeclType -> [DeclType]
DeclType -> DeclType -> DeclType -> [DeclType]
forall a.
(a -> a)
-> (a -> a)
-> (TypeIndex -> a)
-> (a -> TypeIndex)
-> (a -> [a])
-> (a -> a -> [a])
-> (a -> a -> [a])
-> (a -> a -> a -> [a])
-> Enum a
enumFromThenTo :: DeclType -> DeclType -> DeclType -> [DeclType]
$cenumFromThenTo :: DeclType -> DeclType -> DeclType -> [DeclType]
enumFromTo :: DeclType -> DeclType -> [DeclType]
$cenumFromTo :: DeclType -> DeclType -> [DeclType]
enumFromThen :: DeclType -> DeclType -> [DeclType]
$cenumFromThen :: DeclType -> DeclType -> [DeclType]
enumFrom :: DeclType -> [DeclType]
$cenumFrom :: DeclType -> [DeclType]
fromEnum :: DeclType -> TypeIndex
$cfromEnum :: DeclType -> TypeIndex
toEnum :: TypeIndex -> DeclType
$ctoEnum :: TypeIndex -> DeclType
pred :: DeclType -> DeclType
$cpred :: DeclType -> DeclType
succ :: DeclType -> DeclType
$csucc :: DeclType -> DeclType
Enum)

instance Outputable DeclType where
  ppr :: DeclType -> SDoc
ppr DeclType
FamDec = String -> SDoc
text String
"type or data family"
  ppr DeclType
SynDec = String -> SDoc
text String
"type synonym"
  ppr DeclType
DataDec = String -> SDoc
text String
"data"
  ppr DeclType
ConDec = String -> SDoc
text String
"constructor"
  ppr DeclType
PatSynDec = String -> SDoc
text String
"pattern synonym"
  ppr DeclType
ClassDec = String -> SDoc
text String
"class"
  ppr DeclType
InstDec = String -> SDoc
text String
"instance"

instance Binary DeclType where
  put_ :: BinHandle -> DeclType -> IO ()
put_ BinHandle
bh DeclType
b = BinHandle -> Word8 -> IO ()
putByte BinHandle
bh (forall a b. (Integral a, Num b) => a -> b
fromIntegral (forall a. Enum a => a -> TypeIndex
fromEnum DeclType
b))
  get :: BinHandle -> IO DeclType
get BinHandle
bh = do Word8
x <- BinHandle -> IO Word8
getByte BinHandle
bh; forall (f :: * -> *) a. Applicative f => a -> f a
pure forall a b. (a -> b) -> a -> b
$! (forall a. Enum a => TypeIndex -> a
toEnum (forall a b. (Integral a, Num b) => a -> b
fromIntegral Word8
x))

data Scope
  = NoScope
  | LocalScope Span
  | ModuleScope
    deriving (Scope -> Scope -> Bool
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
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
Ord, Typeable, Typeable Scope
Scope -> DataType
Scope -> Constr
(forall b. Data b => b -> b) -> Scope -> Scope
forall a.
Typeable a
-> (forall (c :: * -> *).
    (forall d b. Data d => c (d -> b) -> d -> c b)
    -> (forall g. g -> c g) -> a -> c a)
-> (forall (c :: * -> *).
    (forall b r. Data b => c (b -> r) -> c r)
    -> (forall r. r -> c r) -> Constr -> c a)
-> (a -> Constr)
-> (a -> DataType)
-> (forall (t :: * -> *) (c :: * -> *).
    Typeable t =>
    (forall d. Data d => c (t d)) -> Maybe (c a))
-> (forall (t :: * -> * -> *) (c :: * -> *).
    Typeable t =>
    (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c a))
-> ((forall b. Data b => b -> b) -> a -> a)
-> (forall r r'.
    (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> a -> r)
-> (forall r r'.
    (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> a -> r)
-> (forall u. (forall d. Data d => d -> u) -> a -> [u])
-> (forall u. TypeIndex -> (forall d. Data d => d -> u) -> a -> u)
-> (forall (m :: * -> *).
    Monad m =>
    (forall d. Data d => d -> m d) -> a -> m a)
-> (forall (m :: * -> *).
    MonadPlus m =>
    (forall d. Data d => d -> m d) -> a -> m a)
-> (forall (m :: * -> *).
    MonadPlus m =>
    (forall d. Data d => d -> m d) -> a -> m a)
-> Data a
forall u. TypeIndex -> (forall d. Data d => d -> u) -> Scope -> u
forall u. (forall d. Data d => d -> u) -> Scope -> [u]
forall r r'.
(r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Scope -> r
forall r r'.
(r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Scope -> r
forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> Scope -> m Scope
forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> Scope -> m Scope
forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c Scope
forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> Scope -> c Scope
forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c Scope)
forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Scope)
gmapMo :: forall (m :: * -> *).
MonadPlus m =>
(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 (m :: * -> *).
MonadPlus m =>
(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 (m :: * -> *).
Monad m =>
(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 :: forall u. TypeIndex -> (forall d. Data d => d -> u) -> Scope -> u
$cgmapQi :: forall u. TypeIndex -> (forall d. Data d => d -> u) -> Scope -> u
gmapQ :: forall u. (forall d. Data d => d -> u) -> Scope -> [u]
$cgmapQ :: forall u. (forall d. Data d => d -> u) -> Scope -> [u]
gmapQr :: forall r r'.
(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 :: forall r r'.
(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 (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(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 (t :: * -> *) (c :: * -> *).
Typeable t =>
(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 (c :: * -> *).
(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 (c :: * -> *).
(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
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
<+> 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
    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) <- forall a. Binary a => BinHandle -> IO a
get BinHandle
bh
    case Word8
t of
      Word8
0 -> forall (m :: * -> *) a. Monad m => a -> m a
return Scope
NoScope
      Word8
1 -> Span -> Scope
LocalScope forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> forall a. Binary a => BinHandle -> IO a
get BinHandle
bh
      Word8
2 -> forall (m :: * -> *) a. Monad m => a -> m a
return Scope
ModuleScope
      Word8
_ -> forall a. String -> a
panic String
"Binary Scope: invalid tag"


-- | Scope of a type variable.
--
-- This warrants a data type apart from 'Scope' because of complexities
-- introduced by features like @-XScopedTypeVariables@ and @-XInstanceSigs@. For
-- example, consider:
--
-- @
-- foo, bar, baz :: forall a. a -> a
-- @
--
-- Here @a@ is in scope in all the definitions of @foo@, @bar@, and @baz@, so we
-- need a list of scopes to keep track of this. Furthermore, this list cannot be
-- computed until we resolve the binding sites of @foo@, @bar@, and @baz@.
--
-- Consequently, @a@ starts with an @'UnresolvedScope' [foo, bar, baz] Nothing@
-- which later gets resolved into a 'ResolvedScopes'.
data TyVarScope
  = ResolvedScopes [Scope]

  -- | Unresolved scopes should never show up in the final @.hie@ file
  | UnresolvedScope
        [Name]        -- ^ names of the definitions over which the scope spans
        (Maybe Span)  -- ^ the location of the instance/class declaration for
                      -- the case where the type variable is declared in a
                      -- method type signature
    deriving (TyVarScope -> TyVarScope -> Bool
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
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
Ord)

instance Outputable TyVarScope where
  ppr :: TyVarScope -> SDoc
ppr (ResolvedScopes [Scope]
xs) =
    String -> SDoc
text String
"type variable scopes:" SDoc -> SDoc -> SDoc
<+> [SDoc] -> SDoc
hsep (SDoc -> [SDoc] -> [SDoc]
punctuate SDoc
", " forall a b. (a -> b) -> a -> b
$ forall a b. (a -> b) -> [a] -> [b]
map forall a. Outputable a => a -> SDoc
ppr [Scope]
xs)
  ppr (UnresolvedScope [Name]
ns Maybe Span
sp) =
    String -> SDoc
text String
"unresolved type variable scope for name" SDoc -> SDoc -> SDoc
O.<> forall a. [a] -> SDoc
plural [Name]
ns
      SDoc -> SDoc -> SDoc
<+> Maybe Span -> SDoc
pprBindSpan Maybe Span
sp

instance Binary TyVarScope where
  put_ :: BinHandle -> TyVarScope -> IO ()
put_ BinHandle
bh (ResolvedScopes [Scope]
xs) = do
    BinHandle -> Word8 -> IO ()
putByte BinHandle
bh Word8
0
    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
    forall a. Binary a => BinHandle -> a -> IO ()
put_ BinHandle
bh [Name]
ns
    forall a. Binary a => BinHandle -> a -> IO ()
put_ BinHandle
bh Maybe Span
span

  get :: BinHandle -> IO TyVarScope
get BinHandle
bh = do
    (Word8
t :: Word8) <- forall a. Binary a => BinHandle -> IO a
get BinHandle
bh
    case Word8
t of
      Word8
0 -> [Scope] -> TyVarScope
ResolvedScopes forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> forall a. Binary a => BinHandle -> IO a
get BinHandle
bh
      Word8
1 -> [Name] -> Maybe Span -> TyVarScope
UnresolvedScope forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> forall a. Binary a => BinHandle -> IO a
get BinHandle
bh forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> forall a. Binary a => BinHandle -> IO a
get BinHandle
bh
      Word8
_ -> forall a. String -> a
panic String
"Binary TyVarScope: invalid tag"

-- | `Name`'s get converted into `HieName`'s before being written into @.hie@
-- files. See 'toHieName' and 'fromHieName' for logic on how to convert between
-- these two types.
data HieName
  = ExternalName !Module !OccName !SrcSpan
  | LocalName !OccName !SrcSpan
  | KnownKeyName !Unique
  deriving (HieName -> HieName -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: HieName -> HieName -> Bool
$c/= :: HieName -> HieName -> Bool
== :: HieName -> HieName -> Bool
$c== :: HieName -> HieName -> Bool
Eq)

instance Ord HieName where
  compare :: HieName -> HieName -> Ordering
compare (ExternalName Module
a OccName
b SrcSpan
c) (ExternalName Module
d OccName
e SrcSpan
f) = forall a. Ord a => a -> a -> Ordering
compare (Module
a,OccName
b) (Module
d,OccName
e) Ordering -> Ordering -> Ordering
`thenCmp` SrcSpan -> SrcSpan -> Ordering
leftmost_smallest SrcSpan
c SrcSpan
f
    -- TODO (int-index): Perhaps use RealSrcSpan in HieName?
  compare (LocalName OccName
a SrcSpan
b) (LocalName OccName
c SrcSpan
d) = forall a. Ord a => a -> a -> Ordering
compare OccName
a OccName
c Ordering -> Ordering -> Ordering
`thenCmp` SrcSpan -> SrcSpan -> Ordering
leftmost_smallest SrcSpan
b SrcSpan
d
    -- TODO (int-index): Perhaps use RealSrcSpan in HieName?
  compare (KnownKeyName Unique
a) (KnownKeyName Unique
b) = Unique -> Unique -> Ordering
nonDetCmpUnique Unique
a Unique
b
    -- Not actually non deterministic as it is a KnownKey
  compare ExternalName{} HieName
_ = Ordering
LT
  compare LocalName{} ExternalName{} = Ordering
GT
  compare LocalName{} HieName
_ = Ordering
LT
  compare KnownKeyName{} HieName
_ = Ordering
GT

instance Outputable HieName where
  ppr :: HieName -> SDoc
ppr (ExternalName Module
m OccName
n SrcSpan
sp) = String -> SDoc
text String
"ExternalName" SDoc -> SDoc -> SDoc
<+> forall a. Outputable a => a -> SDoc
ppr Module
m SDoc -> SDoc -> SDoc
<+> forall a. Outputable a => a -> SDoc
ppr OccName
n SDoc -> SDoc -> SDoc
<+> forall a. Outputable a => a -> SDoc
ppr SrcSpan
sp
  ppr (LocalName OccName
n SrcSpan
sp) = String -> SDoc
text String
"LocalName" SDoc -> SDoc -> SDoc
<+> forall a. Outputable a => a -> SDoc
ppr OccName
n SDoc -> SDoc -> SDoc
<+> forall a. Outputable a => a -> SDoc
ppr SrcSpan
sp
  ppr (KnownKeyName Unique
u) = String -> SDoc
text String
"KnownKeyName" SDoc -> SDoc -> SDoc
<+> forall a. Outputable a => a -> SDoc
ppr Unique
u

hieNameOcc :: HieName -> OccName
hieNameOcc :: HieName -> OccName
hieNameOcc (ExternalName Module
_ OccName
occ SrcSpan
_) = OccName
occ
hieNameOcc (LocalName OccName
occ SrcSpan
_) = OccName
occ
hieNameOcc (KnownKeyName Unique
u) =
  case Unique -> Maybe Name
lookupKnownKeyName Unique
u of
    Just Name
n -> Name -> OccName
nameOccName Name
n
    Maybe Name
Nothing -> forall a. HasCallStack => String -> SDoc -> a
pprPanic String
"hieNameOcc:unknown known-key unique"
                        (forall a. Outputable a => a -> SDoc
ppr (Unique -> (Char, TypeIndex)
unpkUnique Unique
u))

toHieName :: Name -> HieName
toHieName :: Name -> HieName
toHieName Name
name
  | Name -> Bool
isKnownKeyName Name
name = Unique -> HieName
KnownKeyName (Name -> Unique
nameUnique Name
name)
  | Name -> Bool
isExternalName Name
name = Module -> OccName -> SrcSpan -> HieName
ExternalName (HasDebugCallStack => Name -> Module
nameModule Name
name)
                                       (Name -> OccName
nameOccName Name
name)
                                       (SrcSpan -> SrcSpan
removeBufSpan forall a b. (a -> b) -> a -> b
$ Name -> SrcSpan
nameSrcSpan Name
name)
  | Bool
otherwise = OccName -> SrcSpan -> HieName
LocalName (Name -> OccName
nameOccName Name
name) (SrcSpan -> SrcSpan
removeBufSpan forall a b. (a -> b) -> a -> b
$ Name -> SrcSpan
nameSrcSpan Name
name)