language-c-0.8.2: Analysis and generation of C code

Copyright(c) 2007..2008 Duncan Coutts Benedikt Huber
LicenseBSD-style
Maintainerbenedikt.huber@gmail.com
Stabilityexperimental
Portabilityghc
Safe HaskellNone
LanguageHaskell98

Language.C.Syntax.Constants

Contents

Description

This module provides support for representing, checking and exporting c constants, i.e. integral, float, character and string constants.

Synopsis

Utilities

newtype Flags f Source #

Constructors

Flags Integer 
Instances
Eq (Flags f) Source # 
Instance details

Defined in Language.C.Syntax.Constants

Methods

(==) :: Flags f -> Flags f -> Bool Source #

(/=) :: Flags f -> Flags f -> Bool Source #

Data f => Data (Flags f) Source # 
Instance details

Defined in Language.C.Syntax.Constants

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Flags f -> c (Flags f) Source #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (Flags f) Source #

toConstr :: Flags f -> Constr Source #

dataTypeOf :: Flags f -> DataType Source #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (Flags f)) Source #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (Flags f)) Source #

gmapT :: (forall b. Data b => b -> b) -> Flags f -> Flags f Source #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Flags f -> r Source #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Flags f -> r Source #

gmapQ :: (forall d. Data d => d -> u) -> Flags f -> [u] Source #

gmapQi :: Int -> (forall d. Data d => d -> u) -> Flags f -> u Source #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> Flags f -> m (Flags f) Source #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Flags f -> m (Flags f) Source #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Flags f -> m (Flags f) Source #

Ord (Flags f) Source # 
Instance details

Defined in Language.C.Syntax.Constants

Methods

compare :: Flags f -> Flags f -> Ordering Source #

(<) :: Flags f -> Flags f -> Bool Source #

(<=) :: Flags f -> Flags f -> Bool Source #

(>) :: Flags f -> Flags f -> Bool Source #

(>=) :: Flags f -> Flags f -> Bool Source #

max :: Flags f -> Flags f -> Flags f Source #

min :: Flags f -> Flags f -> Flags f Source #

Generic (Flags f) Source # 
Instance details

Defined in Language.C.Syntax.Constants

Associated Types

type Rep (Flags f) :: Type -> Type Source #

Methods

from :: Flags f -> Rep (Flags f) x Source #

to :: Rep (Flags f) x -> Flags f Source #

NFData (Flags f) Source # 
Instance details

Defined in Language.C.Syntax.Constants

Methods

rnf :: Flags f -> () Source #

Generic1 Flags Source # 
Instance details

Defined in Language.C.Syntax.Constants

Associated Types

type Rep1 Flags :: k -> Type Source #

Methods

from1 :: Flags a -> Rep1 Flags a Source #

to1 :: Rep1 Flags a -> Flags a Source #

type Rep (Flags f) Source # 
Instance details

Defined in Language.C.Syntax.Constants

type Rep (Flags f) = D1 (MetaData "Flags" "Language.C.Syntax.Constants" "language-c-0.8.2-9HCycZN4u9o56U8HdwrRHa" True) (C1 (MetaCons "Flags" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Integer)))
type Rep1 Flags Source # 
Instance details

Defined in Language.C.Syntax.Constants

type Rep1 Flags = D1 (MetaData "Flags" "Language.C.Syntax.Constants" "language-c-0.8.2-9HCycZN4u9o56U8HdwrRHa" True) (C1 (MetaCons "Flags" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Integer)))

setFlag :: Enum f => f -> Flags f -> Flags f Source #

clearFlag :: Enum f => f -> Flags f -> Flags f Source #

testFlag :: Enum f => f -> Flags f -> Bool Source #

C char constants (and multi-character character constants)

cChar :: Char -> CChar Source #

construct a character constant from a haskell Char Use cchar_w if you want a wide character constant.

cChar_w :: Char -> CChar Source #

construct a wide chararacter constant

cChars :: String -> Bool -> CChar Source #

create a multi-character character constant

data CChar Source #

C char constants (abstract)

Constructors

CChar !Char !Bool 
CChars [Char] !Bool 
Instances
Eq CChar Source # 
Instance details

Defined in Language.C.Syntax.Constants

Methods

(==) :: CChar -> CChar -> Bool Source #

(/=) :: CChar -> CChar -> Bool Source #

Data CChar Source # 
Instance details

Defined in Language.C.Syntax.Constants

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> CChar -> c CChar Source #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c CChar Source #

toConstr :: CChar -> Constr Source #

dataTypeOf :: CChar -> DataType Source #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c CChar) Source #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c CChar) Source #

gmapT :: (forall b. Data b => b -> b) -> CChar -> CChar Source #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> CChar -> r Source #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> CChar -> r Source #

gmapQ :: (forall d. Data d => d -> u) -> CChar -> [u] Source #

gmapQi :: Int -> (forall d. Data d => d -> u) -> CChar -> u Source #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> CChar -> m CChar Source #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> CChar -> m CChar Source #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> CChar -> m CChar Source #

Ord CChar Source # 
Instance details

Defined in Language.C.Syntax.Constants

Show CChar Source # 
Instance details

Defined in Language.C.Syntax.Constants

Generic CChar Source # 
Instance details

Defined in Language.C.Syntax.Constants

Associated Types

type Rep CChar :: Type -> Type Source #

Methods

from :: CChar -> Rep CChar x Source #

to :: Rep CChar x -> CChar Source #

NFData CChar Source # 
Instance details

Defined in Language.C.Syntax.Constants

Methods

rnf :: CChar -> () Source #

type Rep CChar Source # 
Instance details

Defined in Language.C.Syntax.Constants

getCChar :: CChar -> String Source #

get the haskell representation of a char constant

getCCharAsInt :: CChar -> Integer Source #

get integer value of a C char constant undefined result for multi-char char constants

isWideChar :: CChar -> Bool Source #

return true if the character constant is wide.

showCharConst :: Char -> ShowS Source #

showCharConst c prepends _a_ String representing the C char constant corresponding to c. If necessary uses octal or hexadecimal escape sequences.

C integral constants

data CIntFlag Source #

datatype representing type flags for integers

Instances
Bounded CIntFlag Source # 
Instance details

Defined in Language.C.Syntax.Constants

Enum CIntFlag Source # 
Instance details

Defined in Language.C.Syntax.Constants

Eq CIntFlag Source # 
Instance details

Defined in Language.C.Syntax.Constants

Data CIntFlag Source # 
Instance details

Defined in Language.C.Syntax.Constants

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> CIntFlag -> c CIntFlag Source #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c CIntFlag Source #

toConstr :: CIntFlag -> Constr Source #

dataTypeOf :: CIntFlag -> DataType Source #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c CIntFlag) Source #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c CIntFlag) Source #

gmapT :: (forall b. Data b => b -> b) -> CIntFlag -> CIntFlag Source #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> CIntFlag -> r Source #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> CIntFlag -> r Source #

gmapQ :: (forall d. Data d => d -> u) -> CIntFlag -> [u] Source #

gmapQi :: Int -> (forall d. Data d => d -> u) -> CIntFlag -> u Source #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> CIntFlag -> m CIntFlag Source #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> CIntFlag -> m CIntFlag Source #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> CIntFlag -> m CIntFlag Source #

Ord CIntFlag Source # 
Instance details

Defined in Language.C.Syntax.Constants

Show CIntFlag Source # 
Instance details

Defined in Language.C.Syntax.Constants

Generic CIntFlag Source # 
Instance details

Defined in Language.C.Syntax.Constants

Associated Types

type Rep CIntFlag :: Type -> Type Source #

NFData CIntFlag Source # 
Instance details

Defined in Language.C.Syntax.Constants

Methods

rnf :: CIntFlag -> () Source #

type Rep CIntFlag Source # 
Instance details

Defined in Language.C.Syntax.Constants

type Rep CIntFlag = D1 (MetaData "CIntFlag" "Language.C.Syntax.Constants" "language-c-0.8.2-9HCycZN4u9o56U8HdwrRHa" False) ((C1 (MetaCons "FlagUnsigned" PrefixI False) (U1 :: Type -> Type) :+: C1 (MetaCons "FlagLong" PrefixI False) (U1 :: Type -> Type)) :+: (C1 (MetaCons "FlagLongLong" PrefixI False) (U1 :: Type -> Type) :+: C1 (MetaCons "FlagImag" PrefixI False) (U1 :: Type -> Type)))

data CIntRepr Source #

datatype for memorizing the representation of an integer

Constructors

DecRepr 
HexRepr 
OctalRepr 
Instances
Bounded CIntRepr Source # 
Instance details

Defined in Language.C.Syntax.Constants

Enum CIntRepr Source # 
Instance details

Defined in Language.C.Syntax.Constants

Eq CIntRepr Source # 
Instance details

Defined in Language.C.Syntax.Constants

Data CIntRepr Source # 
Instance details

Defined in Language.C.Syntax.Constants

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> CIntRepr -> c CIntRepr Source #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c CIntRepr Source #

toConstr :: CIntRepr -> Constr Source #

dataTypeOf :: CIntRepr -> DataType Source #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c CIntRepr) Source #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c CIntRepr) Source #

gmapT :: (forall b. Data b => b -> b) -> CIntRepr -> CIntRepr Source #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> CIntRepr -> r Source #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> CIntRepr -> r Source #

gmapQ :: (forall d. Data d => d -> u) -> CIntRepr -> [u] Source #

gmapQi :: Int -> (forall d. Data d => d -> u) -> CIntRepr -> u Source #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> CIntRepr -> m CIntRepr Source #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> CIntRepr -> m CIntRepr Source #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> CIntRepr -> m CIntRepr Source #

Ord CIntRepr Source # 
Instance details

Defined in Language.C.Syntax.Constants

Generic CIntRepr Source # 
Instance details

Defined in Language.C.Syntax.Constants

Associated Types

type Rep CIntRepr :: Type -> Type Source #

NFData CIntRepr Source # 
Instance details

Defined in Language.C.Syntax.Constants

Methods

rnf :: CIntRepr -> () Source #

type Rep CIntRepr Source # 
Instance details

Defined in Language.C.Syntax.Constants

type Rep CIntRepr = D1 (MetaData "CIntRepr" "Language.C.Syntax.Constants" "language-c-0.8.2-9HCycZN4u9o56U8HdwrRHa" False) (C1 (MetaCons "DecRepr" PrefixI False) (U1 :: Type -> Type) :+: (C1 (MetaCons "HexRepr" PrefixI False) (U1 :: Type -> Type) :+: C1 (MetaCons "OctalRepr" PrefixI False) (U1 :: Type -> Type)))

cInteger :: Integer -> CInteger Source #

construct a integer constant (without type flags) from a haskell integer

data CInteger Source #

Instances
Eq CInteger Source # 
Instance details

Defined in Language.C.Syntax.Constants

Data CInteger Source # 
Instance details

Defined in Language.C.Syntax.Constants

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> CInteger -> c CInteger Source #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c CInteger Source #

toConstr :: CInteger -> Constr Source #

dataTypeOf :: CInteger -> DataType Source #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c CInteger) Source #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c CInteger) Source #

gmapT :: (forall b. Data b => b -> b) -> CInteger -> CInteger Source #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> CInteger -> r Source #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> CInteger -> r Source #

gmapQ :: (forall d. Data d => d -> u) -> CInteger -> [u] Source #

gmapQi :: Int -> (forall d. Data d => d -> u) -> CInteger -> u Source #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> CInteger -> m CInteger Source #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> CInteger -> m CInteger Source #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> CInteger -> m CInteger Source #

Ord CInteger Source # 
Instance details

Defined in Language.C.Syntax.Constants

Show CInteger Source # 
Instance details

Defined in Language.C.Syntax.Constants

Generic CInteger Source # 
Instance details

Defined in Language.C.Syntax.Constants

Associated Types

type Rep CInteger :: Type -> Type Source #

NFData CInteger Source # 
Instance details

Defined in Language.C.Syntax.Constants

Methods

rnf :: CInteger -> () Source #

type Rep CInteger Source # 
Instance details

Defined in Language.C.Syntax.Constants

C floating point constants

data CFloat Source #

Floats (represented as strings)

Constructors

CFloat !String 
Instances
Eq CFloat Source # 
Instance details

Defined in Language.C.Syntax.Constants

Data CFloat Source # 
Instance details

Defined in Language.C.Syntax.Constants

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> CFloat -> c CFloat Source #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c CFloat Source #

toConstr :: CFloat -> Constr Source #

dataTypeOf :: CFloat -> DataType Source #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c CFloat) Source #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c CFloat) Source #

gmapT :: (forall b. Data b => b -> b) -> CFloat -> CFloat Source #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> CFloat -> r Source #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> CFloat -> r Source #

gmapQ :: (forall d. Data d => d -> u) -> CFloat -> [u] Source #

gmapQi :: Int -> (forall d. Data d => d -> u) -> CFloat -> u Source #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> CFloat -> m CFloat Source #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> CFloat -> m CFloat Source #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> CFloat -> m CFloat Source #

Ord CFloat Source # 
Instance details

Defined in Language.C.Syntax.Constants

Show CFloat Source # 
Instance details

Defined in Language.C.Syntax.Constants

Generic CFloat Source # 
Instance details

Defined in Language.C.Syntax.Constants

Associated Types

type Rep CFloat :: Type -> Type Source #

NFData CFloat Source # 
Instance details

Defined in Language.C.Syntax.Constants

Methods

rnf :: CFloat -> () Source #

type Rep CFloat Source # 
Instance details

Defined in Language.C.Syntax.Constants

type Rep CFloat = D1 (MetaData "CFloat" "Language.C.Syntax.Constants" "language-c-0.8.2-9HCycZN4u9o56U8HdwrRHa" False) (C1 (MetaCons "CFloat" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 String)))

C string literals

data CString Source #

C String literals

Constructors

CString String Bool 
Instances
Eq CString Source # 
Instance details

Defined in Language.C.Syntax.Constants

Data CString Source # 
Instance details

Defined in Language.C.Syntax.Constants

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> CString -> c CString Source #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c CString Source #

toConstr :: CString -> Constr Source #

dataTypeOf :: CString -> DataType Source #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c CString) Source #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c CString) Source #

gmapT :: (forall b. Data b => b -> b) -> CString -> CString Source #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> CString -> r Source #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> CString -> r Source #

gmapQ :: (forall d. Data d => d -> u) -> CString -> [u] Source #

gmapQi :: Int -> (forall d. Data d => d -> u) -> CString -> u Source #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> CString -> m CString Source #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> CString -> m CString Source #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> CString -> m CString Source #

Ord CString Source # 
Instance details

Defined in Language.C.Syntax.Constants

Show CString Source # 
Instance details

Defined in Language.C.Syntax.Constants

Generic CString Source # 
Instance details

Defined in Language.C.Syntax.Constants

Associated Types

type Rep CString :: Type -> Type Source #

NFData CString Source # 
Instance details

Defined in Language.C.Syntax.Constants

Methods

rnf :: CString -> () Source #

type Rep CString Source # 
Instance details

Defined in Language.C.Syntax.Constants

type Rep CString = D1 (MetaData "CString" "Language.C.Syntax.Constants" "language-c-0.8.2-9HCycZN4u9o56U8HdwrRHa" False) (C1 (MetaCons "CString" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 String) :*: S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Bool)))

showStringLit :: String -> ShowS Source #

showStringLiteral s prepends a String representing the C string literal corresponding to s. If necessary it uses octal or hexadecimal escape sequences.

concatCStrings :: [CString] -> CString Source #

concatenate a list of C string literals

Clang C version literals

data ClangCVersion Source #

Constructors

ClangCVersion !String 
Instances
Eq ClangCVersion Source # 
Instance details

Defined in Language.C.Syntax.Constants

Data ClangCVersion Source # 
Instance details

Defined in Language.C.Syntax.Constants

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> ClangCVersion -> c ClangCVersion Source #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c ClangCVersion Source #

toConstr :: ClangCVersion -> Constr Source #

dataTypeOf :: ClangCVersion -> DataType Source #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c ClangCVersion) Source #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c ClangCVersion) Source #

gmapT :: (forall b. Data b => b -> b) -> ClangCVersion -> ClangCVersion Source #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> ClangCVersion -> r Source #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> ClangCVersion -> r Source #

gmapQ :: (forall d. Data d => d -> u) -> ClangCVersion -> [u] Source #

gmapQi :: Int -> (forall d. Data d => d -> u) -> ClangCVersion -> u Source #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> ClangCVersion -> m ClangCVersion Source #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> ClangCVersion -> m ClangCVersion Source #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> ClangCVersion -> m ClangCVersion Source #

Ord ClangCVersion Source # 
Instance details

Defined in Language.C.Syntax.Constants

Show ClangCVersion Source # 
Instance details

Defined in Language.C.Syntax.Constants