{-# LANGUAGE DeriveAnyClass        #-}
{-# LANGUAGE DeriveGeneric         #-}
{-# LANGUAGE DuplicateRecordFields #-}

module Ide.Plugin.CallHierarchy.Types where

import           Data.Aeson
import           Database.SQLite.Simple
import           Database.SQLite.Simple.ToField
import           GHC.Generics

data Vertex = Vertex {
  Vertex -> String
mod    :: String
, Vertex -> String
occ    :: String
, Vertex -> String
hieSrc :: FilePath
, Vertex -> Int
sl     :: Int
, Vertex -> Int
sc     :: Int
, Vertex -> Int
el     :: Int
, Vertex -> Int
ec     :: Int
, Vertex -> Int
casl   :: Int -- sl for call appear
, Vertex -> Int
casc   :: Int -- sc for call appear
, Vertex -> Int
cael   :: Int -- el for call appear
, Vertex -> Int
caec   :: Int -- ec for call appear
} deriving (Vertex -> Vertex -> Bool
(Vertex -> Vertex -> Bool)
-> (Vertex -> Vertex -> Bool) -> Eq Vertex
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: Vertex -> Vertex -> Bool
$c/= :: Vertex -> Vertex -> Bool
== :: Vertex -> Vertex -> Bool
$c== :: Vertex -> Vertex -> Bool
Eq, Int -> Vertex -> ShowS
[Vertex] -> ShowS
Vertex -> String
(Int -> Vertex -> ShowS)
-> (Vertex -> String) -> ([Vertex] -> ShowS) -> Show Vertex
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [Vertex] -> ShowS
$cshowList :: [Vertex] -> ShowS
show :: Vertex -> String
$cshow :: Vertex -> String
showsPrec :: Int -> Vertex -> ShowS
$cshowsPrec :: Int -> Vertex -> ShowS
Show, (forall x. Vertex -> Rep Vertex x)
-> (forall x. Rep Vertex x -> Vertex) -> Generic Vertex
forall x. Rep Vertex x -> Vertex
forall x. Vertex -> Rep Vertex x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep Vertex x -> Vertex
$cfrom :: forall x. Vertex -> Rep Vertex x
Generic, Value -> Parser [Vertex]
Value -> Parser Vertex
(Value -> Parser Vertex)
-> (Value -> Parser [Vertex]) -> FromJSON Vertex
forall a.
(Value -> Parser a) -> (Value -> Parser [a]) -> FromJSON a
parseJSONList :: Value -> Parser [Vertex]
$cparseJSONList :: Value -> Parser [Vertex]
parseJSON :: Value -> Parser Vertex
$cparseJSON :: Value -> Parser Vertex
FromJSON, [Vertex] -> Encoding
[Vertex] -> Value
Vertex -> Encoding
Vertex -> Value
(Vertex -> Value)
-> (Vertex -> Encoding)
-> ([Vertex] -> Value)
-> ([Vertex] -> Encoding)
-> ToJSON Vertex
forall a.
(a -> Value)
-> (a -> Encoding)
-> ([a] -> Value)
-> ([a] -> Encoding)
-> ToJSON a
toEncodingList :: [Vertex] -> Encoding
$ctoEncodingList :: [Vertex] -> Encoding
toJSONList :: [Vertex] -> Value
$ctoJSONList :: [Vertex] -> Value
toEncoding :: Vertex -> Encoding
$ctoEncoding :: Vertex -> Encoding
toJSON :: Vertex -> Value
$ctoJSON :: Vertex -> Value
ToJSON)

instance ToRow Vertex where
  toRow :: Vertex -> [SQLData]
toRow (Vertex String
a String
b String
c Int
d Int
e Int
f Int
g Int
h Int
i Int
j Int
k) =
    [ String -> SQLData
forall a. ToField a => a -> SQLData
toField String
a, String -> SQLData
forall a. ToField a => a -> SQLData
toField String
b, String -> SQLData
forall a. ToField a => a -> SQLData
toField String
c, Int -> SQLData
forall a. ToField a => a -> SQLData
toField Int
d
    , Int -> SQLData
forall a. ToField a => a -> SQLData
toField Int
e, Int -> SQLData
forall a. ToField a => a -> SQLData
toField Int
f, Int -> SQLData
forall a. ToField a => a -> SQLData
toField Int
g, Int -> SQLData
forall a. ToField a => a -> SQLData
toField Int
h
    , Int -> SQLData
forall a. ToField a => a -> SQLData
toField Int
i, Int -> SQLData
forall a. ToField a => a -> SQLData
toField Int
j, Int -> SQLData
forall a. ToField a => a -> SQLData
toField Int
k
    ]

instance FromRow Vertex where
  fromRow :: RowParser Vertex
fromRow = String
-> String
-> String
-> Int
-> Int
-> Int
-> Int
-> Int
-> Int
-> Int
-> Int
-> Vertex
Vertex (String
 -> String
 -> String
 -> Int
 -> Int
 -> Int
 -> Int
 -> Int
 -> Int
 -> Int
 -> Int
 -> Vertex)
-> RowParser String
-> RowParser
     (String
      -> String
      -> Int
      -> Int
      -> Int
      -> Int
      -> Int
      -> Int
      -> Int
      -> Int
      -> Vertex)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> RowParser String
forall a. FromField a => RowParser a
field RowParser
  (String
   -> String
   -> Int
   -> Int
   -> Int
   -> Int
   -> Int
   -> Int
   -> Int
   -> Int
   -> Vertex)
-> RowParser String
-> RowParser
     (String
      -> Int -> Int -> Int -> Int -> Int -> Int -> Int -> Int -> Vertex)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> RowParser String
forall a. FromField a => RowParser a
field RowParser
  (String
   -> Int -> Int -> Int -> Int -> Int -> Int -> Int -> Int -> Vertex)
-> RowParser String
-> RowParser
     (Int -> Int -> Int -> Int -> Int -> Int -> Int -> Int -> Vertex)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> RowParser String
forall a. FromField a => RowParser a
field
                   RowParser
  (Int -> Int -> Int -> Int -> Int -> Int -> Int -> Int -> Vertex)
-> RowParser Int
-> RowParser
     (Int -> Int -> Int -> Int -> Int -> Int -> Int -> Vertex)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> RowParser Int
forall a. FromField a => RowParser a
field RowParser (Int -> Int -> Int -> Int -> Int -> Int -> Int -> Vertex)
-> RowParser Int
-> RowParser (Int -> Int -> Int -> Int -> Int -> Int -> Vertex)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> RowParser Int
forall a. FromField a => RowParser a
field RowParser (Int -> Int -> Int -> Int -> Int -> Int -> Vertex)
-> RowParser Int
-> RowParser (Int -> Int -> Int -> Int -> Int -> Vertex)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> RowParser Int
forall a. FromField a => RowParser a
field
                   RowParser (Int -> Int -> Int -> Int -> Int -> Vertex)
-> RowParser Int -> RowParser (Int -> Int -> Int -> Int -> Vertex)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> RowParser Int
forall a. FromField a => RowParser a
field RowParser (Int -> Int -> Int -> Int -> Vertex)
-> RowParser Int -> RowParser (Int -> Int -> Int -> Vertex)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> RowParser Int
forall a. FromField a => RowParser a
field RowParser (Int -> Int -> Int -> Vertex)
-> RowParser Int -> RowParser (Int -> Int -> Vertex)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> RowParser Int
forall a. FromField a => RowParser a
field
                   RowParser (Int -> Int -> Vertex)
-> RowParser Int -> RowParser (Int -> Vertex)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> RowParser Int
forall a. FromField a => RowParser a
field RowParser (Int -> Vertex) -> RowParser Int -> RowParser Vertex
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> RowParser Int
forall a. FromField a => RowParser a
field
data SymbolPosition = SymbolPosition {
  SymbolPosition -> Int
psl :: Int
, SymbolPosition -> Int
psc :: Int
} deriving (SymbolPosition -> SymbolPosition -> Bool
(SymbolPosition -> SymbolPosition -> Bool)
-> (SymbolPosition -> SymbolPosition -> Bool) -> Eq SymbolPosition
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: SymbolPosition -> SymbolPosition -> Bool
$c/= :: SymbolPosition -> SymbolPosition -> Bool
== :: SymbolPosition -> SymbolPosition -> Bool
$c== :: SymbolPosition -> SymbolPosition -> Bool
Eq, Int -> SymbolPosition -> ShowS
[SymbolPosition] -> ShowS
SymbolPosition -> String
(Int -> SymbolPosition -> ShowS)
-> (SymbolPosition -> String)
-> ([SymbolPosition] -> ShowS)
-> Show SymbolPosition
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [SymbolPosition] -> ShowS
$cshowList :: [SymbolPosition] -> ShowS
show :: SymbolPosition -> String
$cshow :: SymbolPosition -> String
showsPrec :: Int -> SymbolPosition -> ShowS
$cshowsPrec :: Int -> SymbolPosition -> ShowS
Show, (forall x. SymbolPosition -> Rep SymbolPosition x)
-> (forall x. Rep SymbolPosition x -> SymbolPosition)
-> Generic SymbolPosition
forall x. Rep SymbolPosition x -> SymbolPosition
forall x. SymbolPosition -> Rep SymbolPosition x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep SymbolPosition x -> SymbolPosition
$cfrom :: forall x. SymbolPosition -> Rep SymbolPosition x
Generic, Value -> Parser [SymbolPosition]
Value -> Parser SymbolPosition
(Value -> Parser SymbolPosition)
-> (Value -> Parser [SymbolPosition]) -> FromJSON SymbolPosition
forall a.
(Value -> Parser a) -> (Value -> Parser [a]) -> FromJSON a
parseJSONList :: Value -> Parser [SymbolPosition]
$cparseJSONList :: Value -> Parser [SymbolPosition]
parseJSON :: Value -> Parser SymbolPosition
$cparseJSON :: Value -> Parser SymbolPosition
FromJSON, [SymbolPosition] -> Encoding
[SymbolPosition] -> Value
SymbolPosition -> Encoding
SymbolPosition -> Value
(SymbolPosition -> Value)
-> (SymbolPosition -> Encoding)
-> ([SymbolPosition] -> Value)
-> ([SymbolPosition] -> Encoding)
-> ToJSON SymbolPosition
forall a.
(a -> Value)
-> (a -> Encoding)
-> ([a] -> Value)
-> ([a] -> Encoding)
-> ToJSON a
toEncodingList :: [SymbolPosition] -> Encoding
$ctoEncodingList :: [SymbolPosition] -> Encoding
toJSONList :: [SymbolPosition] -> Value
$ctoJSONList :: [SymbolPosition] -> Value
toEncoding :: SymbolPosition -> Encoding
$ctoEncoding :: SymbolPosition -> Encoding
toJSON :: SymbolPosition -> Value
$ctoJSON :: SymbolPosition -> Value
ToJSON)

instance ToRow SymbolPosition where
  toRow :: SymbolPosition -> [SQLData]
toRow (SymbolPosition Int
a Int
b) = (Int, Int) -> [SQLData]
forall a. ToRow a => a -> [SQLData]
toRow (Int
a, Int
b)

instance FromRow SymbolPosition where
  fromRow :: RowParser SymbolPosition
fromRow = Int -> Int -> SymbolPosition
SymbolPosition (Int -> Int -> SymbolPosition)
-> RowParser Int -> RowParser (Int -> SymbolPosition)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> RowParser Int
forall a. FromField a => RowParser a
field RowParser (Int -> SymbolPosition)
-> RowParser Int -> RowParser SymbolPosition
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> RowParser Int
forall a. FromField a => RowParser a
field