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
.
- data CIdentifier
- unCIdentifier :: CIdentifier -> String
- cIdentifierFromString :: 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, Hashable i)
- data CParserContext i
- cCParserContext :: 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_ :: 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
- 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.
unCIdentifier :: CIdentifier -> String Source
data TypeQualifier Source
data FunctionSpecifier Source
TypeSpecifier Specifiers TypeSpecifier | |
Ptr [TypeQualifier] (Type i) | |
Array (ArrayType i) (Type i) | |
Proto (Type i) [ParameterDeclaration i] |
data TypeSpecifier Source
data ParameterDeclaration i Source
Functor ParameterDeclaration | |
Foldable ParameterDeclaration | |
Traversable ParameterDeclaration | |
Eq i => Eq (ParameterDeclaration i) | |
Show i => Show (ParameterDeclaration i) | |
Pretty i => Pretty (ParameterDeclaration i) | |
Typeable (* -> *) ParameterDeclaration |
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.
data CParserContext i 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.
:: 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
Convert to and from high-level views
data UntangleErr Source
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
describeType :: Pretty i => Type i -> Doc Source