{-# OPTIONS_GHC -fno-warn-orphans #-}

-- Only instances exported
module Agda.TypeChecking.Serialise.Instances () where

import Agda.Syntax.Position
import Agda.Syntax.Abstract.Name
import Agda.TypeChecking.Monad.Base
import Agda.TypeChecking.Serialise.Base
import Agda.TypeChecking.Serialise.Instances.Common (SerialisedRange(..))
import Agda.TypeChecking.Serialise.Instances.Highlighting ()
import Agda.TypeChecking.Serialise.Instances.Errors ()
import Agda.Utils.Hash

type RangedImportedModules = [(SerialisedRange, ModuleName, Hash)]

fromImportedModules :: [(ModuleName, Hash)] -> RangedImportedModules
fromImportedModules :: [(ModuleName, Hash)] -> RangedImportedModules
fromImportedModules [(ModuleName, Hash)]
ms = [(Range -> SerialisedRange
SerialisedRange (Range -> SerialisedRange) -> Range -> SerialisedRange
forall a b. (a -> b) -> a -> b
$ ModuleName -> Range
forall a. HasRange a => a -> Range
getRange ModuleName
x, ModuleName
x, Hash
hash) | (ModuleName
x, Hash
hash) <- [(ModuleName, Hash)]
ms]

toImportedModules :: RangedImportedModules -> [(ModuleName, Hash)]
toImportedModules :: RangedImportedModules -> [(ModuleName, Hash)]
toImportedModules RangedImportedModules
ms = [(Range -> ModuleName -> ModuleName
forall a. SetRange a => Range -> a -> a
setRange (SerialisedRange -> Range
underlyingRange SerialisedRange
r) ModuleName
x, Hash
hash) | (SerialisedRange
r, ModuleName
x, Hash
hash) <- RangedImportedModules
ms]

instance EmbPrj Interface where
  icod_ :: Interface -> S Int32
icod_ (Interface Hash
a Text
b FileType
c [(ModuleName, Hash)]
d ModuleName
e Map ModuleName Scope
f ScopeInfo
g Signature
h DisplayForms
i Map QName Text
j Maybe Text
k BuiltinThings (String, QName)
l Map String [ForeignCode]
m HighlightingInfo
n [OptionsPragma]
o [OptionsPragma]
p PragmaOptions
q PatternSynDefns
r [TCWarning]
s Set QName
t) =
      (Hash
 -> Text
 -> FileType
 -> RangedImportedModules
 -> ModuleName
 -> Map ModuleName Scope
 -> ScopeInfo
 -> Signature
 -> DisplayForms
 -> Map QName Text
 -> Maybe Text
 -> BuiltinThings (String, QName)
 -> Map String [ForeignCode]
 -> HighlightingInfo
 -> [OptionsPragma]
 -> [OptionsPragma]
 -> PragmaOptions
 -> PatternSynDefns
 -> [TCWarning]
 -> Set QName
 -> Interface)
-> Hash
-> Text
-> FileType
-> RangedImportedModules
-> ModuleName
-> Map ModuleName Scope
-> ScopeInfo
-> Signature
-> DisplayForms
-> Map QName Text
-> Maybe Text
-> BuiltinThings (String, QName)
-> Map String [ForeignCode]
-> HighlightingInfo
-> [OptionsPragma]
-> [OptionsPragma]
-> PragmaOptions
-> PatternSynDefns
-> [TCWarning]
-> Set QName
-> S Int32
forall t.
(ICODE t (IsBase t), Currying (Domains t) (S Int32),
 All EmbPrj (Domains t)) =>
t -> Arrows (Domains t) (S Int32)
icodeN' Hash
-> Text
-> FileType
-> RangedImportedModules
-> ModuleName
-> Map ModuleName Scope
-> ScopeInfo
-> Signature
-> DisplayForms
-> Map QName Text
-> Maybe Text
-> BuiltinThings (String, QName)
-> Map String [ForeignCode]
-> HighlightingInfo
-> [OptionsPragma]
-> [OptionsPragma]
-> PragmaOptions
-> PatternSynDefns
-> [TCWarning]
-> Set QName
-> Interface
interface Hash
a Text
b FileType
c ([(ModuleName, Hash)] -> RangedImportedModules
fromImportedModules [(ModuleName, Hash)]
d) ModuleName
e Map ModuleName Scope
f ScopeInfo
g Signature
h DisplayForms
i Map QName Text
j Maybe Text
k BuiltinThings (String, QName)
l Map String [ForeignCode]
m HighlightingInfo
n [OptionsPragma]
o [OptionsPragma]
p PragmaOptions
q PatternSynDefns
r [TCWarning]
s Set QName
t
    where interface :: Hash
-> Text
-> FileType
-> RangedImportedModules
-> ModuleName
-> Map ModuleName Scope
-> ScopeInfo
-> Signature
-> DisplayForms
-> Map QName Text
-> Maybe Text
-> BuiltinThings (String, QName)
-> Map String [ForeignCode]
-> HighlightingInfo
-> [OptionsPragma]
-> [OptionsPragma]
-> PragmaOptions
-> PatternSynDefns
-> [TCWarning]
-> Set QName
-> Interface
interface Hash
a Text
b FileType
c = Hash
-> Text
-> FileType
-> [(ModuleName, Hash)]
-> ModuleName
-> Map ModuleName Scope
-> ScopeInfo
-> Signature
-> DisplayForms
-> Map QName Text
-> Maybe Text
-> BuiltinThings (String, QName)
-> Map String [ForeignCode]
-> HighlightingInfo
-> [OptionsPragma]
-> [OptionsPragma]
-> PragmaOptions
-> PatternSynDefns
-> [TCWarning]
-> Set QName
-> Interface
Interface Hash
a Text
b FileType
c ([(ModuleName, Hash)]
 -> ModuleName
 -> Map ModuleName Scope
 -> ScopeInfo
 -> Signature
 -> DisplayForms
 -> Map QName Text
 -> Maybe Text
 -> BuiltinThings (String, QName)
 -> Map String [ForeignCode]
 -> HighlightingInfo
 -> [OptionsPragma]
 -> [OptionsPragma]
 -> PragmaOptions
 -> PatternSynDefns
 -> [TCWarning]
 -> Set QName
 -> Interface)
-> (RangedImportedModules -> [(ModuleName, Hash)])
-> RangedImportedModules
-> ModuleName
-> Map ModuleName Scope
-> ScopeInfo
-> Signature
-> DisplayForms
-> Map QName Text
-> Maybe Text
-> BuiltinThings (String, QName)
-> Map String [ForeignCode]
-> HighlightingInfo
-> [OptionsPragma]
-> [OptionsPragma]
-> PragmaOptions
-> PatternSynDefns
-> [TCWarning]
-> Set QName
-> Interface
forall b c a. (b -> c) -> (a -> b) -> a -> c
. RangedImportedModules -> [(ModuleName, Hash)]
toImportedModules

  value :: Int32 -> R Interface
value = (Node -> R Interface) -> Int32 -> R Interface
forall a. EmbPrj a => (Node -> R a) -> Int32 -> R a
vcase Node -> R Interface
valu where
    valu :: Node -> R Interface
valu [Int32
a, Int32
b, Int32
c, Int32
d, Int32
e, Int32
f, Int32
g, Int32
h, Int32
i, Int32
j, Int32
k, Int32
l, Int32
m, Int32
n, Int32
o, Int32
p, Int32
q, Int32
r, Int32
s, Int32
t] =
        (Hash
 -> Text
 -> FileType
 -> RangedImportedModules
 -> ModuleName
 -> Map ModuleName Scope
 -> ScopeInfo
 -> Signature
 -> DisplayForms
 -> Map QName Text
 -> Maybe Text
 -> BuiltinThings (String, QName)
 -> Map String [ForeignCode]
 -> HighlightingInfo
 -> [OptionsPragma]
 -> [OptionsPragma]
 -> PragmaOptions
 -> PatternSynDefns
 -> [TCWarning]
 -> Set QName
 -> Interface)
-> Int32
-> Int32
-> Int32
-> Int32
-> Int32
-> Int32
-> Int32
-> Int32
-> Int32
-> Int32
-> Int32
-> Int32
-> Int32
-> Int32
-> Int32
-> Int32
-> Int32
-> Int32
-> Int32
-> Int32
-> R Interface
forall t.
(VALU t (IsBase t),
 Currying (Constant Int32 (Domains t)) (R (CoDomain t)),
 All EmbPrj (Domains t)) =>
t -> Arrows (Constant Int32 (Domains t)) (R (CoDomain t))
valuN Hash
-> Text
-> FileType
-> RangedImportedModules
-> ModuleName
-> Map ModuleName Scope
-> ScopeInfo
-> Signature
-> DisplayForms
-> Map QName Text
-> Maybe Text
-> BuiltinThings (String, QName)
-> Map String [ForeignCode]
-> HighlightingInfo
-> [OptionsPragma]
-> [OptionsPragma]
-> PragmaOptions
-> PatternSynDefns
-> [TCWarning]
-> Set QName
-> Interface
interface Int32
a Int32
b Int32
c Int32
d Int32
e Int32
f Int32
g Int32
h Int32
i Int32
j Int32
k Int32
l Int32
m Int32
n Int32
o Int32
p Int32
q Int32
r Int32
s Int32
t
      where interface :: Hash
-> Text
-> FileType
-> RangedImportedModules
-> ModuleName
-> Map ModuleName Scope
-> ScopeInfo
-> Signature
-> DisplayForms
-> Map QName Text
-> Maybe Text
-> BuiltinThings (String, QName)
-> Map String [ForeignCode]
-> HighlightingInfo
-> [OptionsPragma]
-> [OptionsPragma]
-> PragmaOptions
-> PatternSynDefns
-> [TCWarning]
-> Set QName
-> Interface
interface Hash
a Text
b FileType
c = Hash
-> Text
-> FileType
-> [(ModuleName, Hash)]
-> ModuleName
-> Map ModuleName Scope
-> ScopeInfo
-> Signature
-> DisplayForms
-> Map QName Text
-> Maybe Text
-> BuiltinThings (String, QName)
-> Map String [ForeignCode]
-> HighlightingInfo
-> [OptionsPragma]
-> [OptionsPragma]
-> PragmaOptions
-> PatternSynDefns
-> [TCWarning]
-> Set QName
-> Interface
Interface Hash
a Text
b FileType
c ([(ModuleName, Hash)]
 -> ModuleName
 -> Map ModuleName Scope
 -> ScopeInfo
 -> Signature
 -> DisplayForms
 -> Map QName Text
 -> Maybe Text
 -> BuiltinThings (String, QName)
 -> Map String [ForeignCode]
 -> HighlightingInfo
 -> [OptionsPragma]
 -> [OptionsPragma]
 -> PragmaOptions
 -> PatternSynDefns
 -> [TCWarning]
 -> Set QName
 -> Interface)
-> (RangedImportedModules -> [(ModuleName, Hash)])
-> RangedImportedModules
-> ModuleName
-> Map ModuleName Scope
-> ScopeInfo
-> Signature
-> DisplayForms
-> Map QName Text
-> Maybe Text
-> BuiltinThings (String, QName)
-> Map String [ForeignCode]
-> HighlightingInfo
-> [OptionsPragma]
-> [OptionsPragma]
-> PragmaOptions
-> PatternSynDefns
-> [TCWarning]
-> Set QName
-> Interface
forall b c a. (b -> c) -> (a -> b) -> a -> c
. RangedImportedModules -> [(ModuleName, Hash)]
toImportedModules
    valu Node
_ = R Interface
forall a. R a
malformed