Safe Haskell | None |
---|---|
Language | Haskell2010 |
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
- data CIdentifier
- unCIdentifier :: CIdentifier -> String
- cIdentifierFromString :: Bool -> String -> Either String CIdentifier
- data StorageClassSpecifier
- data TypeQualifier
- data FunctionSpecifier = INLINE
- data ArrayType i
- data Specifiers = Specifiers {}
- data Type i
- = TypeSpecifier Specifiers TypeSpecifier
- | Ptr [TypeQualifier] (Type i)
- | Array (ArrayType i) (Type i)
- | Proto (Type i) [ParameterDeclaration i]
- data TypeSpecifier
- data Sign
- data ParameterDeclaration i = ParameterDeclaration {}
- type TypeNames = HashSet CIdentifier
- type CParser i m = (Monad m, Functor m, Applicative m, MonadPlus m, Parsing m, CharParsing m, TokenParsing m, LookAheadParsing m, MonadReader (CParserContext i) m, MonadFail m, Hashable i)
- data CParserContext i
- cCParserContext :: Bool -> TypeNames -> CParserContext CIdentifier
- runCParser :: Stream s Identity Char => CParserContext i -> String -> s -> ReaderT (CParserContext i) (Parsec s ()) a -> Either ParseError a
- quickCParser :: CParserContext i -> String -> ReaderT (CParserContext i) (Parsec String ()) a -> a
- quickCParser_ :: Bool -> String -> ReaderT (CParserContext CIdentifier) (Parsec String ()) a -> a
- parseParameterDeclaration :: (CParser i m, Pretty i) => m (ParameterDeclaration i)
- parseParameterList :: (CParser i m, Pretty i) => m [ParameterDeclaration i]
- parseIdentifier :: CParser i m => m i
- parseEnableCpp :: CParser i m => m Bool
- parseType :: (CParser i m, Pretty i) => m (Type i)
- data UntangleErr
- untangleParameterDeclaration :: ParameterDeclaration i -> Either UntangleErr (ParameterDeclaration i)
- tangleParameterDeclaration :: forall i. ParameterDeclaration i -> ParameterDeclaration i
- describeParameterDeclaration :: Pretty i => ParameterDeclaration i -> Doc
- describeType :: Pretty i => Type i -> Doc
Types
data CIdentifier Source #
A type for C identifiers.
Instances
unCIdentifier :: CIdentifier -> String Source #
cIdentifierFromString :: Bool -> String -> Either String CIdentifier Source #
data StorageClassSpecifier Source #
Instances
Eq StorageClassSpecifier Source # | |
Defined in Language.C.Types.Parse (==) :: StorageClassSpecifier -> StorageClassSpecifier -> Bool # (/=) :: StorageClassSpecifier -> StorageClassSpecifier -> Bool # | |
Show StorageClassSpecifier Source # | |
Defined in Language.C.Types.Parse showsPrec :: Int -> StorageClassSpecifier -> ShowS # show :: StorageClassSpecifier -> String # showList :: [StorageClassSpecifier] -> ShowS # | |
Pretty StorageClassSpecifier Source # | |
Defined in Language.C.Types.Parse pretty :: StorageClassSpecifier -> Doc # prettyList :: [StorageClassSpecifier] -> Doc # |
data TypeQualifier Source #
Instances
Eq TypeQualifier Source # | |
Defined in Language.C.Types.Parse (==) :: TypeQualifier -> TypeQualifier -> Bool # (/=) :: TypeQualifier -> TypeQualifier -> Bool # | |
Show TypeQualifier Source # | |
Defined in Language.C.Types.Parse showsPrec :: Int -> TypeQualifier -> ShowS # show :: TypeQualifier -> String # showList :: [TypeQualifier] -> ShowS # | |
Pretty TypeQualifier Source # | |
Defined in Language.C.Types.Parse pretty :: TypeQualifier -> Doc # prettyList :: [TypeQualifier] -> Doc # |
data FunctionSpecifier Source #
Instances
Eq FunctionSpecifier Source # | |
Defined in Language.C.Types.Parse (==) :: FunctionSpecifier -> FunctionSpecifier -> Bool # (/=) :: FunctionSpecifier -> FunctionSpecifier -> Bool # | |
Show FunctionSpecifier Source # | |
Defined in Language.C.Types.Parse showsPrec :: Int -> FunctionSpecifier -> ShowS # show :: FunctionSpecifier -> String # showList :: [FunctionSpecifier] -> ShowS # | |
Pretty FunctionSpecifier Source # | |
Defined in Language.C.Types.Parse pretty :: FunctionSpecifier -> Doc # prettyList :: [FunctionSpecifier] -> Doc # |
Instances
Functor ArrayType Source # | |
Foldable ArrayType Source # | |
Defined in Language.C.Types.Parse fold :: Monoid m => ArrayType m -> m # foldMap :: Monoid m => (a -> m) -> ArrayType a -> 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] # length :: ArrayType a -> Int # elem :: Eq a => a -> ArrayType a -> Bool # maximum :: Ord a => ArrayType a -> a # minimum :: Ord a => ArrayType a -> a # | |
Traversable ArrayType Source # | |
Eq i => Eq (ArrayType i) Source # | |
Show i => Show (ArrayType i) Source # | |
Pretty i => Pretty (ArrayType i) Source # | |
Defined in Language.C.Types.Parse |
data Specifiers Source #
Instances
Eq Specifiers Source # | |
Defined in Language.C.Types (==) :: Specifiers -> Specifiers -> Bool # (/=) :: Specifiers -> Specifiers -> Bool # | |
Show Specifiers Source # | |
Defined in Language.C.Types showsPrec :: Int -> Specifiers -> ShowS # show :: Specifiers -> String # showList :: [Specifiers] -> ShowS # | |
Semigroup Specifiers Source # | |
Defined in Language.C.Types (<>) :: Specifiers -> Specifiers -> Specifiers # sconcat :: NonEmpty Specifiers -> Specifiers # stimes :: Integral b => b -> Specifiers -> Specifiers # | |
Monoid Specifiers Source # | |
Defined in Language.C.Types mempty :: Specifiers # mappend :: Specifiers -> Specifiers -> Specifiers # mconcat :: [Specifiers] -> Specifiers # |
TypeSpecifier Specifiers TypeSpecifier | |
Ptr [TypeQualifier] (Type i) | |
Array (ArrayType i) (Type i) | |
Proto (Type i) [ParameterDeclaration i] |
Instances
Functor Type Source # | |
Foldable Type Source # | |
Defined in Language.C.Types fold :: Monoid m => Type m -> m # foldMap :: Monoid m => (a -> m) -> Type a -> 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 # elem :: Eq a => a -> Type a -> Bool # maximum :: Ord a => Type a -> a # | |
Traversable Type Source # | |
Eq i => Eq (Type i) Source # | |
Show i => Show (Type i) Source # | |
Pretty i => Pretty (Type i) Source # | |
Defined in Language.C.Types |
data TypeSpecifier Source #
Instances
Eq TypeSpecifier Source # | |
Defined in Language.C.Types (==) :: TypeSpecifier -> TypeSpecifier -> Bool # (/=) :: TypeSpecifier -> TypeSpecifier -> Bool # | |
Ord TypeSpecifier Source # | |
Defined in Language.C.Types compare :: TypeSpecifier -> TypeSpecifier -> Ordering # (<) :: TypeSpecifier -> TypeSpecifier -> Bool # (<=) :: TypeSpecifier -> TypeSpecifier -> Bool # (>) :: TypeSpecifier -> TypeSpecifier -> Bool # (>=) :: TypeSpecifier -> TypeSpecifier -> Bool # max :: TypeSpecifier -> TypeSpecifier -> TypeSpecifier # min :: TypeSpecifier -> TypeSpecifier -> TypeSpecifier # | |
Show TypeSpecifier Source # | |
Defined in Language.C.Types showsPrec :: Int -> TypeSpecifier -> ShowS # show :: TypeSpecifier -> String # showList :: [TypeSpecifier] -> ShowS # | |
Pretty TypeSpecifier Source # | |
Defined in Language.C.Types pretty :: TypeSpecifier -> Doc # prettyList :: [TypeSpecifier] -> Doc # |
data ParameterDeclaration i Source #
Instances
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, MonadFail 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.
data CParserContext i Source #
cCParserContext :: Bool -> TypeNames -> CParserContext CIdentifier Source #
:: Stream s Identity Char | |
=> CParserContext i | |
-> String | Source name. |
-> s | String to parse. |
-> ReaderT (CParserContext i) (Parsec s ()) a | Parser. Anything with type |
-> Either ParseError a |
Runs a
using CParser
parsec
.
:: CParserContext i | |
-> String | String to parse. |
-> ReaderT (CParserContext i) (Parsec String ()) a | Parser. Anything with type |
-> a |
Useful for quick testing. Uses "quickCParser"
as source name, and throws
an error
if parsing fails.
:: Bool | |
-> String | String to parse. |
-> ReaderT (CParserContext CIdentifier) (Parsec String ()) a | Parser. Anything with type |
-> a |
Like quickCParser
, but uses
as
cCParserContext
(const
False
)CParserContext
.
parseParameterDeclaration :: (CParser i m, Pretty i) => m (ParameterDeclaration i) Source #
parseParameterList :: (CParser i m, Pretty i) => m [ParameterDeclaration i] Source #
parseIdentifier :: CParser i m => m i Source #
parseEnableCpp :: CParser i m => m Bool Source #
Convert to and from high-level views
data UntangleErr Source #
MultipleDataTypes [DeclarationSpecifier] | |
NoDataTypes [DeclarationSpecifier] | |
IllegalSpecifiers String [TypeSpecifier] |
Instances
Eq UntangleErr Source # | |
Defined in Language.C.Types (==) :: UntangleErr -> UntangleErr -> Bool # (/=) :: UntangleErr -> UntangleErr -> Bool # | |
Show UntangleErr Source # | |
Defined in Language.C.Types showsPrec :: Int -> UntangleErr -> ShowS # show :: UntangleErr -> String # showList :: [UntangleErr] -> ShowS # | |
Pretty UntangleErr Source # | |
Defined in Language.C.Types pretty :: UntangleErr -> Doc # prettyList :: [UntangleErr] -> Doc # |
untangleParameterDeclaration :: ParameterDeclaration i -> Either UntangleErr (ParameterDeclaration i) Source #
tangleParameterDeclaration :: forall i. ParameterDeclaration i -> ParameterDeclaration i Source #
To english
describeParameterDeclaration :: Pretty i => ParameterDeclaration i -> Doc Source #