{-# LANGUAGE CPP #-}
{-# LANGUAGE FlexibleInstances #-}
{-# OPTIONS_GHC -Wno-orphans #-}
#include "ghc-api-version.h"
module Development.IDE.GHC.Orphans() where
import Bag
import Control.DeepSeq
import Data.Aeson
import Data.Hashable
import Data.String (IsString (fromString))
import Data.Text (Text)
import Development.IDE.GHC.Compat
import Development.IDE.GHC.Util
import GHC ()
import GhcPlugins
import Retrie.ExactPrint (Annotated)
import qualified StringBuffer as SB
instance Show CoreModule where show :: CoreModule -> String
show = CoreModule -> String
forall a. Outputable a => a -> String
prettyPrint
instance NFData CoreModule where rnf :: CoreModule -> ()
rnf = CoreModule -> ()
forall a. a -> ()
rwhnf
instance Show CgGuts where show :: CgGuts -> String
show = Module -> String
forall a. Outputable a => a -> String
prettyPrint (Module -> String) -> (CgGuts -> Module) -> CgGuts -> String
forall b c a. (b -> c) -> (a -> b) -> a -> c
. CgGuts -> Module
cg_module
instance NFData CgGuts where rnf :: CgGuts -> ()
rnf = CgGuts -> ()
forall a. a -> ()
rwhnf
instance Show ModDetails where show :: ModDetails -> String
show = String -> ModDetails -> String
forall a b. a -> b -> a
const String
"<moddetails>"
instance NFData ModDetails where rnf :: ModDetails -> ()
rnf = ModDetails -> ()
forall a. a -> ()
rwhnf
instance NFData SafeHaskellMode where rnf :: SafeHaskellMode -> ()
rnf = SafeHaskellMode -> ()
forall a. a -> ()
rwhnf
instance Show Linkable where show :: Linkable -> String
show = Linkable -> String
forall a. Outputable a => a -> String
prettyPrint
instance NFData Linkable where rnf :: Linkable -> ()
rnf = Linkable -> ()
forall a. a -> ()
rwhnf
instance Show PackageFlag where show :: PackageFlag -> String
show = PackageFlag -> String
forall a. Outputable a => a -> String
prettyPrint
instance Show InteractiveImport where show :: InteractiveImport -> String
show = InteractiveImport -> String
forall a. Outputable a => a -> String
prettyPrint
instance Show ComponentId where show :: ComponentId -> String
show = ComponentId -> String
forall a. Outputable a => a -> String
prettyPrint
instance Show PackageName where show :: PackageName -> String
show = PackageName -> String
forall a. Outputable a => a -> String
prettyPrint
instance Show SourcePackageId where show :: SourcePackageId -> String
show = SourcePackageId -> String
forall a. Outputable a => a -> String
prettyPrint
instance Show InstalledUnitId where
show :: InstalledUnitId -> String
show = InstalledUnitId -> String
installedUnitIdString
instance NFData InstalledUnitId where rnf :: InstalledUnitId -> ()
rnf = FastString -> ()
forall a. a -> ()
rwhnf (FastString -> ())
-> (InstalledUnitId -> FastString) -> InstalledUnitId -> ()
forall b c a. (b -> c) -> (a -> b) -> a -> c
. InstalledUnitId -> FastString
installedUnitIdFS
instance NFData SB.StringBuffer where rnf :: StringBuffer -> ()
rnf = StringBuffer -> ()
forall a. a -> ()
rwhnf
instance Show Module where
show :: Module -> String
show = ModuleName -> String
moduleNameString (ModuleName -> String)
-> (Module -> ModuleName) -> Module -> String
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Module -> ModuleName
moduleName
instance Outputable a => Show (GenLocated SrcSpan a) where show :: GenLocated SrcSpan a -> String
show = GenLocated SrcSpan a -> String
forall a. Outputable a => a -> String
prettyPrint
instance (NFData l, NFData e) => NFData (GenLocated l e) where
rnf :: GenLocated l e -> ()
rnf (L l
l e
e) = l -> ()
forall a. NFData a => a -> ()
rnf l
l () -> () -> ()
`seq` e -> ()
forall a. NFData a => a -> ()
rnf e
e
instance Show ModSummary where
show :: ModSummary -> String
show = Module -> String
forall a. Show a => a -> String
show (Module -> String)
-> (ModSummary -> Module) -> ModSummary -> String
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ModSummary -> Module
ms_mod
instance Show ParsedModule where
show :: ParsedModule -> String
show = ModSummary -> String
forall a. Show a => a -> String
show (ModSummary -> String)
-> (ParsedModule -> ModSummary) -> ParsedModule -> String
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ParsedModule -> ModSummary
pm_mod_summary
instance NFData ModSummary where
rnf :: ModSummary -> ()
rnf = ModSummary -> ()
forall a. a -> ()
rwhnf
#if !MIN_GHC_API_VERSION(8,10,0)
instance NFData FastString where
rnf = rwhnf
#endif
instance NFData ParsedModule where
rnf :: ParsedModule -> ()
rnf = ParsedModule -> ()
forall a. a -> ()
rwhnf
instance Hashable InstalledUnitId where
hashWithSalt :: Int -> InstalledUnitId -> Int
hashWithSalt Int
salt = Int -> String -> Int
forall a. Hashable a => Int -> a -> Int
hashWithSalt Int
salt (String -> Int)
-> (InstalledUnitId -> String) -> InstalledUnitId -> Int
forall b c a. (b -> c) -> (a -> b) -> a -> c
. InstalledUnitId -> String
installedUnitIdString
instance Show HieFile where
show :: HieFile -> String
show = Module -> String
forall a. Show a => a -> String
show (Module -> String) -> (HieFile -> Module) -> HieFile -> String
forall b c a. (b -> c) -> (a -> b) -> a -> c
. HieFile -> Module
hie_module
instance NFData HieFile where
rnf :: HieFile -> ()
rnf = HieFile -> ()
forall a. a -> ()
rwhnf
deriving instance Eq SourceModified
deriving instance Show SourceModified
instance NFData SourceModified where
rnf :: SourceModified -> ()
rnf = SourceModified -> ()
forall a. a -> ()
rwhnf
instance Show ModuleName where
show :: ModuleName -> String
show = ModuleName -> String
moduleNameString
instance Hashable ModuleName where
hashWithSalt :: Int -> ModuleName -> Int
hashWithSalt Int
salt = Int -> String -> Int
forall a. Hashable a => Int -> a -> Int
hashWithSalt Int
salt (String -> Int) -> (ModuleName -> String) -> ModuleName -> Int
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ModuleName -> String
forall a. Show a => a -> String
show
instance NFData a => NFData (IdentifierDetails a) where
rnf :: IdentifierDetails a -> ()
rnf (IdentifierDetails Maybe a
a Set ContextInfo
b) = Maybe a -> ()
forall a. NFData a => a -> ()
rnf Maybe a
a () -> () -> ()
`seq` Int -> ()
forall a. NFData a => a -> ()
rnf (Set ContextInfo -> Int
forall (t :: * -> *) a. Foldable t => t a -> Int
length Set ContextInfo
b)
instance NFData RealSrcSpan where
rnf :: RealSrcSpan -> ()
rnf = RealSrcSpan -> ()
forall a. a -> ()
rwhnf
srcSpanFileTag, srcSpanStartLineTag, srcSpanStartColTag,
srcSpanEndLineTag, srcSpanEndColTag :: Text
srcSpanFileTag :: Text
srcSpanFileTag = Text
"srcSpanFile"
srcSpanStartLineTag :: Text
srcSpanStartLineTag = Text
"srcSpanStartLine"
srcSpanStartColTag :: Text
srcSpanStartColTag = Text
"srcSpanStartCol"
srcSpanEndLineTag :: Text
srcSpanEndLineTag = Text
"srcSpanEndLine"
srcSpanEndColTag :: Text
srcSpanEndColTag = Text
"srcSpanEndCol"
instance ToJSON RealSrcSpan where
toJSON :: RealSrcSpan -> Value
toJSON RealSrcSpan
spn =
[Pair] -> Value
object
[ Text
srcSpanFileTag Text -> String -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
.= FastString -> String
unpackFS (RealSrcSpan -> FastString
srcSpanFile RealSrcSpan
spn)
, Text
srcSpanStartLineTag Text -> Int -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
.= RealSrcSpan -> Int
srcSpanStartLine RealSrcSpan
spn
, Text
srcSpanStartColTag Text -> Int -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
.= RealSrcSpan -> Int
srcSpanStartCol RealSrcSpan
spn
, Text
srcSpanEndLineTag Text -> Int -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
.= RealSrcSpan -> Int
srcSpanEndLine RealSrcSpan
spn
, Text
srcSpanEndColTag Text -> Int -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
.= RealSrcSpan -> Int
srcSpanEndCol RealSrcSpan
spn
]
instance FromJSON RealSrcSpan where
parseJSON :: Value -> Parser RealSrcSpan
parseJSON = String
-> (Object -> Parser RealSrcSpan) -> Value -> Parser RealSrcSpan
forall a. String -> (Object -> Parser a) -> Value -> Parser a
withObject String
"object" ((Object -> Parser RealSrcSpan) -> Value -> Parser RealSrcSpan)
-> (Object -> Parser RealSrcSpan) -> Value -> Parser RealSrcSpan
forall a b. (a -> b) -> a -> b
$ \Object
obj -> do
FastString
file <- String -> FastString
forall a. IsString a => String -> a
fromString (String -> FastString) -> Parser String -> Parser FastString
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> (Object
obj Object -> Text -> Parser String
forall a. FromJSON a => Object -> Text -> Parser a
.: Text
srcSpanFileTag)
RealSrcLoc -> RealSrcLoc -> RealSrcSpan
mkRealSrcSpan
(RealSrcLoc -> RealSrcLoc -> RealSrcSpan)
-> Parser RealSrcLoc -> Parser (RealSrcLoc -> RealSrcSpan)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> (FastString -> Int -> Int -> RealSrcLoc
mkRealSrcLoc FastString
file
(Int -> Int -> RealSrcLoc)
-> Parser Int -> Parser (Int -> RealSrcLoc)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Object
obj Object -> Text -> Parser Int
forall a. FromJSON a => Object -> Text -> Parser a
.: Text
srcSpanStartLineTag
Parser (Int -> RealSrcLoc) -> Parser Int -> Parser RealSrcLoc
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Object
obj Object -> Text -> Parser Int
forall a. FromJSON a => Object -> Text -> Parser a
.: Text
srcSpanStartColTag
)
Parser (RealSrcLoc -> RealSrcSpan)
-> Parser RealSrcLoc -> Parser RealSrcSpan
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> (FastString -> Int -> Int -> RealSrcLoc
mkRealSrcLoc FastString
file
(Int -> Int -> RealSrcLoc)
-> Parser Int -> Parser (Int -> RealSrcLoc)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Object
obj Object -> Text -> Parser Int
forall a. FromJSON a => Object -> Text -> Parser a
.: Text
srcSpanEndLineTag
Parser (Int -> RealSrcLoc) -> Parser Int -> Parser RealSrcLoc
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Object
obj Object -> Text -> Parser Int
forall a. FromJSON a => Object -> Text -> Parser a
.: Text
srcSpanEndColTag
)
instance NFData Type where
rnf :: Type -> ()
rnf = Type -> ()
forall a. a -> ()
rwhnf
instance Show a => Show (Bag a) where
show :: Bag a -> String
show = [a] -> String
forall a. Show a => a -> String
show ([a] -> String) -> (Bag a -> [a]) -> Bag a -> String
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Bag a -> [a]
forall a. Bag a -> [a]
bagToList
instance NFData HsDocString where
rnf :: HsDocString -> ()
rnf = HsDocString -> ()
forall a. a -> ()
rwhnf
instance Show ModGuts where
show :: ModGuts -> String
show ModGuts
_ = String
"modguts"
instance NFData ModGuts where
rnf :: ModGuts -> ()
rnf = ModGuts -> ()
forall a. a -> ()
rwhnf
instance NFData (ImportDecl GhcPs) where
rnf :: ImportDecl GhcPs -> ()
rnf = ImportDecl GhcPs -> ()
forall a. a -> ()
rwhnf
instance Show (Annotated ParsedSource) where
show :: Annotated ParsedSource -> String
show Annotated ParsedSource
_ = String
"<Annotated ParsedSource>"
instance NFData (Annotated ParsedSource) where
rnf :: Annotated ParsedSource -> ()
rnf = Annotated ParsedSource -> ()
forall a. a -> ()
rwhnf