inline-c-0.5.5.9: Write Haskell source files including C code inline. No FFI required.

Safe HaskellNone
LanguageHaskell2010

Language.C.Types

Contents

Description

Views of C datatypes. While Language.C.Types.Parse defines datatypes for representing the concrete syntax tree of C types, this module provides friendlier views of C types, by turning them into a data type matching more closely how we read and think about types, both in Haskell and in C. To appreciate the difference, look at the difference between ParameterDeclaration and ParameterDeclaration.

As a bonus, routines are provided for describing types in natural language (English) -- see describeParameterDeclaration and describeType.

Synopsis

Types

data ArrayType i Source #

Instances

Functor ArrayType Source # 

Methods

fmap :: (a -> b) -> ArrayType a -> ArrayType b #

(<$) :: a -> ArrayType b -> ArrayType a #

Foldable ArrayType Source # 

Methods

fold :: Monoid m => ArrayType m -> m #

foldMap :: Monoid m => (a -> m) -> ArrayType a -> m #

foldr :: (a -> b -> b) -> b -> ArrayType a -> b #

foldr' :: (a -> b -> b) -> b -> ArrayType a -> b #

foldl :: (b -> a -> b) -> b -> ArrayType a -> b #

foldl' :: (b -> a -> b) -> b -> ArrayType a -> b #

foldr1 :: (a -> a -> a) -> ArrayType a -> a #

foldl1 :: (a -> a -> a) -> ArrayType a -> a #

toList :: ArrayType a -> [a] #

null :: ArrayType a -> Bool #

length :: ArrayType a -> Int #

elem :: Eq a => a -> ArrayType a -> Bool #

maximum :: Ord a => ArrayType a -> a #

minimum :: Ord a => ArrayType a -> a #

sum :: Num a => ArrayType a -> a #

product :: Num a => ArrayType a -> a #

Traversable ArrayType Source # 

Methods

traverse :: Applicative f => (a -> f b) -> ArrayType a -> f (ArrayType b) #

sequenceA :: Applicative f => ArrayType (f a) -> f (ArrayType a) #

mapM :: Monad m => (a -> m b) -> ArrayType a -> m (ArrayType b) #

sequence :: Monad m => ArrayType (m a) -> m (ArrayType a) #

Eq i => Eq (ArrayType i) Source # 

Methods

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

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

Show i => Show (ArrayType i) Source # 
Pretty i => Pretty (ArrayType i) Source # 

Methods

pretty :: ArrayType i -> Doc #

prettyList :: [ArrayType i] -> Doc #

data Type i Source #

Instances

Functor Type Source # 

Methods

fmap :: (a -> b) -> Type a -> Type b #

(<$) :: a -> Type b -> Type a #

Foldable Type Source # 

Methods

fold :: Monoid m => Type m -> m #

foldMap :: Monoid m => (a -> m) -> Type a -> m #

foldr :: (a -> b -> b) -> b -> Type a -> b #

foldr' :: (a -> b -> b) -> b -> Type a -> b #

foldl :: (b -> a -> b) -> b -> Type a -> b #

foldl' :: (b -> a -> b) -> b -> Type a -> b #

foldr1 :: (a -> a -> a) -> Type a -> a #

foldl1 :: (a -> a -> a) -> Type a -> a #

toList :: Type a -> [a] #

null :: Type a -> Bool #

length :: Type a -> Int #

elem :: Eq a => a -> Type a -> Bool #

maximum :: Ord a => Type a -> a #

minimum :: Ord a => Type a -> a #

sum :: Num a => Type a -> a #

product :: Num a => Type a -> a #

Traversable Type Source # 

Methods

traverse :: Applicative f => (a -> f b) -> Type a -> f (Type b) #

sequenceA :: Applicative f => Type (f a) -> f (Type a) #

mapM :: Monad m => (a -> m b) -> Type a -> m (Type b) #

sequence :: Monad m => Type (m a) -> m (Type a) #

Eq i => Eq (Type i) Source # 

Methods

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

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

Show i => Show (Type i) Source # 

Methods

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

show :: Type i -> String #

showList :: [Type i] -> ShowS #

Pretty i => Pretty (Type i) Source # 

Methods

pretty :: Type i -> Doc #

prettyList :: [Type i] -> Doc #

data Sign Source #

Constructors

Signed 
Unsigned 

Instances

Eq Sign Source # 

Methods

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

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

Ord Sign Source # 

Methods

compare :: Sign -> Sign -> Ordering #

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

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

(>) :: Sign -> Sign -> Bool #

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

max :: Sign -> Sign -> Sign #

min :: Sign -> Sign -> Sign #

Show Sign Source # 

Methods

showsPrec :: Int -> Sign -> ShowS #

show :: Sign -> String #

showList :: [Sign] -> ShowS #

data ParameterDeclaration i Source #

Instances

Functor ParameterDeclaration Source # 
Foldable ParameterDeclaration Source # 

Methods

fold :: Monoid m => ParameterDeclaration m -> m #

foldMap :: Monoid m => (a -> m) -> ParameterDeclaration a -> m #

foldr :: (a -> b -> b) -> b -> ParameterDeclaration a -> b #

foldr' :: (a -> b -> b) -> b -> ParameterDeclaration a -> b #

foldl :: (b -> a -> b) -> b -> ParameterDeclaration a -> b #

foldl' :: (b -> a -> b) -> b -> ParameterDeclaration a -> b #

foldr1 :: (a -> a -> a) -> ParameterDeclaration a -> a #

foldl1 :: (a -> a -> a) -> ParameterDeclaration a -> a #

toList :: ParameterDeclaration a -> [a] #

null :: ParameterDeclaration a -> Bool #

length :: ParameterDeclaration a -> Int #

elem :: Eq a => a -> ParameterDeclaration a -> Bool #

maximum :: Ord a => ParameterDeclaration a -> a #

minimum :: Ord a => ParameterDeclaration a -> a #

sum :: Num a => ParameterDeclaration a -> a #

product :: Num a => ParameterDeclaration a -> a #

Traversable ParameterDeclaration Source # 
Eq i => Eq (ParameterDeclaration i) Source # 
Show i => Show (ParameterDeclaration i) Source # 
Pretty i => Pretty (ParameterDeclaration i) Source # 

Parsing

type TypeNames = HashSet CIdentifier Source #

A collection of named types (typedefs)

type CParser i m = (Monad m, Functor m, Applicative m, MonadPlus m, Parsing m, CharParsing m, TokenParsing m, LookAheadParsing m, MonadReader (CParserContext i) m, Hashable i) Source #

All the parsing is done using the type classes provided by the parsers package. You can use the parsing routines with any of the parsers that implement the classes, such as parsec or trifecta.

We parametrize the parsing by the type of the variable identifiers, i. We do so because we use this parser to implement anti-quoters referring to Haskell variables, and thus we need to parse Haskell identifiers in certain positions.

runCParser Source #

Arguments

:: Stream s Identity Char 
=> CParserContext i 
-> String

Source name.

-> s

String to parse.

-> ReaderT (CParserContext i) (Parsec s ()) a

Parser. Anything with type forall m. CParser i m => m a is a valid argument.

-> Either ParseError a 

Runs a CParser using parsec.

quickCParser Source #

Arguments

:: CParserContext i 
-> String

String to parse.

-> ReaderT (CParserContext i) (Parsec String ()) a

Parser. Anything with type forall m. CParser i m => m a is a valid argument.

-> a 

Useful for quick testing. Uses "quickCParser" as source name, and throws an error if parsing fails.

quickCParser_ Source #

Arguments

:: String

String to parse.

-> ReaderT (CParserContext CIdentifier) (Parsec String ()) a

Parser. Anything with type forall m. CParser i m => m a is a valid argument.

-> a 

parseType :: (CParser i m, Pretty i) => m (Type i) Source #

Convert to and from high-level views

To english