| Safe Haskell | Safe |
|---|---|
| Language | Haskell2010 |
Yaya.Retrofit
Description
This module re-exports a subset of Fold, intended for when you want
to define recursion scheme instances for your existing recursive types.
This is not the recommended way to use Yaya, but it solves some real problems: 1. you have existing directly-recursive types and you want to start taking advantage of recursion schemes without having to rewrite your existing code, or 2. a directly-recursive type has been imposed on you by some other library and you want to take advantage of recursion schemes.
The distinction between these two cases is whether you have control of the
data declaration. In the first case, you probably do. In that case, you
should only generate the safe instances, and ensure that all the
recursive type references are strict (if you want a Recursive
instance). If you don't have control, then you may need to generate all
instances.
Another difference when you have control is that it means you may migrate away from direct recursion entirely, at which point this import should disappear.
Synopsis
- class Corecursive c t f | t -> f where
- class Projectable c t f | t -> f where
- class Recursive c t f | t -> f where
- class Projectable c t f => Steppable c t f | t -> f where
- recursiveCompare :: (Recursive (->) t f, Steppable (->) u f, Functor f, Foldable f, Ord1 f) => t -> u -> Ordering
- recursiveCompare' :: (Recursive (->) t f, Steppable (->) u f, Functor f, Foldable f) => (f () -> f () -> Ordering) -> t -> u -> Ordering
- recursiveEq :: (Recursive (->) t f, Steppable (->) u f, Functor f, Foldable f, Eq1 f) => t -> u -> Bool
- recursiveEq' :: (Recursive (->) t f, Steppable (->) u f, Functor f, Foldable f) => (f () -> f () -> Bool) -> t -> u -> Bool
- recursiveShowsPrec :: (Recursive (->) t f, Show1 f) => Int -> t -> ShowS
- recursiveShowsPrec' :: Recursive (->) t f => Algebra (->) f (Int -> ShowS) -> Int -> t -> ShowS
- steppableReadPrec :: (Steppable (->) t f, Read1 f) => ReadPrec t
- steppableReadPrec' :: Steppable (->) t f => (ReadPrec t -> ReadPrec [t] -> ReadPrec (f t)) -> ReadPrec t
- data PatternFunctorRules = PatternFunctorRules {
- patternType :: Name -> Name
- patternCon :: Name -> Name
- patternField :: Name -> Name
- defaultRules :: PatternFunctorRules
- extractPatternFunctor :: PatternFunctorRules -> Name -> Q [Dec]
Documentation
class Corecursive c t f | t -> f where Source #
Coinductive (potentially-infinite) structures that guarantee _productivity_ rather than termination.
Instances
| Corecursive (->) (Nu f :: Type) (f :: Type -> Type) Source # | |
| Functor f => Corecursive (->) (Cofix f :: Type) (f :: Type -> Type) Source # | |
| Corecursive (->) (NonEmpty a :: Type) (AndMaybe a :: Type -> Type) Source # | |
| Corecursive (->) ([a] :: Type) (XNor a :: Type -> Type) Source # | |
| Corecursive (->) (Maybe a :: Type) (Const (Maybe a) :: Type -> Type) Source # | |
| Functor f => Corecursive (->) (Cofree f a :: Type) (EnvT a f :: Type -> Type) Source # | |
| Functor f => Corecursive (->) (Free f a :: Type) (FreeF f a :: Type -> Type) Source # | |
| Corecursive (->) (Either a b :: Type) (Const (Either a b) :: Type -> Type) Source # | |
class Projectable c t f | t -> f where Source #
This type class is lawless on its own, but there exist types that can’t
implement the corresponding embed operation. Laws are induced by
implementing either Steppable (which extends this) or Corecursive
(which doesn’t).
Instances
| Projectable (->) Void Identity Source # | |
| Projectable (->) Natural Maybe Source # | |
| Functor f => Projectable (->) (Mu f :: Type) (f :: Type -> Type) Source # | |
| Functor f => Projectable (->) (Nu f :: Type) (f :: Type -> Type) Source # | |
| Projectable (->) (Fix f :: Type) (f :: Type -> Type) Source # | |
| Projectable (->) (Cofix f :: Type) (f :: Type -> Type) Source # | |
| Projectable (->) (NonEmpty a :: Type) (AndMaybe a :: Type -> Type) Source # | |
| Projectable (->) ([a] :: Type) (XNor a :: Type -> Type) Source # | |
| Projectable (->) (Maybe a :: Type) (Const (Maybe a) :: Type -> Type) Source # | |
| Projectable (->) (Cofree f a :: Type) (EnvT a f :: Type -> Type) Source # | |
| Projectable (->) (Free f a :: Type) (FreeF f a :: Type -> Type) Source # | |
| Projectable (->) (Either a b :: Type) (Const (Either a b) :: Type -> Type) Source # | |
class Recursive c t f | t -> f where Source #
Inductive structures that can be reasoned about in the way we usually do – with pattern matching.
Instances
| Recursive (->) Void Identity Source # | |
| Recursive (->) Natural Maybe Source # | |
| Recursive (->) (Mu f :: Type) (f :: Type -> Type) Source # | |
| Functor f => Recursive (->) (Fix f :: Type) (f :: Type -> Type) Source # | |
| Recursive (->) (Maybe a :: Type) (Const (Maybe a) :: Type -> Type) Source # | |
| Recursive (->) (Either a b :: Type) (Const (Either a b) :: Type -> Type) Source # | |
class Projectable c t f => Steppable c t f | t -> f where Source #
Structures you can walk through step-by-step.
Instances
| Steppable (->) Void Identity Source # | |
| Steppable (->) Natural Maybe Source # | |
| Functor f => Steppable (->) (Mu f :: Type) (f :: Type -> Type) Source # | |
| Functor f => Steppable (->) (Nu f :: Type) (f :: Type -> Type) Source # | |
| Steppable (->) (Fix f :: Type) (f :: Type -> Type) Source # | |
| Steppable (->) (Cofix f :: Type) (f :: Type -> Type) Source # | |
| Steppable (->) (NonEmpty a :: Type) (AndMaybe a :: Type -> Type) Source # | |
| Steppable (->) ([a] :: Type) (XNor a :: Type -> Type) Source # | |
| Steppable (->) (Maybe a :: Type) (Const (Maybe a) :: Type -> Type) Source # | |
| Steppable (->) (Cofree f a :: Type) (EnvT a f :: Type -> Type) Source # | |
| Steppable (->) (Free f a :: Type) (FreeF f a :: Type -> Type) Source # | |
| Steppable (->) (Either a b :: Type) (Const (Either a b) :: Type -> Type) Source # | |
recursiveCompare :: (Recursive (->) t f, Steppable (->) u f, Functor f, Foldable f, Ord1 f) => t -> u -> Ordering Source #
An implementation of == for any Recursive instance. Note that this is
actually more general than Ord’s compare, as it can compare between
different fixed-point representations of the same functor.
NB: Use recursiveCompare' if you need to use a custom comparator for
f.
Since: 0.6.1.0
recursiveCompare' :: (Recursive (->) t f, Steppable (->) u f, Functor f, Foldable f) => (f () -> f () -> Ordering) -> t -> u -> Ordering Source #
Like recursiveCompare, but allows you to provide a custom comparator for
f.
Since: 0.6.1.0
recursiveEq :: (Recursive (->) t f, Steppable (->) u f, Functor f, Foldable f, Eq1 f) => t -> u -> Bool Source #
An implementation of == for any Recursive instance. Note that this is
actually more general than Eq’s ==, as it can compare between different
fixed-point representations of the same functor.
NB: Use recursiveEq' if you need to use a custom comparator for f.
recursiveEq' :: (Recursive (->) t f, Steppable (->) u f, Functor f, Foldable f) => (f () -> f () -> Bool) -> t -> u -> Bool Source #
Like recursiveEq, but allows you to provide a custom comparator for f.
Since: 0.6.1.0
recursiveShowsPrec' :: Recursive (->) t f => Algebra (->) f (Int -> ShowS) -> Int -> t -> ShowS Source #
Like recursiveShowsPrec, but allows you to provide a custom display
function for f.
Since: 0.6.1.0
steppableReadPrec :: (Steppable (->) t f, Read1 f) => ReadPrec t Source #
An implementation of readPrec for any Steppable instance.
NB: Use steppableReadPrec' if you need to use a custom parsing
function for f.
NB: This only requires Steppable, but the inverse operation is
recursiveShowsPrec, which requires Recursive instead.
Since: 0.6.1.0
steppableReadPrec' :: Steppable (->) t f => (ReadPrec t -> ReadPrec [t] -> ReadPrec (f t)) -> ReadPrec t Source #
Like steppableReadPrec, but allows you to provide a custom display
function for f.
Since: 0.6.1.0
data PatternFunctorRules Source #
Rules of renaming data names
Constructors
| PatternFunctorRules | |
Fields
| |
defaultRules :: PatternFunctorRules Source #
Default PatternFunctorRules: append F or $ to data type, constructors and field names.
extractPatternFunctor :: PatternFunctorRules -> Name -> Q [Dec] Source #
Extract a pattern functor and relevant instances from a simply recursive type.
e.g.
data Expr a
= Lit a
| Add (Expr a) (Expr a)
| Expr a :* [Expr a]
deriving stock (Show)
extractPatternFunctor defaultRules ''Expr
will create
data ExprF a x
= LitF a
| AddF x x
| x :*$ [x]
deriving stock (Functor, Foldable, Traversable)
instance Projectable (->) (Expr a) (ExprF a) where
project (Lit x) = LitF x
project (Add x y) = AddF x y
project (x :* y) = x :*$ y
instance Steppable (->) (Expr a) (ExprF a) where
embed (LitF x) = Lit x
embed (AddF x y) = Add x y
embed (x :*$ y) = x :* y
instance Recursive (->) (Expr a) (ExprF a) where
cata φ = φ . fmap (cata φ) . project
instance Corecursive (->) (Expr a) (ExprF a) where
ana ψ = embed . fmap (ana ψ) . ψ
Notes:
extractPatternFunctorworks properly only with ADTs. Existentials and GADTs aren't supported, as we don't try to do better than GHC's DeriveFunctor.- we always generate both
RecursiveandCorecursiveinstances, but one of these is always unsafe. In future, we should check the strictness of the recursive parameter and generate only the appropriate one (unless overridden by a rule).