{-# LANGUAGE OverloadedStrings #-}
module Htcc.Parser.AST.Core (
ATKindFor (..),
ATKind (..),
ATree (..),
Treealizable (..),
atBinary, atUnary, atNoLeaf,
atLVar, atGVar,
atAssign, atNumLit, atMemberAcc, atExprStmt,
atBlock, atNull, atDefFunc, atReturn,
atIf, atElse, atWhile, atFor,
atBreak, atContinue, atSwitch, atCase,
atDefault, atGoto, atLabel, atComma,
atConditional, atCast,
isATForInit,
isATForCond,
isATForStmt,
isATForIncr,
fromATKindFor,
isComplexAssign,
isEmptyExprStmt,
isEmptyReturn,
isNonEmptyReturn,
mapATKind,
modifyTypeATKind
) where
import Control.Monad ((>=>))
import qualified Data.Text as T
import qualified Htcc.CRules.Types as CT
data ATKindFor a = ATForkw
| ATForInit (ATree a)
| ATForCond (ATree a)
| ATForIncr (ATree a)
| ATForStmt (ATree a)
deriving Int -> ATKindFor a -> ShowS
[ATKindFor a] -> ShowS
ATKindFor a -> String
(Int -> ATKindFor a -> ShowS)
-> (ATKindFor a -> String)
-> ([ATKindFor a] -> ShowS)
-> Show (ATKindFor a)
forall a. Show a => Int -> ATKindFor a -> ShowS
forall a. Show a => [ATKindFor a] -> ShowS
forall a. Show a => ATKindFor a -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [ATKindFor a] -> ShowS
$cshowList :: forall a. Show a => [ATKindFor a] -> ShowS
show :: ATKindFor a -> String
$cshow :: forall a. Show a => ATKindFor a -> String
showsPrec :: Int -> ATKindFor a -> ShowS
$cshowsPrec :: forall a. Show a => Int -> ATKindFor a -> ShowS
Show
{-# INLINE isATForInit #-}
isATForInit :: ATKindFor a -> Bool
isATForInit :: ATKindFor a -> Bool
isATForInit (ATForInit _) = Bool
True
isATForInit _ = Bool
False
{-# INLINE isATForCond #-}
isATForCond :: ATKindFor a -> Bool
isATForCond :: ATKindFor a -> Bool
isATForCond (ATForCond _) = Bool
True
isATForCond _ = Bool
False
{-# INLINE isATForStmt #-}
isATForStmt :: ATKindFor a -> Bool
isATForStmt :: ATKindFor a -> Bool
isATForStmt (ATForStmt _) = Bool
True
isATForStmt _ = Bool
False
{-# INLINE isATForIncr #-}
isATForIncr :: ATKindFor a -> Bool
isATForIncr :: ATKindFor a -> Bool
isATForIncr (ATForIncr _) = Bool
True
isATForIncr _ = Bool
False
{-# INLINE fromATKindFor #-}
fromATKindFor :: ATKindFor a -> ATree a
fromATKindFor :: ATKindFor a -> ATree a
fromATKindFor (ATForInit x :: ATree a
x) = ATree a
x
fromATKindFor (ATForCond x :: ATree a
x) = ATree a
x
fromATKindFor (ATForIncr x :: ATree a
x) = ATree a
x
fromATKindFor (ATForStmt x :: ATree a
x) = ATree a
x
fromATKindFor _ = String -> ATree a
forall a. HasCallStack => String -> a
error "ATKindFor is ATForkw"
data ATKind a = ATAdd
| ATAddPtr
| ATSub
| ATSubPtr
| ATPtrDis
| ATMul
| ATDiv
| ATMod
| ATAddAssign
| ATSubAssign
| ATMulAssign
| ATDivAssign
| ATAddPtrAssign
| ATSubPtrAssign
| ATLAnd
| ATLOr
| ATAnd
| ATAndAssign
| ATOr
| ATOrAssign
| ATXor
| ATXorAssign
| ATBitNot
| ATShl
| ATShlAssign
| ATShr
| ATShrAssign
| ATLT
| ATLEQ
| ATGT
| ATGEQ
| ATEQ
| ATNEQ
| ATNot
| ATAddr
| ATDeref
| ATAssign
| ATPreInc
| ATPreDec
| ATPostInc
| ATPostDec
| ATNum a
| ATConditional (ATree a) (ATree a) (ATree a)
| ATComma
| ATCast
| ATMemberAcc (CT.StructMember a)
| ATReturn
| ATIf
| ATElse
| ATSwitch (ATree a) [ATree a]
| ATCase a a
| ATDefault a
| ATWhile
| ATFor [ATKindFor a]
| ATBreak
| ATContinue
| ATGoto T.Text
| ATLabel T.Text
| ATBlock [ATree a]
| ATLVar (CT.StorageClass a) a
| ATGVar (CT.StorageClass a) T.Text
| ATDefFunc T.Text (Maybe [ATree a])
| ATCallFunc T.Text (Maybe [ATree a])
| ATExprStmt
| ATStmtExpr [ATree a]
| ATNull (ATree a)
deriving Int -> ATKind a -> ShowS
[ATKind a] -> ShowS
ATKind a -> String
(Int -> ATKind a -> ShowS)
-> (ATKind a -> String) -> ([ATKind a] -> ShowS) -> Show (ATKind a)
forall a. Show a => Int -> ATKind a -> ShowS
forall a. Show a => [ATKind a] -> ShowS
forall a. Show a => ATKind a -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [ATKind a] -> ShowS
$cshowList :: forall a. Show a => [ATKind a] -> ShowS
show :: ATKind a -> String
$cshow :: forall a. Show a => ATKind a -> String
showsPrec :: Int -> ATKind a -> ShowS
$cshowsPrec :: forall a. Show a => Int -> ATKind a -> ShowS
Show
{-# INLINE fromATVar #-}
fromATVar :: ATKind i -> Maybe (CT.StorageClass i)
fromATVar :: ATKind i -> Maybe (StorageClass i)
fromATVar (ATLVar s :: StorageClass i
s _) = StorageClass i -> Maybe (StorageClass i)
forall a. a -> Maybe a
Just StorageClass i
s
fromATVar (ATGVar s :: StorageClass i
s _) = StorageClass i -> Maybe (StorageClass i)
forall a. a -> Maybe a
Just StorageClass i
s
fromATVar _ = Maybe (StorageClass i)
forall a. Maybe a
Nothing
instance CT.IncompleteBase ATKind where
isIncompleteArray :: ATKind i -> Bool
isIncompleteArray = Bool -> (StorageClass i -> Bool) -> Maybe (StorageClass i) -> Bool
forall b a. b -> (a -> b) -> Maybe a -> b
maybe Bool
False StorageClass i -> Bool
forall (a :: * -> *) i. IncompleteBase a => a i -> Bool
CT.isIncompleteArray (Maybe (StorageClass i) -> Bool)
-> (ATKind i -> Maybe (StorageClass i)) -> ATKind i -> Bool
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ATKind i -> Maybe (StorageClass i)
forall i. ATKind i -> Maybe (StorageClass i)
fromATVar
isIncompleteStruct :: ATKind i -> Bool
isIncompleteStruct = Bool -> (StorageClass i -> Bool) -> Maybe (StorageClass i) -> Bool
forall b a. b -> (a -> b) -> Maybe a -> b
maybe Bool
False StorageClass i -> Bool
forall (a :: * -> *) i. IncompleteBase a => a i -> Bool
CT.isIncompleteStruct (Maybe (StorageClass i) -> Bool)
-> (ATKind i -> Maybe (StorageClass i)) -> ATKind i -> Bool
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ATKind i -> Maybe (StorageClass i)
forall i. ATKind i -> Maybe (StorageClass i)
fromATVar
fromIncompleteArray :: ATKind i -> Maybe (TypeKind i)
fromIncompleteArray = ATKind i -> Maybe (StorageClass i)
forall i. ATKind i -> Maybe (StorageClass i)
fromATVar (ATKind i -> Maybe (StorageClass i))
-> (StorageClass i -> Maybe (TypeKind i))
-> ATKind i
-> Maybe (TypeKind i)
forall (m :: * -> *) a b c.
Monad m =>
(a -> m b) -> (b -> m c) -> a -> m c
>=> StorageClass i -> Maybe (TypeKind i)
forall (a :: * -> *) i.
IncompleteBase a =>
a i -> Maybe (TypeKind i)
CT.fromIncompleteArray
fromIncompleteStruct :: ATKind i -> Maybe Text
fromIncompleteStruct = ATKind i -> Maybe (StorageClass i)
forall i. ATKind i -> Maybe (StorageClass i)
fromATVar (ATKind i -> Maybe (StorageClass i))
-> (StorageClass i -> Maybe Text) -> ATKind i -> Maybe Text
forall (m :: * -> *) a b c.
Monad m =>
(a -> m b) -> (b -> m c) -> a -> m c
>=> StorageClass i -> Maybe Text
forall (a :: * -> *) i. IncompleteBase a => a i -> Maybe Text
CT.fromIncompleteStruct
isValidIncomplete :: ATKind i -> Bool
isValidIncomplete = Bool -> (StorageClass i -> Bool) -> Maybe (StorageClass i) -> Bool
forall b a. b -> (a -> b) -> Maybe a -> b
maybe Bool
False StorageClass i -> Bool
forall (a :: * -> *) i. (IncompleteBase a, Ord i) => a i -> Bool
CT.isValidIncomplete (Maybe (StorageClass i) -> Bool)
-> (ATKind i -> Maybe (StorageClass i)) -> ATKind i -> Bool
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ATKind i -> Maybe (StorageClass i)
forall i. ATKind i -> Maybe (StorageClass i)
fromATVar
{-# INLINE isComplexAssign #-}
isComplexAssign :: ATKind a -> Bool
isComplexAssign :: ATKind a -> Bool
isComplexAssign ATAddAssign = Bool
True
isComplexAssign ATSubAssign = Bool
True
isComplexAssign ATMulAssign = Bool
True
isComplexAssign ATDivAssign = Bool
True
isComplexAssign ATAddPtrAssign = Bool
True
isComplexAssign ATSubPtrAssign = Bool
True
isComplexAssign ATOrAssign = Bool
True
isComplexAssign ATAndAssign = Bool
True
isComplexAssign ATXorAssign = Bool
True
isComplexAssign ATShlAssign = Bool
True
isComplexAssign ATShrAssign = Bool
True
isComplexAssign _ = Bool
False
data ATree a = ATEmpty
| ATNode {
ATree a -> ATKind a
atkind :: ATKind a,
ATree a -> StorageClass a
atype :: CT.StorageClass a,
ATree a -> ATree a
atL :: ATree a,
ATree a -> ATree a
atR :: ATree a
}
deriving Int -> ATree a -> ShowS
[ATree a] -> ShowS
ATree a -> String
(Int -> ATree a -> ShowS)
-> (ATree a -> String) -> ([ATree a] -> ShowS) -> Show (ATree a)
forall a. Show a => Int -> ATree a -> ShowS
forall a. Show a => [ATree a] -> ShowS
forall a. Show a => ATree a -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [ATree a] -> ShowS
$cshowList :: forall a. Show a => [ATree a] -> ShowS
show :: ATree a -> String
$cshow :: forall a. Show a => ATree a -> String
showsPrec :: Int -> ATree a -> ShowS
$cshowsPrec :: forall a. Show a => Int -> ATree a -> ShowS
Show
class Treealizable a where
treealize :: a i -> ATree i
{-# INLINE isEmptyExprStmt #-}
isEmptyExprStmt :: ATree a -> Bool
isEmptyExprStmt :: ATree a -> Bool
isEmptyExprStmt (ATNode ATExprStmt _ ATEmpty ATEmpty) = Bool
True
isEmptyExprStmt _ = Bool
False
{-# INLINE isNonEmptyReturn #-}
isNonEmptyReturn :: ATree a -> Bool
isNonEmptyReturn :: ATree a -> Bool
isNonEmptyReturn (ATNode ATReturn _ ATEmpty _) = Bool
False
isNonEmptyReturn (ATNode ATReturn _ _ _) = Bool
True
isNonEmptyReturn _ = Bool
False
{-# INLINE isEmptyReturn #-}
isEmptyReturn :: ATree a -> Bool
isEmptyReturn :: ATree a -> Bool
isEmptyReturn (ATNode ATReturn _ ATEmpty _) = Bool
True
isEmptyReturn _ = Bool
False
{-# INLINE atBinary #-}
atBinary :: ATKind i -> CT.StorageClass i -> ATree i -> ATree i -> ATree i
atBinary :: ATKind i -> StorageClass i -> ATree i -> ATree i -> ATree i
atBinary = ATKind i -> StorageClass i -> ATree i -> ATree i -> ATree i
forall a.
ATKind a -> StorageClass a -> ATree a -> ATree a -> ATree a
ATNode
{-# INLINE atUnary #-}
atUnary :: ATKind i -> CT.StorageClass i -> ATree i -> ATree i
atUnary :: ATKind i -> StorageClass i -> ATree i -> ATree i
atUnary k :: ATKind i
k t :: StorageClass i
t n :: ATree i
n = ATKind i -> StorageClass i -> ATree i -> ATree i -> ATree i
forall a.
ATKind a -> StorageClass a -> ATree a -> ATree a -> ATree a
atBinary ATKind i
k StorageClass i
t ATree i
n ATree i
forall a. ATree a
ATEmpty
{-# INLINE atNoLeaf #-}
atNoLeaf :: ATKind i -> CT.StorageClass i -> ATree i
atNoLeaf :: ATKind i -> StorageClass i -> ATree i
atNoLeaf k :: ATKind i
k t :: StorageClass i
t = ATKind i -> StorageClass i -> ATree i -> ATree i -> ATree i
forall a.
ATKind a -> StorageClass a -> ATree a -> ATree a -> ATree a
ATNode ATKind i
k StorageClass i
t ATree i
forall a. ATree a
ATEmpty ATree i
forall a. ATree a
ATEmpty
{-# INLINE atLVar #-}
atLVar :: CT.StorageClass i -> i -> ATree i
atLVar :: StorageClass i -> i -> ATree i
atLVar t :: StorageClass i
t rbpO :: i
rbpO = ATKind i -> StorageClass i -> ATree i
forall i. ATKind i -> StorageClass i -> ATree i
atNoLeaf (StorageClass i -> i -> ATKind i
forall a. StorageClass a -> a -> ATKind a
ATLVar StorageClass i
t i
rbpO) StorageClass i
t
{-# INLINE atGVar #-}
atGVar :: CT.StorageClass i -> T.Text -> ATree i
atGVar :: StorageClass i -> Text -> ATree i
atGVar t :: StorageClass i
t ident :: Text
ident = ATKind i -> StorageClass i -> ATree i
forall i. ATKind i -> StorageClass i -> ATree i
atNoLeaf (StorageClass i -> Text -> ATKind i
forall a. StorageClass a -> Text -> ATKind a
ATGVar StorageClass i
t Text
ident) StorageClass i
t
{-# INLINE atNumLit #-}
atNumLit :: i -> ATree i
atNumLit :: i -> ATree i
atNumLit = (ATKind i -> StorageClass i -> ATree i)
-> StorageClass i -> ATKind i -> ATree i
forall a b c. (a -> b -> c) -> b -> a -> c
flip ATKind i -> StorageClass i -> ATree i
forall i. ATKind i -> StorageClass i -> ATree i
atNoLeaf (TypeKind i -> StorageClass i
forall i. TypeKind i -> StorageClass i
CT.SCAuto (TypeKind i -> StorageClass i) -> TypeKind i -> StorageClass i
forall a b. (a -> b) -> a -> b
$ TypeKind i -> TypeKind i
forall i. TypeKind i -> TypeKind i
CT.CTLong TypeKind i
forall i. TypeKind i
CT.CTInt) (ATKind i -> ATree i) -> (i -> ATKind i) -> i -> ATree i
forall b c a. (b -> c) -> (a -> b) -> a -> c
. i -> ATKind i
forall a. a -> ATKind a
ATNum
{-# INLINE atAssign #-}
atAssign :: ATree i -> ATree i -> ATree i
atAssign :: ATree i -> ATree i -> ATree i
atAssign lhs :: ATree i
lhs = ATKind i -> StorageClass i -> ATree i -> ATree i -> ATree i
forall a.
ATKind a -> StorageClass a -> ATree a -> ATree a -> ATree a
atBinary ATKind i
forall a. ATKind a
ATAssign (ATree i -> StorageClass i
forall a. ATree a -> StorageClass a
atype ATree i
lhs) ATree i
lhs
{-# INLINE atMemberAcc #-}
atMemberAcc :: CT.StructMember i -> ATree i -> ATree i
atMemberAcc :: StructMember i -> ATree i -> ATree i
atMemberAcc sm :: StructMember i
sm = ATKind i -> StorageClass i -> ATree i -> ATree i
forall i. ATKind i -> StorageClass i -> ATree i -> ATree i
atUnary (StructMember i -> ATKind i
forall a. StructMember a -> ATKind a
ATMemberAcc StructMember i
sm) (TypeKind i -> StorageClass i
forall i. TypeKind i -> StorageClass i
CT.SCAuto (TypeKind i -> StorageClass i) -> TypeKind i -> StorageClass i
forall a b. (a -> b) -> a -> b
$ StructMember i -> TypeKind i
forall i. StructMember i -> TypeKind i
CT.smType StructMember i
sm)
{-# INLINE atExprStmt #-}
atExprStmt :: ATree i -> ATree i
atExprStmt :: ATree i -> ATree i
atExprStmt = ATKind i -> StorageClass i -> ATree i -> ATree i
forall i. ATKind i -> StorageClass i -> ATree i -> ATree i
atUnary ATKind i
forall a. ATKind a
ATExprStmt (TypeKind i -> StorageClass i
forall i. TypeKind i -> StorageClass i
CT.SCUndef TypeKind i
forall i. TypeKind i
CT.CTUndef)
{-# INLINE atBlock #-}
atBlock :: [ATree i] -> ATree i
atBlock :: [ATree i] -> ATree i
atBlock atl :: [ATree i]
atl = ATKind i -> StorageClass i -> ATree i -> ATree i -> ATree i
forall a.
ATKind a -> StorageClass a -> ATree a -> ATree a -> ATree a
ATNode ([ATree i] -> ATKind i
forall a. [ATree a] -> ATKind a
ATBlock [ATree i]
atl) (TypeKind i -> StorageClass i
forall i. TypeKind i -> StorageClass i
CT.SCUndef TypeKind i
forall i. TypeKind i
CT.CTUndef) ATree i
forall a. ATree a
ATEmpty ATree i
forall a. ATree a
ATEmpty
{-# INLINE atNull #-}
atNull :: ATree i -> ATree i
atNull :: ATree i -> ATree i
atNull at :: ATree i
at = ATKind i -> StorageClass i -> ATree i
forall i. ATKind i -> StorageClass i -> ATree i
atNoLeaf (ATree i -> ATKind i
forall a. ATree a -> ATKind a
ATNull ATree i
at) (TypeKind i -> StorageClass i
forall i. TypeKind i -> StorageClass i
CT.SCUndef TypeKind i
forall i. TypeKind i
CT.CTUndef)
{-# INLINE atDefFunc #-}
atDefFunc :: T.Text -> Maybe [ATree i] -> CT.StorageClass i -> ATree i -> ATree i
atDefFunc :: Text -> Maybe [ATree i] -> StorageClass i -> ATree i -> ATree i
atDefFunc = (ATKind i -> StorageClass i -> ATree i -> ATree i)
-> (Maybe [ATree i] -> ATKind i)
-> Maybe [ATree i]
-> StorageClass i
-> ATree i
-> ATree i
forall b c a. (b -> c) -> (a -> b) -> a -> c
(.) ATKind i -> StorageClass i -> ATree i -> ATree i
forall i. ATKind i -> StorageClass i -> ATree i -> ATree i
atUnary ((Maybe [ATree i] -> ATKind i)
-> Maybe [ATree i] -> StorageClass i -> ATree i -> ATree i)
-> (Text -> Maybe [ATree i] -> ATKind i)
-> Text
-> Maybe [ATree i]
-> StorageClass i
-> ATree i
-> ATree i
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Text -> Maybe [ATree i] -> ATKind i
forall a. Text -> Maybe [ATree a] -> ATKind a
ATDefFunc
{-# INLINE atReturn #-}
atReturn :: CT.StorageClass i -> ATree i -> ATree i
atReturn :: StorageClass i -> ATree i -> ATree i
atReturn = ATKind i -> StorageClass i -> ATree i -> ATree i
forall i. ATKind i -> StorageClass i -> ATree i -> ATree i
atUnary ATKind i
forall a. ATKind a
ATReturn
{-# INLINE atIf #-}
atIf :: ATree i -> ATree i -> ATree i
atIf :: ATree i -> ATree i -> ATree i
atIf = ATKind i -> StorageClass i -> ATree i -> ATree i -> ATree i
forall a.
ATKind a -> StorageClass a -> ATree a -> ATree a -> ATree a
atBinary ATKind i
forall a. ATKind a
ATIf (TypeKind i -> StorageClass i
forall i. TypeKind i -> StorageClass i
CT.SCUndef TypeKind i
forall i. TypeKind i
CT.CTUndef)
{-# INLINE atElse #-}
atElse :: ATree i -> ATree i -> ATree i
atElse :: ATree i -> ATree i -> ATree i
atElse = ATKind i -> StorageClass i -> ATree i -> ATree i -> ATree i
forall a.
ATKind a -> StorageClass a -> ATree a -> ATree a -> ATree a
atBinary ATKind i
forall a. ATKind a
ATElse (TypeKind i -> StorageClass i
forall i. TypeKind i -> StorageClass i
CT.SCUndef TypeKind i
forall i. TypeKind i
CT.CTUndef)
{-# INLINE atWhile #-}
atWhile :: ATree i -> ATree i -> ATree i
atWhile :: ATree i -> ATree i -> ATree i
atWhile = ATKind i -> StorageClass i -> ATree i -> ATree i -> ATree i
forall a.
ATKind a -> StorageClass a -> ATree a -> ATree a -> ATree a
atBinary ATKind i
forall a. ATKind a
ATWhile (TypeKind i -> StorageClass i
forall i. TypeKind i -> StorageClass i
CT.SCUndef TypeKind i
forall i. TypeKind i
CT.CTUndef)
{-# INLINE atFor #-}
atFor :: [ATKindFor i] -> ATree i
atFor :: [ATKindFor i] -> ATree i
atFor = (ATKind i -> StorageClass i -> ATree i)
-> StorageClass i -> ATKind i -> ATree i
forall a b c. (a -> b -> c) -> b -> a -> c
flip ATKind i -> StorageClass i -> ATree i
forall i. ATKind i -> StorageClass i -> ATree i
atNoLeaf (TypeKind i -> StorageClass i
forall i. TypeKind i -> StorageClass i
CT.SCUndef TypeKind i
forall i. TypeKind i
CT.CTUndef) (ATKind i -> ATree i)
-> ([ATKindFor i] -> ATKind i) -> [ATKindFor i] -> ATree i
forall b c a. (b -> c) -> (a -> b) -> a -> c
. [ATKindFor i] -> ATKind i
forall a. [ATKindFor a] -> ATKind a
ATFor
{-# INLINE atBreak #-}
atBreak :: ATree i
atBreak :: ATree i
atBreak = ATKind i -> StorageClass i -> ATree i
forall i. ATKind i -> StorageClass i -> ATree i
atNoLeaf ATKind i
forall a. ATKind a
ATBreak (TypeKind i -> StorageClass i
forall i. TypeKind i -> StorageClass i
CT.SCUndef TypeKind i
forall i. TypeKind i
CT.CTUndef)
{-# INLINE atContinue #-}
atContinue :: ATree i
atContinue :: ATree i
atContinue = ATKind i -> StorageClass i -> ATree i
forall i. ATKind i -> StorageClass i -> ATree i
atNoLeaf ATKind i
forall a. ATKind a
ATContinue (TypeKind i -> StorageClass i
forall i. TypeKind i -> StorageClass i
CT.SCUndef TypeKind i
forall i. TypeKind i
CT.CTUndef)
{-# INLINE atSwitch #-}
atSwitch :: ATree i -> [ATree i] -> CT.StorageClass i -> ATree i
atSwitch :: ATree i -> [ATree i] -> StorageClass i -> ATree i
atSwitch = (ATKind i -> StorageClass i -> ATree i)
-> ([ATree i] -> ATKind i)
-> [ATree i]
-> StorageClass i
-> ATree i
forall b c a. (b -> c) -> (a -> b) -> a -> c
(.) ATKind i -> StorageClass i -> ATree i
forall i. ATKind i -> StorageClass i -> ATree i
atNoLeaf (([ATree i] -> ATKind i) -> [ATree i] -> StorageClass i -> ATree i)
-> (ATree i -> [ATree i] -> ATKind i)
-> ATree i
-> [ATree i]
-> StorageClass i
-> ATree i
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ATree i -> [ATree i] -> ATKind i
forall a. ATree a -> [ATree a] -> ATKind a
ATSwitch
{-# INLINE atCase #-}
atCase :: i -> i -> ATree i -> ATree i
atCase :: i -> i -> ATree i -> ATree i
atCase = (ATKind i -> ATree i -> ATree i)
-> (i -> ATKind i) -> i -> ATree i -> ATree i
forall b c a. (b -> c) -> (a -> b) -> a -> c
(.) (ATKind i -> StorageClass i -> ATree i -> ATree i
forall i. ATKind i -> StorageClass i -> ATree i -> ATree i
`atUnary` TypeKind i -> StorageClass i
forall i. TypeKind i -> StorageClass i
CT.SCUndef TypeKind i
forall i. TypeKind i
CT.CTUndef) ((i -> ATKind i) -> i -> ATree i -> ATree i)
-> (i -> i -> ATKind i) -> i -> i -> ATree i -> ATree i
forall b c a. (b -> c) -> (a -> b) -> a -> c
. i -> i -> ATKind i
forall a. a -> a -> ATKind a
ATCase
{-# INLINE atDefault #-}
atDefault :: i -> ATree i -> ATree i
atDefault :: i -> ATree i -> ATree i
atDefault = (ATKind i -> StorageClass i -> ATree i -> ATree i)
-> StorageClass i -> ATKind i -> ATree i -> ATree i
forall a b c. (a -> b -> c) -> b -> a -> c
flip ATKind i -> StorageClass i -> ATree i -> ATree i
forall i. ATKind i -> StorageClass i -> ATree i -> ATree i
atUnary (TypeKind i -> StorageClass i
forall i. TypeKind i -> StorageClass i
CT.SCUndef TypeKind i
forall i. TypeKind i
CT.CTUndef) (ATKind i -> ATree i -> ATree i)
-> (i -> ATKind i) -> i -> ATree i -> ATree i
forall b c a. (b -> c) -> (a -> b) -> a -> c
. i -> ATKind i
forall a. a -> ATKind a
ATDefault
{-# INLINE atGoto #-}
atGoto :: T.Text -> ATree i
atGoto :: Text -> ATree i
atGoto = (ATKind i -> StorageClass i -> ATree i)
-> StorageClass i -> ATKind i -> ATree i
forall a b c. (a -> b -> c) -> b -> a -> c
flip ATKind i -> StorageClass i -> ATree i
forall i. ATKind i -> StorageClass i -> ATree i
atNoLeaf (TypeKind i -> StorageClass i
forall i. TypeKind i -> StorageClass i
CT.SCUndef TypeKind i
forall i. TypeKind i
CT.CTUndef) (ATKind i -> ATree i) -> (Text -> ATKind i) -> Text -> ATree i
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Text -> ATKind i
forall a. Text -> ATKind a
ATGoto
{-# INLINE atLabel #-}
atLabel :: T.Text -> ATree i
atLabel :: Text -> ATree i
atLabel = (ATKind i -> StorageClass i -> ATree i)
-> StorageClass i -> ATKind i -> ATree i
forall a b c. (a -> b -> c) -> b -> a -> c
flip ATKind i -> StorageClass i -> ATree i
forall i. ATKind i -> StorageClass i -> ATree i
atNoLeaf (TypeKind i -> StorageClass i
forall i. TypeKind i -> StorageClass i
CT.SCUndef TypeKind i
forall i. TypeKind i
CT.CTUndef) (ATKind i -> ATree i) -> (Text -> ATKind i) -> Text -> ATree i
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Text -> ATKind i
forall a. Text -> ATKind a
ATLabel
{-# INLINE atComma #-}
atComma :: CT.StorageClass i -> ATree i -> ATree i -> ATree i
atComma :: StorageClass i -> ATree i -> ATree i -> ATree i
atComma = ATKind i -> StorageClass i -> ATree i -> ATree i -> ATree i
forall a.
ATKind a -> StorageClass a -> ATree a -> ATree a -> ATree a
atBinary ATKind i
forall a. ATKind a
ATComma
{-# INLINE atConditional #-}
atConditional :: CT.StorageClass i -> ATree i -> ATree i -> ATree i -> ATree i
atConditional :: StorageClass i -> ATree i -> ATree i -> ATree i -> ATree i
atConditional ty :: StorageClass i
ty c :: ATree i
c t :: ATree i
t f :: ATree i
f = ATKind i -> StorageClass i -> ATree i
forall i. ATKind i -> StorageClass i -> ATree i
atNoLeaf (ATree i -> ATree i -> ATree i -> ATKind i
forall a. ATree a -> ATree a -> ATree a -> ATKind a
ATConditional ATree i
c ATree i
t ATree i
f) StorageClass i
ty
{-# INLINE atCast #-}
atCast :: CT.StorageClass i -> ATree i -> ATree i
atCast :: StorageClass i -> ATree i -> ATree i
atCast = ATKind i -> StorageClass i -> ATree i -> ATree i
forall i. ATKind i -> StorageClass i -> ATree i -> ATree i
atUnary ATKind i
forall a. ATKind a
ATCast
mapATKind :: (ATKind i -> ATKind i) -> ATree i -> ATree i
mapATKind :: (ATKind i -> ATKind i) -> ATree i -> ATree i
mapATKind f :: ATKind i -> ATKind i
f (ATNode atk :: ATKind i
atk t :: StorageClass i
t l :: ATree i
l r :: ATree i
r) = ATKind i -> StorageClass i -> ATree i -> ATree i -> ATree i
forall a.
ATKind a -> StorageClass a -> ATree a -> ATree a -> ATree a
ATNode (ATKind i -> ATKind i
f ATKind i
atk) StorageClass i
t ((ATKind i -> ATKind i) -> ATree i -> ATree i
forall i. (ATKind i -> ATKind i) -> ATree i -> ATree i
mapATKind ATKind i -> ATKind i
f ATree i
l) ((ATKind i -> ATKind i) -> ATree i -> ATree i
forall i. (ATKind i -> ATKind i) -> ATree i -> ATree i
mapATKind ATKind i -> ATKind i
f ATree i
r)
mapATKind _ ATEmpty = ATree i
forall a. ATree a
ATEmpty
modifyTypeATKind :: (CT.StorageClass i -> CT.StorageClass i) -> ATKind i -> ATKind i
modifyTypeATKind :: (StorageClass i -> StorageClass i) -> ATKind i -> ATKind i
modifyTypeATKind f :: StorageClass i -> StorageClass i
f (ATLVar t :: StorageClass i
t o :: i
o) = StorageClass i -> i -> ATKind i
forall a. StorageClass a -> a -> ATKind a
ATLVar (StorageClass i -> StorageClass i
f StorageClass i
t) i
o
modifyTypeATKind f :: StorageClass i -> StorageClass i
f (ATGVar t :: StorageClass i
t o :: Text
o) = StorageClass i -> Text -> ATKind i
forall a. StorageClass a -> Text -> ATKind a
ATGVar (StorageClass i -> StorageClass i
f StorageClass i
t) Text
o
modifyTypeATKind _ _ = ATree i -> ATKind i
forall a. ATree a -> ATKind a
ATNull ATree i
forall a. ATree a
ATEmpty