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 #

Constructors

Flags Integer 
Instances
Eq (Flags f) # 
Instance details

Defined in Language.C.Syntax.Constants

Methods

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

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

Data f => Data (Flags f) # 
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) #

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

toConstr :: Flags f -> Constr #

dataTypeOf :: Flags f -> DataType #

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

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

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

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

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

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

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

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

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

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

Ord (Flags f) # 
Instance details

Defined in Language.C.Syntax.Constants

Methods

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

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

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

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

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

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

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

Generic (Flags f) # 
Instance details

Defined in Language.C.Syntax.Constants

Associated Types

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

Methods

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

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

NFData (Flags f) # 
Instance details

Defined in Language.C.Syntax.Constants

Methods

rnf :: Flags f -> () #

Generic1 Flags # 
Instance details

Defined in Language.C.Syntax.Constants

Associated Types

type Rep1 Flags :: k -> Type #

Methods

from1 :: Flags a -> Rep1 Flags a #

to1 :: Rep1 Flags a -> Flags a #

type Rep (Flags f) # 
Instance details

Defined in Language.C.Syntax.Constants

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

Defined in Language.C.Syntax.Constants

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

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

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

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

C char constants (and multi-character character constants)

cChar :: Char -> CChar #

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

cChar_w :: Char -> CChar #

construct a wide chararacter constant

cChars :: String -> Bool -> CChar #

create a multi-character character constant

data CChar #

C char constants (abstract)

Constructors

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

Defined in Language.C.Syntax.Constants

Methods

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

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

Data CChar # 
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 #

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

toConstr :: CChar -> Constr #

dataTypeOf :: CChar -> DataType #

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

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

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

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

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

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

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

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

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

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

Ord CChar # 
Instance details

Defined in Language.C.Syntax.Constants

Methods

compare :: CChar -> CChar -> Ordering #

(<) :: CChar -> CChar -> Bool #

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

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

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

max :: CChar -> CChar -> CChar #

min :: CChar -> CChar -> CChar #

Show CChar # 
Instance details

Defined in Language.C.Syntax.Constants

Methods

showsPrec :: Int -> CChar -> ShowS #

show :: CChar -> String #

showList :: [CChar] -> ShowS #

Generic CChar # 
Instance details

Defined in Language.C.Syntax.Constants

Associated Types

type Rep CChar :: Type -> Type #

Methods

from :: CChar -> Rep CChar x #

to :: Rep CChar x -> CChar #

NFData CChar # 
Instance details

Defined in Language.C.Syntax.Constants

Methods

rnf :: CChar -> () #

type Rep CChar # 
Instance details

Defined in Language.C.Syntax.Constants

getCChar :: CChar -> String #

get the haskell representation of a char constant

getCCharAsInt :: CChar -> Integer #

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

isWideChar :: CChar -> Bool #

return true if the character constant is wide.

showCharConst :: Char -> ShowS #

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 #

datatype representing type flags for integers

Instances
Bounded CIntFlag # 
Instance details

Defined in Language.C.Syntax.Constants

Enum CIntFlag # 
Instance details

Defined in Language.C.Syntax.Constants

Eq CIntFlag # 
Instance details

Defined in Language.C.Syntax.Constants

Data CIntFlag # 
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 #

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

toConstr :: CIntFlag -> Constr #

dataTypeOf :: CIntFlag -> DataType #

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

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

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

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

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

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

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

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

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

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

Ord CIntFlag # 
Instance details

Defined in Language.C.Syntax.Constants

Show CIntFlag # 
Instance details

Defined in Language.C.Syntax.Constants

Generic CIntFlag # 
Instance details

Defined in Language.C.Syntax.Constants

Associated Types

type Rep CIntFlag :: Type -> Type #

Methods

from :: CIntFlag -> Rep CIntFlag x #

to :: Rep CIntFlag x -> CIntFlag #

NFData CIntFlag # 
Instance details

Defined in Language.C.Syntax.Constants

Methods

rnf :: CIntFlag -> () #

type Rep CIntFlag # 
Instance details

Defined in Language.C.Syntax.Constants

type Rep CIntFlag = D1 (MetaData "CIntFlag" "Language.C.Syntax.Constants" "language-c-0.8.2-KO6GGy0fbH5KZxtBHfA7kD" 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 #

datatype for memorizing the representation of an integer

Constructors

DecRepr 
HexRepr 
OctalRepr 
Instances
Bounded CIntRepr # 
Instance details

Defined in Language.C.Syntax.Constants

Enum CIntRepr # 
Instance details

Defined in Language.C.Syntax.Constants

Eq CIntRepr # 
Instance details

Defined in Language.C.Syntax.Constants

Data CIntRepr # 
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 #

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

toConstr :: CIntRepr -> Constr #

dataTypeOf :: CIntRepr -> DataType #

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

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

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

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

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

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

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

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

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

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

Ord CIntRepr # 
Instance details

Defined in Language.C.Syntax.Constants

Generic CIntRepr # 
Instance details

Defined in Language.C.Syntax.Constants

Associated Types

type Rep CIntRepr :: Type -> Type #

Methods

from :: CIntRepr -> Rep CIntRepr x #

to :: Rep CIntRepr x -> CIntRepr #

NFData CIntRepr # 
Instance details

Defined in Language.C.Syntax.Constants

Methods

rnf :: CIntRepr -> () #

type Rep CIntRepr # 
Instance details

Defined in Language.C.Syntax.Constants

type Rep CIntRepr = D1 (MetaData "CIntRepr" "Language.C.Syntax.Constants" "language-c-0.8.2-KO6GGy0fbH5KZxtBHfA7kD" 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 #

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

data CInteger #

Instances
Eq CInteger # 
Instance details

Defined in Language.C.Syntax.Constants

Data CInteger # 
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 #

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

toConstr :: CInteger -> Constr #

dataTypeOf :: CInteger -> DataType #

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

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

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

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

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

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

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

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

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

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

Ord CInteger # 
Instance details

Defined in Language.C.Syntax.Constants

Show CInteger # 
Instance details

Defined in Language.C.Syntax.Constants

Generic CInteger # 
Instance details

Defined in Language.C.Syntax.Constants

Associated Types

type Rep CInteger :: Type -> Type #

Methods

from :: CInteger -> Rep CInteger x #

to :: Rep CInteger x -> CInteger #

NFData CInteger # 
Instance details

Defined in Language.C.Syntax.Constants

Methods

rnf :: CInteger -> () #

type Rep CInteger # 
Instance details

Defined in Language.C.Syntax.Constants

C floating point constants

data CFloat #

Floats (represented as strings)

Constructors

CFloat !String 
Instances
Eq CFloat # 
Instance details

Defined in Language.C.Syntax.Constants

Methods

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

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

Data CFloat # 
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 #

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

toConstr :: CFloat -> Constr #

dataTypeOf :: CFloat -> DataType #

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

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

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

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

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

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

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

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

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

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

Ord CFloat # 
Instance details

Defined in Language.C.Syntax.Constants

Show CFloat # 
Instance details

Defined in Language.C.Syntax.Constants

Generic CFloat # 
Instance details

Defined in Language.C.Syntax.Constants

Associated Types

type Rep CFloat :: Type -> Type #

Methods

from :: CFloat -> Rep CFloat x #

to :: Rep CFloat x -> CFloat #

NFData CFloat # 
Instance details

Defined in Language.C.Syntax.Constants

Methods

rnf :: CFloat -> () #

type Rep CFloat # 
Instance details

Defined in Language.C.Syntax.Constants

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

C string literals

data CString #

C String literals

Constructors

CString String Bool 
Instances
Eq CString # 
Instance details

Defined in Language.C.Syntax.Constants

Methods

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

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

Data CString # 
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 #

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

toConstr :: CString -> Constr #

dataTypeOf :: CString -> DataType #

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

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

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

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

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

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

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

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

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

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

Ord CString # 
Instance details

Defined in Language.C.Syntax.Constants

Show CString # 
Instance details

Defined in Language.C.Syntax.Constants

Generic CString # 
Instance details

Defined in Language.C.Syntax.Constants

Associated Types

type Rep CString :: Type -> Type #

Methods

from :: CString -> Rep CString x #

to :: Rep CString x -> CString #

NFData CString # 
Instance details

Defined in Language.C.Syntax.Constants

Methods

rnf :: CString -> () #

type Rep CString # 
Instance details

Defined in Language.C.Syntax.Constants

type Rep CString = D1 (MetaData "CString" "Language.C.Syntax.Constants" "language-c-0.8.2-KO6GGy0fbH5KZxtBHfA7kD" 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 #

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 #

concatenate a list of C string literals

Clang C version literals

data ClangCVersion #

Constructors

ClangCVersion !String 
Instances
Eq ClangCVersion # 
Instance details

Defined in Language.C.Syntax.Constants

Data ClangCVersion # 
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 #

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

toConstr :: ClangCVersion -> Constr #

dataTypeOf :: ClangCVersion -> DataType #

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

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

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

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

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

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

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

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

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

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

Ord ClangCVersion # 
Instance details

Defined in Language.C.Syntax.Constants

Show ClangCVersion # 
Instance details

Defined in Language.C.Syntax.Constants