ethereum-analyzer-3.2.0: A Ethereum contract analyzer.

Safe HaskellNone
LanguageHaskell98

Ethereum.Analyzer.Solidity

Documentation

data SolNode Source #

Instances

Eq SolNode Source # 

Methods

(==) :: SolNode -> SolNode -> Bool #

(/=) :: SolNode -> SolNode -> Bool #

Show SolNode Source # 
Generic SolNode Source # 

Associated Types

type Rep SolNode :: * -> * #

Methods

from :: SolNode -> Rep SolNode x #

to :: Rep SolNode x -> SolNode #

FromJSON SolNode Source # 
ToJSON SolNode Source # 
Pretty SolNode Source # 

Methods

pretty :: SolNode -> Doc #

prettyList :: [SolNode] -> Doc #

type Rep SolNode Source # 
type Rep SolNode = D1 (MetaData "SolNode" "Ethereum.Analyzer.Solidity.AstJson" "ethereum-analyzer-3.2.0-8ovrKRGGMLI3GThPL7l3Fk" False) (C1 (MetaCons "SolNode" PrefixI True) ((:*:) ((:*:) ((:*:) ((:*:) (S1 (MetaSel (Just Symbol "name") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe Text))) (S1 (MetaSel (Just Symbol "_id") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe Int)))) ((:*:) (S1 (MetaSel (Just Symbol "_type") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe Text))) ((:*:) (S1 (MetaSel (Just Symbol "_AST") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe SolNode))) (S1 (MetaSel (Just Symbol "attributes") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe SolNode)))))) ((:*:) ((:*:) (S1 (MetaSel (Just Symbol "constant") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe Bool))) ((:*:) (S1 (MetaSel (Just Symbol "components") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe [Maybe SolNode]))) (S1 (MetaSel (Just Symbol "fullyImplemented") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe Bool))))) ((:*:) (S1 (MetaSel (Just Symbol "hexvalue") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe Text))) ((:*:) (S1 (MetaSel (Just Symbol "isLibrary") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe Bool))) (S1 (MetaSel (Just Symbol "linearizedBaseContracts") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe [Int]))))))) ((:*:) ((:*:) ((:*:) (S1 (MetaSel (Just Symbol "literals") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe [Text]))) ((:*:) (S1 (MetaSel (Just Symbol "member_name") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe Text))) (S1 (MetaSel (Just Symbol "operator") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe Text))))) ((:*:) (S1 (MetaSel (Just Symbol "payable") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe Bool))) ((:*:) (S1 (MetaSel (Just Symbol "src") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe Text))) (S1 (MetaSel (Just Symbol "storageLocation") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe Text)))))) ((:*:) ((:*:) (S1 (MetaSel (Just Symbol "subdenomination") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe Text))) ((:*:) (S1 (MetaSel (Just Symbol "token") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe Text))) (S1 (MetaSel (Just Symbol "type_conversion") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe Bool))))) ((:*:) (S1 (MetaSel (Just Symbol "value") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe Text))) ((:*:) (S1 (MetaSel (Just Symbol "visibility") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe Text))) (S1 (MetaSel (Just Symbol "children") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe [SolNode])))))))))

data HFunDefinition Source #

Constructors

HFunDefinition 

Fields

data Contract Source #

Constructors

Contract 

Instances

Eq Contract Source # 
Show Contract Source # 
Generic Contract Source # 

Associated Types

type Rep Contract :: * -> * #

Methods

from :: Contract -> Rep Contract x #

to :: Rep Contract x -> Contract #

Out Contract Source # 

Methods

docPrec :: Int -> Contract -> Doc #

doc :: Contract -> Doc #

docList :: [Contract] -> Doc #

type Rep Contract Source # 
type Rep Contract = D1 (MetaData "Contract" "Ethereum.Analyzer.Solidity.Simple" "ethereum-analyzer-3.2.0-8ovrKRGGMLI3GThPL7l3Fk" False) (C1 (MetaCons "Contract" PrefixI True) ((:*:) (S1 (MetaSel (Just Symbol "cName") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Text)) ((:*:) (S1 (MetaSel (Just Symbol "cStateVars") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 [VarDecl])) (S1 (MetaSel (Just Symbol "cFunctions") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 [FunDefinition])))))

data VarDecl Source #

Constructors

VarDecl 

Fields

Instances

Eq VarDecl Source # 

Methods

(==) :: VarDecl -> VarDecl -> Bool #

(/=) :: VarDecl -> VarDecl -> Bool #

Show VarDecl Source # 
Generic VarDecl Source # 

Associated Types

type Rep VarDecl :: * -> * #

Methods

from :: VarDecl -> Rep VarDecl x #

to :: Rep VarDecl x -> VarDecl #

Out VarDecl Source # 

Methods

docPrec :: Int -> VarDecl -> Doc #

doc :: VarDecl -> Doc #

docList :: [VarDecl] -> Doc #

type Rep VarDecl Source # 
type Rep VarDecl = D1 (MetaData "VarDecl" "Ethereum.Analyzer.Solidity.Simple" "ethereum-analyzer-3.2.0-8ovrKRGGMLI3GThPL7l3Fk" False) (C1 (MetaCons "VarDecl" PrefixI True) ((:*:) (S1 (MetaSel (Just Symbol "vName") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Idfr)) (S1 (MetaSel (Just Symbol "vType") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 VarType))))

newtype Idfr Source #

Constructors

Idfr 

Fields

Instances

Eq Idfr Source # 

Methods

(==) :: Idfr -> Idfr -> Bool #

(/=) :: Idfr -> Idfr -> Bool #

Show Idfr Source # 

Methods

showsPrec :: Int -> Idfr -> ShowS #

show :: Idfr -> String #

showList :: [Idfr] -> ShowS #

Generic Idfr Source # 

Associated Types

type Rep Idfr :: * -> * #

Methods

from :: Idfr -> Rep Idfr x #

to :: Rep Idfr x -> Idfr #

Out Idfr Source # 

Methods

docPrec :: Int -> Idfr -> Doc #

doc :: Idfr -> Doc #

docList :: [Idfr] -> Doc #

type Rep Idfr Source # 
type Rep Idfr = D1 (MetaData "Idfr" "Ethereum.Analyzer.Solidity.Simple" "ethereum-analyzer-3.2.0-8ovrKRGGMLI3GThPL7l3Fk" True) (C1 (MetaCons "Idfr" PrefixI True) (S1 (MetaSel (Just Symbol "unIdfr") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Text)))

data LValue Source #

Constructors

JustId Idfr 
Index 

Fields

Member 

Fields

Tuple [LValue] 

data Statement Source #

Instances

Eq Statement Source # 
Show Statement Source # 
Generic Statement Source # 

Associated Types

type Rep Statement :: * -> * #

Out Statement Source # 

Methods

docPrec :: Int -> Statement -> Doc #

doc :: Statement -> Doc #

docList :: [Statement] -> Doc #

type Rep Statement Source # 
type Rep Statement = D1 (MetaData "Statement" "Ethereum.Analyzer.Solidity.Simple" "ethereum-analyzer-3.2.0-8ovrKRGGMLI3GThPL7l3Fk" False) ((:+:) ((:+:) ((:+:) (C1 (MetaCons "StLocalVarDecl" PrefixI False) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 VarDecl))) (C1 (MetaCons "StAssign" PrefixI False) ((:*:) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 LValue)) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Expression))))) ((:+:) (C1 (MetaCons "StIf" PrefixI False) ((:*:) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 LValue)) ((:*:) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 [Statement])) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 [Statement]))))) ((:+:) (C1 (MetaCons "StLoop" PrefixI False) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 [Statement]))) (C1 (MetaCons "StBreak" PrefixI False) U1)))) ((:+:) ((:+:) (C1 (MetaCons "StContinue" PrefixI False) U1) (C1 (MetaCons "StReturn" PrefixI False) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 [LValue])))) ((:+:) (C1 (MetaCons "StDelete" PrefixI False) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 LValue))) ((:+:) (C1 (MetaCons "StTodo" PrefixI False) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Text))) (C1 (MetaCons "StThrow" PrefixI False) U1)))))

data Expression Source #

Instances

Eq Expression Source # 
Show Expression Source # 
Generic Expression Source # 

Associated Types

type Rep Expression :: * -> * #

Out Expression Source # 
type Rep Expression Source #