{-# LANGUAGE DeriveGeneric #-}
{-# LANGUAGE DeriveAnyClass #-}
{-# LANGUAGE OverloadedStrings #-}
module Callable
where
import Cfg
import Fqn
import Token
import Location
import Data.Aeson
import GHC.Generics
data Callables
= Callables
{
Callables -> [Callable]
actualCallables :: [ Callable ]
}
deriving ( Int -> Callables -> ShowS
[Callables] -> ShowS
Callables -> String
(Int -> Callables -> ShowS)
-> (Callables -> String)
-> ([Callables] -> ShowS)
-> Show Callables
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> Callables -> ShowS
showsPrec :: Int -> Callables -> ShowS
$cshow :: Callables -> String
show :: Callables -> String
$cshowList :: [Callables] -> ShowS
showList :: [Callables] -> ShowS
Show, Callables -> Callables -> Bool
(Callables -> Callables -> Bool)
-> (Callables -> Callables -> Bool) -> Eq Callables
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: Callables -> Callables -> Bool
== :: Callables -> Callables -> Bool
$c/= :: Callables -> Callables -> Bool
/= :: Callables -> Callables -> Bool
Eq, Eq Callables
Eq Callables
-> (Callables -> Callables -> Ordering)
-> (Callables -> Callables -> Bool)
-> (Callables -> Callables -> Bool)
-> (Callables -> Callables -> Bool)
-> (Callables -> Callables -> Bool)
-> (Callables -> Callables -> Callables)
-> (Callables -> Callables -> Callables)
-> Ord Callables
Callables -> Callables -> Bool
Callables -> Callables -> Ordering
Callables -> Callables -> Callables
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
$ccompare :: Callables -> Callables -> Ordering
compare :: Callables -> Callables -> Ordering
$c< :: Callables -> Callables -> Bool
< :: Callables -> Callables -> Bool
$c<= :: Callables -> Callables -> Bool
<= :: Callables -> Callables -> Bool
$c> :: Callables -> Callables -> Bool
> :: Callables -> Callables -> Bool
$c>= :: Callables -> Callables -> Bool
>= :: Callables -> Callables -> Bool
$cmax :: Callables -> Callables -> Callables
max :: Callables -> Callables -> Callables
$cmin :: Callables -> Callables -> Callables
min :: Callables -> Callables -> Callables
Ord, (forall x. Callables -> Rep Callables x)
-> (forall x. Rep Callables x -> Callables) -> Generic Callables
forall x. Rep Callables x -> Callables
forall x. Callables -> Rep Callables x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cfrom :: forall x. Callables -> Rep Callables x
from :: forall x. Callables -> Rep Callables x
$cto :: forall x. Rep Callables x -> Callables
to :: forall x. Rep Callables x -> Callables
Generic, [Callables] -> Value
[Callables] -> Encoding
Callables -> Bool
Callables -> Value
Callables -> Encoding
(Callables -> Value)
-> (Callables -> Encoding)
-> ([Callables] -> Value)
-> ([Callables] -> Encoding)
-> (Callables -> Bool)
-> ToJSON Callables
forall a.
(a -> Value)
-> (a -> Encoding)
-> ([a] -> Value)
-> ([a] -> Encoding)
-> (a -> Bool)
-> ToJSON a
$ctoJSON :: Callables -> Value
toJSON :: Callables -> Value
$ctoEncoding :: Callables -> Encoding
toEncoding :: Callables -> Encoding
$ctoJSONList :: [Callables] -> Value
toJSONList :: [Callables] -> Value
$ctoEncodingList :: [Callables] -> Encoding
toEncodingList :: [Callables] -> Encoding
$comitField :: Callables -> Bool
omitField :: Callables -> Bool
ToJSON, Maybe Callables
Value -> Parser [Callables]
Value -> Parser Callables
(Value -> Parser Callables)
-> (Value -> Parser [Callables])
-> Maybe Callables
-> FromJSON Callables
forall a.
(Value -> Parser a)
-> (Value -> Parser [a]) -> Maybe a -> FromJSON a
$cparseJSON :: Value -> Parser Callables
parseJSON :: Value -> Parser Callables
$cparseJSONList :: Value -> Parser [Callables]
parseJSONList :: Value -> Parser [Callables]
$comittedField :: Maybe Callables
omittedField :: Maybe Callables
FromJSON )
data Callable
= Method MethodContent
| Lambda LambdaContent
| Script ScriptContent
| Function FunctionContent
deriving ( Int -> Callable -> ShowS
[Callable] -> ShowS
Callable -> String
(Int -> Callable -> ShowS)
-> (Callable -> String) -> ([Callable] -> ShowS) -> Show Callable
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> Callable -> ShowS
showsPrec :: Int -> Callable -> ShowS
$cshow :: Callable -> String
show :: Callable -> String
$cshowList :: [Callable] -> ShowS
showList :: [Callable] -> ShowS
Show, Callable -> Callable -> Bool
(Callable -> Callable -> Bool)
-> (Callable -> Callable -> Bool) -> Eq Callable
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: Callable -> Callable -> Bool
== :: Callable -> Callable -> Bool
$c/= :: Callable -> Callable -> Bool
/= :: Callable -> Callable -> Bool
Eq, Eq Callable
Eq Callable
-> (Callable -> Callable -> Ordering)
-> (Callable -> Callable -> Bool)
-> (Callable -> Callable -> Bool)
-> (Callable -> Callable -> Bool)
-> (Callable -> Callable -> Bool)
-> (Callable -> Callable -> Callable)
-> (Callable -> Callable -> Callable)
-> Ord Callable
Callable -> Callable -> Bool
Callable -> Callable -> Ordering
Callable -> Callable -> Callable
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
$ccompare :: Callable -> Callable -> Ordering
compare :: Callable -> Callable -> Ordering
$c< :: Callable -> Callable -> Bool
< :: Callable -> Callable -> Bool
$c<= :: Callable -> Callable -> Bool
<= :: Callable -> Callable -> Bool
$c> :: Callable -> Callable -> Bool
> :: Callable -> Callable -> Bool
$c>= :: Callable -> Callable -> Bool
>= :: Callable -> Callable -> Bool
$cmax :: Callable -> Callable -> Callable
max :: Callable -> Callable -> Callable
$cmin :: Callable -> Callable -> Callable
min :: Callable -> Callable -> Callable
Ord, (forall x. Callable -> Rep Callable x)
-> (forall x. Rep Callable x -> Callable) -> Generic Callable
forall x. Rep Callable x -> Callable
forall x. Callable -> Rep Callable x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cfrom :: forall x. Callable -> Rep Callable x
from :: forall x. Callable -> Rep Callable x
$cto :: forall x. Rep Callable x -> Callable
to :: forall x. Rep Callable x -> Callable
Generic, [Callable] -> Value
[Callable] -> Encoding
Callable -> Bool
Callable -> Value
Callable -> Encoding
(Callable -> Value)
-> (Callable -> Encoding)
-> ([Callable] -> Value)
-> ([Callable] -> Encoding)
-> (Callable -> Bool)
-> ToJSON Callable
forall a.
(a -> Value)
-> (a -> Encoding)
-> ([a] -> Value)
-> ([a] -> Encoding)
-> (a -> Bool)
-> ToJSON a
$ctoJSON :: Callable -> Value
toJSON :: Callable -> Value
$ctoEncoding :: Callable -> Encoding
toEncoding :: Callable -> Encoding
$ctoJSONList :: [Callable] -> Value
toJSONList :: [Callable] -> Value
$ctoEncodingList :: [Callable] -> Encoding
toEncodingList :: [Callable] -> Encoding
$comitField :: Callable -> Bool
omitField :: Callable -> Bool
ToJSON, Maybe Callable
Value -> Parser [Callable]
Value -> Parser Callable
(Value -> Parser Callable)
-> (Value -> Parser [Callable])
-> Maybe Callable
-> FromJSON Callable
forall a.
(Value -> Parser a)
-> (Value -> Parser [a]) -> Maybe a -> FromJSON a
$cparseJSON :: Value -> Parser Callable
parseJSON :: Value -> Parser Callable
$cparseJSONList :: Value -> Parser [Callable]
parseJSONList :: Value -> Parser [Callable]
$comittedField :: Maybe Callable
omittedField :: Maybe Callable
FromJSON )
data MethodContent
= MethodContent
{
MethodContent -> MethdName
methodName :: Token.MethdName,
MethodContent -> ClassName
hostingClassName :: Token.ClassName,
MethodContent -> [Fqn]
hostingClassSupers :: [ Fqn ],
MethodContent -> Cfg
methodBody :: Cfg,
MethodContent -> Location
methodLocation :: Location
}
deriving ( Int -> MethodContent -> ShowS
[MethodContent] -> ShowS
MethodContent -> String
(Int -> MethodContent -> ShowS)
-> (MethodContent -> String)
-> ([MethodContent] -> ShowS)
-> Show MethodContent
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> MethodContent -> ShowS
showsPrec :: Int -> MethodContent -> ShowS
$cshow :: MethodContent -> String
show :: MethodContent -> String
$cshowList :: [MethodContent] -> ShowS
showList :: [MethodContent] -> ShowS
Show, MethodContent -> MethodContent -> Bool
(MethodContent -> MethodContent -> Bool)
-> (MethodContent -> MethodContent -> Bool) -> Eq MethodContent
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: MethodContent -> MethodContent -> Bool
== :: MethodContent -> MethodContent -> Bool
$c/= :: MethodContent -> MethodContent -> Bool
/= :: MethodContent -> MethodContent -> Bool
Eq, Eq MethodContent
Eq MethodContent
-> (MethodContent -> MethodContent -> Ordering)
-> (MethodContent -> MethodContent -> Bool)
-> (MethodContent -> MethodContent -> Bool)
-> (MethodContent -> MethodContent -> Bool)
-> (MethodContent -> MethodContent -> Bool)
-> (MethodContent -> MethodContent -> MethodContent)
-> (MethodContent -> MethodContent -> MethodContent)
-> Ord MethodContent
MethodContent -> MethodContent -> Bool
MethodContent -> MethodContent -> Ordering
MethodContent -> MethodContent -> MethodContent
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
$ccompare :: MethodContent -> MethodContent -> Ordering
compare :: MethodContent -> MethodContent -> Ordering
$c< :: MethodContent -> MethodContent -> Bool
< :: MethodContent -> MethodContent -> Bool
$c<= :: MethodContent -> MethodContent -> Bool
<= :: MethodContent -> MethodContent -> Bool
$c> :: MethodContent -> MethodContent -> Bool
> :: MethodContent -> MethodContent -> Bool
$c>= :: MethodContent -> MethodContent -> Bool
>= :: MethodContent -> MethodContent -> Bool
$cmax :: MethodContent -> MethodContent -> MethodContent
max :: MethodContent -> MethodContent -> MethodContent
$cmin :: MethodContent -> MethodContent -> MethodContent
min :: MethodContent -> MethodContent -> MethodContent
Ord, (forall x. MethodContent -> Rep MethodContent x)
-> (forall x. Rep MethodContent x -> MethodContent)
-> Generic MethodContent
forall x. Rep MethodContent x -> MethodContent
forall x. MethodContent -> Rep MethodContent x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cfrom :: forall x. MethodContent -> Rep MethodContent x
from :: forall x. MethodContent -> Rep MethodContent x
$cto :: forall x. Rep MethodContent x -> MethodContent
to :: forall x. Rep MethodContent x -> MethodContent
Generic, [MethodContent] -> Value
[MethodContent] -> Encoding
MethodContent -> Bool
MethodContent -> Value
MethodContent -> Encoding
(MethodContent -> Value)
-> (MethodContent -> Encoding)
-> ([MethodContent] -> Value)
-> ([MethodContent] -> Encoding)
-> (MethodContent -> Bool)
-> ToJSON MethodContent
forall a.
(a -> Value)
-> (a -> Encoding)
-> ([a] -> Value)
-> ([a] -> Encoding)
-> (a -> Bool)
-> ToJSON a
$ctoJSON :: MethodContent -> Value
toJSON :: MethodContent -> Value
$ctoEncoding :: MethodContent -> Encoding
toEncoding :: MethodContent -> Encoding
$ctoJSONList :: [MethodContent] -> Value
toJSONList :: [MethodContent] -> Value
$ctoEncodingList :: [MethodContent] -> Encoding
toEncodingList :: [MethodContent] -> Encoding
$comitField :: MethodContent -> Bool
omitField :: MethodContent -> Bool
ToJSON, Maybe MethodContent
Value -> Parser [MethodContent]
Value -> Parser MethodContent
(Value -> Parser MethodContent)
-> (Value -> Parser [MethodContent])
-> Maybe MethodContent
-> FromJSON MethodContent
forall a.
(Value -> Parser a)
-> (Value -> Parser [a]) -> Maybe a -> FromJSON a
$cparseJSON :: Value -> Parser MethodContent
parseJSON :: Value -> Parser MethodContent
$cparseJSONList :: Value -> Parser [MethodContent]
parseJSONList :: Value -> Parser [MethodContent]
$comittedField :: Maybe MethodContent
omittedField :: Maybe MethodContent
FromJSON )
data LambdaContent
= LambdaContent
{
LambdaContent -> Cfg
lambdaBody :: Cfg,
LambdaContent -> Location
lambdaLocation :: Location
}
deriving ( Int -> LambdaContent -> ShowS
[LambdaContent] -> ShowS
LambdaContent -> String
(Int -> LambdaContent -> ShowS)
-> (LambdaContent -> String)
-> ([LambdaContent] -> ShowS)
-> Show LambdaContent
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> LambdaContent -> ShowS
showsPrec :: Int -> LambdaContent -> ShowS
$cshow :: LambdaContent -> String
show :: LambdaContent -> String
$cshowList :: [LambdaContent] -> ShowS
showList :: [LambdaContent] -> ShowS
Show, LambdaContent -> LambdaContent -> Bool
(LambdaContent -> LambdaContent -> Bool)
-> (LambdaContent -> LambdaContent -> Bool) -> Eq LambdaContent
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: LambdaContent -> LambdaContent -> Bool
== :: LambdaContent -> LambdaContent -> Bool
$c/= :: LambdaContent -> LambdaContent -> Bool
/= :: LambdaContent -> LambdaContent -> Bool
Eq, Eq LambdaContent
Eq LambdaContent
-> (LambdaContent -> LambdaContent -> Ordering)
-> (LambdaContent -> LambdaContent -> Bool)
-> (LambdaContent -> LambdaContent -> Bool)
-> (LambdaContent -> LambdaContent -> Bool)
-> (LambdaContent -> LambdaContent -> Bool)
-> (LambdaContent -> LambdaContent -> LambdaContent)
-> (LambdaContent -> LambdaContent -> LambdaContent)
-> Ord LambdaContent
LambdaContent -> LambdaContent -> Bool
LambdaContent -> LambdaContent -> Ordering
LambdaContent -> LambdaContent -> LambdaContent
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
$ccompare :: LambdaContent -> LambdaContent -> Ordering
compare :: LambdaContent -> LambdaContent -> Ordering
$c< :: LambdaContent -> LambdaContent -> Bool
< :: LambdaContent -> LambdaContent -> Bool
$c<= :: LambdaContent -> LambdaContent -> Bool
<= :: LambdaContent -> LambdaContent -> Bool
$c> :: LambdaContent -> LambdaContent -> Bool
> :: LambdaContent -> LambdaContent -> Bool
$c>= :: LambdaContent -> LambdaContent -> Bool
>= :: LambdaContent -> LambdaContent -> Bool
$cmax :: LambdaContent -> LambdaContent -> LambdaContent
max :: LambdaContent -> LambdaContent -> LambdaContent
$cmin :: LambdaContent -> LambdaContent -> LambdaContent
min :: LambdaContent -> LambdaContent -> LambdaContent
Ord, (forall x. LambdaContent -> Rep LambdaContent x)
-> (forall x. Rep LambdaContent x -> LambdaContent)
-> Generic LambdaContent
forall x. Rep LambdaContent x -> LambdaContent
forall x. LambdaContent -> Rep LambdaContent x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cfrom :: forall x. LambdaContent -> Rep LambdaContent x
from :: forall x. LambdaContent -> Rep LambdaContent x
$cto :: forall x. Rep LambdaContent x -> LambdaContent
to :: forall x. Rep LambdaContent x -> LambdaContent
Generic, [LambdaContent] -> Value
[LambdaContent] -> Encoding
LambdaContent -> Bool
LambdaContent -> Value
LambdaContent -> Encoding
(LambdaContent -> Value)
-> (LambdaContent -> Encoding)
-> ([LambdaContent] -> Value)
-> ([LambdaContent] -> Encoding)
-> (LambdaContent -> Bool)
-> ToJSON LambdaContent
forall a.
(a -> Value)
-> (a -> Encoding)
-> ([a] -> Value)
-> ([a] -> Encoding)
-> (a -> Bool)
-> ToJSON a
$ctoJSON :: LambdaContent -> Value
toJSON :: LambdaContent -> Value
$ctoEncoding :: LambdaContent -> Encoding
toEncoding :: LambdaContent -> Encoding
$ctoJSONList :: [LambdaContent] -> Value
toJSONList :: [LambdaContent] -> Value
$ctoEncodingList :: [LambdaContent] -> Encoding
toEncodingList :: [LambdaContent] -> Encoding
$comitField :: LambdaContent -> Bool
omitField :: LambdaContent -> Bool
ToJSON, Maybe LambdaContent
Value -> Parser [LambdaContent]
Value -> Parser LambdaContent
(Value -> Parser LambdaContent)
-> (Value -> Parser [LambdaContent])
-> Maybe LambdaContent
-> FromJSON LambdaContent
forall a.
(Value -> Parser a)
-> (Value -> Parser [a]) -> Maybe a -> FromJSON a
$cparseJSON :: Value -> Parser LambdaContent
parseJSON :: Value -> Parser LambdaContent
$cparseJSONList :: Value -> Parser [LambdaContent]
parseJSONList :: Value -> Parser [LambdaContent]
$comittedField :: Maybe LambdaContent
omittedField :: Maybe LambdaContent
FromJSON )
data ScriptContent
= ScriptContent
{
ScriptContent -> String
filename :: String,
ScriptContent -> Cfg
scriptBody :: Cfg
}
deriving ( Int -> ScriptContent -> ShowS
[ScriptContent] -> ShowS
ScriptContent -> String
(Int -> ScriptContent -> ShowS)
-> (ScriptContent -> String)
-> ([ScriptContent] -> ShowS)
-> Show ScriptContent
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> ScriptContent -> ShowS
showsPrec :: Int -> ScriptContent -> ShowS
$cshow :: ScriptContent -> String
show :: ScriptContent -> String
$cshowList :: [ScriptContent] -> ShowS
showList :: [ScriptContent] -> ShowS
Show, ScriptContent -> ScriptContent -> Bool
(ScriptContent -> ScriptContent -> Bool)
-> (ScriptContent -> ScriptContent -> Bool) -> Eq ScriptContent
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: ScriptContent -> ScriptContent -> Bool
== :: ScriptContent -> ScriptContent -> Bool
$c/= :: ScriptContent -> ScriptContent -> Bool
/= :: ScriptContent -> ScriptContent -> Bool
Eq, Eq ScriptContent
Eq ScriptContent
-> (ScriptContent -> ScriptContent -> Ordering)
-> (ScriptContent -> ScriptContent -> Bool)
-> (ScriptContent -> ScriptContent -> Bool)
-> (ScriptContent -> ScriptContent -> Bool)
-> (ScriptContent -> ScriptContent -> Bool)
-> (ScriptContent -> ScriptContent -> ScriptContent)
-> (ScriptContent -> ScriptContent -> ScriptContent)
-> Ord ScriptContent
ScriptContent -> ScriptContent -> Bool
ScriptContent -> ScriptContent -> Ordering
ScriptContent -> ScriptContent -> ScriptContent
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
$ccompare :: ScriptContent -> ScriptContent -> Ordering
compare :: ScriptContent -> ScriptContent -> Ordering
$c< :: ScriptContent -> ScriptContent -> Bool
< :: ScriptContent -> ScriptContent -> Bool
$c<= :: ScriptContent -> ScriptContent -> Bool
<= :: ScriptContent -> ScriptContent -> Bool
$c> :: ScriptContent -> ScriptContent -> Bool
> :: ScriptContent -> ScriptContent -> Bool
$c>= :: ScriptContent -> ScriptContent -> Bool
>= :: ScriptContent -> ScriptContent -> Bool
$cmax :: ScriptContent -> ScriptContent -> ScriptContent
max :: ScriptContent -> ScriptContent -> ScriptContent
$cmin :: ScriptContent -> ScriptContent -> ScriptContent
min :: ScriptContent -> ScriptContent -> ScriptContent
Ord, (forall x. ScriptContent -> Rep ScriptContent x)
-> (forall x. Rep ScriptContent x -> ScriptContent)
-> Generic ScriptContent
forall x. Rep ScriptContent x -> ScriptContent
forall x. ScriptContent -> Rep ScriptContent x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cfrom :: forall x. ScriptContent -> Rep ScriptContent x
from :: forall x. ScriptContent -> Rep ScriptContent x
$cto :: forall x. Rep ScriptContent x -> ScriptContent
to :: forall x. Rep ScriptContent x -> ScriptContent
Generic, [ScriptContent] -> Value
[ScriptContent] -> Encoding
ScriptContent -> Bool
ScriptContent -> Value
ScriptContent -> Encoding
(ScriptContent -> Value)
-> (ScriptContent -> Encoding)
-> ([ScriptContent] -> Value)
-> ([ScriptContent] -> Encoding)
-> (ScriptContent -> Bool)
-> ToJSON ScriptContent
forall a.
(a -> Value)
-> (a -> Encoding)
-> ([a] -> Value)
-> ([a] -> Encoding)
-> (a -> Bool)
-> ToJSON a
$ctoJSON :: ScriptContent -> Value
toJSON :: ScriptContent -> Value
$ctoEncoding :: ScriptContent -> Encoding
toEncoding :: ScriptContent -> Encoding
$ctoJSONList :: [ScriptContent] -> Value
toJSONList :: [ScriptContent] -> Value
$ctoEncodingList :: [ScriptContent] -> Encoding
toEncodingList :: [ScriptContent] -> Encoding
$comitField :: ScriptContent -> Bool
omitField :: ScriptContent -> Bool
ToJSON, Maybe ScriptContent
Value -> Parser [ScriptContent]
Value -> Parser ScriptContent
(Value -> Parser ScriptContent)
-> (Value -> Parser [ScriptContent])
-> Maybe ScriptContent
-> FromJSON ScriptContent
forall a.
(Value -> Parser a)
-> (Value -> Parser [a]) -> Maybe a -> FromJSON a
$cparseJSON :: Value -> Parser ScriptContent
parseJSON :: Value -> Parser ScriptContent
$cparseJSONList :: Value -> Parser [ScriptContent]
parseJSONList :: Value -> Parser [ScriptContent]
$comittedField :: Maybe ScriptContent
omittedField :: Maybe ScriptContent
FromJSON )
data Annotation
= Annotation
{
Annotation -> String
annotationFqn :: String,
Annotation -> [String]
annotationConstantStrings :: [ String ]
}
deriving ( Int -> Annotation -> ShowS
[Annotation] -> ShowS
Annotation -> String
(Int -> Annotation -> ShowS)
-> (Annotation -> String)
-> ([Annotation] -> ShowS)
-> Show Annotation
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> Annotation -> ShowS
showsPrec :: Int -> Annotation -> ShowS
$cshow :: Annotation -> String
show :: Annotation -> String
$cshowList :: [Annotation] -> ShowS
showList :: [Annotation] -> ShowS
Show, Annotation -> Annotation -> Bool
(Annotation -> Annotation -> Bool)
-> (Annotation -> Annotation -> Bool) -> Eq Annotation
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: Annotation -> Annotation -> Bool
== :: Annotation -> Annotation -> Bool
$c/= :: Annotation -> Annotation -> Bool
/= :: Annotation -> Annotation -> Bool
Eq, Eq Annotation
Eq Annotation
-> (Annotation -> Annotation -> Ordering)
-> (Annotation -> Annotation -> Bool)
-> (Annotation -> Annotation -> Bool)
-> (Annotation -> Annotation -> Bool)
-> (Annotation -> Annotation -> Bool)
-> (Annotation -> Annotation -> Annotation)
-> (Annotation -> Annotation -> Annotation)
-> Ord Annotation
Annotation -> Annotation -> Bool
Annotation -> Annotation -> Ordering
Annotation -> Annotation -> Annotation
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
$ccompare :: Annotation -> Annotation -> Ordering
compare :: Annotation -> Annotation -> Ordering
$c< :: Annotation -> Annotation -> Bool
< :: Annotation -> Annotation -> Bool
$c<= :: Annotation -> Annotation -> Bool
<= :: Annotation -> Annotation -> Bool
$c> :: Annotation -> Annotation -> Bool
> :: Annotation -> Annotation -> Bool
$c>= :: Annotation -> Annotation -> Bool
>= :: Annotation -> Annotation -> Bool
$cmax :: Annotation -> Annotation -> Annotation
max :: Annotation -> Annotation -> Annotation
$cmin :: Annotation -> Annotation -> Annotation
min :: Annotation -> Annotation -> Annotation
Ord, (forall x. Annotation -> Rep Annotation x)
-> (forall x. Rep Annotation x -> Annotation) -> Generic Annotation
forall x. Rep Annotation x -> Annotation
forall x. Annotation -> Rep Annotation x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cfrom :: forall x. Annotation -> Rep Annotation x
from :: forall x. Annotation -> Rep Annotation x
$cto :: forall x. Rep Annotation x -> Annotation
to :: forall x. Rep Annotation x -> Annotation
Generic, [Annotation] -> Value
[Annotation] -> Encoding
Annotation -> Bool
Annotation -> Value
Annotation -> Encoding
(Annotation -> Value)
-> (Annotation -> Encoding)
-> ([Annotation] -> Value)
-> ([Annotation] -> Encoding)
-> (Annotation -> Bool)
-> ToJSON Annotation
forall a.
(a -> Value)
-> (a -> Encoding)
-> ([a] -> Value)
-> ([a] -> Encoding)
-> (a -> Bool)
-> ToJSON a
$ctoJSON :: Annotation -> Value
toJSON :: Annotation -> Value
$ctoEncoding :: Annotation -> Encoding
toEncoding :: Annotation -> Encoding
$ctoJSONList :: [Annotation] -> Value
toJSONList :: [Annotation] -> Value
$ctoEncodingList :: [Annotation] -> Encoding
toEncodingList :: [Annotation] -> Encoding
$comitField :: Annotation -> Bool
omitField :: Annotation -> Bool
ToJSON, Maybe Annotation
Value -> Parser [Annotation]
Value -> Parser Annotation
(Value -> Parser Annotation)
-> (Value -> Parser [Annotation])
-> Maybe Annotation
-> FromJSON Annotation
forall a.
(Value -> Parser a)
-> (Value -> Parser [a]) -> Maybe a -> FromJSON a
$cparseJSON :: Value -> Parser Annotation
parseJSON :: Value -> Parser Annotation
$cparseJSONList :: Value -> Parser [Annotation]
parseJSONList :: Value -> Parser [Annotation]
$comittedField :: Maybe Annotation
omittedField :: Maybe Annotation
FromJSON )
data FunctionContent
= FunctionContent
{
FunctionContent -> FuncName
funcName :: Token.FuncName,
FunctionContent -> Cfg
funcBody :: Cfg,
FunctionContent -> [Annotation]
funcAnnotations :: [ Annotation ],
FunctionContent -> Location
funcLocation :: Location
}
deriving ( Int -> FunctionContent -> ShowS
[FunctionContent] -> ShowS
FunctionContent -> String
(Int -> FunctionContent -> ShowS)
-> (FunctionContent -> String)
-> ([FunctionContent] -> ShowS)
-> Show FunctionContent
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> FunctionContent -> ShowS
showsPrec :: Int -> FunctionContent -> ShowS
$cshow :: FunctionContent -> String
show :: FunctionContent -> String
$cshowList :: [FunctionContent] -> ShowS
showList :: [FunctionContent] -> ShowS
Show, FunctionContent -> FunctionContent -> Bool
(FunctionContent -> FunctionContent -> Bool)
-> (FunctionContent -> FunctionContent -> Bool)
-> Eq FunctionContent
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: FunctionContent -> FunctionContent -> Bool
== :: FunctionContent -> FunctionContent -> Bool
$c/= :: FunctionContent -> FunctionContent -> Bool
/= :: FunctionContent -> FunctionContent -> Bool
Eq, Eq FunctionContent
Eq FunctionContent
-> (FunctionContent -> FunctionContent -> Ordering)
-> (FunctionContent -> FunctionContent -> Bool)
-> (FunctionContent -> FunctionContent -> Bool)
-> (FunctionContent -> FunctionContent -> Bool)
-> (FunctionContent -> FunctionContent -> Bool)
-> (FunctionContent -> FunctionContent -> FunctionContent)
-> (FunctionContent -> FunctionContent -> FunctionContent)
-> Ord FunctionContent
FunctionContent -> FunctionContent -> Bool
FunctionContent -> FunctionContent -> Ordering
FunctionContent -> FunctionContent -> FunctionContent
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
$ccompare :: FunctionContent -> FunctionContent -> Ordering
compare :: FunctionContent -> FunctionContent -> Ordering
$c< :: FunctionContent -> FunctionContent -> Bool
< :: FunctionContent -> FunctionContent -> Bool
$c<= :: FunctionContent -> FunctionContent -> Bool
<= :: FunctionContent -> FunctionContent -> Bool
$c> :: FunctionContent -> FunctionContent -> Bool
> :: FunctionContent -> FunctionContent -> Bool
$c>= :: FunctionContent -> FunctionContent -> Bool
>= :: FunctionContent -> FunctionContent -> Bool
$cmax :: FunctionContent -> FunctionContent -> FunctionContent
max :: FunctionContent -> FunctionContent -> FunctionContent
$cmin :: FunctionContent -> FunctionContent -> FunctionContent
min :: FunctionContent -> FunctionContent -> FunctionContent
Ord, (forall x. FunctionContent -> Rep FunctionContent x)
-> (forall x. Rep FunctionContent x -> FunctionContent)
-> Generic FunctionContent
forall x. Rep FunctionContent x -> FunctionContent
forall x. FunctionContent -> Rep FunctionContent x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cfrom :: forall x. FunctionContent -> Rep FunctionContent x
from :: forall x. FunctionContent -> Rep FunctionContent x
$cto :: forall x. Rep FunctionContent x -> FunctionContent
to :: forall x. Rep FunctionContent x -> FunctionContent
Generic, [FunctionContent] -> Value
[FunctionContent] -> Encoding
FunctionContent -> Bool
FunctionContent -> Value
FunctionContent -> Encoding
(FunctionContent -> Value)
-> (FunctionContent -> Encoding)
-> ([FunctionContent] -> Value)
-> ([FunctionContent] -> Encoding)
-> (FunctionContent -> Bool)
-> ToJSON FunctionContent
forall a.
(a -> Value)
-> (a -> Encoding)
-> ([a] -> Value)
-> ([a] -> Encoding)
-> (a -> Bool)
-> ToJSON a
$ctoJSON :: FunctionContent -> Value
toJSON :: FunctionContent -> Value
$ctoEncoding :: FunctionContent -> Encoding
toEncoding :: FunctionContent -> Encoding
$ctoJSONList :: [FunctionContent] -> Value
toJSONList :: [FunctionContent] -> Value
$ctoEncodingList :: [FunctionContent] -> Encoding
toEncodingList :: [FunctionContent] -> Encoding
$comitField :: FunctionContent -> Bool
omitField :: FunctionContent -> Bool
ToJSON, Maybe FunctionContent
Value -> Parser [FunctionContent]
Value -> Parser FunctionContent
(Value -> Parser FunctionContent)
-> (Value -> Parser [FunctionContent])
-> Maybe FunctionContent
-> FromJSON FunctionContent
forall a.
(Value -> Parser a)
-> (Value -> Parser [a]) -> Maybe a -> FromJSON a
$cparseJSON :: Value -> Parser FunctionContent
parseJSON :: Value -> Parser FunctionContent
$cparseJSONList :: Value -> Parser [FunctionContent]
parseJSONList :: Value -> Parser [FunctionContent]
$comittedField :: Maybe FunctionContent
omittedField :: Maybe FunctionContent
FromJSON )