{-# OPTIONS_GHC -Wunused-imports #-}

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

module Agda.TypeChecking.Serialise.Instances.Highlighting where

import qualified Data.Map.Strict as Map
import Data.Strict.Tuple (Pair(..))
import Data.Int (Int32)

import qualified Agda.Interaction.Highlighting.Range   as HR
import qualified Agda.Interaction.Highlighting.Precise as HP
import qualified Agda.Utils.RangeMap                   as RM

import Agda.TypeChecking.Serialise.Base
import Agda.TypeChecking.Serialise.Instances.Common () --instance only

instance EmbPrj HR.Range where
  icod_ :: Range -> S Int32
icod_ (HR.Range Int
a Int
b) = (Int -> Int -> Range)
-> Arrows (Domains (Int -> Int -> Range)) (S Int32)
forall t.
(ICODE t (IsBase t), StrictCurrying (Domains t) (S Int32),
 All EmbPrj (Domains t)) =>
t -> Arrows (Domains t) (S Int32)
icodeN' Int -> Int -> Range
HR.Range Int
a Int
b

  value :: Int32 -> R Range
value = (Int -> Int -> Range)
-> Int32 -> R (CoDomain (Int -> Int -> Range))
forall t.
(VALU t (IsBase t), All EmbPrj (CoDomain t : Domains t)) =>
t -> Int32 -> R (CoDomain t)
valueN Int -> Int -> Range
HR.Range

instance EmbPrj HP.NameKind where
  icod_ :: NameKind -> S Int32
icod_ NameKind
HP.Bound           = NameKind -> Arrows (Domains NameKind) (S Int32)
forall t.
(ICODE t (IsBase t), StrictCurrying (Domains t) (S Int32),
 All EmbPrj (Domains t)) =>
t -> Arrows (Domains t) (S Int32)
icodeN' NameKind
HP.Bound
  icod_ (HP.Constructor Induction
a) = Int32
-> (Induction -> NameKind)
-> Arrows (Domains (Induction -> NameKind)) (S Int32)
forall t.
(ICODE t (IsBase t), StrictCurrying (Domains t) (S Int32),
 All EmbPrj (Domains t)) =>
Int32 -> t -> Arrows (Domains t) (S Int32)
icodeN Int32
1 Induction -> NameKind
HP.Constructor Induction
a
  icod_ NameKind
HP.Datatype        = Int32 -> () -> Arrows (Domains ()) (S Int32)
forall t.
(ICODE t (IsBase t), StrictCurrying (Domains t) (S Int32),
 All EmbPrj (Domains t)) =>
Int32 -> t -> Arrows (Domains t) (S Int32)
icodeN Int32
2 ()
  icod_ NameKind
HP.Field           = Int32 -> () -> Arrows (Domains ()) (S Int32)
forall t.
(ICODE t (IsBase t), StrictCurrying (Domains t) (S Int32),
 All EmbPrj (Domains t)) =>
Int32 -> t -> Arrows (Domains t) (S Int32)
icodeN Int32
3 ()
  icod_ NameKind
HP.Function        = Int32 -> () -> Arrows (Domains ()) (S Int32)
forall t.
(ICODE t (IsBase t), StrictCurrying (Domains t) (S Int32),
 All EmbPrj (Domains t)) =>
Int32 -> t -> Arrows (Domains t) (S Int32)
icodeN Int32
4 ()
  icod_ NameKind
HP.Module          = Int32 -> () -> Arrows (Domains ()) (S Int32)
forall t.
(ICODE t (IsBase t), StrictCurrying (Domains t) (S Int32),
 All EmbPrj (Domains t)) =>
Int32 -> t -> Arrows (Domains t) (S Int32)
icodeN Int32
5 ()
  icod_ NameKind
HP.Postulate       = Int32 -> () -> Arrows (Domains ()) (S Int32)
forall t.
(ICODE t (IsBase t), StrictCurrying (Domains t) (S Int32),
 All EmbPrj (Domains t)) =>
Int32 -> t -> Arrows (Domains t) (S Int32)
icodeN Int32
6 ()
  icod_ NameKind
HP.Primitive       = Int32 -> () -> Arrows (Domains ()) (S Int32)
forall t.
(ICODE t (IsBase t), StrictCurrying (Domains t) (S Int32),
 All EmbPrj (Domains t)) =>
Int32 -> t -> Arrows (Domains t) (S Int32)
icodeN Int32
7 ()
  icod_ NameKind
HP.Record          = Int32 -> () -> Arrows (Domains ()) (S Int32)
forall t.
(ICODE t (IsBase t), StrictCurrying (Domains t) (S Int32),
 All EmbPrj (Domains t)) =>
Int32 -> t -> Arrows (Domains t) (S Int32)
icodeN Int32
8 ()
  icod_ NameKind
HP.Argument        = Int32 -> () -> Arrows (Domains ()) (S Int32)
forall t.
(ICODE t (IsBase t), StrictCurrying (Domains t) (S Int32),
 All EmbPrj (Domains t)) =>
Int32 -> t -> Arrows (Domains t) (S Int32)
icodeN Int32
9 ()
  icod_ NameKind
HP.Macro           = Int32 -> () -> Arrows (Domains ()) (S Int32)
forall t.
(ICODE t (IsBase t), StrictCurrying (Domains t) (S Int32),
 All EmbPrj (Domains t)) =>
Int32 -> t -> Arrows (Domains t) (S Int32)
icodeN Int32
10 ()
  icod_ NameKind
HP.Generalizable   = Int32 -> () -> Arrows (Domains ()) (S Int32)
forall t.
(ICODE t (IsBase t), StrictCurrying (Domains t) (S Int32),
 All EmbPrj (Domains t)) =>
Int32 -> t -> Arrows (Domains t) (S Int32)
icodeN Int32
11 ()

  value :: Int32 -> R NameKind
value = ([Int32] -> R NameKind) -> Int32 -> R NameKind
forall a. EmbPrj a => ([Int32] -> R a) -> Int32 -> R a
vcase [Int32] -> R NameKind
valu where
    valu :: [Int32]
-> Arrows
     (Constant Int32 (Domains NameKind)) (R (CoDomain NameKind))
valu []      = NameKind
-> Arrows
     (Constant Int32 (Domains NameKind)) (R (CoDomain NameKind))
forall t.
(VALU t (IsBase t),
 StrictCurrying (Constant Int32 (Domains t)) (R (CoDomain t)),
 All EmbPrj (Domains t)) =>
t -> Arrows (Constant Int32 (Domains t)) (R (CoDomain t))
valuN NameKind
HP.Bound
    valu [Int32
1 , Int32
a] = (Induction -> NameKind)
-> Arrows
     (Constant Int32 (Domains (Induction -> NameKind)))
     (R (CoDomain (Induction -> NameKind)))
forall t.
(VALU t (IsBase t),
 StrictCurrying (Constant Int32 (Domains t)) (R (CoDomain t)),
 All EmbPrj (Domains t)) =>
t -> Arrows (Constant Int32 (Domains t)) (R (CoDomain t))
valuN Induction -> NameKind
HP.Constructor Int32
a
    valu [Int32
2]     = NameKind
-> Arrows
     (Constant Int32 (Domains NameKind)) (R (CoDomain NameKind))
forall t.
(VALU t (IsBase t),
 StrictCurrying (Constant Int32 (Domains t)) (R (CoDomain t)),
 All EmbPrj (Domains t)) =>
t -> Arrows (Constant Int32 (Domains t)) (R (CoDomain t))
valuN NameKind
HP.Datatype
    valu [Int32
3]     = NameKind
-> Arrows
     (Constant Int32 (Domains NameKind)) (R (CoDomain NameKind))
forall t.
(VALU t (IsBase t),
 StrictCurrying (Constant Int32 (Domains t)) (R (CoDomain t)),
 All EmbPrj (Domains t)) =>
t -> Arrows (Constant Int32 (Domains t)) (R (CoDomain t))
valuN NameKind
HP.Field
    valu [Int32
4]     = NameKind
-> Arrows
     (Constant Int32 (Domains NameKind)) (R (CoDomain NameKind))
forall t.
(VALU t (IsBase t),
 StrictCurrying (Constant Int32 (Domains t)) (R (CoDomain t)),
 All EmbPrj (Domains t)) =>
t -> Arrows (Constant Int32 (Domains t)) (R (CoDomain t))
valuN NameKind
HP.Function
    valu [Int32
5]     = NameKind
-> Arrows
     (Constant Int32 (Domains NameKind)) (R (CoDomain NameKind))
forall t.
(VALU t (IsBase t),
 StrictCurrying (Constant Int32 (Domains t)) (R (CoDomain t)),
 All EmbPrj (Domains t)) =>
t -> Arrows (Constant Int32 (Domains t)) (R (CoDomain t))
valuN NameKind
HP.Module
    valu [Int32
6]     = NameKind
-> Arrows
     (Constant Int32 (Domains NameKind)) (R (CoDomain NameKind))
forall t.
(VALU t (IsBase t),
 StrictCurrying (Constant Int32 (Domains t)) (R (CoDomain t)),
 All EmbPrj (Domains t)) =>
t -> Arrows (Constant Int32 (Domains t)) (R (CoDomain t))
valuN NameKind
HP.Postulate
    valu [Int32
7]     = NameKind
-> Arrows
     (Constant Int32 (Domains NameKind)) (R (CoDomain NameKind))
forall t.
(VALU t (IsBase t),
 StrictCurrying (Constant Int32 (Domains t)) (R (CoDomain t)),
 All EmbPrj (Domains t)) =>
t -> Arrows (Constant Int32 (Domains t)) (R (CoDomain t))
valuN NameKind
HP.Primitive
    valu [Int32
8]     = NameKind
-> Arrows
     (Constant Int32 (Domains NameKind)) (R (CoDomain NameKind))
forall t.
(VALU t (IsBase t),
 StrictCurrying (Constant Int32 (Domains t)) (R (CoDomain t)),
 All EmbPrj (Domains t)) =>
t -> Arrows (Constant Int32 (Domains t)) (R (CoDomain t))
valuN NameKind
HP.Record
    valu [Int32
9]     = NameKind
-> Arrows
     (Constant Int32 (Domains NameKind)) (R (CoDomain NameKind))
forall t.
(VALU t (IsBase t),
 StrictCurrying (Constant Int32 (Domains t)) (R (CoDomain t)),
 All EmbPrj (Domains t)) =>
t -> Arrows (Constant Int32 (Domains t)) (R (CoDomain t))
valuN NameKind
HP.Argument
    valu [Int32
10]    = NameKind
-> Arrows
     (Constant Int32 (Domains NameKind)) (R (CoDomain NameKind))
forall t.
(VALU t (IsBase t),
 StrictCurrying (Constant Int32 (Domains t)) (R (CoDomain t)),
 All EmbPrj (Domains t)) =>
t -> Arrows (Constant Int32 (Domains t)) (R (CoDomain t))
valuN NameKind
HP.Macro
    valu [Int32
11]    = NameKind
-> Arrows
     (Constant Int32 (Domains NameKind)) (R (CoDomain NameKind))
forall t.
(VALU t (IsBase t),
 StrictCurrying (Constant Int32 (Domains t)) (R (CoDomain t)),
 All EmbPrj (Domains t)) =>
t -> Arrows (Constant Int32 (Domains t)) (R (CoDomain t))
valuN NameKind
HP.Generalizable
    valu [Int32]
_       = R NameKind
Arrows (Constant Int32 (Domains NameKind)) (R (CoDomain NameKind))
forall a. R a
malformed

instance EmbPrj HP.Aspect where
  icod_ :: Aspect -> S Int32
icod_ Aspect
HP.Comment        = Int32 -> () -> Arrows (Domains ()) (S Int32)
forall t.
(ICODE t (IsBase t), StrictCurrying (Domains t) (S Int32),
 All EmbPrj (Domains t)) =>
Int32 -> t -> Arrows (Domains t) (S Int32)
icodeN Int32
0 ()
  icod_ Aspect
HP.Keyword       = Int32 -> () -> Arrows (Domains ()) (S Int32)
forall t.
(ICODE t (IsBase t), StrictCurrying (Domains t) (S Int32),
 All EmbPrj (Domains t)) =>
Int32 -> t -> Arrows (Domains t) (S Int32)
icodeN Int32
1 ()
  icod_ Aspect
HP.String        = Int32 -> () -> Arrows (Domains ()) (S Int32)
forall t.
(ICODE t (IsBase t), StrictCurrying (Domains t) (S Int32),
 All EmbPrj (Domains t)) =>
Int32 -> t -> Arrows (Domains t) (S Int32)
icodeN Int32
2 ()
  icod_ Aspect
HP.Number        = Int32 -> () -> Arrows (Domains ()) (S Int32)
forall t.
(ICODE t (IsBase t), StrictCurrying (Domains t) (S Int32),
 All EmbPrj (Domains t)) =>
Int32 -> t -> Arrows (Domains t) (S Int32)
icodeN Int32
3 ()
  icod_ Aspect
HP.Symbol        = Aspect -> Arrows (Domains Aspect) (S Int32)
forall t.
(ICODE t (IsBase t), StrictCurrying (Domains t) (S Int32),
 All EmbPrj (Domains t)) =>
t -> Arrows (Domains t) (S Int32)
icodeN' Aspect
HP.Symbol
  icod_ Aspect
HP.PrimitiveType = Int32 -> () -> Arrows (Domains ()) (S Int32)
forall t.
(ICODE t (IsBase t), StrictCurrying (Domains t) (S Int32),
 All EmbPrj (Domains t)) =>
Int32 -> t -> Arrows (Domains t) (S Int32)
icodeN Int32
4 ()
  icod_ (HP.Name Maybe NameKind
mk Bool
b)   = Int32
-> (Maybe NameKind -> Bool -> Aspect)
-> Arrows (Domains (Maybe NameKind -> Bool -> Aspect)) (S Int32)
forall t.
(ICODE t (IsBase t), StrictCurrying (Domains t) (S Int32),
 All EmbPrj (Domains t)) =>
Int32 -> t -> Arrows (Domains t) (S Int32)
icodeN Int32
5 Maybe NameKind -> Bool -> Aspect
HP.Name Maybe NameKind
mk Bool
b
  icod_ Aspect
HP.Pragma        = Int32 -> () -> Arrows (Domains ()) (S Int32)
forall t.
(ICODE t (IsBase t), StrictCurrying (Domains t) (S Int32),
 All EmbPrj (Domains t)) =>
Int32 -> t -> Arrows (Domains t) (S Int32)
icodeN Int32
6 ()
  icod_ Aspect
HP.Background    = Int32 -> () -> Arrows (Domains ()) (S Int32)
forall t.
(ICODE t (IsBase t), StrictCurrying (Domains t) (S Int32),
 All EmbPrj (Domains t)) =>
Int32 -> t -> Arrows (Domains t) (S Int32)
icodeN Int32
7 ()
  icod_ Aspect
HP.Markup        = Int32 -> () -> Arrows (Domains ()) (S Int32)
forall t.
(ICODE t (IsBase t), StrictCurrying (Domains t) (S Int32),
 All EmbPrj (Domains t)) =>
Int32 -> t -> Arrows (Domains t) (S Int32)
icodeN Int32
8 ()
  icod_ Aspect
HP.Hole          = Int32 -> () -> Arrows (Domains ()) (S Int32)
forall t.
(ICODE t (IsBase t), StrictCurrying (Domains t) (S Int32),
 All EmbPrj (Domains t)) =>
Int32 -> t -> Arrows (Domains t) (S Int32)
icodeN Int32
9 ()

  value :: Int32 -> R Aspect
value = ([Int32] -> R Aspect) -> Int32 -> R Aspect
forall a. EmbPrj a => ([Int32] -> R a) -> Int32 -> R a
vcase [Int32] -> R Aspect
valu where
    valu :: [Int32]
-> Arrows (Constant Int32 (Domains Aspect)) (R (CoDomain Aspect))
valu [Int32
0]        = Aspect
-> Arrows (Constant Int32 (Domains Aspect)) (R (CoDomain Aspect))
forall t.
(VALU t (IsBase t),
 StrictCurrying (Constant Int32 (Domains t)) (R (CoDomain t)),
 All EmbPrj (Domains t)) =>
t -> Arrows (Constant Int32 (Domains t)) (R (CoDomain t))
valuN Aspect
HP.Comment
    valu [Int32
1]        = Aspect
-> Arrows (Constant Int32 (Domains Aspect)) (R (CoDomain Aspect))
forall t.
(VALU t (IsBase t),
 StrictCurrying (Constant Int32 (Domains t)) (R (CoDomain t)),
 All EmbPrj (Domains t)) =>
t -> Arrows (Constant Int32 (Domains t)) (R (CoDomain t))
valuN Aspect
HP.Keyword
    valu [Int32
2]        = Aspect
-> Arrows (Constant Int32 (Domains Aspect)) (R (CoDomain Aspect))
forall t.
(VALU t (IsBase t),
 StrictCurrying (Constant Int32 (Domains t)) (R (CoDomain t)),
 All EmbPrj (Domains t)) =>
t -> Arrows (Constant Int32 (Domains t)) (R (CoDomain t))
valuN Aspect
HP.String
    valu [Int32
3]        = Aspect
-> Arrows (Constant Int32 (Domains Aspect)) (R (CoDomain Aspect))
forall t.
(VALU t (IsBase t),
 StrictCurrying (Constant Int32 (Domains t)) (R (CoDomain t)),
 All EmbPrj (Domains t)) =>
t -> Arrows (Constant Int32 (Domains t)) (R (CoDomain t))
valuN Aspect
HP.Number
    valu []         = Aspect
-> Arrows (Constant Int32 (Domains Aspect)) (R (CoDomain Aspect))
forall t.
(VALU t (IsBase t),
 StrictCurrying (Constant Int32 (Domains t)) (R (CoDomain t)),
 All EmbPrj (Domains t)) =>
t -> Arrows (Constant Int32 (Domains t)) (R (CoDomain t))
valuN Aspect
HP.Symbol
    valu [Int32
4]        = Aspect
-> Arrows (Constant Int32 (Domains Aspect)) (R (CoDomain Aspect))
forall t.
(VALU t (IsBase t),
 StrictCurrying (Constant Int32 (Domains t)) (R (CoDomain t)),
 All EmbPrj (Domains t)) =>
t -> Arrows (Constant Int32 (Domains t)) (R (CoDomain t))
valuN Aspect
HP.PrimitiveType
    valu [Int32
5, Int32
mk, Int32
b] = (Maybe NameKind -> Bool -> Aspect)
-> Arrows
     (Constant Int32 (Domains (Maybe NameKind -> Bool -> Aspect)))
     (R (CoDomain (Maybe NameKind -> Bool -> Aspect)))
forall t.
(VALU t (IsBase t),
 StrictCurrying (Constant Int32 (Domains t)) (R (CoDomain t)),
 All EmbPrj (Domains t)) =>
t -> Arrows (Constant Int32 (Domains t)) (R (CoDomain t))
valuN Maybe NameKind -> Bool -> Aspect
HP.Name Int32
mk Int32
b
    valu [Int32
6]        = Aspect
-> Arrows (Constant Int32 (Domains Aspect)) (R (CoDomain Aspect))
forall t.
(VALU t (IsBase t),
 StrictCurrying (Constant Int32 (Domains t)) (R (CoDomain t)),
 All EmbPrj (Domains t)) =>
t -> Arrows (Constant Int32 (Domains t)) (R (CoDomain t))
valuN Aspect
HP.Pragma
    valu [Int32
7]        = Aspect
-> Arrows (Constant Int32 (Domains Aspect)) (R (CoDomain Aspect))
forall t.
(VALU t (IsBase t),
 StrictCurrying (Constant Int32 (Domains t)) (R (CoDomain t)),
 All EmbPrj (Domains t)) =>
t -> Arrows (Constant Int32 (Domains t)) (R (CoDomain t))
valuN Aspect
HP.Background
    valu [Int32
8]        = Aspect
-> Arrows (Constant Int32 (Domains Aspect)) (R (CoDomain Aspect))
forall t.
(VALU t (IsBase t),
 StrictCurrying (Constant Int32 (Domains t)) (R (CoDomain t)),
 All EmbPrj (Domains t)) =>
t -> Arrows (Constant Int32 (Domains t)) (R (CoDomain t))
valuN Aspect
HP.Markup
    valu [Int32
9]        = Aspect
-> Arrows (Constant Int32 (Domains Aspect)) (R (CoDomain Aspect))
forall t.
(VALU t (IsBase t),
 StrictCurrying (Constant Int32 (Domains t)) (R (CoDomain t)),
 All EmbPrj (Domains t)) =>
t -> Arrows (Constant Int32 (Domains t)) (R (CoDomain t))
valuN Aspect
HP.Hole
    valu [Int32]
_          = R Aspect
Arrows (Constant Int32 (Domains Aspect)) (R (CoDomain Aspect))
forall a. R a
malformed

instance EmbPrj HP.OtherAspect where
  icod_ :: OtherAspect -> S Int32
icod_ OtherAspect
HP.Error                = Int32 -> S Int32
forall a. a -> ReaderT Dict IO a
forall (f :: * -> *) a. Applicative f => a -> f a
pure Int32
0
  icod_ OtherAspect
HP.ErrorWarning         = Int32 -> S Int32
forall a. a -> ReaderT Dict IO a
forall (f :: * -> *) a. Applicative f => a -> f a
pure Int32
1
  icod_ OtherAspect
HP.DottedPattern        = Int32 -> S Int32
forall a. a -> ReaderT Dict IO a
forall (f :: * -> *) a. Applicative f => a -> f a
pure Int32
2
  icod_ OtherAspect
HP.UnsolvedMeta         = Int32 -> S Int32
forall a. a -> ReaderT Dict IO a
forall (f :: * -> *) a. Applicative f => a -> f a
pure Int32
3
  icod_ OtherAspect
HP.TerminationProblem   = Int32 -> S Int32
forall a. a -> ReaderT Dict IO a
forall (f :: * -> *) a. Applicative f => a -> f a
pure Int32
4
  icod_ OtherAspect
HP.IncompletePattern    = Int32 -> S Int32
forall a. a -> ReaderT Dict IO a
forall (f :: * -> *) a. Applicative f => a -> f a
pure Int32
5
  icod_ OtherAspect
HP.TypeChecks           = Int32 -> S Int32
forall a. a -> ReaderT Dict IO a
forall (f :: * -> *) a. Applicative f => a -> f a
pure Int32
6
  icod_ OtherAspect
HP.UnsolvedConstraint   = Int32 -> S Int32
forall a. a -> ReaderT Dict IO a
forall (f :: * -> *) a. Applicative f => a -> f a
pure Int32
7
  icod_ OtherAspect
HP.PositivityProblem    = Int32 -> S Int32
forall a. a -> ReaderT Dict IO a
forall (f :: * -> *) a. Applicative f => a -> f a
pure Int32
8
  icod_ OtherAspect
HP.Deadcode             = Int32 -> S Int32
forall a. a -> ReaderT Dict IO a
forall (f :: * -> *) a. Applicative f => a -> f a
pure Int32
9
  icod_ OtherAspect
HP.CoverageProblem      = Int32 -> S Int32
forall a. a -> ReaderT Dict IO a
forall (f :: * -> *) a. Applicative f => a -> f a
pure Int32
10
  icod_ OtherAspect
HP.CatchallClause       = Int32 -> S Int32
forall a. a -> ReaderT Dict IO a
forall (f :: * -> *) a. Applicative f => a -> f a
pure Int32
11
  icod_ OtherAspect
HP.ConfluenceProblem    = Int32 -> S Int32
forall a. a -> ReaderT Dict IO a
forall (f :: * -> *) a. Applicative f => a -> f a
pure Int32
12
  icod_ OtherAspect
HP.MissingDefinition    = Int32 -> S Int32
forall a. a -> ReaderT Dict IO a
forall (f :: * -> *) a. Applicative f => a -> f a
pure Int32
13
  icod_ OtherAspect
HP.ShadowingInTelescope = Int32 -> S Int32
forall a. a -> ReaderT Dict IO a
forall (f :: * -> *) a. Applicative f => a -> f a
pure Int32
14

  value :: Int32 -> R OtherAspect
value = \case
    Int32
0  -> OtherAspect -> R OtherAspect
forall a. a -> StateT St IO a
forall (f :: * -> *) a. Applicative f => a -> f a
pure OtherAspect
HP.Error
    Int32
1  -> OtherAspect -> R OtherAspect
forall a. a -> StateT St IO a
forall (f :: * -> *) a. Applicative f => a -> f a
pure OtherAspect
HP.ErrorWarning
    Int32
2  -> OtherAspect -> R OtherAspect
forall a. a -> StateT St IO a
forall (f :: * -> *) a. Applicative f => a -> f a
pure OtherAspect
HP.DottedPattern
    Int32
3  -> OtherAspect -> R OtherAspect
forall a. a -> StateT St IO a
forall (f :: * -> *) a. Applicative f => a -> f a
pure OtherAspect
HP.UnsolvedMeta
    Int32
4  -> OtherAspect -> R OtherAspect
forall a. a -> StateT St IO a
forall (f :: * -> *) a. Applicative f => a -> f a
pure OtherAspect
HP.TerminationProblem
    Int32
5  -> OtherAspect -> R OtherAspect
forall a. a -> StateT St IO a
forall (f :: * -> *) a. Applicative f => a -> f a
pure OtherAspect
HP.IncompletePattern
    Int32
6  -> OtherAspect -> R OtherAspect
forall a. a -> StateT St IO a
forall (f :: * -> *) a. Applicative f => a -> f a
pure OtherAspect
HP.TypeChecks
    Int32
7  -> OtherAspect -> R OtherAspect
forall a. a -> StateT St IO a
forall (f :: * -> *) a. Applicative f => a -> f a
pure OtherAspect
HP.UnsolvedConstraint
    Int32
8  -> OtherAspect -> R OtherAspect
forall a. a -> StateT St IO a
forall (f :: * -> *) a. Applicative f => a -> f a
pure OtherAspect
HP.PositivityProblem
    Int32
9  -> OtherAspect -> R OtherAspect
forall a. a -> StateT St IO a
forall (f :: * -> *) a. Applicative f => a -> f a
pure OtherAspect
HP.Deadcode
    Int32
10 -> OtherAspect -> R OtherAspect
forall a. a -> StateT St IO a
forall (f :: * -> *) a. Applicative f => a -> f a
pure OtherAspect
HP.CoverageProblem
    Int32
11 -> OtherAspect -> R OtherAspect
forall a. a -> StateT St IO a
forall (f :: * -> *) a. Applicative f => a -> f a
pure OtherAspect
HP.CatchallClause
    Int32
12 -> OtherAspect -> R OtherAspect
forall a. a -> StateT St IO a
forall (f :: * -> *) a. Applicative f => a -> f a
pure OtherAspect
HP.ConfluenceProblem
    Int32
13 -> OtherAspect -> R OtherAspect
forall a. a -> StateT St IO a
forall (f :: * -> *) a. Applicative f => a -> f a
pure OtherAspect
HP.MissingDefinition
    Int32
14 -> OtherAspect -> R OtherAspect
forall a. a -> StateT St IO a
forall (f :: * -> *) a. Applicative f => a -> f a
pure OtherAspect
HP.ShadowingInTelescope
    Int32
_  -> R OtherAspect
forall a. R a
malformed

instance EmbPrj HP.Aspects where
  icod_ :: Aspects -> S Int32
icod_ (HP.Aspects Maybe Aspect
a Set OtherAspect
b String
c Maybe DefinitionSite
d TokenBased
e) = (Maybe Aspect
 -> Set OtherAspect
 -> String
 -> Maybe DefinitionSite
 -> TokenBased
 -> Aspects)
-> Arrows
     (Domains
        (Maybe Aspect
         -> Set OtherAspect
         -> String
         -> Maybe DefinitionSite
         -> TokenBased
         -> Aspects))
     (S Int32)
forall t.
(ICODE t (IsBase t), StrictCurrying (Domains t) (S Int32),
 All EmbPrj (Domains t)) =>
t -> Arrows (Domains t) (S Int32)
icodeN' Maybe Aspect
-> Set OtherAspect
-> String
-> Maybe DefinitionSite
-> TokenBased
-> Aspects
HP.Aspects Maybe Aspect
a Set OtherAspect
b String
c Maybe DefinitionSite
d TokenBased
e

  value :: Int32 -> R Aspects
value = (Maybe Aspect
 -> Set OtherAspect
 -> String
 -> Maybe DefinitionSite
 -> TokenBased
 -> Aspects)
-> Int32
-> R (CoDomain
        (Maybe Aspect
         -> Set OtherAspect
         -> String
         -> Maybe DefinitionSite
         -> TokenBased
         -> Aspects))
forall t.
(VALU t (IsBase t), All EmbPrj (CoDomain t : Domains t)) =>
t -> Int32 -> R (CoDomain t)
valueN Maybe Aspect
-> Set OtherAspect
-> String
-> Maybe DefinitionSite
-> TokenBased
-> Aspects
HP.Aspects

instance EmbPrj HP.DefinitionSite where
  icod_ :: DefinitionSite -> S Int32
icod_ (HP.DefinitionSite TopLevelModuleName' Range
a Int
b Bool
c Maybe String
d) = (TopLevelModuleName' Range
 -> Int -> Bool -> Maybe String -> DefinitionSite)
-> Arrows
     (Domains
        (TopLevelModuleName' Range
         -> Int -> Bool -> Maybe String -> DefinitionSite))
     (S Int32)
forall t.
(ICODE t (IsBase t), StrictCurrying (Domains t) (S Int32),
 All EmbPrj (Domains t)) =>
t -> Arrows (Domains t) (S Int32)
icodeN' TopLevelModuleName' Range
-> Int -> Bool -> Maybe String -> DefinitionSite
HP.DefinitionSite TopLevelModuleName' Range
a Int
b Bool
c Maybe String
d

  value :: Int32 -> R DefinitionSite
value = (TopLevelModuleName' Range
 -> Int -> Bool -> Maybe String -> DefinitionSite)
-> Int32
-> R (CoDomain
        (TopLevelModuleName' Range
         -> Int -> Bool -> Maybe String -> DefinitionSite))
forall t.
(VALU t (IsBase t), All EmbPrj (CoDomain t : Domains t)) =>
t -> Int32 -> R (CoDomain t)
valueN TopLevelModuleName' Range
-> Int -> Bool -> Maybe String -> DefinitionSite
HP.DefinitionSite

instance EmbPrj a => EmbPrj (RM.RangeMap a) where
  -- Write the RangeMap as flat list rather than a list of (Int, (Int, x)). Much
  -- like Map, we need to call `convert' in the tail position and so the output
  -- list is written (and read) in reverse order.
  icod_ :: RangeMap a -> S Int32
icod_ (RM.RangeMap Map Int (PairInt a)
f) = Node -> S Int32
icodeNode (Node -> S Int32) -> ReaderT Dict IO Node -> S Int32
forall (m :: * -> *) a b. Monad m => (a -> m b) -> m a -> m b
=<< Node -> [(Int, PairInt a)] -> ReaderT Dict IO Node
convert Node
Empty (Map Int (PairInt a) -> [(Int, PairInt a)]
forall k a. Map k a -> [(k, a)]
Map.toAscList Map Int (PairInt a)
f) where
    convert :: Node -> [(Int, RM.PairInt a)] -> S Node
    convert :: Node -> [(Int, PairInt a)] -> ReaderT Dict IO Node
convert !Node
ys [] = Node -> ReaderT Dict IO Node
forall a. a -> ReaderT Dict IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Node
ys
    convert  Node
ys ((Int
start, RM.PairInt (Int
end :!: a
entry)):[(Int, PairInt a)]
xs) = do
      !Int32
start <- Int -> S Int32
forall a. EmbPrj a => a -> S Int32
icode Int
start
      !Int32
end <- Int -> S Int32
forall a. EmbPrj a => a -> S Int32
icode Int
end
      !Int32
entry <- a -> S Int32
forall a. EmbPrj a => a -> S Int32
icode a
entry
      Node -> [(Int, PairInt a)] -> ReaderT Dict IO Node
convert (Int32 -> Node -> Node
Cons Int32
start (Int32 -> Node -> Node
Cons Int32
end (Int32 -> Node -> Node
Cons Int32
entry Node
ys))) [(Int, PairInt a)]
xs

  value :: Int32 -> R (RangeMap a)
value = ([Int32] -> R (RangeMap a)) -> Int32 -> R (RangeMap a)
forall a. EmbPrj a => ([Int32] -> R a) -> Int32 -> R a
vcase (([(Int, PairInt a)] -> RangeMap a)
-> StateT St IO [(Int, PairInt a)] -> R (RangeMap a)
forall a b. (a -> b) -> StateT St IO a -> StateT St IO b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap (Map Int (PairInt a) -> RangeMap a
forall a. Map Int (PairInt a) -> RangeMap a
RM.RangeMap (Map Int (PairInt a) -> RangeMap a)
-> ([(Int, PairInt a)] -> Map Int (PairInt a))
-> [(Int, PairInt a)]
-> RangeMap a
forall b c a. (b -> c) -> (a -> b) -> a -> c
. [(Int, PairInt a)] -> Map Int (PairInt a)
forall k a. [(k, a)] -> Map k a
Map.fromDistinctAscList) (StateT St IO [(Int, PairInt a)] -> R (RangeMap a))
-> ([Int32] -> StateT St IO [(Int, PairInt a)])
-> [Int32]
-> R (RangeMap a)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. [(Int, PairInt a)] -> [Int32] -> StateT St IO [(Int, PairInt a)]
convert []) where
    convert :: [(Int, RM.PairInt a)] -> [Int32] -> R [(Int, RM.PairInt a)]
    convert :: [(Int, PairInt a)] -> [Int32] -> StateT St IO [(Int, PairInt a)]
convert ![(Int, PairInt a)]
ys [] = [(Int, PairInt a)] -> StateT St IO [(Int, PairInt a)]
forall a. a -> StateT St IO a
forall (m :: * -> *) a. Monad m => a -> m a
return [(Int, PairInt a)]
ys
    convert  [(Int, PairInt a)]
ys (Int32
start:Int32
end:Int32
entry:[Int32]
xs) = do
      !Int
start <- Int32 -> R Int
forall a. EmbPrj a => Int32 -> R a
value Int32
start
      !Int
end <- Int32 -> R Int
forall a. EmbPrj a => Int32 -> R a
value Int32
end
      !a
entry <- Int32 -> R a
forall a. EmbPrj a => Int32 -> R a
value Int32
entry
      [(Int, PairInt a)] -> [Int32] -> StateT St IO [(Int, PairInt a)]
convert ((Int
start, Pair Int a -> PairInt a
forall a. Pair Int a -> PairInt a
RM.PairInt (Int
end Int -> a -> Pair Int a
forall a b. a -> b -> Pair a b
:!: a
entry))(Int, PairInt a) -> [(Int, PairInt a)] -> [(Int, PairInt a)]
forall a. a -> [a] -> [a]
:[(Int, PairInt a)]
ys) [Int32]
xs
    convert [(Int, PairInt a)]
_ [Int32]
_ = StateT St IO [(Int, PairInt a)]
forall a. R a
malformed

instance EmbPrj HP.TokenBased where
  icod_ :: TokenBased -> S Int32
icod_ TokenBased
HP.TokenBased        = Int32 -> S Int32
forall a. a -> ReaderT Dict IO a
forall (f :: * -> *) a. Applicative f => a -> f a
pure Int32
0
  icod_ TokenBased
HP.NotOnlyTokenBased = Int32 -> S Int32
forall a. a -> ReaderT Dict IO a
forall (f :: * -> *) a. Applicative f => a -> f a
pure Int32
1

  value :: Int32 -> R TokenBased
value = \case
    Int32
0 -> TokenBased -> R TokenBased
forall a. a -> StateT St IO a
forall (f :: * -> *) a. Applicative f => a -> f a
pure TokenBased
HP.TokenBased
    Int32
1 -> TokenBased -> R TokenBased
forall a. a -> StateT St IO a
forall (f :: * -> *) a. Applicative f => a -> f a
pure TokenBased
HP.NotOnlyTokenBased
    Int32
_ -> R TokenBased
forall a. R a
malformed