htcc-0.0.0.1: The full scratch implementation of tiny C compiler (x86_64)
Copyright(c) roki 2019
LicenseMIT
Maintainerfalgon53@yahoo.co.jp
Stabilityexperimental
PortabilityPOSIX
Safe HaskellNone
LanguageHaskell2010

Htcc.Parser.ConstructionData.Scope.Var

Description

The Data type of variables and its utilities used in parsing

Synopsis

The classes

class Var a where Source #

The type class of the type representing the variable

Methods

vtype :: a i -> StorageClass i Source #

vtype returns the type of the variable

Instances

Instances details
Var Literal Source # 
Instance details

Defined in Htcc.Parser.ConstructionData.Scope.Var

Methods

vtype :: Literal i -> StorageClass i Source #

Var LVar Source # 
Instance details

Defined in Htcc.Parser.ConstructionData.Scope.Var

Methods

vtype :: LVar i -> StorageClass i Source #

Var GVar Source # 
Instance details

Defined in Htcc.Parser.ConstructionData.Scope.Var

Methods

vtype :: GVar i -> StorageClass i Source #

The data type

type SomeVars v = Map Text v Source #

The type of variables

data GVarInitWith i Source #

The informations type about initial value of the global variable

Instances

Instances details
Eq i => Eq (GVarInitWith i) Source # 
Instance details

Defined in Htcc.Parser.ConstructionData.Scope.Var

Ord i => Ord (GVarInitWith i) Source # 
Instance details

Defined in Htcc.Parser.ConstructionData.Scope.Var

Show i => Show (GVarInitWith i) Source # 
Instance details

Defined in Htcc.Parser.ConstructionData.Scope.Var

Generic (GVarInitWith i) Source # 
Instance details

Defined in Htcc.Parser.ConstructionData.Scope.Var

Associated Types

type Rep (GVarInitWith i) :: Type -> Type #

Methods

from :: GVarInitWith i -> Rep (GVarInitWith i) x #

to :: Rep (GVarInitWith i) x -> GVarInitWith i #

NFData i => NFData (GVarInitWith i) Source # 
Instance details

Defined in Htcc.Parser.ConstructionData.Scope.Var

Methods

rnf :: GVarInitWith i -> () #

type Rep (GVarInitWith i) Source # 
Instance details

Defined in Htcc.Parser.ConstructionData.Scope.Var

type Rep (GVarInitWith i) = D1 ('MetaData "GVarInitWith" "Htcc.Parser.ConstructionData.Scope.Var" "htcc-0.0.0.1-I8tHuOdNzco4DzUthNftqr" 'False) (C1 ('MetaCons "GVarInitWithZero" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "GVarInitWithOG" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Text)) :+: C1 ('MetaCons "GVarInitWithVal" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 i))))

data GVar i Source #

The data type of the global variable

Constructors

GVar

The constructor of the global variable

Fields

Instances

Instances details
Var GVar Source # 
Instance details

Defined in Htcc.Parser.ConstructionData.Scope.Var

Methods

vtype :: GVar i -> StorageClass i Source #

Eq i => Eq (GVar i) Source # 
Instance details

Defined in Htcc.Parser.ConstructionData.Scope.Var

Methods

(==) :: GVar i -> GVar i -> Bool #

(/=) :: GVar i -> GVar i -> Bool #

Ord i => Ord (GVar i) Source # 
Instance details

Defined in Htcc.Parser.ConstructionData.Scope.Var

Methods

compare :: GVar i -> GVar i -> Ordering #

(<) :: GVar i -> GVar i -> Bool #

(<=) :: GVar i -> GVar i -> Bool #

(>) :: GVar i -> GVar i -> Bool #

(>=) :: GVar i -> GVar i -> Bool #

max :: GVar i -> GVar i -> GVar i #

min :: GVar i -> GVar i -> GVar i #

Show i => Show (GVar i) Source # 
Instance details

Defined in Htcc.Parser.ConstructionData.Scope.Var

Methods

showsPrec :: Int -> GVar i -> ShowS #

show :: GVar i -> String #

showList :: [GVar i] -> ShowS #

Generic (GVar i) Source # 
Instance details

Defined in Htcc.Parser.ConstructionData.Scope.Var

Associated Types

type Rep (GVar i) :: Type -> Type #

Methods

from :: GVar i -> Rep (GVar i) x #

to :: Rep (GVar i) x -> GVar i #

NFData i => NFData (GVar i) Source # 
Instance details

Defined in Htcc.Parser.ConstructionData.Scope.Var

Methods

rnf :: GVar i -> () #

ManagedScope (GVar i) Source # 
Instance details

Defined in Htcc.Parser.ConstructionData.Scope.Var

Methods

lookup :: Text -> Map Text (GVar i) -> Maybe (GVar i) Source #

fallBack :: Map Text (GVar i) -> Map Text (GVar i) -> Map Text (GVar i) Source #

initial :: Map Text (GVar i) Source #

type Rep (GVar i) Source # 
Instance details

Defined in Htcc.Parser.ConstructionData.Scope.Var

type Rep (GVar i) = D1 ('MetaData "GVar" "Htcc.Parser.ConstructionData.Scope.Var" "htcc-0.0.0.1-I8tHuOdNzco4DzUthNftqr" 'False) (C1 ('MetaCons "GVar" 'PrefixI 'True) (S1 ('MetaSel ('Just "gvtype") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (StorageClass i)) :*: S1 ('MetaSel ('Just "initWith") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (GVarInitWith i))))

data LVar a Source #

The data type of local variable

Constructors

LVar

The constructor of local variable

Fields

Instances

Instances details
Treealizable LVar Source # 
Instance details

Defined in Htcc.Parser.ConstructionData.Scope.Var

Methods

treealize :: LVar i -> ATree i Source #

Var LVar Source # 
Instance details

Defined in Htcc.Parser.ConstructionData.Scope.Var

Methods

vtype :: LVar i -> StorageClass i Source #

Eq a => Eq (LVar a) Source # 
Instance details

Defined in Htcc.Parser.ConstructionData.Scope.Var

Methods

(==) :: LVar a -> LVar a -> Bool #

(/=) :: LVar a -> LVar a -> Bool #

Ord a => Ord (LVar a) Source # 
Instance details

Defined in Htcc.Parser.ConstructionData.Scope.Var

Methods

compare :: LVar a -> LVar a -> Ordering #

(<) :: LVar a -> LVar a -> Bool #

(<=) :: LVar a -> LVar a -> Bool #

(>) :: LVar a -> LVar a -> Bool #

(>=) :: LVar a -> LVar a -> Bool #

max :: LVar a -> LVar a -> LVar a #

min :: LVar a -> LVar a -> LVar a #

Show a => Show (LVar a) Source # 
Instance details

Defined in Htcc.Parser.ConstructionData.Scope.Var

Methods

showsPrec :: Int -> LVar a -> ShowS #

show :: LVar a -> String #

showList :: [LVar a] -> ShowS #

Generic (LVar a) Source # 
Instance details

Defined in Htcc.Parser.ConstructionData.Scope.Var

Associated Types

type Rep (LVar a) :: Type -> Type #

Methods

from :: LVar a -> Rep (LVar a) x #

to :: Rep (LVar a) x -> LVar a #

NFData a => NFData (LVar a) Source # 
Instance details

Defined in Htcc.Parser.ConstructionData.Scope.Var

Methods

rnf :: LVar a -> () #

ManagedScope (LVar a) Source # 
Instance details

Defined in Htcc.Parser.ConstructionData.Scope.Var

Methods

lookup :: Text -> Map Text (LVar a) -> Maybe (LVar a) Source #

fallBack :: Map Text (LVar a) -> Map Text (LVar a) -> Map Text (LVar a) Source #

initial :: Map Text (LVar a) Source #

type Rep (LVar a) Source # 
Instance details

Defined in Htcc.Parser.ConstructionData.Scope.Var

type Rep (LVar a) = D1 ('MetaData "LVar" "Htcc.Parser.ConstructionData.Scope.Var" "htcc-0.0.0.1-I8tHuOdNzco4DzUthNftqr" 'False) (C1 ('MetaCons "LVar" 'PrefixI 'True) (S1 ('MetaSel ('Just "lvtype") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (StorageClass a)) :*: (S1 ('MetaSel ('Just "rbpOffset") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 a) :*: S1 ('MetaSel ('Just "nestDepth") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Natural))))

data Literal a Source #

The literal

Constructors

Literal

The literal constructor

Fields

Instances

Instances details
Var Literal Source # 
Instance details

Defined in Htcc.Parser.ConstructionData.Scope.Var

Methods

vtype :: Literal i -> StorageClass i Source #

Eq a => Eq (Literal a) Source # 
Instance details

Defined in Htcc.Parser.ConstructionData.Scope.Var

Methods

(==) :: Literal a -> Literal a -> Bool #

(/=) :: Literal a -> Literal a -> Bool #

Show a => Show (Literal a) Source # 
Instance details

Defined in Htcc.Parser.ConstructionData.Scope.Var

Methods

showsPrec :: Int -> Literal a -> ShowS #

show :: Literal a -> String #

showList :: [Literal a] -> ShowS #

Generic (Literal a) Source # 
Instance details

Defined in Htcc.Parser.ConstructionData.Scope.Var

Associated Types

type Rep (Literal a) :: Type -> Type #

Methods

from :: Literal a -> Rep (Literal a) x #

to :: Rep (Literal a) x -> Literal a #

NFData a => NFData (Literal a) Source # 
Instance details

Defined in Htcc.Parser.ConstructionData.Scope.Var

Methods

rnf :: Literal a -> () #

type Rep (Literal a) Source # 
Instance details

Defined in Htcc.Parser.ConstructionData.Scope.Var

type Rep (Literal a) = D1 ('MetaData "Literal" "Htcc.Parser.ConstructionData.Scope.Var" "htcc-0.0.0.1-I8tHuOdNzco4DzUthNftqr" 'False) (C1 ('MetaCons "Literal" 'PrefixI 'True) (S1 ('MetaSel ('Just "litype") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (StorageClass a)) :*: (S1 ('MetaSel ('Just "ln") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Natural) :*: S1 ('MetaSel ('Just "lcts") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 ByteString))))

type GlobalVars a = SomeVars (GVar a) Source #

The type of global variables

type LocalVars a = SomeVars (LVar a) Source #

The type of global variables

type Literals a = [Literal a] Source #

The type of literals

data Vars a Source #

The data type of local variables

Constructors

Vars

The constructor of variables

Fields

Instances

Instances details
Show a => Show (Vars a) Source # 
Instance details

Defined in Htcc.Parser.ConstructionData.Scope.Var

Methods

showsPrec :: Int -> Vars a -> ShowS #

show :: Vars a -> String #

showList :: [Vars a] -> ShowS #

Generic (Vars a) Source # 
Instance details

Defined in Htcc.Parser.ConstructionData.Scope.Var

Associated Types

type Rep (Vars a) :: Type -> Type #

Methods

from :: Vars a -> Rep (Vars a) x #

to :: Rep (Vars a) x -> Vars a #

NFData a => NFData (Vars a) Source # 
Instance details

Defined in Htcc.Parser.ConstructionData.Scope.Var

Methods

rnf :: Vars a -> () #

Generic1 Vars Source # 
Instance details

Defined in Htcc.Parser.ConstructionData.Scope.Var

Associated Types

type Rep1 Vars :: k -> Type #

Methods

from1 :: forall (a :: k). Vars a -> Rep1 Vars a #

to1 :: forall (a :: k). Rep1 Vars a -> Vars a #

type Rep (Vars a) Source # 
Instance details

Defined in Htcc.Parser.ConstructionData.Scope.Var

type Rep (Vars a) = D1 ('MetaData "Vars" "Htcc.Parser.ConstructionData.Scope.Var" "htcc-0.0.0.1-I8tHuOdNzco4DzUthNftqr" 'False) (C1 ('MetaCons "Vars" 'PrefixI 'True) (S1 ('MetaSel ('Just "globals") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (GlobalVars a)) :*: (S1 ('MetaSel ('Just "locals") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (LocalVars a)) :*: S1 ('MetaSel ('Just "literals") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Literals a)))))
type Rep1 Vars Source # 
Instance details

Defined in Htcc.Parser.ConstructionData.Scope.Var

type Rep1 Vars = D1 ('MetaData "Vars" "Htcc.Parser.ConstructionData.Scope.Var" "htcc-0.0.0.1-I8tHuOdNzco4DzUthNftqr" 'False) (C1 ('MetaCons "Vars" 'PrefixI 'True) (S1 ('MetaSel ('Just "globals") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Map Text :.: Rec1 GVar) :*: (S1 ('MetaSel ('Just "locals") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Map Text :.: Rec1 LVar) :*: S1 ('MetaSel ('Just "literals") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) ([] :.: Rec1 Literal))))

Functions for adding and searching for variables and literals

lookupLVar :: Text -> Vars a -> Maybe (LVar a) Source #

Search for a local variable with a given name

lookupGVar :: Text -> Vars a -> Maybe (GVar a) Source #

Search for a global variable with a given name

lookupVar :: Text -> Vars a -> Maybe (Either (GVar a) (LVar a)) Source #

First, search for local variables, and if not found, search for global variables. If nothing is found, Nothing is returned

addLVar :: (Integral i, Bits i) => Natural -> StorageClass i -> TokenLC i -> Vars i -> Either (ASTError i) (ATree i, Vars i) Source #

If the specified token is TKIdent and the local variable does not exist in the list, addLVar adds a new local variable to the list, constructs a pair with the node representing the variable, wraps it in Right and return it. Otherwise, returns an error message and token pair wrapped in Left.

addGVarWith :: Num i => StorageClass i -> TokenLC i -> GVarInitWith i -> Vars i -> Either (ASTError i) (ATree i, Vars i) Source #

If the specified token is TKIdent and the global variable does not exist in the list, addLVar adds a new global variable to the list, constructs a pair with the node representing the variable, wraps it in Right and return it. Otherwise, returns an error message and token pair wrapped in Left.

addGVar :: Num i => StorageClass i -> TokenLC i -> Vars i -> Either (ASTError i) (ATree i, Vars i) Source #

If the specified token is TKIdent and the global variable does not exist in the list, addLVar adds a new global variable that will be initialized by zero to the list, constructs a pair with the node representing the variable, wraps it in Right and return it. Otherwise, returns an error message and token pair wrapped in Left.

addLiteral :: (Ord i, Num i) => StorageClass i -> TokenLC i -> Vars i -> Either (ASTError i) (ATree i, Vars i) Source #

If the specified token is TKString, addLiteral adds a new literal to the list, constructs a pair with the node representing the variable, wraps it in Right and return it. Otherwise, returns an error message and token pair wrapped in Left.

Utilities

initVars :: Vars a Source #

Helper function representing an empty variables

resetLocal :: Vars a -> Vars a Source #

resetLocal initialize the local variable list for Vars

fallBack :: Vars a -> Vars a -> Vars a Source #

Organize variable list state after scoping