Safe Haskell | None |
---|---|
Language | Haskell2010 |
Synopsis
- posType :: IsString a => a
- posConstr :: IsString a => a
- noPosConstr :: IsString a => a
- hasPositionClass :: IsString a => a
- hasPositionMethod :: IsString a => a
- noWarnUnusedMatches :: IsString a => a
- parserName :: Cat -> Doc
- hsReservedWords :: [String]
- avoidReservedWords :: [String] -> String -> String
- mkDefName :: IsFun f => f -> String
- typeToHaskell :: Type -> String
- typeToHaskell' :: String -> Type -> String
- catToType :: (Doc -> Doc) -> Doc -> Cat -> Doc
- catToVar :: [String] -> Cat -> String
- catvars :: [String] -> [Cat] -> [Doc]
- tokenTextImport :: TokenText -> [String]
- tokenTextType :: TokenText -> String
- tokenTextPack :: TokenText -> String -> String
- tokenTextPackParens :: TokenText -> String -> String
- tokenTextUnpack :: TokenText -> String -> String
Documentation
noPosConstr :: IsString a => a Source #
hasPositionClass :: IsString a => a Source #
hasPositionMethod :: IsString a => a Source #
noWarnUnusedMatches :: IsString a => a Source #
parserName :: Cat -> Doc Source #
Create a valid parser function name for a given category.
>>>
parserName (Cat "Abcd")
pAbcd
>>>
parserName (ListCat (Cat "Xyz"))
pListXyz
hsReservedWords :: [String] Source #
Haskell's reserved words.
avoidReservedWords :: [String] -> String -> String Source #
Avoid Haskell keywords plus additional reserved words.
typeToHaskell :: Type -> String Source #
Convert a function type to Haskell syntax in curried form.
catToType :: (Doc -> Doc) -> Doc -> Cat -> Doc Source #
Render a category from the grammar to a Haskell type.
>>>
catToType id empty (Cat "A")
A>>>
catToType id empty (ListCat (Cat "A"))
[A]>>>
catToType ("Foo." P.<>) empty (TokenCat "Ident")
Foo.Ident
Note that there is no haskell type for coerced categories: they should be normalized: >>> catToType id empty (CoercCat Expr 2) Expr
If a type parameter is given it is added to the type name: >>> catToType id (text "a") (Cat A) (A a)
>>>
catToType id (text "a") (ListCat (Cat "A"))
[A a]
but not added to Token categories: >>> catToType ("Foo." P.<>) (text "a") (TokenCat Integer) Integer
>>>
catToType id (text "a") (ListCat (TokenCat "Integer"))
[Integer]
>>>
catToType id empty (ListCat (CoercCat "Exp" 2))
[Exp]
>>>
catToType ("Foo." P.<>) (text "()") (ListCat (CoercCat "Exp" 2))
[Foo.Exp ()]
catvars :: [String] -> [Cat] -> [Doc] Source #
Gives a list of variables usable for pattern matching.
Example: Given the rule Aba. S ::= A B A ;
with the generated data type
data S = Aba A B A
from the list of categories on the RHS of the rule [A,B,A], we generate the
list [a1,b,a2] to be used in a pattern matching like
case s of
Aba a1 b a2 -> ...
...
>>>
catvars [] [Cat "A", Cat "B", Cat "A"]
[a1,b,a2]
It should avoid reserved words: >>> catvars ["foo"] [Cat Foo, Cat IF, Cat Case, Cat Type, Cat If] [foo_,if_1,case_,type_,if_2]
It uses a suffix -s to mark lists: >>> catvars [] [Cat A, ListCat (Cat A), ListCat (ListCat (Cat A))] [a,as_,ass]
tokenTextImport :: TokenText -> [String] Source #
tokenTextType :: TokenText -> String Source #