{-# LANGUAGE DeriveFunctor      #-}
{-# LANGUAGE DeriveGeneric      #-}
{-# LANGUAGE DeriveTraversable  #-}
{-# LANGUAGE DerivingVia        #-}
{-# LANGUAGE FlexibleInstances  #-}
{-# LANGUAGE StandaloneDeriving #-}
{-# LANGUAGE StrictData         #-}
module Language.Cimple.Ast
    ( AssignOp (..)
    , BinaryOp (..)
    , UnaryOp (..)
    , LiteralType (..)
    , Node, NodeF (..)
    , Scope (..)
    , CommentStyle (..)
    ) where

import           Data.Aeson                   (FromJSON, FromJSON1, ToJSON,
                                               ToJSON1)
import           Data.Fix                     (Fix)
import           Data.Functor.Classes         (Eq1, Read1, Show1)
import           Data.Functor.Classes.Generic (FunctorClassesDefault (..))
import           GHC.Generics                 (Generic, Generic1)

data NodeF lexeme a
    -- Preprocessor
    = PreprocInclude lexeme
    | PreprocDefine lexeme
    | PreprocDefineConst lexeme a
    | PreprocDefineMacro lexeme [a] a
    | PreprocIf a [a] a
    | PreprocIfdef lexeme [a] a
    | PreprocIfndef lexeme [a] a
    | PreprocElse [a]
    | PreprocElif a [a] a
    | PreprocUndef lexeme
    | PreprocDefined lexeme
    | PreprocScopedDefine a [a] a
    | MacroBodyStmt a
    | MacroBodyFunCall a
    | MacroParam lexeme
    | StaticAssert a lexeme
    -- Comments
    | LicenseDecl lexeme [a]
    | CopyrightDecl lexeme (Maybe lexeme) [lexeme]
    | Comment CommentStyle lexeme [lexeme] lexeme
    | CommentBlock lexeme
    | Commented a a
    -- Namespace-like blocks
    | ExternC [a]
    -- Statements
    | CompoundStmt [a]
    | Break
    | Goto lexeme
    | Continue
    | Return (Maybe a)
    | SwitchStmt a [a]
    | IfStmt a a (Maybe a)
    | ForStmt a a a a
    | WhileStmt a a
    | DoWhileStmt a a
    | Case a a
    | Default a
    | Label lexeme a
    -- Variable declarations
    | VLA a lexeme a
    | VarDecl a a
    | Declarator a (Maybe a)
    | DeclSpecVar lexeme
    | DeclSpecArray a (Maybe a)
    -- Expressions
    | InitialiserList [a]
    | UnaryExpr UnaryOp a
    | BinaryExpr a BinaryOp a
    | TernaryExpr a a a
    | AssignExpr a AssignOp a
    | ParenExpr a
    | CastExpr a a
    | CompoundExpr a a
    | SizeofExpr a
    | SizeofType a
    | LiteralExpr LiteralType lexeme
    | VarExpr lexeme
    | MemberAccess a lexeme
    | PointerAccess a lexeme
    | ArrayAccess a a
    | FunctionCall a [a]
    | CommentExpr a a
    -- Type definitions
    | EnumConsts (Maybe lexeme) [a]
    | EnumDecl lexeme [a] lexeme
    | Enumerator lexeme (Maybe a)
    | Typedef a lexeme
    | TypedefFunction a
    | Struct lexeme [a]
    | Union lexeme [a]
    | MemberDecl a a (Maybe lexeme)
    | TyConst a
    | TyPointer a
    | TyStruct lexeme
    | TyFunc lexeme
    | TyStd lexeme
    | TyUserDefined lexeme
    -- Functions
    | FunctionDecl Scope a
    | FunctionDefn Scope a a
    | FunctionPrototype a lexeme [a]
    | FunctionParam a a
    | Ellipsis
    -- Constants
    | ConstDecl a lexeme
    | ConstDefn Scope a lexeme a
    deriving (Int -> NodeF lexeme a -> ShowS
[NodeF lexeme a] -> ShowS
NodeF lexeme a -> String
(Int -> NodeF lexeme a -> ShowS)
-> (NodeF lexeme a -> String)
-> ([NodeF lexeme a] -> ShowS)
-> Show (NodeF lexeme a)
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
forall lexeme a.
(Show lexeme, Show a) =>
Int -> NodeF lexeme a -> ShowS
forall lexeme a. (Show lexeme, Show a) => [NodeF lexeme a] -> ShowS
forall lexeme a. (Show lexeme, Show a) => NodeF lexeme a -> String
showList :: [NodeF lexeme a] -> ShowS
$cshowList :: forall lexeme a. (Show lexeme, Show a) => [NodeF lexeme a] -> ShowS
show :: NodeF lexeme a -> String
$cshow :: forall lexeme a. (Show lexeme, Show a) => NodeF lexeme a -> String
showsPrec :: Int -> NodeF lexeme a -> ShowS
$cshowsPrec :: forall lexeme a.
(Show lexeme, Show a) =>
Int -> NodeF lexeme a -> ShowS
Show, ReadPrec [NodeF lexeme a]
ReadPrec (NodeF lexeme a)
Int -> ReadS (NodeF lexeme a)
ReadS [NodeF lexeme a]
(Int -> ReadS (NodeF lexeme a))
-> ReadS [NodeF lexeme a]
-> ReadPrec (NodeF lexeme a)
-> ReadPrec [NodeF lexeme a]
-> Read (NodeF lexeme a)
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
forall lexeme a. (Read lexeme, Read a) => ReadPrec [NodeF lexeme a]
forall lexeme a. (Read lexeme, Read a) => ReadPrec (NodeF lexeme a)
forall lexeme a.
(Read lexeme, Read a) =>
Int -> ReadS (NodeF lexeme a)
forall lexeme a. (Read lexeme, Read a) => ReadS [NodeF lexeme a]
readListPrec :: ReadPrec [NodeF lexeme a]
$creadListPrec :: forall lexeme a. (Read lexeme, Read a) => ReadPrec [NodeF lexeme a]
readPrec :: ReadPrec (NodeF lexeme a)
$creadPrec :: forall lexeme a. (Read lexeme, Read a) => ReadPrec (NodeF lexeme a)
readList :: ReadS [NodeF lexeme a]
$creadList :: forall lexeme a. (Read lexeme, Read a) => ReadS [NodeF lexeme a]
readsPrec :: Int -> ReadS (NodeF lexeme a)
$creadsPrec :: forall lexeme a.
(Read lexeme, Read a) =>
Int -> ReadS (NodeF lexeme a)
Read, NodeF lexeme a -> NodeF lexeme a -> Bool
(NodeF lexeme a -> NodeF lexeme a -> Bool)
-> (NodeF lexeme a -> NodeF lexeme a -> Bool)
-> Eq (NodeF lexeme a)
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
forall lexeme a.
(Eq lexeme, Eq a) =>
NodeF lexeme a -> NodeF lexeme a -> Bool
/= :: NodeF lexeme a -> NodeF lexeme a -> Bool
$c/= :: forall lexeme a.
(Eq lexeme, Eq a) =>
NodeF lexeme a -> NodeF lexeme a -> Bool
== :: NodeF lexeme a -> NodeF lexeme a -> Bool
$c== :: forall lexeme a.
(Eq lexeme, Eq a) =>
NodeF lexeme a -> NodeF lexeme a -> Bool
Eq, (forall x. NodeF lexeme a -> Rep (NodeF lexeme a) x)
-> (forall x. Rep (NodeF lexeme a) x -> NodeF lexeme a)
-> Generic (NodeF lexeme a)
forall x. Rep (NodeF lexeme a) x -> NodeF lexeme a
forall x. NodeF lexeme a -> Rep (NodeF lexeme a) x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
forall lexeme a x. Rep (NodeF lexeme a) x -> NodeF lexeme a
forall lexeme a x. NodeF lexeme a -> Rep (NodeF lexeme a) x
$cto :: forall lexeme a x. Rep (NodeF lexeme a) x -> NodeF lexeme a
$cfrom :: forall lexeme a x. NodeF lexeme a -> Rep (NodeF lexeme a) x
Generic, (forall a. NodeF lexeme a -> Rep1 (NodeF lexeme) a)
-> (forall a. Rep1 (NodeF lexeme) a -> NodeF lexeme a)
-> Generic1 (NodeF lexeme)
forall a. Rep1 (NodeF lexeme) a -> NodeF lexeme a
forall a. NodeF lexeme a -> Rep1 (NodeF lexeme) a
forall lexeme a. Rep1 (NodeF lexeme) a -> NodeF lexeme a
forall lexeme a. NodeF lexeme a -> Rep1 (NodeF lexeme) a
forall k (f :: k -> *).
(forall (a :: k). f a -> Rep1 f a)
-> (forall (a :: k). Rep1 f a -> f a) -> Generic1 f
$cto1 :: forall lexeme a. Rep1 (NodeF lexeme) a -> NodeF lexeme a
$cfrom1 :: forall lexeme a. NodeF lexeme a -> Rep1 (NodeF lexeme) a
Generic1, (forall a b. (a -> b) -> NodeF lexeme a -> NodeF lexeme b)
-> (forall a b. a -> NodeF lexeme b -> NodeF lexeme a)
-> Functor (NodeF lexeme)
forall a b. a -> NodeF lexeme b -> NodeF lexeme a
forall a b. (a -> b) -> NodeF lexeme a -> NodeF lexeme b
forall lexeme a b. a -> NodeF lexeme b -> NodeF lexeme a
forall lexeme a b. (a -> b) -> NodeF lexeme a -> NodeF lexeme b
forall (f :: * -> *).
(forall a b. (a -> b) -> f a -> f b)
-> (forall a b. a -> f b -> f a) -> Functor f
<$ :: forall a b. a -> NodeF lexeme b -> NodeF lexeme a
$c<$ :: forall lexeme a b. a -> NodeF lexeme b -> NodeF lexeme a
fmap :: forall a b. (a -> b) -> NodeF lexeme a -> NodeF lexeme b
$cfmap :: forall lexeme a b. (a -> b) -> NodeF lexeme a -> NodeF lexeme b
Functor, (forall m. Monoid m => NodeF lexeme m -> m)
-> (forall m a. Monoid m => (a -> m) -> NodeF lexeme a -> m)
-> (forall m a. Monoid m => (a -> m) -> NodeF lexeme a -> m)
-> (forall a b. (a -> b -> b) -> b -> NodeF lexeme a -> b)
-> (forall a b. (a -> b -> b) -> b -> NodeF lexeme a -> b)
-> (forall b a. (b -> a -> b) -> b -> NodeF lexeme a -> b)
-> (forall b a. (b -> a -> b) -> b -> NodeF lexeme a -> b)
-> (forall a. (a -> a -> a) -> NodeF lexeme a -> a)
-> (forall a. (a -> a -> a) -> NodeF lexeme a -> a)
-> (forall a. NodeF lexeme a -> [a])
-> (forall a. NodeF lexeme a -> Bool)
-> (forall a. NodeF lexeme a -> Int)
-> (forall a. Eq a => a -> NodeF lexeme a -> Bool)
-> (forall a. Ord a => NodeF lexeme a -> a)
-> (forall a. Ord a => NodeF lexeme a -> a)
-> (forall a. Num a => NodeF lexeme a -> a)
-> (forall a. Num a => NodeF lexeme a -> a)
-> Foldable (NodeF lexeme)
forall a. Eq a => a -> NodeF lexeme a -> Bool
forall a. Num a => NodeF lexeme a -> a
forall a. Ord a => NodeF lexeme a -> a
forall m. Monoid m => NodeF lexeme m -> m
forall a. NodeF lexeme a -> Bool
forall a. NodeF lexeme a -> Int
forall a. NodeF lexeme a -> [a]
forall a. (a -> a -> a) -> NodeF lexeme a -> a
forall lexeme a. Eq a => a -> NodeF lexeme a -> Bool
forall lexeme a. Num a => NodeF lexeme a -> a
forall lexeme a. Ord a => NodeF lexeme a -> a
forall m a. Monoid m => (a -> m) -> NodeF lexeme a -> m
forall lexeme m. Monoid m => NodeF lexeme m -> m
forall lexeme a. NodeF lexeme a -> Bool
forall lexeme a. NodeF lexeme a -> Int
forall lexeme a. NodeF lexeme a -> [a]
forall b a. (b -> a -> b) -> b -> NodeF lexeme a -> b
forall a b. (a -> b -> b) -> b -> NodeF lexeme a -> b
forall lexeme a. (a -> a -> a) -> NodeF lexeme a -> a
forall lexeme m a. Monoid m => (a -> m) -> NodeF lexeme a -> m
forall lexeme b a. (b -> a -> b) -> b -> NodeF lexeme a -> b
forall lexeme a b. (a -> b -> b) -> b -> NodeF lexeme a -> b
forall (t :: * -> *).
(forall m. Monoid m => t m -> m)
-> (forall m a. Monoid m => (a -> m) -> t a -> m)
-> (forall m a. Monoid m => (a -> m) -> t a -> m)
-> (forall a b. (a -> b -> b) -> b -> t a -> b)
-> (forall a b. (a -> b -> b) -> b -> t a -> b)
-> (forall b a. (b -> a -> b) -> b -> t a -> b)
-> (forall b a. (b -> a -> b) -> b -> t a -> b)
-> (forall a. (a -> a -> a) -> t a -> a)
-> (forall a. (a -> a -> a) -> t a -> a)
-> (forall a. t a -> [a])
-> (forall a. t a -> Bool)
-> (forall a. t a -> Int)
-> (forall a. Eq a => a -> t a -> Bool)
-> (forall a. Ord a => t a -> a)
-> (forall a. Ord a => t a -> a)
-> (forall a. Num a => t a -> a)
-> (forall a. Num a => t a -> a)
-> Foldable t
product :: forall a. Num a => NodeF lexeme a -> a
$cproduct :: forall lexeme a. Num a => NodeF lexeme a -> a
sum :: forall a. Num a => NodeF lexeme a -> a
$csum :: forall lexeme a. Num a => NodeF lexeme a -> a
minimum :: forall a. Ord a => NodeF lexeme a -> a
$cminimum :: forall lexeme a. Ord a => NodeF lexeme a -> a
maximum :: forall a. Ord a => NodeF lexeme a -> a
$cmaximum :: forall lexeme a. Ord a => NodeF lexeme a -> a
elem :: forall a. Eq a => a -> NodeF lexeme a -> Bool
$celem :: forall lexeme a. Eq a => a -> NodeF lexeme a -> Bool
length :: forall a. NodeF lexeme a -> Int
$clength :: forall lexeme a. NodeF lexeme a -> Int
null :: forall a. NodeF lexeme a -> Bool
$cnull :: forall lexeme a. NodeF lexeme a -> Bool
toList :: forall a. NodeF lexeme a -> [a]
$ctoList :: forall lexeme a. NodeF lexeme a -> [a]
foldl1 :: forall a. (a -> a -> a) -> NodeF lexeme a -> a
$cfoldl1 :: forall lexeme a. (a -> a -> a) -> NodeF lexeme a -> a
foldr1 :: forall a. (a -> a -> a) -> NodeF lexeme a -> a
$cfoldr1 :: forall lexeme a. (a -> a -> a) -> NodeF lexeme a -> a
foldl' :: forall b a. (b -> a -> b) -> b -> NodeF lexeme a -> b
$cfoldl' :: forall lexeme b a. (b -> a -> b) -> b -> NodeF lexeme a -> b
foldl :: forall b a. (b -> a -> b) -> b -> NodeF lexeme a -> b
$cfoldl :: forall lexeme b a. (b -> a -> b) -> b -> NodeF lexeme a -> b
foldr' :: forall a b. (a -> b -> b) -> b -> NodeF lexeme a -> b
$cfoldr' :: forall lexeme a b. (a -> b -> b) -> b -> NodeF lexeme a -> b
foldr :: forall a b. (a -> b -> b) -> b -> NodeF lexeme a -> b
$cfoldr :: forall lexeme a b. (a -> b -> b) -> b -> NodeF lexeme a -> b
foldMap' :: forall m a. Monoid m => (a -> m) -> NodeF lexeme a -> m
$cfoldMap' :: forall lexeme m a. Monoid m => (a -> m) -> NodeF lexeme a -> m
foldMap :: forall m a. Monoid m => (a -> m) -> NodeF lexeme a -> m
$cfoldMap :: forall lexeme m a. Monoid m => (a -> m) -> NodeF lexeme a -> m
fold :: forall m. Monoid m => NodeF lexeme m -> m
$cfold :: forall lexeme m. Monoid m => NodeF lexeme m -> m
Foldable, Functor (NodeF lexeme)
Foldable (NodeF lexeme)
Functor (NodeF lexeme)
-> Foldable (NodeF lexeme)
-> (forall (f :: * -> *) a b.
    Applicative f =>
    (a -> f b) -> NodeF lexeme a -> f (NodeF lexeme b))
-> (forall (f :: * -> *) a.
    Applicative f =>
    NodeF lexeme (f a) -> f (NodeF lexeme a))
-> (forall (m :: * -> *) a b.
    Monad m =>
    (a -> m b) -> NodeF lexeme a -> m (NodeF lexeme b))
-> (forall (m :: * -> *) a.
    Monad m =>
    NodeF lexeme (m a) -> m (NodeF lexeme a))
-> Traversable (NodeF lexeme)
forall lexeme. Functor (NodeF lexeme)
forall lexeme. Foldable (NodeF lexeme)
forall lexeme (m :: * -> *) a.
Monad m =>
NodeF lexeme (m a) -> m (NodeF lexeme a)
forall lexeme (f :: * -> *) a.
Applicative f =>
NodeF lexeme (f a) -> f (NodeF lexeme a)
forall lexeme (m :: * -> *) a b.
Monad m =>
(a -> m b) -> NodeF lexeme a -> m (NodeF lexeme b)
forall lexeme (f :: * -> *) a b.
Applicative f =>
(a -> f b) -> NodeF lexeme a -> f (NodeF lexeme b)
forall (t :: * -> *).
Functor t
-> Foldable t
-> (forall (f :: * -> *) a b.
    Applicative f =>
    (a -> f b) -> t a -> f (t b))
-> (forall (f :: * -> *) a. Applicative f => t (f a) -> f (t a))
-> (forall (m :: * -> *) a b.
    Monad m =>
    (a -> m b) -> t a -> m (t b))
-> (forall (m :: * -> *) a. Monad m => t (m a) -> m (t a))
-> Traversable t
forall (m :: * -> *) a.
Monad m =>
NodeF lexeme (m a) -> m (NodeF lexeme a)
forall (f :: * -> *) a.
Applicative f =>
NodeF lexeme (f a) -> f (NodeF lexeme a)
forall (m :: * -> *) a b.
Monad m =>
(a -> m b) -> NodeF lexeme a -> m (NodeF lexeme b)
forall (f :: * -> *) a b.
Applicative f =>
(a -> f b) -> NodeF lexeme a -> f (NodeF lexeme b)
sequence :: forall (m :: * -> *) a.
Monad m =>
NodeF lexeme (m a) -> m (NodeF lexeme a)
$csequence :: forall lexeme (m :: * -> *) a.
Monad m =>
NodeF lexeme (m a) -> m (NodeF lexeme a)
mapM :: forall (m :: * -> *) a b.
Monad m =>
(a -> m b) -> NodeF lexeme a -> m (NodeF lexeme b)
$cmapM :: forall lexeme (m :: * -> *) a b.
Monad m =>
(a -> m b) -> NodeF lexeme a -> m (NodeF lexeme b)
sequenceA :: forall (f :: * -> *) a.
Applicative f =>
NodeF lexeme (f a) -> f (NodeF lexeme a)
$csequenceA :: forall lexeme (f :: * -> *) a.
Applicative f =>
NodeF lexeme (f a) -> f (NodeF lexeme a)
traverse :: forall (f :: * -> *) a b.
Applicative f =>
(a -> f b) -> NodeF lexeme a -> f (NodeF lexeme b)
$ctraverse :: forall lexeme (f :: * -> *) a b.
Applicative f =>
(a -> f b) -> NodeF lexeme a -> f (NodeF lexeme b)
Traversable)
    deriving ((forall a.
 (Int -> a -> ShowS)
 -> ([a] -> ShowS) -> Int -> NodeF lexeme a -> ShowS)
-> (forall a.
    (Int -> a -> ShowS) -> ([a] -> ShowS) -> [NodeF lexeme a] -> ShowS)
-> Show1 (NodeF lexeme)
forall lexeme a.
Show lexeme =>
(Int -> a -> ShowS)
-> ([a] -> ShowS) -> Int -> NodeF lexeme a -> ShowS
forall lexeme a.
Show lexeme =>
(Int -> a -> ShowS) -> ([a] -> ShowS) -> [NodeF lexeme a] -> ShowS
forall a.
(Int -> a -> ShowS)
-> ([a] -> ShowS) -> Int -> NodeF lexeme a -> ShowS
forall a.
(Int -> a -> ShowS) -> ([a] -> ShowS) -> [NodeF lexeme a] -> ShowS
forall (f :: * -> *).
(forall a.
 (Int -> a -> ShowS) -> ([a] -> ShowS) -> Int -> f a -> ShowS)
-> (forall a.
    (Int -> a -> ShowS) -> ([a] -> ShowS) -> [f a] -> ShowS)
-> Show1 f
liftShowList :: forall a.
(Int -> a -> ShowS) -> ([a] -> ShowS) -> [NodeF lexeme a] -> ShowS
$cliftShowList :: forall lexeme a.
Show lexeme =>
(Int -> a -> ShowS) -> ([a] -> ShowS) -> [NodeF lexeme a] -> ShowS
liftShowsPrec :: forall a.
(Int -> a -> ShowS)
-> ([a] -> ShowS) -> Int -> NodeF lexeme a -> ShowS
$cliftShowsPrec :: forall lexeme a.
Show lexeme =>
(Int -> a -> ShowS)
-> ([a] -> ShowS) -> Int -> NodeF lexeme a -> ShowS
Show1, (forall a.
 (Int -> ReadS a) -> ReadS [a] -> Int -> ReadS (NodeF lexeme a))
-> (forall a.
    (Int -> ReadS a) -> ReadS [a] -> ReadS [NodeF lexeme a])
-> (forall a.
    ReadPrec a -> ReadPrec [a] -> ReadPrec (NodeF lexeme a))
-> (forall a.
    ReadPrec a -> ReadPrec [a] -> ReadPrec [NodeF lexeme a])
-> Read1 (NodeF lexeme)
forall lexeme a.
Read lexeme =>
ReadPrec a -> ReadPrec [a] -> ReadPrec [NodeF lexeme a]
forall lexeme a.
Read lexeme =>
ReadPrec a -> ReadPrec [a] -> ReadPrec (NodeF lexeme a)
forall lexeme a.
Read lexeme =>
(Int -> ReadS a) -> ReadS [a] -> Int -> ReadS (NodeF lexeme a)
forall lexeme a.
Read lexeme =>
(Int -> ReadS a) -> ReadS [a] -> ReadS [NodeF lexeme a]
forall a. ReadPrec a -> ReadPrec [a] -> ReadPrec [NodeF lexeme a]
forall a. ReadPrec a -> ReadPrec [a] -> ReadPrec (NodeF lexeme a)
forall a.
(Int -> ReadS a) -> ReadS [a] -> Int -> ReadS (NodeF lexeme a)
forall a. (Int -> ReadS a) -> ReadS [a] -> ReadS [NodeF lexeme a]
forall (f :: * -> *).
(forall a. (Int -> ReadS a) -> ReadS [a] -> Int -> ReadS (f a))
-> (forall a. (Int -> ReadS a) -> ReadS [a] -> ReadS [f a])
-> (forall a. ReadPrec a -> ReadPrec [a] -> ReadPrec (f a))
-> (forall a. ReadPrec a -> ReadPrec [a] -> ReadPrec [f a])
-> Read1 f
liftReadListPrec :: forall a. ReadPrec a -> ReadPrec [a] -> ReadPrec [NodeF lexeme a]
$cliftReadListPrec :: forall lexeme a.
Read lexeme =>
ReadPrec a -> ReadPrec [a] -> ReadPrec [NodeF lexeme a]
liftReadPrec :: forall a. ReadPrec a -> ReadPrec [a] -> ReadPrec (NodeF lexeme a)
$cliftReadPrec :: forall lexeme a.
Read lexeme =>
ReadPrec a -> ReadPrec [a] -> ReadPrec (NodeF lexeme a)
liftReadList :: forall a. (Int -> ReadS a) -> ReadS [a] -> ReadS [NodeF lexeme a]
$cliftReadList :: forall lexeme a.
Read lexeme =>
(Int -> ReadS a) -> ReadS [a] -> ReadS [NodeF lexeme a]
liftReadsPrec :: forall a.
(Int -> ReadS a) -> ReadS [a] -> Int -> ReadS (NodeF lexeme a)
$cliftReadsPrec :: forall lexeme a.
Read lexeme =>
(Int -> ReadS a) -> ReadS [a] -> Int -> ReadS (NodeF lexeme a)
Read1, (forall a b.
 (a -> b -> Bool) -> NodeF lexeme a -> NodeF lexeme b -> Bool)
-> Eq1 (NodeF lexeme)
forall lexeme a b.
Eq lexeme =>
(a -> b -> Bool) -> NodeF lexeme a -> NodeF lexeme b -> Bool
forall a b.
(a -> b -> Bool) -> NodeF lexeme a -> NodeF lexeme b -> Bool
forall (f :: * -> *).
(forall a b. (a -> b -> Bool) -> f a -> f b -> Bool) -> Eq1 f
liftEq :: forall a b.
(a -> b -> Bool) -> NodeF lexeme a -> NodeF lexeme b -> Bool
$cliftEq :: forall lexeme a b.
Eq lexeme =>
(a -> b -> Bool) -> NodeF lexeme a -> NodeF lexeme b -> Bool
Eq1) via FunctorClassesDefault (NodeF lexeme)

type Node lexeme = Fix (NodeF lexeme)

instance FromJSON lexeme => FromJSON1 (NodeF lexeme)
instance ToJSON lexeme => ToJSON1 (NodeF lexeme)

data AssignOp
    = AopEq
    | AopMul
    | AopDiv
    | AopPlus
    | AopMinus
    | AopBitAnd
    | AopBitOr
    | AopBitXor
    | AopMod
    | AopLsh
    | AopRsh
    deriving (Int -> AssignOp -> ShowS
[AssignOp] -> ShowS
AssignOp -> String
(Int -> AssignOp -> ShowS)
-> (AssignOp -> String) -> ([AssignOp] -> ShowS) -> Show AssignOp
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [AssignOp] -> ShowS
$cshowList :: [AssignOp] -> ShowS
show :: AssignOp -> String
$cshow :: AssignOp -> String
showsPrec :: Int -> AssignOp -> ShowS
$cshowsPrec :: Int -> AssignOp -> ShowS
Show, ReadPrec [AssignOp]
ReadPrec AssignOp
Int -> ReadS AssignOp
ReadS [AssignOp]
(Int -> ReadS AssignOp)
-> ReadS [AssignOp]
-> ReadPrec AssignOp
-> ReadPrec [AssignOp]
-> Read AssignOp
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [AssignOp]
$creadListPrec :: ReadPrec [AssignOp]
readPrec :: ReadPrec AssignOp
$creadPrec :: ReadPrec AssignOp
readList :: ReadS [AssignOp]
$creadList :: ReadS [AssignOp]
readsPrec :: Int -> ReadS AssignOp
$creadsPrec :: Int -> ReadS AssignOp
Read, AssignOp -> AssignOp -> Bool
(AssignOp -> AssignOp -> Bool)
-> (AssignOp -> AssignOp -> Bool) -> Eq AssignOp
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: AssignOp -> AssignOp -> Bool
$c/= :: AssignOp -> AssignOp -> Bool
== :: AssignOp -> AssignOp -> Bool
$c== :: AssignOp -> AssignOp -> Bool
Eq, (forall x. AssignOp -> Rep AssignOp x)
-> (forall x. Rep AssignOp x -> AssignOp) -> Generic AssignOp
forall x. Rep AssignOp x -> AssignOp
forall x. AssignOp -> Rep AssignOp x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep AssignOp x -> AssignOp
$cfrom :: forall x. AssignOp -> Rep AssignOp x
Generic)

instance FromJSON AssignOp
instance ToJSON AssignOp

data BinaryOp
    = BopNe
    | BopEq
    | BopOr
    | BopBitXor
    | BopBitOr
    | BopAnd
    | BopBitAnd
    | BopDiv
    | BopMul
    | BopMod
    | BopPlus
    | BopMinus
    | BopLt
    | BopLe
    | BopLsh
    | BopGt
    | BopGe
    | BopRsh
    deriving (Int -> BinaryOp -> ShowS
[BinaryOp] -> ShowS
BinaryOp -> String
(Int -> BinaryOp -> ShowS)
-> (BinaryOp -> String) -> ([BinaryOp] -> ShowS) -> Show BinaryOp
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [BinaryOp] -> ShowS
$cshowList :: [BinaryOp] -> ShowS
show :: BinaryOp -> String
$cshow :: BinaryOp -> String
showsPrec :: Int -> BinaryOp -> ShowS
$cshowsPrec :: Int -> BinaryOp -> ShowS
Show, ReadPrec [BinaryOp]
ReadPrec BinaryOp
Int -> ReadS BinaryOp
ReadS [BinaryOp]
(Int -> ReadS BinaryOp)
-> ReadS [BinaryOp]
-> ReadPrec BinaryOp
-> ReadPrec [BinaryOp]
-> Read BinaryOp
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [BinaryOp]
$creadListPrec :: ReadPrec [BinaryOp]
readPrec :: ReadPrec BinaryOp
$creadPrec :: ReadPrec BinaryOp
readList :: ReadS [BinaryOp]
$creadList :: ReadS [BinaryOp]
readsPrec :: Int -> ReadS BinaryOp
$creadsPrec :: Int -> ReadS BinaryOp
Read, BinaryOp -> BinaryOp -> Bool
(BinaryOp -> BinaryOp -> Bool)
-> (BinaryOp -> BinaryOp -> Bool) -> Eq BinaryOp
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: BinaryOp -> BinaryOp -> Bool
$c/= :: BinaryOp -> BinaryOp -> Bool
== :: BinaryOp -> BinaryOp -> Bool
$c== :: BinaryOp -> BinaryOp -> Bool
Eq, (forall x. BinaryOp -> Rep BinaryOp x)
-> (forall x. Rep BinaryOp x -> BinaryOp) -> Generic BinaryOp
forall x. Rep BinaryOp x -> BinaryOp
forall x. BinaryOp -> Rep BinaryOp x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep BinaryOp x -> BinaryOp
$cfrom :: forall x. BinaryOp -> Rep BinaryOp x
Generic)

instance FromJSON BinaryOp
instance ToJSON BinaryOp

data UnaryOp
    = UopNot
    | UopNeg
    | UopMinus
    | UopAddress
    | UopDeref
    | UopIncr
    | UopDecr
    deriving (Int -> UnaryOp -> ShowS
[UnaryOp] -> ShowS
UnaryOp -> String
(Int -> UnaryOp -> ShowS)
-> (UnaryOp -> String) -> ([UnaryOp] -> ShowS) -> Show UnaryOp
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [UnaryOp] -> ShowS
$cshowList :: [UnaryOp] -> ShowS
show :: UnaryOp -> String
$cshow :: UnaryOp -> String
showsPrec :: Int -> UnaryOp -> ShowS
$cshowsPrec :: Int -> UnaryOp -> ShowS
Show, ReadPrec [UnaryOp]
ReadPrec UnaryOp
Int -> ReadS UnaryOp
ReadS [UnaryOp]
(Int -> ReadS UnaryOp)
-> ReadS [UnaryOp]
-> ReadPrec UnaryOp
-> ReadPrec [UnaryOp]
-> Read UnaryOp
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [UnaryOp]
$creadListPrec :: ReadPrec [UnaryOp]
readPrec :: ReadPrec UnaryOp
$creadPrec :: ReadPrec UnaryOp
readList :: ReadS [UnaryOp]
$creadList :: ReadS [UnaryOp]
readsPrec :: Int -> ReadS UnaryOp
$creadsPrec :: Int -> ReadS UnaryOp
Read, UnaryOp -> UnaryOp -> Bool
(UnaryOp -> UnaryOp -> Bool)
-> (UnaryOp -> UnaryOp -> Bool) -> Eq UnaryOp
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: UnaryOp -> UnaryOp -> Bool
$c/= :: UnaryOp -> UnaryOp -> Bool
== :: UnaryOp -> UnaryOp -> Bool
$c== :: UnaryOp -> UnaryOp -> Bool
Eq, (forall x. UnaryOp -> Rep UnaryOp x)
-> (forall x. Rep UnaryOp x -> UnaryOp) -> Generic UnaryOp
forall x. Rep UnaryOp x -> UnaryOp
forall x. UnaryOp -> Rep UnaryOp x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep UnaryOp x -> UnaryOp
$cfrom :: forall x. UnaryOp -> Rep UnaryOp x
Generic)

instance FromJSON UnaryOp
instance ToJSON UnaryOp

data LiteralType
    = Char
    | Int
    | Bool
    | String
    | ConstId
    deriving (Int -> LiteralType -> ShowS
[LiteralType] -> ShowS
LiteralType -> String
(Int -> LiteralType -> ShowS)
-> (LiteralType -> String)
-> ([LiteralType] -> ShowS)
-> Show LiteralType
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [LiteralType] -> ShowS
$cshowList :: [LiteralType] -> ShowS
show :: LiteralType -> String
$cshow :: LiteralType -> String
showsPrec :: Int -> LiteralType -> ShowS
$cshowsPrec :: Int -> LiteralType -> ShowS
Show, ReadPrec [LiteralType]
ReadPrec LiteralType
Int -> ReadS LiteralType
ReadS [LiteralType]
(Int -> ReadS LiteralType)
-> ReadS [LiteralType]
-> ReadPrec LiteralType
-> ReadPrec [LiteralType]
-> Read LiteralType
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [LiteralType]
$creadListPrec :: ReadPrec [LiteralType]
readPrec :: ReadPrec LiteralType
$creadPrec :: ReadPrec LiteralType
readList :: ReadS [LiteralType]
$creadList :: ReadS [LiteralType]
readsPrec :: Int -> ReadS LiteralType
$creadsPrec :: Int -> ReadS LiteralType
Read, LiteralType -> LiteralType -> Bool
(LiteralType -> LiteralType -> Bool)
-> (LiteralType -> LiteralType -> Bool) -> Eq LiteralType
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: LiteralType -> LiteralType -> Bool
$c/= :: LiteralType -> LiteralType -> Bool
== :: LiteralType -> LiteralType -> Bool
$c== :: LiteralType -> LiteralType -> Bool
Eq, (forall x. LiteralType -> Rep LiteralType x)
-> (forall x. Rep LiteralType x -> LiteralType)
-> Generic LiteralType
forall x. Rep LiteralType x -> LiteralType
forall x. LiteralType -> Rep LiteralType x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep LiteralType x -> LiteralType
$cfrom :: forall x. LiteralType -> Rep LiteralType x
Generic)

instance FromJSON LiteralType
instance ToJSON LiteralType

data Scope
    = Global
    | Static
    deriving (Int -> Scope -> ShowS
[Scope] -> ShowS
Scope -> String
(Int -> Scope -> ShowS)
-> (Scope -> String) -> ([Scope] -> ShowS) -> Show Scope
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [Scope] -> ShowS
$cshowList :: [Scope] -> ShowS
show :: Scope -> String
$cshow :: Scope -> String
showsPrec :: Int -> Scope -> ShowS
$cshowsPrec :: Int -> Scope -> ShowS
Show, ReadPrec [Scope]
ReadPrec Scope
Int -> ReadS Scope
ReadS [Scope]
(Int -> ReadS Scope)
-> ReadS [Scope]
-> ReadPrec Scope
-> ReadPrec [Scope]
-> Read Scope
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [Scope]
$creadListPrec :: ReadPrec [Scope]
readPrec :: ReadPrec Scope
$creadPrec :: ReadPrec Scope
readList :: ReadS [Scope]
$creadList :: ReadS [Scope]
readsPrec :: Int -> ReadS Scope
$creadsPrec :: Int -> ReadS Scope
Read, Scope -> Scope -> Bool
(Scope -> Scope -> Bool) -> (Scope -> Scope -> Bool) -> Eq Scope
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: Scope -> Scope -> Bool
$c/= :: Scope -> Scope -> Bool
== :: Scope -> Scope -> Bool
$c== :: Scope -> Scope -> Bool
Eq, (forall x. Scope -> Rep Scope x)
-> (forall x. Rep Scope x -> Scope) -> Generic Scope
forall x. Rep Scope x -> Scope
forall x. Scope -> Rep Scope x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep Scope x -> Scope
$cfrom :: forall x. Scope -> Rep Scope x
Generic)

instance FromJSON Scope
instance ToJSON Scope

data CommentStyle
    = Regular
    | Doxygen
    | Block
    deriving (Int -> CommentStyle -> ShowS
[CommentStyle] -> ShowS
CommentStyle -> String
(Int -> CommentStyle -> ShowS)
-> (CommentStyle -> String)
-> ([CommentStyle] -> ShowS)
-> Show CommentStyle
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [CommentStyle] -> ShowS
$cshowList :: [CommentStyle] -> ShowS
show :: CommentStyle -> String
$cshow :: CommentStyle -> String
showsPrec :: Int -> CommentStyle -> ShowS
$cshowsPrec :: Int -> CommentStyle -> ShowS
Show, ReadPrec [CommentStyle]
ReadPrec CommentStyle
Int -> ReadS CommentStyle
ReadS [CommentStyle]
(Int -> ReadS CommentStyle)
-> ReadS [CommentStyle]
-> ReadPrec CommentStyle
-> ReadPrec [CommentStyle]
-> Read CommentStyle
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [CommentStyle]
$creadListPrec :: ReadPrec [CommentStyle]
readPrec :: ReadPrec CommentStyle
$creadPrec :: ReadPrec CommentStyle
readList :: ReadS [CommentStyle]
$creadList :: ReadS [CommentStyle]
readsPrec :: Int -> ReadS CommentStyle
$creadsPrec :: Int -> ReadS CommentStyle
Read, CommentStyle -> CommentStyle -> Bool
(CommentStyle -> CommentStyle -> Bool)
-> (CommentStyle -> CommentStyle -> Bool) -> Eq CommentStyle
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: CommentStyle -> CommentStyle -> Bool
$c/= :: CommentStyle -> CommentStyle -> Bool
== :: CommentStyle -> CommentStyle -> Bool
$c== :: CommentStyle -> CommentStyle -> Bool
Eq, (forall x. CommentStyle -> Rep CommentStyle x)
-> (forall x. Rep CommentStyle x -> CommentStyle)
-> Generic CommentStyle
forall x. Rep CommentStyle x -> CommentStyle
forall x. CommentStyle -> Rep CommentStyle x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep CommentStyle x -> CommentStyle
$cfrom :: forall x. CommentStyle -> Rep CommentStyle x
Generic)

instance FromJSON CommentStyle
instance ToJSON CommentStyle