yaya-0.3.2.0: Total recursion schemes.

Safe HaskellNone
LanguageHaskell2010

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

Documentation

class Corecursive c t f | t -> f where Source #

Coinductive (potentially-infinite) structures that guarantee _productivity_ rather than termination.

Methods

ana :: Coalgebra c f a -> a `c` t Source #

Instances
Corecursive ((->) :: Type -> Type -> Type) (Nu f :: Type) (f :: Type -> Type) Source # 
Instance details

Defined in Yaya.Fold

Methods

ana :: Coalgebra (->) f a -> a -> Nu f Source #

Functor f => Corecursive ((->) :: Type -> Type -> Type) (Fix f :: Type) (f :: Type -> Type) Source # 
Instance details

Defined in Yaya.Fold.Native

Methods

ana :: Coalgebra (->) f a -> a -> Fix f Source #

Corecursive ((->) :: Type -> Type -> Type) ([a] :: Type) (XNor a :: Type -> Type) Source # 
Instance details

Defined in Yaya.Fold.Native

Methods

ana :: Coalgebra (->) (XNor a) a0 -> a0 -> [a] Source #

Corecursive ((->) :: Type -> Type -> Type) (NonEmpty a :: Type) (AndMaybe a :: Type -> Type) Source # 
Instance details

Defined in Yaya.Fold.Native

Methods

ana :: Coalgebra (->) (AndMaybe a) a0 -> a0 -> NonEmpty a Source #

Corecursive ((->) :: Type -> Type -> Type) (Maybe a :: Type) (Const (Maybe a) :: Type -> Type) Source # 
Instance details

Defined in Yaya.Fold

Methods

ana :: Coalgebra (->) (Const (Maybe a)) a0 -> a0 -> Maybe a Source #

Corecursive ((->) :: Type -> Type -> Type) (Either a b :: Type) (Const (Either a b) :: Type -> Type) Source # 
Instance details

Defined in Yaya.Fold

Methods

ana :: Coalgebra (->) (Const (Either a b)) a0 -> a0 -> Either a b Source #

Functor f => Corecursive ((->) :: Type -> Type -> Type) (Cofree f a :: Type) (EnvT a f :: Type -> Type) Source # 
Instance details

Defined in Yaya.Fold.Native

Methods

ana :: Coalgebra (->) (EnvT a f) a0 -> a0 -> Cofree f a Source #

Functor f => Corecursive ((->) :: Type -> Type -> Type) (Free f a :: Type) (FreeF f a :: Type -> Type) Source # 
Instance details

Defined in Yaya.Fold.Native

Methods

ana :: Coalgebra (->) (FreeF f a) a0 -> a0 -> Free f a 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.

Methods

cata :: Algebra c f a -> t `c` a Source #

Instances
Recursive ((->) :: Type -> Type -> Type) Natural Maybe Source # 
Instance details

Defined in Yaya.Fold.Native

Methods

cata :: Algebra (->) Maybe a -> Natural -> a Source #

Recursive ((->) :: Type -> Type -> Type) Void Identity Source # 
Instance details

Defined in Yaya.Fold

Methods

cata :: Algebra (->) Identity a -> Void -> a Source #

Recursive ((->) :: Type -> Type -> Type) (Mu f :: Type) (f :: Type -> Type) Source # 
Instance details

Defined in Yaya.Fold

Methods

cata :: Algebra (->) f a -> Mu f -> a Source #

Recursive ((->) :: Type -> Type -> Type) (Maybe a :: Type) (Const (Maybe a) :: Type -> Type) Source # 
Instance details

Defined in Yaya.Fold

Methods

cata :: Algebra (->) (Const (Maybe a)) a0 -> Maybe a -> a0 Source #

Recursive ((->) :: Type -> Type -> Type) (Either a b :: Type) (Const (Either a b) :: Type -> Type) Source # 
Instance details

Defined in Yaya.Fold

Methods

cata :: Algebra (->) (Const (Either a b)) a0 -> Either a b -> a0 Source #

class Projectable c t f => Steppable c t f | t -> f where Source #

Structures you can walk through step-by-step.

Methods

embed :: Algebra c f t Source #

Instances
Steppable ((->) :: Type -> Type -> Type) Natural Maybe Source # 
Instance details

Defined in Yaya.Fold

Steppable ((->) :: Type -> Type -> Type) Void Identity Source # 
Instance details

Defined in Yaya.Fold

Functor f => Steppable ((->) :: Type -> Type -> Type) (Nu f :: Type) (f :: Type -> Type) Source # 
Instance details

Defined in Yaya.Fold

Methods

embed :: Algebra (->) f (Nu f) Source #

Functor f => Steppable ((->) :: Type -> Type -> Type) (Mu f :: Type) (f :: Type -> Type) Source # 
Instance details

Defined in Yaya.Fold

Methods

embed :: Algebra (->) f (Mu f) Source #

Steppable ((->) :: Type -> Type -> Type) (Fix f :: Type) (f :: Type -> Type) Source # 
Instance details

Defined in Yaya.Fold.Native

Methods

embed :: Algebra (->) f (Fix f) Source #

Steppable ((->) :: Type -> Type -> Type) ([a] :: Type) (XNor a :: Type -> Type) Source # 
Instance details

Defined in Yaya.Fold

Methods

embed :: Algebra (->) (XNor a) [a] Source #

Steppable ((->) :: Type -> Type -> Type) (NonEmpty a :: Type) (AndMaybe a :: Type -> Type) Source # 
Instance details

Defined in Yaya.Fold

Methods

embed :: Algebra (->) (AndMaybe a) (NonEmpty a) Source #

Steppable ((->) :: Type -> Type -> Type) (Maybe a :: Type) (Const (Maybe a) :: Type -> Type) Source # 
Instance details

Defined in Yaya.Fold

Methods

embed :: Algebra (->) (Const (Maybe a)) (Maybe a) Source #

Steppable ((->) :: Type -> Type -> Type) (Either a b :: Type) (Const (Either a b) :: Type -> Type) Source # 
Instance details

Defined in Yaya.Fold

Methods

embed :: Algebra (->) (Const (Either a b)) (Either a b) Source #

Steppable ((->) :: Type -> Type -> Type) (Cofree f a :: Type) (EnvT a f :: Type -> Type) Source # 
Instance details

Defined in Yaya.Fold

Methods

embed :: Algebra (->) (EnvT a f) (Cofree f a) Source #

Steppable ((->) :: Type -> Type -> Type) (Free f a :: Type) (FreeF f a :: Type -> Type) Source # 
Instance details

Defined in Yaya.Fold

Methods

embed :: Algebra (->) (FreeF f a) (Free f a) 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).

Methods

project :: Coalgebra c f t Source #

Instances
Projectable ((->) :: Type -> Type -> Type) Natural Maybe Source # 
Instance details

Defined in Yaya.Fold

Projectable ((->) :: Type -> Type -> Type) Void Identity Source # 
Instance details

Defined in Yaya.Fold

Functor f => Projectable ((->) :: Type -> Type -> Type) (Nu f :: Type) (f :: Type -> Type) Source # 
Instance details

Defined in Yaya.Fold

Methods

project :: Coalgebra (->) f (Nu f) Source #

Functor f => Projectable ((->) :: Type -> Type -> Type) (Mu f :: Type) (f :: Type -> Type) Source # 
Instance details

Defined in Yaya.Fold

Methods

project :: Coalgebra (->) f (Mu f) Source #

Projectable ((->) :: Type -> Type -> Type) (Fix f :: Type) (f :: Type -> Type) Source # 
Instance details

Defined in Yaya.Fold.Native

Methods

project :: Coalgebra (->) f (Fix f) Source #

Projectable ((->) :: Type -> Type -> Type) ([a] :: Type) (XNor a :: Type -> Type) Source # 
Instance details

Defined in Yaya.Fold

Methods

project :: Coalgebra (->) (XNor a) [a] Source #

Projectable ((->) :: Type -> Type -> Type) (NonEmpty a :: Type) (AndMaybe a :: Type -> Type) Source # 
Instance details

Defined in Yaya.Fold

Methods

project :: Coalgebra (->) (AndMaybe a) (NonEmpty a) Source #

Projectable ((->) :: Type -> Type -> Type) (Maybe a :: Type) (Const (Maybe a) :: Type -> Type) Source # 
Instance details

Defined in Yaya.Fold

Methods

project :: Coalgebra (->) (Const (Maybe a)) (Maybe a) Source #

Projectable ((->) :: Type -> Type -> Type) (Either a b :: Type) (Const (Either a b) :: Type -> Type) Source # 
Instance details

Defined in Yaya.Fold

Methods

project :: Coalgebra (->) (Const (Either a b)) (Either a b) Source #

Projectable ((->) :: Type -> Type -> Type) (Cofree f a :: Type) (EnvT a f :: Type -> Type) Source # 
Instance details

Defined in Yaya.Fold

Methods

project :: Coalgebra (->) (EnvT a f) (Cofree f a) Source #

Projectable ((->) :: Type -> Type -> Type) (Free f a :: Type) (FreeF f a :: Type -> Type) Source # 
Instance details

Defined in Yaya.Fold

Methods

project :: Coalgebra (->) (FreeF f a) (Free f a) Source #

recursiveEq :: (Recursive (->) t f, Steppable (->) u f, Functor f, Foldable f, Eq1 f) => t -> u -> Bool Source #

An implementation of Eq for any Recursive instance. Note that this is actually more general than Eq, as it can compare between different fixed-point representations of the same functor.

recursiveShowsPrec :: (Recursive (->) t f, Show1 f) => Int -> t -> ShowS Source #

An implementation of Show for any Recursive instance.

data PatternFunctorRules Source #

Rules of renaming data names

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 (Show)

extractPatternFunctor defaultRules ''Expr

will create

data ExprF a x
    = LitF a
    | AddF x x
    | x :*$ [x]
  deriving (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:

  • extractPatternFunctor works 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 Recursive and Corecursive instances, 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).