| Safe Haskell | None |
|---|---|
| Language | Haskell2010 |
Pinchot.SyntaxTree.Optics
- rulesToOptics :: (Lift t, Data t) => Qualifier -> Name -> [Rule t] -> Q [Dec]
- ruleToOptics :: (Lift t, Data t) => Qualifier -> Name -> Rule t -> Q [Dec]
- terminalToOptics :: Lift t => Qualifier -> Name -> String -> Predicate t -> Q [Dec]
- seriesToOptics :: (Data t, Lift t) => Qualifier -> Name -> String -> NonEmpty t -> Q [Dec]
- prismSignature :: Qualifier -> String -> Branch t -> DecQ
- setterPatAndExpn :: Qualifier -> BranchName -> [a] -> Q (PatQ, ExpQ)
- prismSetter :: Qualifier -> Branch t -> ExpQ
- rightPatternAndExpression :: Qualifier -> BranchName -> Int -> Q (PatQ, ExpQ)
- leftPatternAndExpression :: [a] -> Maybe (Q (PatQ, ExpQ))
- prismGetter :: Qualifier -> Branch t -> [Branch t] -> ExpQ
- nonTerminalToOptics :: Qualifier -> String -> NonEmpty (Branch t) -> [Q Dec]
- recordLensSignature :: Qualifier -> RuleName -> RuleName -> Int -> DecQ
- recordLensGetter :: Qualifier -> String -> ExpQ
- recordLensSetter :: Qualifier -> String -> ExpQ
- recordLensFunction :: Qualifier -> RuleName -> RuleName -> Int -> DecQ
- recordsToOptics :: Qualifier -> String -> [Rule t] -> [Q Dec]
- forallA :: TypeQ -> TypeQ
Documentation
Arguments
| :: (Lift t, Data t) | |
| => Qualifier | Qualifier for module containing the data types that will get optics |
| -> Name | Type name for the terminal |
| -> [Rule t] | |
| -> Q [Dec] |
Creates optics declarations for a Rule, if optics can
be made for the Rule:
terminalgets a singlePrismnonTerminalgets aPrismfor each constructorrecordgets a singleLenswrap,opt,star, andplusdo not get optics. For those, you will typically want to usewrappedInstances.
Each rule in the sequence of Rule, as well as all ancestors of
those Rules, will be handled.
Example: Pinchot.Examples.RulesToOptics.
Arguments
| :: Lift t | |
| => Qualifier | Qualifier for module containing the data type that will get optics |
| -> Name | Terminal type name |
| -> String | Rule name |
| -> Predicate t | |
| -> Q [Dec] |
Creates a prism for a terminal type. Although a newtype wraps each terminal, do not make a Wrapped or an Iso, because the relationship between the outer type and the type that it wraps typically is not isometric. Thus, use a Prism instead, which captures this relationship properly.
Arguments
| :: Qualifier | |
| -> BranchName | |
| -> [a] | List of rules |
| -> Q (PatQ, ExpQ) |
rightPatternAndExpression Source #
Returns a pattern and expression to match a particular branch; if there is a match, the expression will return each field, in a tuple in a Right.
leftPatternAndExpression Source #
Returns a pattern and expression for branches that did not match. Does not return anything if there are no other branches.
Arguments
| :: Qualifier | Qualifier for module containing the data type that will get optics |
| -> String | Rule name |
| -> NonEmpty (Branch t) | |
| -> [Q Dec] |
Creates prisms for each Branch.