{-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE PatternSynonyms #-}
module Demangler.Structure
where
import Data.List.NonEmpty ( NonEmpty )
import Data.Text ( Text )
import Numeric.Natural
import Demangler.Context
data Demangled = Original Coord
| Encoded Encoding
| VendorExtended Encoding Coord
data Encoding = EncFunc FunctionName (Maybe Type_) (NonEmpty Type_)
| EncStaticFunc FunctionName (Maybe Type_) (NonEmpty Type_)
| EncData Name
| EncSpecial SpecialName
| EncConstStructData UnqualifiedName
deriving (Encoding -> Encoding -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: Encoding -> Encoding -> Bool
$c/= :: Encoding -> Encoding -> Bool
== :: Encoding -> Encoding -> Bool
$c== :: Encoding -> Encoding -> Bool
Eq, Int -> Encoding -> ShowS
[Encoding] -> ShowS
Encoding -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [Encoding] -> ShowS
$cshowList :: [Encoding] -> ShowS
show :: Encoding -> String
$cshow :: Encoding -> String
showsPrec :: Int -> Encoding -> ShowS
$cshowsPrec :: Int -> Encoding -> ShowS
Show)
data FunctionName = FunctionName Name
deriving (FunctionName -> FunctionName -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: FunctionName -> FunctionName -> Bool
$c/= :: FunctionName -> FunctionName -> Bool
== :: FunctionName -> FunctionName -> Bool
$c== :: FunctionName -> FunctionName -> Bool
Eq, Int -> FunctionName -> ShowS
[FunctionName] -> ShowS
FunctionName -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [FunctionName] -> ShowS
$cshowList :: [FunctionName] -> ShowS
show :: FunctionName -> String
$cshow :: FunctionName -> String
showsPrec :: Int -> FunctionName -> ShowS
$cshowsPrec :: Int -> FunctionName -> ShowS
Show)
data Name = NameNested NestedName
| UnscopedName Bool UnqualifiedName
| UnscopedTemplateName Name TemplateArgs
| LocalName FunctionScope FunctionEntity (Maybe Discriminator)
| StringLitName FunctionScope (Maybe Discriminator)
deriving (Name -> Name -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: Name -> Name -> Bool
$c/= :: Name -> Name -> Bool
== :: Name -> Name -> Bool
$c== :: Name -> Name -> Bool
Eq, Int -> Name -> ShowS
[Name] -> ShowS
Name -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [Name] -> ShowS
$cshowList :: [Name] -> ShowS
show :: Name -> String
$cshow :: Name -> String
showsPrec :: Int -> Name -> ShowS
$cshowsPrec :: Int -> Name -> ShowS
Show)
data NestedName = NestedName Prefix UnqualifiedName
[CVQualifier] (Maybe RefQualifier)
| NestedTemplateName TemplatePrefix TemplateArgs
[CVQualifier] (Maybe RefQualifier)
deriving (NestedName -> NestedName -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: NestedName -> NestedName -> Bool
$c/= :: NestedName -> NestedName -> Bool
== :: NestedName -> NestedName -> Bool
$c== :: NestedName -> NestedName -> Bool
Eq, Int -> NestedName -> ShowS
[NestedName] -> ShowS
NestedName -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [NestedName] -> ShowS
$cshowList :: [NestedName] -> ShowS
show :: NestedName -> String
$cshow :: NestedName -> String
showsPrec :: Int -> NestedName -> ShowS
$cshowsPrec :: Int -> NestedName -> ShowS
Show)
type FunctionScope = Coord
type FunctionEntity = Coord
type Discriminator = Coord
data ModuleName = ModuleName IsPartition SourceName
deriving (ModuleName -> ModuleName -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: ModuleName -> ModuleName -> Bool
$c/= :: ModuleName -> ModuleName -> Bool
== :: ModuleName -> ModuleName -> Bool
$c== :: ModuleName -> ModuleName -> Bool
Eq, Int -> ModuleName -> ShowS
[ModuleName] -> ShowS
ModuleName -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [ModuleName] -> ShowS
$cshowList :: [ModuleName] -> ShowS
show :: ModuleName -> String
$cshow :: ModuleName -> String
showsPrec :: Int -> ModuleName -> ShowS
$cshowsPrec :: Int -> ModuleName -> ShowS
Show)
type IsPartition = Bool
data UnqualifiedName = SourceName SourceName [ABI_Tag]
| OperatorName Operator [ABI_Tag]
| CtorDtorName CtorDtor
| StdSubst Substitution
| ModuleNamed [ModuleName] UnqualifiedName
deriving (UnqualifiedName -> UnqualifiedName -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: UnqualifiedName -> UnqualifiedName -> Bool
$c/= :: UnqualifiedName -> UnqualifiedName -> Bool
== :: UnqualifiedName -> UnqualifiedName -> Bool
$c== :: UnqualifiedName -> UnqualifiedName -> Bool
Eq, Int -> UnqualifiedName -> ShowS
[UnqualifiedName] -> ShowS
UnqualifiedName -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [UnqualifiedName] -> ShowS
$cshowList :: [UnqualifiedName] -> ShowS
show :: UnqualifiedName -> String
$cshow :: UnqualifiedName -> String
showsPrec :: Int -> UnqualifiedName -> ShowS
$cshowsPrec :: Int -> UnqualifiedName -> ShowS
Show)
newtype SourceName = SrcName Coord
deriving (SourceName -> SourceName -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: SourceName -> SourceName -> Bool
$c/= :: SourceName -> SourceName -> Bool
== :: SourceName -> SourceName -> Bool
$c== :: SourceName -> SourceName -> Bool
Eq, Int -> SourceName -> ShowS
[SourceName] -> ShowS
SourceName -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [SourceName] -> ShowS
$cshowList :: [SourceName] -> ShowS
show :: SourceName -> String
$cshow :: SourceName -> String
showsPrec :: Int -> SourceName -> ShowS
$cshowsPrec :: Int -> SourceName -> ShowS
Show)
data CtorDtor = CompleteCtor
| BaseCtor
| CompleteAllocatingCtor
| CompleteInheritingCtor Type_
| BaseInheritingCtor Type_
| DeletingDtor
| CompleteDtor
| BaseDtor
deriving (CtorDtor -> CtorDtor -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: CtorDtor -> CtorDtor -> Bool
$c/= :: CtorDtor -> CtorDtor -> Bool
== :: CtorDtor -> CtorDtor -> Bool
$c== :: CtorDtor -> CtorDtor -> Bool
Eq, Int -> CtorDtor -> ShowS
[CtorDtor] -> ShowS
CtorDtor -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [CtorDtor] -> ShowS
$cshowList :: [CtorDtor] -> ShowS
show :: CtorDtor -> String
$cshow :: CtorDtor -> String
showsPrec :: Int -> CtorDtor -> ShowS
$cshowsPrec :: Int -> CtorDtor -> ShowS
Show)
data Operator = OpNew
| OpNewArr
| OpDel
| OpDelArr
| OpCoAwait
| OpPositive
| OpNegative
| OpAddress
| OpDeReference
| OpComplement
| OpPlus
| OpMinus
| OpMultiply
| OpDivide
| OpRemainder
| OpAnd
| OpOr
| OpXOR
| OpAssign
| OpAssignPlus
| OpAssignMinus
| OpAssignMul
| OpAssignDiv
| OpAssignRem
| OpAssignAnd
| OpAssignOr
| OpAssignXOR
| OpLeftShift
| OpRightShift
| OpAssignShL
| OpAssignShR
| OpEq
| OpNotEq
| OpLT
| OpGT
| OpLTE
| OpGTE
| OpSpan
| OpNot
| OpLogicalAnd
| OpLogicalOr
| OpPlusPlus
| OpMinusMinus
| OpComma
| OpPointStar
| OpPoint
| OpCall
| OpIndex
| OpQuestion
| OpSizeOfType
| OpSizeOfExpr
| OpAlignOfType
| OpAlignOfExpr
| OpCast Type_
| OpString SourceName
| OpVendor Natural SourceName
deriving (Operator -> Operator -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: Operator -> Operator -> Bool
$c/= :: Operator -> Operator -> Bool
== :: Operator -> Operator -> Bool
$c== :: Operator -> Operator -> Bool
Eq, Int -> Operator -> ShowS
[Operator] -> ShowS
Operator -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [Operator] -> ShowS
$cshowList :: [Operator] -> ShowS
show :: Operator -> String
$cshow :: Operator -> String
showsPrec :: Int -> Operator -> ShowS
$cshowsPrec :: Int -> Operator -> ShowS
Show)
data ABI_Tag = ABITag SourceName
deriving (ABI_Tag -> ABI_Tag -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: ABI_Tag -> ABI_Tag -> Bool
$c/= :: ABI_Tag -> ABI_Tag -> Bool
== :: ABI_Tag -> ABI_Tag -> Bool
$c== :: ABI_Tag -> ABI_Tag -> Bool
Eq, Int -> ABI_Tag -> ShowS
[ABI_Tag] -> ShowS
ABI_Tag -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [ABI_Tag] -> ShowS
$cshowList :: [ABI_Tag] -> ShowS
show :: ABI_Tag -> String
$cshow :: ABI_Tag -> String
showsPrec :: Int -> ABI_Tag -> ShowS
$cshowsPrec :: Int -> ABI_Tag -> ShowS
Show)
data SpecialName = VirtualTable Type_
| TemplateParameterObj TemplateArg
| VTT Type_
| TypeInfo Type_
| TypeInfoName Type_
| Thunk CallOffset Encoding
| CtorVTable ()
deriving (SpecialName -> SpecialName -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: SpecialName -> SpecialName -> Bool
$c/= :: SpecialName -> SpecialName -> Bool
== :: SpecialName -> SpecialName -> Bool
$c== :: SpecialName -> SpecialName -> Bool
Eq, Int -> SpecialName -> ShowS
[SpecialName] -> ShowS
SpecialName -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [SpecialName] -> ShowS
$cshowList :: [SpecialName] -> ShowS
show :: SpecialName -> String
$cshow :: SpecialName -> String
showsPrec :: Int -> SpecialName -> ShowS
$cshowsPrec :: Int -> SpecialName -> ShowS
Show)
data CallOffset = VirtualOffset Int Int
| NonVirtualOffset Int
deriving (CallOffset -> CallOffset -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: CallOffset -> CallOffset -> Bool
$c/= :: CallOffset -> CallOffset -> Bool
== :: CallOffset -> CallOffset -> Bool
$c== :: CallOffset -> CallOffset -> Bool
Eq, Int -> CallOffset -> ShowS
[CallOffset] -> ShowS
CallOffset -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [CallOffset] -> ShowS
$cshowList :: [CallOffset] -> ShowS
show :: CallOffset -> String
$cshow :: CallOffset -> String
showsPrec :: Int -> CallOffset -> ShowS
$cshowsPrec :: Int -> CallOffset -> ShowS
Show)
data Substitution' = SubsFirst
| Subs Natural
| SubsConst Substitution
deriving Int -> Substitution' -> ShowS
[Substitution'] -> ShowS
Substitution' -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [Substitution'] -> ShowS
$cshowList :: [Substitution'] -> ShowS
show :: Substitution' -> String
$cshow :: Substitution' -> String
showsPrec :: Int -> Substitution' -> ShowS
$cshowsPrec :: Int -> Substitution' -> ShowS
Show
data Substitution = SubStd
| SubAlloc
| SubBasicString
| SubStdType StdType
deriving (Substitution -> Substitution -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: Substitution -> Substitution -> Bool
$c/= :: Substitution -> Substitution -> Bool
== :: Substitution -> Substitution -> Bool
$c== :: Substitution -> Substitution -> Bool
Eq, Int -> Substitution -> ShowS
[Substitution] -> ShowS
Substitution -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [Substitution] -> ShowS
$cshowList :: [Substitution] -> ShowS
show :: Substitution -> String
$cshow :: Substitution -> String
showsPrec :: Int -> Substitution -> ShowS
$cshowsPrec :: Int -> Substitution -> ShowS
Show)
data Type_ = BaseType BaseType
| QualifiedType [ExtendedQualifier] [CVQualifier] Type_
| ClassUnionStructEnum Name
| ClassStruct Name
| Union Name
| Enum Name
| Function [CVQualifier] (Maybe ExceptionSpec)
Transaction Bool Type_ (NonEmpty Type_) (Maybe RefQualifier)
| Template TemplateParam TemplateArgs
| Pointer Type_
| LValRef Type_
| RValRef Type_
| ComplexPair Type_
| Imaginary Type_
| Cpp11PackExpansion (NonEmpty Type_)
| StdType StdType
| ArrayType ArrayBound Type_
deriving (Type_ -> Type_ -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: Type_ -> Type_ -> Bool
$c/= :: Type_ -> Type_ -> Bool
== :: Type_ -> Type_ -> Bool
$c== :: Type_ -> Type_ -> Bool
Eq, Int -> Type_ -> ShowS
[Type_] -> ShowS
Type_ -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [Type_] -> ShowS
$cshowList :: [Type_] -> ShowS
show :: Type_ -> String
$cshow :: Type_ -> String
showsPrec :: Int -> Type_ -> ShowS
$cshowsPrec :: Int -> Type_ -> ShowS
Show)
data ArrayBound = NumBound Int
| ExprBound Expression
| NoBounds
deriving (ArrayBound -> ArrayBound -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: ArrayBound -> ArrayBound -> Bool
$c/= :: ArrayBound -> ArrayBound -> Bool
== :: ArrayBound -> ArrayBound -> Bool
$c== :: ArrayBound -> ArrayBound -> Bool
Eq, Int -> ArrayBound -> ShowS
[ArrayBound] -> ShowS
ArrayBound -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [ArrayBound] -> ShowS
$cshowList :: [ArrayBound] -> ShowS
show :: ArrayBound -> String
$cshow :: ArrayBound -> String
showsPrec :: Int -> ArrayBound -> ShowS
$cshowsPrec :: Int -> ArrayBound -> ShowS
Show)
data ExceptionSpec = NonThrowing
| ComputedThrow Expression
| Throwing (NonEmpty Type_)
deriving (ExceptionSpec -> ExceptionSpec -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: ExceptionSpec -> ExceptionSpec -> Bool
$c/= :: ExceptionSpec -> ExceptionSpec -> Bool
== :: ExceptionSpec -> ExceptionSpec -> Bool
$c== :: ExceptionSpec -> ExceptionSpec -> Bool
Eq, Int -> ExceptionSpec -> ShowS
[ExceptionSpec] -> ShowS
ExceptionSpec -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [ExceptionSpec] -> ShowS
$cshowList :: [ExceptionSpec] -> ShowS
show :: ExceptionSpec -> String
$cshow :: ExceptionSpec -> String
showsPrec :: Int -> ExceptionSpec -> ShowS
$cshowsPrec :: Int -> ExceptionSpec -> ShowS
Show)
data Transaction = TransactionSafe | TransactionUnsafe
deriving (Transaction -> Transaction -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: Transaction -> Transaction -> Bool
$c/= :: Transaction -> Transaction -> Bool
== :: Transaction -> Transaction -> Bool
$c== :: Transaction -> Transaction -> Bool
Eq, Int -> Transaction -> ShowS
[Transaction] -> ShowS
Transaction -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [Transaction] -> ShowS
$cshowList :: [Transaction] -> ShowS
show :: Transaction -> String
$cshow :: Transaction -> String
showsPrec :: Int -> Transaction -> ShowS
$cshowsPrec :: Int -> Transaction -> ShowS
Show)
data BaseType = Void | Wchar_t | Bool_
| Char_ | SChar | UChar
| Short | UShort
| Int_ | UInt
| Long | ULong
| LongLong | ULongLong
| Int128 | UInt128
| Float_ | Double_ | LongDouble80 | Float128
| Ellipsis
| IEE754rDecFloat64
| IEE754rDecFloat128
| IEE754rDecFloat32
| IEE754rDecFloat16
| FloatN Natural
| FloatNx Natural
| BFloat16
| SBitInt Natural | UBitInt Natural
| Char32 | Char16 | Char8
| Auto | DeclTypeAuto
| NullPtr
| N1168FixedPointAccum
| N1168FixedPointAccumSat
| N1168FixedPointFract
| N1168FixedPointFractSat
| VendorExtendedType SourceName (Maybe TemplateArgs)
deriving (BaseType -> BaseType -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: BaseType -> BaseType -> Bool
$c/= :: BaseType -> BaseType -> Bool
== :: BaseType -> BaseType -> Bool
$c== :: BaseType -> BaseType -> Bool
Eq, Int -> BaseType -> ShowS
[BaseType] -> ShowS
BaseType -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [BaseType] -> ShowS
$cshowList :: [BaseType] -> ShowS
show :: BaseType -> String
$cshow :: BaseType -> String
showsPrec :: Int -> BaseType -> ShowS
$cshowsPrec :: Int -> BaseType -> ShowS
Show)
data StdType = BasicStringChar
| BasicIStream
| BasicOStream
| BasicIOStream
deriving (StdType -> StdType -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: StdType -> StdType -> Bool
$c/= :: StdType -> StdType -> Bool
== :: StdType -> StdType -> Bool
$c== :: StdType -> StdType -> Bool
Eq, Int -> StdType -> ShowS
[StdType] -> ShowS
StdType -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [StdType] -> ShowS
$cshowList :: [StdType] -> ShowS
show :: StdType -> String
$cshow :: StdType -> String
showsPrec :: Int -> StdType -> ShowS
$cshowsPrec :: Int -> StdType -> ShowS
Show)
data CVQualifier = Restrict | Volatile | Const_
deriving (CVQualifier -> CVQualifier -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: CVQualifier -> CVQualifier -> Bool
$c/= :: CVQualifier -> CVQualifier -> Bool
== :: CVQualifier -> CVQualifier -> Bool
$c== :: CVQualifier -> CVQualifier -> Bool
Eq, Int -> CVQualifier -> ShowS
[CVQualifier] -> ShowS
CVQualifier -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [CVQualifier] -> ShowS
$cshowList :: [CVQualifier] -> ShowS
show :: CVQualifier -> String
$cshow :: CVQualifier -> String
showsPrec :: Int -> CVQualifier -> ShowS
$cshowsPrec :: Int -> CVQualifier -> ShowS
Show)
data RefQualifier = Ref | RefRef
deriving (RefQualifier -> RefQualifier -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: RefQualifier -> RefQualifier -> Bool
$c/= :: RefQualifier -> RefQualifier -> Bool
== :: RefQualifier -> RefQualifier -> Bool
$c== :: RefQualifier -> RefQualifier -> Bool
Eq, Int -> RefQualifier -> ShowS
[RefQualifier] -> ShowS
RefQualifier -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [RefQualifier] -> ShowS
$cshowList :: [RefQualifier] -> ShowS
show :: RefQualifier -> String
$cshow :: RefQualifier -> String
showsPrec :: Int -> RefQualifier -> ShowS
$cshowsPrec :: Int -> RefQualifier -> ShowS
Show)
type ExtendedQualifier = ()
data Prefix = PrefixTemplateParam TemplateParam PrefixR
| PrefixDeclType DeclType PrefixR
| PrefixClosure ClosurePrefix
| Prefix PrefixR
deriving (Prefix -> Prefix -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: Prefix -> Prefix -> Bool
$c/= :: Prefix -> Prefix -> Bool
== :: Prefix -> Prefix -> Bool
$c== :: Prefix -> Prefix -> Bool
Eq, Int -> Prefix -> ShowS
[Prefix] -> ShowS
Prefix -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [Prefix] -> ShowS
$cshowList :: [Prefix] -> ShowS
show :: Prefix -> String
$cshow :: Prefix -> String
showsPrec :: Int -> Prefix -> ShowS
$cshowsPrec :: Int -> Prefix -> ShowS
Show)
data PrefixR = PrefixUQName UnqualifiedName PrefixR
| PrefixTemplateArgs TemplateArgs PrefixR
| PrefixEnd
deriving (PrefixR -> PrefixR -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: PrefixR -> PrefixR -> Bool
$c/= :: PrefixR -> PrefixR -> Bool
== :: PrefixR -> PrefixR -> Bool
$c== :: PrefixR -> PrefixR -> Bool
Eq, Int -> PrefixR -> ShowS
[PrefixR] -> ShowS
PrefixR -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [PrefixR] -> ShowS
$cshowList :: [PrefixR] -> ShowS
show :: PrefixR -> String
$cshow :: PrefixR -> String
showsPrec :: Int -> PrefixR -> ShowS
$cshowsPrec :: Int -> PrefixR -> ShowS
Show)
pattern EmptyPrefix :: Prefix
pattern $bEmptyPrefix :: Prefix
$mEmptyPrefix :: forall {r}. Prefix -> ((# #) -> r) -> ((# #) -> r) -> r
EmptyPrefix = Prefix PrefixEnd
data TemplatePrefix = GlobalTemplate (NonEmpty UnqualifiedName)
| NestedTemplate Prefix (NonEmpty UnqualifiedName)
| TemplateTemplateParam TemplateParam
deriving (TemplatePrefix -> TemplatePrefix -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: TemplatePrefix -> TemplatePrefix -> Bool
$c/= :: TemplatePrefix -> TemplatePrefix -> Bool
== :: TemplatePrefix -> TemplatePrefix -> Bool
$c== :: TemplatePrefix -> TemplatePrefix -> Bool
Eq, Int -> TemplatePrefix -> ShowS
[TemplatePrefix] -> ShowS
TemplatePrefix -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [TemplatePrefix] -> ShowS
$cshowList :: [TemplatePrefix] -> ShowS
show :: TemplatePrefix -> String
$cshow :: TemplatePrefix -> String
showsPrec :: Int -> TemplatePrefix -> ShowS
$cshowsPrec :: Int -> TemplatePrefix -> ShowS
Show)
type TemplateName = Name
type TemplateArgs = NonEmpty TemplateArg
data TemplateArg = TArgType Type_
| TArgExpr Expression
| TArgSimpleExpr ExprPrimary
| TArgPack [TemplateArg]
deriving (TemplateArg -> TemplateArg -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: TemplateArg -> TemplateArg -> Bool
$c/= :: TemplateArg -> TemplateArg -> Bool
== :: TemplateArg -> TemplateArg -> Bool
$c== :: TemplateArg -> TemplateArg -> Bool
Eq, Int -> TemplateArg -> ShowS
[TemplateArg] -> ShowS
TemplateArg -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [TemplateArg] -> ShowS
$cshowList :: [TemplateArg] -> ShowS
show :: TemplateArg -> String
$cshow :: TemplateArg -> String
showsPrec :: Int -> TemplateArg -> ShowS
$cshowsPrec :: Int -> TemplateArg -> ShowS
Show)
type TemplateParam = TemplateArg
data Expression = ExprPack Expression
| ExprTemplateParam TemplateParam
| ExprPrim ExprPrimary
deriving (Expression -> Expression -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: Expression -> Expression -> Bool
$c/= :: Expression -> Expression -> Bool
== :: Expression -> Expression -> Bool
$c== :: Expression -> Expression -> Bool
Eq, Int -> Expression -> ShowS
[Expression] -> ShowS
Expression -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [Expression] -> ShowS
$cshowList :: [Expression] -> ShowS
show :: Expression -> String
$cshow :: Expression -> String
showsPrec :: Int -> Expression -> ShowS
$cshowsPrec :: Int -> Expression -> ShowS
Show)
data ExprPrimary = IntLit Type_ Int
| FloatLit Type_ Float
| DirectLit Type_
| NullPtrTemplateArg Type_
| ComplexFloatLit Type_ Float Float
| ExternalNameLit Encoding
deriving (ExprPrimary -> ExprPrimary -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: ExprPrimary -> ExprPrimary -> Bool
$c/= :: ExprPrimary -> ExprPrimary -> Bool
== :: ExprPrimary -> ExprPrimary -> Bool
$c== :: ExprPrimary -> ExprPrimary -> Bool
Eq, Int -> ExprPrimary -> ShowS
[ExprPrimary] -> ShowS
ExprPrimary -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [ExprPrimary] -> ShowS
$cshowList :: [ExprPrimary] -> ShowS
show :: ExprPrimary -> String
$cshow :: ExprPrimary -> String
showsPrec :: Int -> ExprPrimary -> ShowS
$cshowsPrec :: Int -> ExprPrimary -> ShowS
Show)
type ClosurePrefix = ()
type DeclType = ()
builtinTypeTable :: [ (BaseType, (Text, Text, Text)) ]
builtinTypeTable :: [(BaseType, (Text, Text, Text))]
builtinTypeTable =
[ (BaseType
Void, (Text
"v", Text
"void", Text
""))
, (BaseType
Wchar_t, (Text
"w", Text
"wchar_t", Text
""))
, (BaseType
Bool_, (Text
"b", Text
"bool", Text
""))
, (BaseType
Char_, (Text
"c", Text
"char", Text
""))
, (BaseType
SChar, (Text
"a", Text
"signed char", Text
""))
, (BaseType
UChar, (Text
"h", Text
"unsigned char", Text
""))
, (BaseType
Short, (Text
"s", Text
"short", Text
""))
, (BaseType
UShort, (Text
"t", Text
"unsigned short", Text
""))
, (BaseType
Int_, (Text
"i", Text
"int", Text
""))
, (BaseType
UInt, (Text
"j", Text
"unsigned int", Text
""))
, (BaseType
Long, (Text
"l", Text
"long", Text
"l"))
, (BaseType
ULong, (Text
"m", Text
"unsigned long", Text
"ul"))
, (BaseType
LongLong, (Text
"x", Text
"long long", Text
""))
, (BaseType
ULongLong, (Text
"y", Text
"unsigned long long", Text
""))
, (BaseType
Int128, (Text
"n", Text
"__int128", Text
""))
, (BaseType
UInt128, (Text
"o", Text
"unsigned __int128", Text
""))
, (BaseType
Float_, (Text
"f", Text
"float", Text
""))
, (BaseType
Double_, (Text
"d", Text
"double", Text
""))
, (BaseType
LongDouble80, (Text
"e", Text
"long double", Text
""))
, (BaseType
Float128, (Text
"g", Text
"__float128", Text
""))
, (BaseType
Ellipsis, (Text
"z", Text
"...", Text
""))
, (BaseType
IEE754rDecFloat64, (Text
"Dd", Text
"__ieeefloat64", Text
""))
, (BaseType
IEE754rDecFloat128, (Text
"De", Text
"__ieeefloat128", Text
""))
, (BaseType
IEE754rDecFloat32, (Text
"Df", Text
"__ieeefloat32", Text
""))
, (BaseType
IEE754rDecFloat16, (Text
"Dh", Text
"__ieeefloat16", Text
""))
, (BaseType
BFloat16, (Text
"DF16b", Text
"std::bfloat16_t", Text
""))
, (BaseType
Char32, (Text
"Di", Text
"char32_t", Text
""))
, (BaseType
Char16, (Text
"Ds", Text
"char16_t", Text
""))
, (BaseType
Char8, (Text
"Du", Text
"char8_t", Text
""))
, (BaseType
Auto, (Text
"Da", Text
"auto", Text
""))
, (BaseType
DeclTypeAuto, (Text
"Dc", Text
"decltype(auto)", Text
""))
, (BaseType
NullPtr, (Text
"Dn", Text
"std::nullptr_t", Text
""))
, (BaseType
N1168FixedPointAccum, (Text
"DA", Text
"T _Accum", Text
""))
, (BaseType
N1168FixedPointAccumSat, (Text
"DS DA", Text
"_Sat T _Accum", Text
""))
, (BaseType
N1168FixedPointFract, (Text
"DR", Text
"T _Fract", Text
""))
, (BaseType
N1168FixedPointFractSat, (Text
"DS DR", Text
"_Sat T _Fract", Text
""))
]
opTable :: [ (Operator, (Text, Text)) ]
opTable :: [(Operator, (Text, Text))]
opTable =
[ (Operator
OpNew, (Text
"nw", Text
" new"))
, (Operator
OpNewArr, (Text
"na", Text
" new[]"))
, (Operator
OpDel, (Text
"dl", Text
" delete"))
, (Operator
OpDelArr, (Text
"da", Text
" delete[]"))
, (Operator
OpCoAwait, (Text
"aw", Text
" co_await"))
, (Operator
OpPositive, (Text
"ps", Text
"+"))
, (Operator
OpNegative, (Text
"ng", Text
"-"))
, (Operator
OpAddress, (Text
"ad", Text
"&"))
, (Operator
OpDeReference, (Text
"de", Text
"*"))
, (Operator
OpComplement, (Text
"co", Text
"~"))
, (Operator
OpPlus, (Text
"pl", Text
"+"))
, (Operator
OpMinus, (Text
"mi", Text
"-"))
, (Operator
OpMultiply, (Text
"ml", Text
"*"))
, (Operator
OpDivide, (Text
"dv", Text
"/"))
, (Operator
OpRemainder, (Text
"rm", Text
"%"))
, (Operator
OpAnd, (Text
"an", Text
"&"))
, (Operator
OpOr, (Text
"or", Text
"|"))
, (Operator
OpXOR, (Text
"eo", Text
"^"))
, (Operator
OpAssign, (Text
"aS", Text
"="))
, (Operator
OpAssignPlus, (Text
"pL", Text
"+="))
, (Operator
OpAssignMinus, (Text
"mI", Text
"-="))
, (Operator
OpAssignMul, (Text
"mL", Text
"*="))
, (Operator
OpAssignDiv, (Text
"dV", Text
"/="))
, (Operator
OpAssignRem, (Text
"rM", Text
"%="))
, (Operator
OpAssignAnd, (Text
"aN", Text
"&="))
, (Operator
OpAssignOr, (Text
"oR", Text
"|="))
, (Operator
OpAssignXOR, (Text
"eO", Text
"^="))
, (Operator
OpLeftShift, (Text
"ls", Text
"<<"))
, (Operator
OpRightShift, (Text
"rs", Text
">>"))
, (Operator
OpAssignShL, (Text
"lS", Text
"<<="))
, (Operator
OpAssignShR, (Text
"rS", Text
">>="))
, (Operator
OpEq, (Text
"eq", Text
"=="))
, (Operator
OpNotEq, (Text
"ne", Text
"!="))
, (Operator
OpLT, (Text
"lt", Text
"<"))
, (Operator
OpGT, (Text
"gt", Text
">"))
, (Operator
OpLTE, (Text
"le", Text
"<="))
, (Operator
OpGTE, (Text
"ge", Text
">="))
, (Operator
OpSpan, (Text
"ss", Text
"<=>"))
, (Operator
OpNot, (Text
"nt", Text
"!"))
, (Operator
OpLogicalAnd, (Text
"aa", Text
"&&"))
, (Operator
OpLogicalOr, (Text
"oo", Text
"||"))
, (Operator
OpPlusPlus, (Text
"pp", Text
"++"))
, (Operator
OpMinusMinus, (Text
"mm", Text
"--"))
, (Operator
OpComma, (Text
"cm", Text
","))
, (Operator
OpPointStar, (Text
"pm", Text
"->*"))
, (Operator
OpPoint, (Text
"pt", Text
"->"))
, (Operator
OpCall, (Text
"cl", Text
"()"))
, (Operator
OpIndex, (Text
"ix", Text
"[]"))
, (Operator
OpQuestion, (Text
"qu", Text
"?"))
, (Operator
OpSizeOfType, (Text
"st", Text
" sizeof"))
, (Operator
OpAlignOfType, (Text
"at", Text
" alignof"))
, (Operator
OpSizeOfExpr, (Text
"sz", Text
" sizeof"))
, (Operator
OpAlignOfExpr, (Text
"az", Text
" alignof"))
]
data SubsCandidate = SC_Type Type_
| SC_UQName Bool UnqualifiedName
| SC_Prefix Prefix
| SC_TemplatePrefix TemplatePrefix
deriving (SubsCandidate -> SubsCandidate -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: SubsCandidate -> SubsCandidate -> Bool
$c/= :: SubsCandidate -> SubsCandidate -> Bool
== :: SubsCandidate -> SubsCandidate -> Bool
$c== :: SubsCandidate -> SubsCandidate -> Bool
Eq, Int -> SubsCandidate -> ShowS
[SubsCandidate] -> ShowS
SubsCandidate -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [SubsCandidate] -> ShowS
$cshowList :: [SubsCandidate] -> ShowS
show :: SubsCandidate -> String
$cshow :: SubsCandidate -> String
showsPrec :: Int -> SubsCandidate -> ShowS
$cshowsPrec :: Int -> SubsCandidate -> ShowS
Show)