language-c-0.4.7: 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) 
Data f => Data (Flags f) 
Ord (Flags f) 
Typeable (* -> *) Flags 

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 :: [Char] -> Bool -> CChar Source

create a multi-character character constant

data CChar Source

C char constants (abstract)

Constructors

CChar !Char !Bool 
CChars [Char] !Bool 

getCChar :: CChar -> [Char] 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

data CIntRepr Source

datatype for memorizing the representation of an integer

Constructors

DecRepr 
HexRepr 
OctalRepr 

cInteger :: Integer -> CInteger Source

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

C floating point constants

data CFloat Source

Floats (represented as strings)

Constructors

CFloat !String 

C string literals

data CString Source

C String literals

Constructors

CString [Char] 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