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.CRules.Types.TypeKind

Description

The types of C language

Synopsis

TypeKind data type

data StructMember i Source #

The type and offset value of a data member.

Constructors

StructMember

StructMember constructor

Fields

Instances

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

Defined in Htcc.CRules.Types.TypeKind

(Show i, Read i, Ord i) => Read (StructMember i) Source # 
Instance details

Defined in Htcc.CRules.Types.TypeKind

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

Defined in Htcc.CRules.Types.TypeKind

Generic (StructMember i) Source # 
Instance details

Defined in Htcc.CRules.Types.TypeKind

Associated Types

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

Methods

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

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

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

Defined in Htcc.CRules.Types.TypeKind

Methods

rnf :: StructMember i -> () #

type Rep (StructMember i) Source # 
Instance details

Defined in Htcc.CRules.Types.TypeKind

type Rep (StructMember i) = D1 ('MetaData "StructMember" "Htcc.CRules.Types.TypeKind" "htcc-0.0.0.1-I8tHuOdNzco4DzUthNftqr" 'False) (C1 ('MetaCons "StructMember" 'PrefixI 'True) (S1 ('MetaSel ('Just "smType") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (TypeKind i)) :*: S1 ('MetaSel ('Just "smOffset") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Natural)))

data TypeKind i Source #

The kinds of types in C language.

Constructors

CTInt

The type int as C language

CTChar

The type char as C language

CTSigned (TypeKind i)

The type signed as C language

CTShort (TypeKind i)

The type short as C language

CTLong (TypeKind i)

The type long as C language

CTBool

The type _Bool as C language

CTVoid

The type void as C language

CTPtr (TypeKind i)

The pointer type of TypeKind

CTArray Natural (TypeKind i)

The array type

CTEnum (TypeKind i) (Map Text i)

The enum, has its underlying type and a map

CTStruct (Map Text (StructMember i))

The struct, has its members and their names.

CTIncomplete (Incomplete i)

The incomplete type.

CTUndef

Undefined type

Instances

Instances details
IncompleteBase TypeKind Source # 
Instance details

Defined in Htcc.CRules.Types.TypeKind

TypeKindBase TypeKind Source # 
Instance details

Defined in Htcc.CRules.Types.TypeKind

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

Defined in Htcc.CRules.Types.TypeKind

Methods

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

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

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

Defined in Htcc.CRules.Types.TypeKind

Methods

compare :: TypeKind i -> TypeKind i -> Ordering #

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

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

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

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

max :: TypeKind i -> TypeKind i -> TypeKind i #

min :: TypeKind i -> TypeKind i -> TypeKind i #

(Show i, Read i, Ord i) => Read (TypeKind i) Source # 
Instance details

Defined in Htcc.CRules.Types.TypeKind

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

Defined in Htcc.CRules.Types.TypeKind

Methods

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

show :: TypeKind i -> String #

showList :: [TypeKind i] -> ShowS #

Generic (TypeKind i) Source # 
Instance details

Defined in Htcc.CRules.Types.TypeKind

Associated Types

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

Methods

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

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

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

Defined in Htcc.CRules.Types.TypeKind

Methods

rnf :: TypeKind i -> () #

Ord i => CType (TypeKind i) Source # 
Instance details

Defined in Htcc.CRules.Types.TypeKind

type Rep (TypeKind i) Source # 
Instance details

Defined in Htcc.CRules.Types.TypeKind

type Rep (TypeKind i) = D1 ('MetaData "TypeKind" "Htcc.CRules.Types.TypeKind" "htcc-0.0.0.1-I8tHuOdNzco4DzUthNftqr" 'False) (((C1 ('MetaCons "CTInt" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "CTChar" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "CTSigned" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (TypeKind i))))) :+: (C1 ('MetaCons "CTShort" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (TypeKind i))) :+: (C1 ('MetaCons "CTLong" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (TypeKind i))) :+: C1 ('MetaCons "CTBool" 'PrefixI 'False) (U1 :: Type -> Type)))) :+: ((C1 ('MetaCons "CTVoid" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "CTPtr" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (TypeKind i))) :+: C1 ('MetaCons "CTArray" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Natural) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (TypeKind i))))) :+: ((C1 ('MetaCons "CTEnum" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (TypeKind i)) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Map Text i))) :+: C1 ('MetaCons "CTStruct" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Map Text (StructMember i))))) :+: (C1 ('MetaCons "CTIncomplete" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Incomplete i))) :+: C1 ('MetaCons "CTUndef" 'PrefixI 'False) (U1 :: Type -> Type)))))

data Incomplete i Source #

The type representing an incomplete type

Constructors

IncompleteArray (TypeKind i)

incomplete array, it has a base type.

IncompleteStruct Text

incomplete struct, it has a tag name.

Instances

Instances details
IncompleteBase Incomplete Source # 
Instance details

Defined in Htcc.CRules.Types.TypeKind

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

Defined in Htcc.CRules.Types.TypeKind

Methods

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

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

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

Defined in Htcc.CRules.Types.TypeKind

Generic (Incomplete i) Source # 
Instance details

Defined in Htcc.CRules.Types.TypeKind

Associated Types

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

Methods

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

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

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

Defined in Htcc.CRules.Types.TypeKind

Methods

rnf :: Incomplete i -> () #

type Rep (Incomplete i) Source # 
Instance details

Defined in Htcc.CRules.Types.TypeKind

type Rep (Incomplete i) = D1 ('MetaData "Incomplete" "Htcc.CRules.Types.TypeKind" "htcc-0.0.0.1-I8tHuOdNzco4DzUthNftqr" 'False) (C1 ('MetaCons "IncompleteArray" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (TypeKind i))) :+: C1 ('MetaCons "IncompleteStruct" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Text)))

Type classes that can be converted to TypeKind

class TypeKindBase a where Source #

Class to a type based on TypeKind.

Methods

isCTArray :: a i -> Bool Source #

isCTArray returns True when the given argument is CTArray. Otherwise, returns False

isArray :: a i -> Bool Source #

isArray return True when the given argument is CTArray or IncompleteArray Otherwise, returns False

isCTStruct :: a i -> Bool Source #

isCTStruct returns True when the given argument is CTStruct. Otherwise, returns False

isCTUndef :: a i -> Bool Source #

isCTUndef returns True when the given argument is CTUndef. Otherwise, returns False

isCTIncomplete :: a i -> Bool Source #

isCTIncomplete returns True when the given argument is CTIncomplete.

makeCTArray :: [Natural] -> a i -> a i Source #

makeCTArray retunrs a multidimensional array based on the arguments (list of each dimension). e.g.:

>>> makeCTArray [1, 2] CTInt
int[1][2]
>>> makeCTArray [1, 2] (CTArray 2 CTInt)
int[2][1][2]

concatCTArray :: Ord i => a i -> a i -> Maybe (a i) Source #

Only if both arguments is CTArray, concatCTArray returns a new multidimensional array by conbining the types of multidimensional arrays as follows.

>>> makeCTArray [1, 2] CTInt `concatCTArray` makeCTArray [3, 4] CTInt
Just int[1][2][3][4]
>>> CTInt `concatCTArray` CTArray 2 CTInt
Nothing

toTypeKind :: a i -> TypeKind i Source #

Convert to TypeKind.

mapTypeKind :: (TypeKind i -> TypeKind j) -> a i -> a j Source #

Application to TypeKind.

class IncompleteBase a where Source #

A class requesting a type that represents an incomplete type.

Methods

isIncompleteArray :: a i -> Bool Source #

When the given argument is incomplete array, isIncompleteArray returns True, otherwise False.

isIncompleteStruct :: a i -> Bool Source #

When the given argument is incmoplete struct, isIncompleteStruct returns True, otherwise False.

fromIncompleteStruct :: a i -> Maybe Text Source #

Extract the tag name from IncompleteStruct. If not IncompleteStruct, Nothing is retunred.

fromIncompleteArray :: a i -> Maybe (TypeKind i) Source #

Extract the type of array from IncompleteArray. If not IncompleteArray, Nothing is retunred.

isValidIncomplete :: Ord i => a i -> Bool Source #

Returns True if the incomplete type is temporarily valid at the time of declaration. Otherwise returns False.

Instances

Instances details
IncompleteBase TypeKind Source # 
Instance details

Defined in Htcc.CRules.Types.TypeKind

IncompleteBase Incomplete Source # 
Instance details

Defined in Htcc.CRules.Types.TypeKind

IncompleteBase StorageClass Source # 
Instance details

Defined in Htcc.CRules.Types.StorageClass

IncompleteBase ATKind Source # 
Instance details

Defined in Htcc.Parser.AST.Core

Lookup functions

lookupMember :: Text -> TypeKind i -> Maybe (StructMember i) Source #

lookupMember search the specified member by its name from CTStruct.

Utilities of C type

alignas :: (Bits a, Num a, Enum a) => a -> a -> a Source #

alignas align to n.

data Desg i Source #

The type of designator

Constructors

DesgIdx i

index type

DesgMem (StructMember i)

struct member type

Instances

Instances details
(Enum i, Integral i) => Enum (Desg i) Source # 
Instance details

Defined in Htcc.CRules.Types.TypeKind

Methods

succ :: Desg i -> Desg i #

pred :: Desg i -> Desg i #

toEnum :: Int -> Desg i #

fromEnum :: Desg i -> Int #

enumFrom :: Desg i -> [Desg i] #

enumFromThen :: Desg i -> Desg i -> [Desg i] #

enumFromTo :: Desg i -> Desg i -> [Desg i] #

enumFromThenTo :: Desg i -> Desg i -> Desg i -> [Desg i] #

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

Defined in Htcc.CRules.Types.TypeKind

Methods

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

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

(Eq i, Ord i, Integral i) => Ord (Desg i) Source # 
Instance details

Defined in Htcc.CRules.Types.TypeKind

Methods

compare :: Desg i -> Desg i -> Ordering #

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

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

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

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

max :: Desg i -> Desg i -> Desg i #

min :: Desg i -> Desg i -> Desg i #

accessibleIndices :: Integral i => TypeKind i -> [[Desg i]] Source #

If the given argument is CTArray, it returns a list of accessible indexes of the array. Othrewise returns empty list.