module Data.HFunctor.Interpret (
Interpret(..), forI
, iget
, icollect
, icollect1
, itraverse
, iapply
, ifanout
, ifanout1
, getI, collectI
, AltConst(..)
, AndC
, WrapHF(..)
) where
import Control.Applicative
import Control.Applicative.Backwards
import Control.Applicative.Lift
import Control.Applicative.ListF
import Control.Applicative.Step
import Control.Comonad.Trans.Env (EnvT(..))
import Control.Monad.Freer.Church
import Control.Monad.Reader
import Control.Monad.Trans.Compose
import Control.Monad.Trans.Identity
import Control.Natural
import Data.Coerce
import Data.Data
import Data.Functor.Bind
import Data.Functor.Classes
import Data.Functor.Contravariant
import Data.Functor.Contravariant.Conclude
import Data.Functor.Contravariant.Decide
import Data.Functor.Contravariant.Divise
import Data.Functor.Contravariant.Divisible
import Data.Functor.Coyoneda
import Data.Functor.Invariant
import Data.Functor.Plus
import Data.Functor.Product
import Data.Functor.Reverse
import Data.Functor.Sum
import Data.Functor.These
import Data.HFunctor
import Data.HFunctor.Internal
import Data.List.NonEmpty (NonEmpty(..))
import Data.Maybe
import Data.Pointed
import Data.Semigroup (Endo(..))
import Data.Semigroup.Foldable
import GHC.Generics
import qualified Control.Alternative.Free as Alt
import qualified Control.Applicative.Free as Ap
import qualified Control.Applicative.Free.Fast as FAF
import qualified Control.Applicative.Free.Final as FA
import qualified Data.Functor.Contravariant.Coyoneda as CCY
import qualified Data.Map.NonEmpty as NEM
class Inject t => Interpret t f where
retract :: t f ~> f
retract = (f ~> f) -> t f ~> f
forall {k} (t :: (k -> *) -> k -> *) (f :: k -> *) (g :: k -> *).
Interpret t f =>
(g ~> f) -> t g ~> f
forall (g :: k -> *). (g ~> f) -> t g ~> f
interpret f x -> f x
f ~> f
forall a. a -> a
id
interpret :: (g ~> f) -> t g ~> f
interpret g ~> f
f = t f x -> f x
t f ~> f
forall {k} (t :: (k -> *) -> k -> *) (f :: k -> *).
Interpret t f =>
t f ~> f
retract (t f x -> f x) -> (t g x -> t f x) -> t g x -> f x
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (g ~> f) -> t g ~> t f
forall {k} {k1} (t :: (k -> *) -> k1 -> *) (f :: k -> *)
(g :: k -> *).
HFunctor t =>
(f ~> g) -> t f ~> t g
forall (f :: k -> *) (g :: k -> *). (f ~> g) -> t f ~> t g
hmap g x -> f x
g ~> f
f
{-# MINIMAL retract | interpret #-}
forI
:: Interpret t f
=> t g a
-> (g ~> f)
-> f a
forI :: forall {k} (t :: (k -> *) -> k -> *) (f :: k -> *) (g :: k -> *)
(a :: k).
Interpret t f =>
t g a -> (g ~> f) -> f a
forI t g a
x g ~> f
f = (g ~> f) -> t g ~> f
forall {k} (t :: (k -> *) -> k -> *) (f :: k -> *) (g :: k -> *).
Interpret t f =>
(g ~> f) -> t g ~> f
forall (g :: k -> *). (g ~> f) -> t g ~> f
interpret g x -> f x
g ~> f
f t g a
x
iget
:: Interpret t (AltConst b)
=> (forall x. f x -> b)
-> t f a
-> b
iget :: forall {k} (t :: (k -> *) -> k -> *) b (f :: k -> *) (a :: k).
Interpret t (AltConst b) =>
(forall (x :: k). f x -> b) -> t f a -> b
iget forall (x :: k). f x -> b
f = AltConst b a -> b
forall {k} w (a :: k). AltConst w a -> w
getAltConst (AltConst b a -> b) -> (t f a -> AltConst b a) -> t f a -> b
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (f ~> AltConst b) -> t f ~> AltConst b
forall {k} (t :: (k -> *) -> k -> *) (f :: k -> *) (g :: k -> *).
Interpret t f =>
(g ~> f) -> t g ~> f
forall (g :: k -> *). (g ~> AltConst b) -> t g ~> AltConst b
interpret (b -> AltConst b x
forall {k} w (a :: k). w -> AltConst w a
AltConst (b -> AltConst b x) -> (f x -> b) -> f x -> AltConst b x
forall b c a. (b -> c) -> (a -> b) -> a -> c
. f x -> b
forall (x :: k). f x -> b
f)
getI :: Interpret t (AltConst b) => (forall x. f x -> b) -> t f a -> b
getI :: forall {k} (t :: (k -> *) -> k -> *) b (f :: k -> *) (a :: k).
Interpret t (AltConst b) =>
(forall (x :: k). f x -> b) -> t f a -> b
getI = (forall (x :: k). f x -> b) -> t f a -> b
forall {k} (t :: (k -> *) -> k -> *) b (f :: k -> *) (a :: k).
Interpret t (AltConst b) =>
(forall (x :: k). f x -> b) -> t f a -> b
iget
{-# DEPRECATED getI "Use iget instead" #-}
icollect
:: (forall m. Monoid m => Interpret t (AltConst m))
=> (forall x. f x -> b)
-> t f a
-> [b]
icollect :: forall {k} (t :: (k -> *) -> k -> *) (f :: k -> *) b (a :: k).
(forall m. Monoid m => Interpret t (AltConst m)) =>
(forall (x :: k). f x -> b) -> t f a -> [b]
icollect forall (x :: k). f x -> b
f = (Endo [b] -> [b] -> [b]) -> [b] -> Endo [b] -> [b]
forall a b c. (a -> b -> c) -> b -> a -> c
flip Endo [b] -> [b] -> [b]
forall a. Endo a -> a -> a
appEndo [] (Endo [b] -> [b]) -> (t f a -> Endo [b]) -> t f a -> [b]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (forall (x :: k). f x -> Endo [b]) -> t f a -> Endo [b]
forall {k} (t :: (k -> *) -> k -> *) b (f :: k -> *) (a :: k).
Interpret t (AltConst b) =>
(forall (x :: k). f x -> b) -> t f a -> b
iget (([b] -> [b]) -> Endo [b]
forall a. (a -> a) -> Endo a
Endo (([b] -> [b]) -> Endo [b])
-> (f x -> [b] -> [b]) -> f x -> Endo [b]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (:) (b -> [b] -> [b]) -> (f x -> b) -> f x -> [b] -> [b]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. f x -> b
forall (x :: k). f x -> b
f)
collectI :: (forall m. Monoid m => Interpret t (AltConst m)) => (forall x. f x -> b) -> t f a -> [b]
collectI :: forall {k} (t :: (k -> *) -> k -> *) (f :: k -> *) b (a :: k).
(forall m. Monoid m => Interpret t (AltConst m)) =>
(forall (x :: k). f x -> b) -> t f a -> [b]
collectI = (forall (x :: k). f x -> b) -> t f a -> [b]
forall {k} (t :: (k -> *) -> k -> *) (f :: k -> *) b (a :: k).
(forall m. Monoid m => Interpret t (AltConst m)) =>
(forall (x :: k). f x -> b) -> t f a -> [b]
icollect
{-# DEPRECATED collectI "Use icollect instead" #-}
icollect1
:: (forall m. Semigroup m => Interpret t (AltConst m))
=> (forall x. f x -> b)
-> t f a
-> NonEmpty b
icollect1 :: forall {k} (t :: (k -> *) -> k -> *) (f :: k -> *) b (a :: k).
(forall m. Semigroup m => Interpret t (AltConst m)) =>
(forall (x :: k). f x -> b) -> t f a -> NonEmpty b
icollect1 forall (x :: k). f x -> b
f = NDL b -> NonEmpty b
forall a. NDL a -> NonEmpty a
fromNDL (NDL b -> NonEmpty b) -> (t f a -> NDL b) -> t f a -> NonEmpty b
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (forall (x :: k). f x -> NDL b) -> t f a -> NDL b
forall {k} (t :: (k -> *) -> k -> *) b (f :: k -> *) (a :: k).
Interpret t (AltConst b) =>
(forall (x :: k). f x -> b) -> t f a -> b
iget (b -> NDL b
forall a. a -> NDL a
ndlSingleton (b -> NDL b) -> (f x -> b) -> f x -> NDL b
forall b c a. (b -> c) -> (a -> b) -> a -> c
. f x -> b
forall (x :: k). f x -> b
f)
itraverse
:: (Functor h, Interpret t (Comp h (t g)))
=> (forall x. f x -> h (g x))
-> t f a
-> h (t g a)
itraverse :: forall {k} (h :: * -> *) (t :: (k -> *) -> k -> *) (g :: k -> *)
(f :: k -> *) (a :: k).
(Functor h, Interpret t (Comp h (t g))) =>
(forall (x :: k). f x -> h (g x)) -> t f a -> h (t g a)
itraverse forall (x :: k). f x -> h (g x)
f = Comp h (t g) a -> h (t g a)
forall {k} (f :: * -> *) (g :: k -> *) (a :: k).
Functor f =>
Comp f g a -> f (g a)
unComp (Comp h (t g) a -> h (t g a))
-> (t f a -> Comp h (t g) a) -> t f a -> h (t g a)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (f ~> Comp h (t g)) -> t f ~> Comp h (t g)
forall {k} (t :: (k -> *) -> k -> *) (f :: k -> *) (g :: k -> *).
Interpret t f =>
(g ~> f) -> t g ~> f
forall (g :: k -> *). (g ~> Comp h (t g)) -> t g ~> Comp h (t g)
interpret (\f x
x -> f x -> h (g x)
forall (x :: k). f x -> h (g x)
f f x
x h (g x) -> (g x -> t g x) -> Comp h (t g) x
forall {k} (f :: * -> *) (g :: k -> *) (a :: k) x.
f x -> (x -> g a) -> Comp f g a
:>>= g x -> t g x
forall {k} (t :: (k -> *) -> k -> *) (f :: k -> *).
Inject t =>
f ~> t f
forall (f :: k -> *). f ~> t f
inject)
iapply
:: Interpret t (Op b)
=> (forall x. f x -> x -> b)
-> t f a
-> a
-> b
iapply :: forall (t :: (* -> *) -> * -> *) b (f :: * -> *) a.
Interpret t (Op b) =>
(forall x. f x -> x -> b) -> t f a -> a -> b
iapply forall x. f x -> x -> b
f = Op b a -> a -> b
forall a b. Op a b -> b -> a
getOp (Op b a -> a -> b) -> (t f a -> Op b a) -> t f a -> a -> b
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (f ~> Op b) -> t f ~> Op b
forall {k} (t :: (k -> *) -> k -> *) (f :: k -> *) (g :: k -> *).
Interpret t f =>
(g ~> f) -> t g ~> f
forall (g :: * -> *). (g ~> Op b) -> t g ~> Op b
interpret ((x -> b) -> Op b x
forall a b. (b -> a) -> Op a b
Op ((x -> b) -> Op b x) -> (f x -> x -> b) -> f x -> Op b x
forall b c a. (b -> c) -> (a -> b) -> a -> c
. f x -> x -> b
forall x. f x -> x -> b
f)
ifanout
:: (forall m. Monoid m => Interpret t (Op m))
=> (forall x. f x -> x -> b)
-> t f a
-> a
-> [b]
ifanout :: forall (t :: (* -> *) -> * -> *) (f :: * -> *) b a.
(forall m. Monoid m => Interpret t (Op m)) =>
(forall x. f x -> x -> b) -> t f a -> a -> [b]
ifanout forall x. f x -> x -> b
f t f a
t = (Endo [b] -> [b] -> [b]) -> [b] -> Endo [b] -> [b]
forall a b c. (a -> b -> c) -> b -> a -> c
flip Endo [b] -> [b] -> [b]
forall a. Endo a -> a -> a
appEndo [] (Endo [b] -> [b]) -> (a -> Endo [b]) -> a -> [b]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (forall x. f x -> x -> Endo [b]) -> t f a -> a -> Endo [b]
forall (t :: (* -> *) -> * -> *) b (f :: * -> *) a.
Interpret t (Op b) =>
(forall x. f x -> x -> b) -> t f a -> a -> b
iapply (\f x
x x
y -> ([b] -> [b]) -> Endo [b]
forall a. (a -> a) -> Endo a
Endo (f x -> x -> b
forall x. f x -> x -> b
f f x
x x
y b -> [b] -> [b]
forall a. a -> [a] -> [a]
:)) t f a
t
ifanout1
:: (forall m. Semigroup m => Interpret t (Op m))
=> (forall x. f x -> x -> b)
-> t f a
-> a
-> NonEmpty b
ifanout1 :: forall (t :: (* -> *) -> * -> *) (f :: * -> *) b a.
(forall m. Semigroup m => Interpret t (Op m)) =>
(forall x. f x -> x -> b) -> t f a -> a -> NonEmpty b
ifanout1 forall x. f x -> x -> b
f t f a
t = NDL b -> NonEmpty b
forall a. NDL a -> NonEmpty a
fromNDL (NDL b -> NonEmpty b) -> (a -> NDL b) -> a -> NonEmpty b
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (forall x. f x -> x -> NDL b) -> t f a -> a -> NDL b
forall (t :: (* -> *) -> * -> *) b (f :: * -> *) a.
Interpret t (Op b) =>
(forall x. f x -> x -> b) -> t f a -> a -> b
iapply (\f x
x -> b -> NDL b
forall a. a -> NDL a
ndlSingleton (b -> NDL b) -> (x -> b) -> x -> NDL b
forall b c a. (b -> c) -> (a -> b) -> a -> c
. f x -> x -> b
forall x. f x -> x -> b
f f x
x) t f a
t
newtype AltConst w a = AltConst { forall {k} w (a :: k). AltConst w a -> w
getAltConst :: w }
deriving (Int -> AltConst w a -> ShowS
[AltConst w a] -> ShowS
AltConst w a -> String
(Int -> AltConst w a -> ShowS)
-> (AltConst w a -> String)
-> ([AltConst w a] -> ShowS)
-> Show (AltConst w a)
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
forall w k (a :: k). Show w => Int -> AltConst w a -> ShowS
forall w k (a :: k). Show w => [AltConst w a] -> ShowS
forall w k (a :: k). Show w => AltConst w a -> String
$cshowsPrec :: forall w k (a :: k). Show w => Int -> AltConst w a -> ShowS
showsPrec :: Int -> AltConst w a -> ShowS
$cshow :: forall w k (a :: k). Show w => AltConst w a -> String
show :: AltConst w a -> String
$cshowList :: forall w k (a :: k). Show w => [AltConst w a] -> ShowS
showList :: [AltConst w a] -> ShowS
Show, AltConst w a -> AltConst w a -> Bool
(AltConst w a -> AltConst w a -> Bool)
-> (AltConst w a -> AltConst w a -> Bool) -> Eq (AltConst w a)
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
forall w k (a :: k). Eq w => AltConst w a -> AltConst w a -> Bool
$c== :: forall w k (a :: k). Eq w => AltConst w a -> AltConst w a -> Bool
== :: AltConst w a -> AltConst w a -> Bool
$c/= :: forall w k (a :: k). Eq w => AltConst w a -> AltConst w a -> Bool
/= :: AltConst w a -> AltConst w a -> Bool
Eq, Eq (AltConst w a)
Eq (AltConst w a) =>
(AltConst w a -> AltConst w a -> Ordering)
-> (AltConst w a -> AltConst w a -> Bool)
-> (AltConst w a -> AltConst w a -> Bool)
-> (AltConst w a -> AltConst w a -> Bool)
-> (AltConst w a -> AltConst w a -> Bool)
-> (AltConst w a -> AltConst w a -> AltConst w a)
-> (AltConst w a -> AltConst w a -> AltConst w a)
-> Ord (AltConst w a)
AltConst w a -> AltConst w a -> Bool
AltConst w a -> AltConst w a -> Ordering
AltConst w a -> AltConst w a -> AltConst w a
forall a.
Eq a =>
(a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
forall w k (a :: k). Ord w => Eq (AltConst w a)
forall w k (a :: k). Ord w => AltConst w a -> AltConst w a -> Bool
forall w k (a :: k).
Ord w =>
AltConst w a -> AltConst w a -> Ordering
forall w k (a :: k).
Ord w =>
AltConst w a -> AltConst w a -> AltConst w a
$ccompare :: forall w k (a :: k).
Ord w =>
AltConst w a -> AltConst w a -> Ordering
compare :: AltConst w a -> AltConst w a -> Ordering
$c< :: forall w k (a :: k). Ord w => AltConst w a -> AltConst w a -> Bool
< :: AltConst w a -> AltConst w a -> Bool
$c<= :: forall w k (a :: k). Ord w => AltConst w a -> AltConst w a -> Bool
<= :: AltConst w a -> AltConst w a -> Bool
$c> :: forall w k (a :: k). Ord w => AltConst w a -> AltConst w a -> Bool
> :: AltConst w a -> AltConst w a -> Bool
$c>= :: forall w k (a :: k). Ord w => AltConst w a -> AltConst w a -> Bool
>= :: AltConst w a -> AltConst w a -> Bool
$cmax :: forall w k (a :: k).
Ord w =>
AltConst w a -> AltConst w a -> AltConst w a
max :: AltConst w a -> AltConst w a -> AltConst w a
$cmin :: forall w k (a :: k).
Ord w =>
AltConst w a -> AltConst w a -> AltConst w a
min :: AltConst w a -> AltConst w a -> AltConst w a
Ord, (forall x. AltConst w a -> Rep (AltConst w a) x)
-> (forall x. Rep (AltConst w a) x -> AltConst w a)
-> Generic (AltConst w a)
forall x. Rep (AltConst w a) x -> AltConst w a
forall x. AltConst w a -> Rep (AltConst w a) x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
forall w k (a :: k) x. Rep (AltConst w a) x -> AltConst w a
forall w k (a :: k) x. AltConst w a -> Rep (AltConst w a) x
$cfrom :: forall w k (a :: k) x. AltConst w a -> Rep (AltConst w a) x
from :: forall x. AltConst w a -> Rep (AltConst w a) x
$cto :: forall w k (a :: k) x. Rep (AltConst w a) x -> AltConst w a
to :: forall x. Rep (AltConst w a) x -> AltConst w a
Generic, (forall a b. (a -> b) -> AltConst w a -> AltConst w b)
-> (forall a b. a -> AltConst w b -> AltConst w a)
-> Functor (AltConst w)
forall a b. a -> AltConst w b -> AltConst w a
forall a b. (a -> b) -> AltConst w a -> AltConst w b
forall w a b. a -> AltConst w b -> AltConst w a
forall w a b. (a -> b) -> AltConst w a -> AltConst w b
forall (f :: * -> *).
(forall a b. (a -> b) -> f a -> f b)
-> (forall a b. a -> f b -> f a) -> Functor f
$cfmap :: forall w a b. (a -> b) -> AltConst w a -> AltConst w b
fmap :: forall a b. (a -> b) -> AltConst w a -> AltConst w b
$c<$ :: forall w a b. a -> AltConst w b -> AltConst w a
<$ :: forall a b. a -> AltConst w b -> AltConst w a
Functor, (forall m. Monoid m => AltConst w m -> m)
-> (forall m a. Monoid m => (a -> m) -> AltConst w a -> m)
-> (forall m a. Monoid m => (a -> m) -> AltConst w a -> m)
-> (forall a b. (a -> b -> b) -> b -> AltConst w a -> b)
-> (forall a b. (a -> b -> b) -> b -> AltConst w a -> b)
-> (forall b a. (b -> a -> b) -> b -> AltConst w a -> b)
-> (forall b a. (b -> a -> b) -> b -> AltConst w a -> b)
-> (forall a. (a -> a -> a) -> AltConst w a -> a)
-> (forall a. (a -> a -> a) -> AltConst w a -> a)
-> (forall a. AltConst w a -> [a])
-> (forall a. AltConst w a -> Bool)
-> (forall a. AltConst w a -> Int)
-> (forall a. Eq a => a -> AltConst w a -> Bool)
-> (forall a. Ord a => AltConst w a -> a)
-> (forall a. Ord a => AltConst w a -> a)
-> (forall a. Num a => AltConst w a -> a)
-> (forall a. Num a => AltConst w a -> a)
-> Foldable (AltConst w)
forall a. Eq a => a -> AltConst w a -> Bool
forall a. Num a => AltConst w a -> a
forall a. Ord a => AltConst w a -> a
forall m. Monoid m => AltConst w m -> m
forall a. AltConst w a -> Bool
forall a. AltConst w a -> Int
forall a. AltConst w a -> [a]
forall a. (a -> a -> a) -> AltConst w a -> a
forall w a. Eq a => a -> AltConst w a -> Bool
forall w a. Num a => AltConst w a -> a
forall w a. Ord a => AltConst w a -> a
forall m a. Monoid m => (a -> m) -> AltConst w a -> m
forall w m. Monoid m => AltConst w m -> m
forall w a. AltConst w a -> Bool
forall w a. AltConst w a -> Int
forall w a. AltConst w a -> [a]
forall b a. (b -> a -> b) -> b -> AltConst w a -> b
forall a b. (a -> b -> b) -> b -> AltConst w a -> b
forall w a. (a -> a -> a) -> AltConst w a -> a
forall w m a. Monoid m => (a -> m) -> AltConst w a -> m
forall w b a. (b -> a -> b) -> b -> AltConst w a -> b
forall w a b. (a -> b -> b) -> b -> AltConst w a -> b
forall (t :: * -> *).
(forall m. Monoid m => t m -> m)
-> (forall m a. Monoid m => (a -> m) -> t a -> m)
-> (forall m a. Monoid m => (a -> m) -> t a -> m)
-> (forall a b. (a -> b -> b) -> b -> t a -> b)
-> (forall a b. (a -> b -> b) -> b -> t a -> b)
-> (forall b a. (b -> a -> b) -> b -> t a -> b)
-> (forall b a. (b -> a -> b) -> b -> t a -> b)
-> (forall a. (a -> a -> a) -> t a -> a)
-> (forall a. (a -> a -> a) -> t a -> a)
-> (forall a. t a -> [a])
-> (forall a. t a -> Bool)
-> (forall a. t a -> Int)
-> (forall a. Eq a => a -> t a -> Bool)
-> (forall a. Ord a => t a -> a)
-> (forall a. Ord a => t a -> a)
-> (forall a. Num a => t a -> a)
-> (forall a. Num a => t a -> a)
-> Foldable t
$cfold :: forall w m. Monoid m => AltConst w m -> m
fold :: forall m. Monoid m => AltConst w m -> m
$cfoldMap :: forall w m a. Monoid m => (a -> m) -> AltConst w a -> m
foldMap :: forall m a. Monoid m => (a -> m) -> AltConst w a -> m
$cfoldMap' :: forall w m a. Monoid m => (a -> m) -> AltConst w a -> m
foldMap' :: forall m a. Monoid m => (a -> m) -> AltConst w a -> m
$cfoldr :: forall w a b. (a -> b -> b) -> b -> AltConst w a -> b
foldr :: forall a b. (a -> b -> b) -> b -> AltConst w a -> b
$cfoldr' :: forall w a b. (a -> b -> b) -> b -> AltConst w a -> b
foldr' :: forall a b. (a -> b -> b) -> b -> AltConst w a -> b
$cfoldl :: forall w b a. (b -> a -> b) -> b -> AltConst w a -> b
foldl :: forall b a. (b -> a -> b) -> b -> AltConst w a -> b
$cfoldl' :: forall w b a. (b -> a -> b) -> b -> AltConst w a -> b
foldl' :: forall b a. (b -> a -> b) -> b -> AltConst w a -> b
$cfoldr1 :: forall w a. (a -> a -> a) -> AltConst w a -> a
foldr1 :: forall a. (a -> a -> a) -> AltConst w a -> a
$cfoldl1 :: forall w a. (a -> a -> a) -> AltConst w a -> a
foldl1 :: forall a. (a -> a -> a) -> AltConst w a -> a
$ctoList :: forall w a. AltConst w a -> [a]
toList :: forall a. AltConst w a -> [a]
$cnull :: forall w a. AltConst w a -> Bool
null :: forall a. AltConst w a -> Bool
$clength :: forall w a. AltConst w a -> Int
length :: forall a. AltConst w a -> Int
$celem :: forall w a. Eq a => a -> AltConst w a -> Bool
elem :: forall a. Eq a => a -> AltConst w a -> Bool
$cmaximum :: forall w a. Ord a => AltConst w a -> a
maximum :: forall a. Ord a => AltConst w a -> a
$cminimum :: forall w a. Ord a => AltConst w a -> a
minimum :: forall a. Ord a => AltConst w a -> a
$csum :: forall w a. Num a => AltConst w a -> a
sum :: forall a. Num a => AltConst w a -> a
$cproduct :: forall w a. Num a => AltConst w a -> a
product :: forall a. Num a => AltConst w a -> a
Foldable, Functor (AltConst w)
Foldable (AltConst w)
(Functor (AltConst w), Foldable (AltConst w)) =>
(forall (f :: * -> *) a b.
Applicative f =>
(a -> f b) -> AltConst w a -> f (AltConst w b))
-> (forall (f :: * -> *) a.
Applicative f =>
AltConst w (f a) -> f (AltConst w a))
-> (forall (m :: * -> *) a b.
Monad m =>
(a -> m b) -> AltConst w a -> m (AltConst w b))
-> (forall (m :: * -> *) a.
Monad m =>
AltConst w (m a) -> m (AltConst w a))
-> Traversable (AltConst w)
forall w. Functor (AltConst w)
forall w. Foldable (AltConst w)
forall w (m :: * -> *) a.
Monad m =>
AltConst w (m a) -> m (AltConst w a)
forall w (f :: * -> *) a.
Applicative f =>
AltConst w (f a) -> f (AltConst w a)
forall w (m :: * -> *) a b.
Monad m =>
(a -> m b) -> AltConst w a -> m (AltConst w b)
forall w (f :: * -> *) a b.
Applicative f =>
(a -> f b) -> AltConst w a -> f (AltConst w b)
forall (t :: * -> *).
(Functor t, Foldable t) =>
(forall (f :: * -> *) a b.
Applicative f =>
(a -> f b) -> t a -> f (t b))
-> (forall (f :: * -> *) a. Applicative f => t (f a) -> f (t a))
-> (forall (m :: * -> *) a b.
Monad m =>
(a -> m b) -> t a -> m (t b))
-> (forall (m :: * -> *) a. Monad m => t (m a) -> m (t a))
-> Traversable t
forall (m :: * -> *) a.
Monad m =>
AltConst w (m a) -> m (AltConst w a)
forall (f :: * -> *) a.
Applicative f =>
AltConst w (f a) -> f (AltConst w a)
forall (m :: * -> *) a b.
Monad m =>
(a -> m b) -> AltConst w a -> m (AltConst w b)
forall (f :: * -> *) a b.
Applicative f =>
(a -> f b) -> AltConst w a -> f (AltConst w b)
$ctraverse :: forall w (f :: * -> *) a b.
Applicative f =>
(a -> f b) -> AltConst w a -> f (AltConst w b)
traverse :: forall (f :: * -> *) a b.
Applicative f =>
(a -> f b) -> AltConst w a -> f (AltConst w b)
$csequenceA :: forall w (f :: * -> *) a.
Applicative f =>
AltConst w (f a) -> f (AltConst w a)
sequenceA :: forall (f :: * -> *) a.
Applicative f =>
AltConst w (f a) -> f (AltConst w a)
$cmapM :: forall w (m :: * -> *) a b.
Monad m =>
(a -> m b) -> AltConst w a -> m (AltConst w b)
mapM :: forall (m :: * -> *) a b.
Monad m =>
(a -> m b) -> AltConst w a -> m (AltConst w b)
$csequence :: forall w (m :: * -> *) a.
Monad m =>
AltConst w (m a) -> m (AltConst w a)
sequence :: forall (m :: * -> *) a.
Monad m =>
AltConst w (m a) -> m (AltConst w a)
Traversable, Typeable (AltConst w a)
Typeable (AltConst w a) =>
(forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> AltConst w a -> c (AltConst w a))
-> (forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c (AltConst w a))
-> (AltConst w a -> Constr)
-> (AltConst w a -> DataType)
-> (forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c (AltConst w a)))
-> (forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c (AltConst w a)))
-> ((forall b. Data b => b -> b) -> AltConst w a -> AltConst w a)
-> (forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> AltConst w a -> r)
-> (forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> AltConst w a -> r)
-> (forall u. (forall d. Data d => d -> u) -> AltConst w a -> [u])
-> (forall u.
Int -> (forall d. Data d => d -> u) -> AltConst w a -> u)
-> (forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> AltConst w a -> m (AltConst w a))
-> (forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> AltConst w a -> m (AltConst w a))
-> (forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> AltConst w a -> m (AltConst w a))
-> Data (AltConst w a)
AltConst w a -> Constr
AltConst w a -> DataType
(forall b. Data b => b -> b) -> AltConst w a -> AltConst w a
forall a.
Typeable a =>
(forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> a -> c a)
-> (forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c a)
-> (a -> Constr)
-> (a -> DataType)
-> (forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c a))
-> (forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c a))
-> ((forall b. Data b => b -> b) -> a -> a)
-> (forall r r'.
(r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> a -> r)
-> (forall r r'.
(r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> a -> r)
-> (forall u. (forall d. Data d => d -> u) -> a -> [u])
-> (forall u. Int -> (forall d. Data d => d -> u) -> a -> u)
-> (forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> a -> m a)
-> (forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> a -> m a)
-> (forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> a -> m a)
-> Data a
forall u. Int -> (forall d. Data d => d -> u) -> AltConst w a -> u
forall u. (forall d. Data d => d -> u) -> AltConst w a -> [u]
forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> AltConst w a -> r
forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> AltConst w a -> r
forall w k (a :: k).
(Typeable a, Typeable k, Data w) =>
Typeable (AltConst w a)
forall w k (a :: k).
(Typeable a, Typeable k, Data w) =>
AltConst w a -> Constr
forall w k (a :: k).
(Typeable a, Typeable k, Data w) =>
AltConst w a -> DataType
forall w k (a :: k).
(Typeable a, Typeable k, Data w) =>
(forall b. Data b => b -> b) -> AltConst w a -> AltConst w a
forall w k (a :: k) u.
(Typeable a, Typeable k, Data w) =>
Int -> (forall d. Data d => d -> u) -> AltConst w a -> u
forall w k (a :: k) u.
(Typeable a, Typeable k, Data w) =>
(forall d. Data d => d -> u) -> AltConst w a -> [u]
forall w k (a :: k) r r'.
(Typeable a, Typeable k, Data w) =>
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> AltConst w a -> r
forall w k (a :: k) r r'.
(Typeable a, Typeable k, Data w) =>
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> AltConst w a -> r
forall w k (a :: k) (m :: * -> *).
(Typeable a, Typeable k, Data w, Monad m) =>
(forall d. Data d => d -> m d) -> AltConst w a -> m (AltConst w a)
forall w k (a :: k) (m :: * -> *).
(Typeable a, Typeable k, Data w, MonadPlus m) =>
(forall d. Data d => d -> m d) -> AltConst w a -> m (AltConst w a)
forall w k (a :: k) (c :: * -> *).
(Typeable a, Typeable k, Data w) =>
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c (AltConst w a)
forall w k (a :: k) (c :: * -> *).
(Typeable a, Typeable k, Data w) =>
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> AltConst w a -> c (AltConst w a)
forall w k (a :: k) (t :: * -> *) (c :: * -> *).
(Typeable a, Typeable k, Data w, Typeable t) =>
(forall d. Data d => c (t d)) -> Maybe (c (AltConst w a))
forall w k (a :: k) (t :: * -> * -> *) (c :: * -> *).
(Typeable a, Typeable k, Data w, Typeable t) =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c (AltConst w a))
forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> AltConst w a -> m (AltConst w a)
forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> AltConst w a -> m (AltConst w a)
forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c (AltConst w a)
forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> AltConst w a -> c (AltConst w a)
forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c (AltConst w a))
forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c (AltConst w a))
$cgfoldl :: forall w k (a :: k) (c :: * -> *).
(Typeable a, Typeable k, Data w) =>
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> AltConst w a -> c (AltConst w a)
gfoldl :: forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> AltConst w a -> c (AltConst w a)
$cgunfold :: forall w k (a :: k) (c :: * -> *).
(Typeable a, Typeable k, Data w) =>
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c (AltConst w a)
gunfold :: forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c (AltConst w a)
$ctoConstr :: forall w k (a :: k).
(Typeable a, Typeable k, Data w) =>
AltConst w a -> Constr
toConstr :: AltConst w a -> Constr
$cdataTypeOf :: forall w k (a :: k).
(Typeable a, Typeable k, Data w) =>
AltConst w a -> DataType
dataTypeOf :: AltConst w a -> DataType
$cdataCast1 :: forall w k (a :: k) (t :: * -> *) (c :: * -> *).
(Typeable a, Typeable k, Data w, Typeable t) =>
(forall d. Data d => c (t d)) -> Maybe (c (AltConst w a))
dataCast1 :: forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c (AltConst w a))
$cdataCast2 :: forall w k (a :: k) (t :: * -> * -> *) (c :: * -> *).
(Typeable a, Typeable k, Data w, Typeable t) =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c (AltConst w a))
dataCast2 :: forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c (AltConst w a))
$cgmapT :: forall w k (a :: k).
(Typeable a, Typeable k, Data w) =>
(forall b. Data b => b -> b) -> AltConst w a -> AltConst w a
gmapT :: (forall b. Data b => b -> b) -> AltConst w a -> AltConst w a
$cgmapQl :: forall w k (a :: k) r r'.
(Typeable a, Typeable k, Data w) =>
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> AltConst w a -> r
gmapQl :: forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> AltConst w a -> r
$cgmapQr :: forall w k (a :: k) r r'.
(Typeable a, Typeable k, Data w) =>
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> AltConst w a -> r
gmapQr :: forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> AltConst w a -> r
$cgmapQ :: forall w k (a :: k) u.
(Typeable a, Typeable k, Data w) =>
(forall d. Data d => d -> u) -> AltConst w a -> [u]
gmapQ :: forall u. (forall d. Data d => d -> u) -> AltConst w a -> [u]
$cgmapQi :: forall w k (a :: k) u.
(Typeable a, Typeable k, Data w) =>
Int -> (forall d. Data d => d -> u) -> AltConst w a -> u
gmapQi :: forall u. Int -> (forall d. Data d => d -> u) -> AltConst w a -> u
$cgmapM :: forall w k (a :: k) (m :: * -> *).
(Typeable a, Typeable k, Data w, Monad m) =>
(forall d. Data d => d -> m d) -> AltConst w a -> m (AltConst w a)
gmapM :: forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> AltConst w a -> m (AltConst w a)
$cgmapMp :: forall w k (a :: k) (m :: * -> *).
(Typeable a, Typeable k, Data w, MonadPlus m) =>
(forall d. Data d => d -> m d) -> AltConst w a -> m (AltConst w a)
gmapMp :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> AltConst w a -> m (AltConst w a)
$cgmapMo :: forall w k (a :: k) (m :: * -> *).
(Typeable a, Typeable k, Data w, MonadPlus m) =>
(forall d. Data d => d -> m d) -> AltConst w a -> m (AltConst w a)
gmapMo :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> AltConst w a -> m (AltConst w a)
Data)
instance Show w => Show1 (AltConst w) where
liftShowsPrec :: forall a.
(Int -> a -> ShowS)
-> ([a] -> ShowS) -> Int -> AltConst w a -> ShowS
liftShowsPrec Int -> a -> ShowS
_ [a] -> ShowS
_ Int
d (AltConst w
x) = (Int -> w -> ShowS) -> String -> Int -> w -> ShowS
forall a. (Int -> a -> ShowS) -> String -> Int -> a -> ShowS
showsUnaryWith Int -> w -> ShowS
forall a. Show a => Int -> a -> ShowS
showsPrec String
"AltConst" Int
d w
x
instance Eq w => Eq1 (AltConst w) where
liftEq :: forall a b.
(a -> b -> Bool) -> AltConst w a -> AltConst w b -> Bool
liftEq a -> b -> Bool
_ (AltConst w
x) (AltConst w
y) = w
x w -> w -> Bool
forall a. Eq a => a -> a -> Bool
== w
y
instance Ord w => Ord1 (AltConst w) where
liftCompare :: forall a b.
(a -> b -> Ordering) -> AltConst w a -> AltConst w b -> Ordering
liftCompare a -> b -> Ordering
_ (AltConst w
x) (AltConst w
y) = w -> w -> Ordering
forall a. Ord a => a -> a -> Ordering
compare w
x w
y
instance Contravariant (AltConst w) where
contramap :: forall a' a. (a' -> a) -> AltConst w a -> AltConst w a'
contramap a' -> a
_ = AltConst w a -> AltConst w a'
forall a b. Coercible a b => a -> b
coerce
instance Invariant (AltConst w) where
invmap :: forall a b. (a -> b) -> (b -> a) -> AltConst w a -> AltConst w b
invmap a -> b
_ b -> a
_ = AltConst w a -> AltConst w b
forall a b. Coercible a b => a -> b
coerce
instance Semigroup w => Apply (AltConst w) where
AltConst w
x <.> :: forall a b. AltConst w (a -> b) -> AltConst w a -> AltConst w b
<.> AltConst w
y = w -> AltConst w b
forall {k} w (a :: k). w -> AltConst w a
AltConst (w
x w -> w -> w
forall a. Semigroup a => a -> a -> a
<> w
y)
instance Monoid w => Applicative (AltConst w) where
<*> :: forall a b. AltConst w (a -> b) -> AltConst w a -> AltConst w b
(<*>) = AltConst w (a -> b) -> AltConst w a -> AltConst w b
forall a b. AltConst w (a -> b) -> AltConst w a -> AltConst w b
forall (f :: * -> *) a b. Apply f => f (a -> b) -> f a -> f b
(<.>)
pure :: forall a. a -> AltConst w a
pure a
_ = w -> AltConst w a
forall {k} w (a :: k). w -> AltConst w a
AltConst w
forall a. Monoid a => a
mempty
instance Semigroup w => Alt (AltConst w) where
AltConst w
x <!> :: forall a. AltConst w a -> AltConst w a -> AltConst w a
<!> AltConst w
y = w -> AltConst w a
forall {k} w (a :: k). w -> AltConst w a
AltConst (w
x w -> w -> w
forall a. Semigroup a => a -> a -> a
<> w
y)
instance Monoid w => Plus (AltConst w) where
zero :: forall a. AltConst w a
zero = w -> AltConst w a
forall {k} w (a :: k). w -> AltConst w a
AltConst w
forall a. Monoid a => a
mempty
instance Semigroup w => Divise (AltConst w) where
divise :: forall a b c.
(a -> (b, c)) -> AltConst w b -> AltConst w c -> AltConst w a
divise a -> (b, c)
_ (AltConst w
x) (AltConst w
y) = w -> AltConst w a
forall {k} w (a :: k). w -> AltConst w a
AltConst (w
x w -> w -> w
forall a. Semigroup a => a -> a -> a
<> w
y)
instance Monoid w => Divisible (AltConst w) where
divide :: forall a b c.
(a -> (b, c)) -> AltConst w b -> AltConst w c -> AltConst w a
divide = (a -> (b, c)) -> AltConst w b -> AltConst w c -> AltConst w a
forall a b c.
(a -> (b, c)) -> AltConst w b -> AltConst w c -> AltConst w a
forall (f :: * -> *) a b c.
Divise f =>
(a -> (b, c)) -> f b -> f c -> f a
divise
conquer :: forall a. AltConst w a
conquer = w -> AltConst w a
forall {k} w (a :: k). w -> AltConst w a
AltConst w
forall a. Monoid a => a
mempty
instance Semigroup w => Decide (AltConst w) where
decide :: forall a b c.
(a -> Either b c) -> AltConst w b -> AltConst w c -> AltConst w a
decide a -> Either b c
_ (AltConst w
x) (AltConst w
y) = w -> AltConst w a
forall {k} w (a :: k). w -> AltConst w a
AltConst (w
x w -> w -> w
forall a. Semigroup a => a -> a -> a
<> w
y)
instance Monoid w => Conclude (AltConst w) where
conclude :: forall a. (a -> Void) -> AltConst w a
conclude a -> Void
_ = w -> AltConst w a
forall {k} w (a :: k). w -> AltConst w a
AltConst w
forall a. Monoid a => a
mempty
instance Functor f => Interpret Coyoneda f where
retract :: Coyoneda f ~> f
retract = Coyoneda f x -> f x
forall (f :: * -> *) a. Functor f => Coyoneda f a -> f a
lowerCoyoneda
interpret :: forall (g :: * -> *). (g ~> f) -> Coyoneda g ~> f
interpret g ~> f
f (Coyoneda b -> x
g g b
x) = b -> x
g (b -> x) -> f b -> f x
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> g b -> f b
g ~> f
f g b
x
instance Contravariant f => Interpret CCY.Coyoneda f where
retract :: Coyoneda f ~> f
retract = Coyoneda f x -> f x
forall (f :: * -> *) a. Contravariant f => Coyoneda f a -> f a
CCY.lowerCoyoneda
interpret :: forall (g :: * -> *). (g ~> f) -> Coyoneda g ~> f
interpret g ~> f
f (CCY.Coyoneda x -> b
g g b
x) = (x -> b) -> f b -> f x
forall a' a. (a' -> a) -> f a -> f a'
forall (f :: * -> *) a' a.
Contravariant f =>
(a' -> a) -> f a -> f a'
contramap x -> b
g (g b -> f b
g ~> f
f g b
x)
instance Applicative f => Interpret Ap.Ap f where
retract :: Ap f ~> f
retract = \case
Ap.Pure x
x -> x -> f x
forall a. a -> f a
forall (f :: * -> *) a. Applicative f => a -> f a
pure x
x
Ap.Ap f a1
x Ap f (a1 -> x)
xs -> f a1
x f a1 -> f (a1 -> x) -> f x
forall (f :: * -> *) a b. Applicative f => f a -> f (a -> b) -> f b
<**> Ap f (a1 -> x) -> f (a1 -> x)
Ap f ~> f
forall {k} (t :: (k -> *) -> k -> *) (f :: k -> *).
Interpret t f =>
t f ~> f
retract Ap f (a1 -> x)
xs
interpret :: forall (g :: * -> *). (g ~> f) -> Ap g ~> f
interpret g ~> f
f Ap g x
x = (g ~> f) -> Ap g x -> f x
forall (g :: * -> *) (f :: * -> *) a.
Applicative g =>
(forall x. f x -> g x) -> Ap f a -> g a
Ap.runAp g x -> f x
g ~> f
f Ap g x
x
instance Plus f => Interpret ListF f where
retract :: ListF f ~> f
retract = (f x -> f x -> f x) -> f x -> [f x] -> f x
forall a b. (a -> b -> b) -> b -> [a] -> b
forall (t :: * -> *) a b.
Foldable t =>
(a -> b -> b) -> b -> t a -> b
foldr f x -> f x -> f x
forall a. f a -> f a -> f a
forall (f :: * -> *) a. Alt f => f a -> f a -> f a
(<!>) f x
forall a. f a
forall (f :: * -> *) a. Plus f => f a
zero ([f x] -> f x) -> (ListF f x -> [f x]) -> ListF f x -> f x
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ListF f x -> [f x]
forall {k} (f :: k -> *) (a :: k). ListF f a -> [f a]
runListF
interpret :: forall (g :: * -> *). (g ~> f) -> ListF g ~> f
interpret g ~> f
f = (g x -> f x -> f x) -> f x -> [g x] -> f x
forall a b. (a -> b -> b) -> b -> [a] -> b
forall (t :: * -> *) a b.
Foldable t =>
(a -> b -> b) -> b -> t a -> b
foldr (f x -> f x -> f x
forall a. f a -> f a -> f a
forall (f :: * -> *) a. Alt f => f a -> f a -> f a
(<!>) (f x -> f x -> f x) -> (g x -> f x) -> g x -> f x -> f x
forall b c a. (b -> c) -> (a -> b) -> a -> c
. g x -> f x
g ~> f
f) f x
forall a. f a
forall (f :: * -> *) a. Plus f => f a
zero ([g x] -> f x) -> (ListF g x -> [g x]) -> ListF g x -> f x
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ListF g x -> [g x]
forall {k} (f :: k -> *) (a :: k). ListF f a -> [f a]
runListF
instance Alt f => Interpret NonEmptyF f where
retract :: NonEmptyF f ~> f
retract = NonEmpty (f x) -> f x
forall (t :: * -> *) (m :: * -> *) a.
(Foldable1 t, Alt m) =>
t (m a) -> m a
asum1 (NonEmpty (f x) -> f x)
-> (NonEmptyF f x -> NonEmpty (f x)) -> NonEmptyF f x -> f x
forall b c a. (b -> c) -> (a -> b) -> a -> c
. NonEmptyF f x -> NonEmpty (f x)
forall {k} (f :: k -> *) (a :: k). NonEmptyF f a -> NonEmpty (f a)
runNonEmptyF
interpret :: forall (g :: * -> *). (g ~> f) -> NonEmptyF g ~> f
interpret g ~> f
f = NonEmpty (f x) -> f x
forall (t :: * -> *) (m :: * -> *) a.
(Foldable1 t, Alt m) =>
t (m a) -> m a
asum1 (NonEmpty (f x) -> f x)
-> (NonEmptyF g x -> NonEmpty (f x)) -> NonEmptyF g x -> f x
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (g x -> f x) -> NonEmpty (g x) -> NonEmpty (f x)
forall a b. (a -> b) -> NonEmpty a -> NonEmpty b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap g x -> f x
g ~> f
f (NonEmpty (g x) -> NonEmpty (f x))
-> (NonEmptyF g x -> NonEmpty (g x))
-> NonEmptyF g x
-> NonEmpty (f x)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. NonEmptyF g x -> NonEmpty (g x)
forall {k} (f :: k -> *) (a :: k). NonEmptyF f a -> NonEmpty (f a)
runNonEmptyF
instance Plus f => Interpret MaybeF f where
retract :: MaybeF f ~> f
retract = f x -> Maybe (f x) -> f x
forall a. a -> Maybe a -> a
fromMaybe f x
forall a. f a
forall (f :: * -> *) a. Plus f => f a
zero (Maybe (f x) -> f x)
-> (MaybeF f x -> Maybe (f x)) -> MaybeF f x -> f x
forall b c a. (b -> c) -> (a -> b) -> a -> c
. MaybeF f x -> Maybe (f x)
forall {k} (f :: k -> *) (a :: k). MaybeF f a -> Maybe (f a)
runMaybeF
interpret :: forall (g :: * -> *). (g ~> f) -> MaybeF g ~> f
interpret g ~> f
f = f x -> (g x -> f x) -> Maybe (g x) -> f x
forall b a. b -> (a -> b) -> Maybe a -> b
maybe f x
forall a. f a
forall (f :: * -> *) a. Plus f => f a
zero g x -> f x
g ~> f
f (Maybe (g x) -> f x)
-> (MaybeF g x -> Maybe (g x)) -> MaybeF g x -> f x
forall b c a. (b -> c) -> (a -> b) -> a -> c
. MaybeF g x -> Maybe (g x)
forall {k} (f :: k -> *) (a :: k). MaybeF f a -> Maybe (f a)
runMaybeF
instance (Monoid k, Plus f) => Interpret (MapF k) f where
retract :: MapF k f ~> f
retract = (f x -> f x -> f x) -> f x -> Map k (f x) -> f x
forall a b. (a -> b -> b) -> b -> Map k a -> b
forall (t :: * -> *) a b.
Foldable t =>
(a -> b -> b) -> b -> t a -> b
foldr f x -> f x -> f x
forall a. f a -> f a -> f a
forall (f :: * -> *) a. Alt f => f a -> f a -> f a
(<!>) f x
forall a. f a
forall (f :: * -> *) a. Plus f => f a
zero (Map k (f x) -> f x)
-> (MapF k f x -> Map k (f x)) -> MapF k f x -> f x
forall b c a. (b -> c) -> (a -> b) -> a -> c
. MapF k f x -> Map k (f x)
forall {k1} k2 (f :: k1 -> *) (a :: k1).
MapF k2 f a -> Map k2 (f a)
runMapF
interpret :: forall (g :: * -> *). (g ~> f) -> MapF k g ~> f
interpret g ~> f
f = (g x -> f x -> f x) -> f x -> Map k (g x) -> f x
forall a b. (a -> b -> b) -> b -> Map k a -> b
forall (t :: * -> *) a b.
Foldable t =>
(a -> b -> b) -> b -> t a -> b
foldr (f x -> f x -> f x
forall a. f a -> f a -> f a
forall (f :: * -> *) a. Alt f => f a -> f a -> f a
(<!>) (f x -> f x -> f x) -> (g x -> f x) -> g x -> f x -> f x
forall b c a. (b -> c) -> (a -> b) -> a -> c
. g x -> f x
g ~> f
f) f x
forall a. f a
forall (f :: * -> *) a. Plus f => f a
zero (Map k (g x) -> f x)
-> (MapF k g x -> Map k (g x)) -> MapF k g x -> f x
forall b c a. (b -> c) -> (a -> b) -> a -> c
. MapF k g x -> Map k (g x)
forall {k1} k2 (f :: k1 -> *) (a :: k1).
MapF k2 f a -> Map k2 (f a)
runMapF
instance (Monoid k, Alt f) => Interpret (NEMapF k) f where
retract :: NEMapF k f ~> f
retract = NEMap k (f x) -> f x
forall (t :: * -> *) (m :: * -> *) a.
(Foldable1 t, Alt m) =>
t (m a) -> m a
asum1 (NEMap k (f x) -> f x)
-> (NEMapF k f x -> NEMap k (f x)) -> NEMapF k f x -> f x
forall b c a. (b -> c) -> (a -> b) -> a -> c
. NEMapF k f x -> NEMap k (f x)
forall {k1} k2 (f :: k1 -> *) (a :: k1).
NEMapF k2 f a -> NEMap k2 (f a)
runNEMapF
interpret :: forall (g :: * -> *). (g ~> f) -> NEMapF k g ~> f
interpret g ~> f
f = NEMap k (f x) -> f x
forall (t :: * -> *) (m :: * -> *) a.
(Foldable1 t, Alt m) =>
t (m a) -> m a
asum1 (NEMap k (f x) -> f x)
-> (NEMapF k g x -> NEMap k (f x)) -> NEMapF k g x -> f x
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (g x -> f x) -> NEMap k (g x) -> NEMap k (f x)
forall a b. (a -> b) -> NEMap k a -> NEMap k b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap g x -> f x
g ~> f
f (NEMap k (g x) -> NEMap k (f x))
-> (NEMapF k g x -> NEMap k (g x)) -> NEMapF k g x -> NEMap k (f x)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. NEMapF k g x -> NEMap k (g x)
forall {k1} k2 (f :: k1 -> *) (a :: k1).
NEMapF k2 f a -> NEMap k2 (f a)
runNEMapF
instance Interpret Step f where
retract :: Step f ~> f
retract = Step f x -> f x
forall k (f :: k -> *). Step f ~> f
stepVal
interpret :: forall (g :: k -> *). (g ~> f) -> Step g ~> f
interpret g ~> f
f = g x -> f x
g ~> f
f (g x -> f x) -> (Step g x -> g x) -> Step g x -> f x
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Step g x -> g x
forall k (f :: k -> *). Step f ~> f
stepVal
instance Alt f => Interpret Steps f where
retract :: Steps f ~> f
retract = NEMap Natural (f x) -> f x
forall (t :: * -> *) (m :: * -> *) a.
(Foldable1 t, Alt m) =>
t (m a) -> m a
asum1 (NEMap Natural (f x) -> f x)
-> (Steps f x -> NEMap Natural (f x)) -> Steps f x -> f x
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Steps f x -> NEMap Natural (f x)
forall {k} (f :: k -> *) (a :: k). Steps f a -> NEMap Natural (f a)
getSteps
interpret :: forall (g :: * -> *). (g ~> f) -> Steps g ~> f
interpret g ~> f
f = NEMap Natural (f x) -> f x
forall (t :: * -> *) (m :: * -> *) a.
(Foldable1 t, Alt m) =>
t (m a) -> m a
asum1 (NEMap Natural (f x) -> f x)
-> (Steps g x -> NEMap Natural (f x)) -> Steps g x -> f x
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (g x -> f x) -> NEMap Natural (g x) -> NEMap Natural (f x)
forall a b k. (a -> b) -> NEMap k a -> NEMap k b
NEM.map g x -> f x
g ~> f
f (NEMap Natural (g x) -> NEMap Natural (f x))
-> (Steps g x -> NEMap Natural (g x))
-> Steps g x
-> NEMap Natural (f x)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Steps g x -> NEMap Natural (g x)
forall {k} (f :: k -> *) (a :: k). Steps f a -> NEMap Natural (f a)
getSteps
instance Interpret Flagged f where
retract :: Flagged f ~> f
retract = Flagged f x -> f x
forall k (f :: k -> *). Flagged f ~> f
flaggedVal
interpret :: forall (g :: k -> *). (g ~> f) -> Flagged g ~> f
interpret g ~> f
f = g x -> f x
g ~> f
f (g x -> f x) -> (Flagged g x -> g x) -> Flagged g x -> f x
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Flagged g x -> g x
forall k (f :: k -> *). Flagged f ~> f
flaggedVal
instance Plus f => Interpret (These1 g) f where
retract :: These1 g f ~> f
retract = \case
This1 g x
_ -> f x
forall a. f a
forall (f :: * -> *) a. Plus f => f a
zero
That1 f x
y -> f x
y
These1 g x
_ f x
y -> f x
y
interpret :: forall (g :: * -> *). (g ~> f) -> These1 g g ~> f
interpret g ~> f
f = \case
This1 g x
_ -> f x
forall a. f a
forall (f :: * -> *) a. Plus f => f a
zero
That1 g x
y -> g x -> f x
g ~> f
f g x
y
These1 g x
_ g x
y -> g x -> f x
g ~> f
f g x
y
instance Alternative f => Interpret Alt.Alt f where
interpret :: forall (g :: * -> *). (g ~> f) -> Alt g ~> f
interpret g ~> f
f Alt g x
x = (g ~> f) -> Alt g x -> f x
forall (f :: * -> *) (g :: * -> *) a.
Alternative g =>
(forall x. f x -> g x) -> Alt f a -> g a
Alt.runAlt g x -> f x
g ~> f
f Alt g x
x
instance Plus g => Interpret ((:*:) g) f where
retract :: (g :*: f) ~> f
retract (g x
_ :*: f x
y) = f x
y
instance Plus g => Interpret (Product g) f where
retract :: Product g f ~> f
retract (Pair g x
_ f x
y) = f x
y
instance Plus f => Interpret ((:+:) g) f where
retract :: (g :+: f) ~> f
retract = \case
L1 g x
_ -> f x
forall a. f a
forall (f :: * -> *) a. Plus f => f a
zero
R1 f x
y -> f x
y
instance Plus f => Interpret (Sum g) f where
retract :: Sum g f ~> f
retract = \case
InL g x
_ -> f x
forall a. f a
forall (f :: * -> *) a. Plus f => f a
zero
InR f x
y -> f x
y
instance Interpret (M1 i c) f where
retract :: M1 i c f ~> f
retract (M1 f x
x) = f x
x
interpret :: forall (g :: k -> *). (g ~> f) -> M1 i c g ~> f
interpret g ~> f
f (M1 g x
x) = g x -> f x
g ~> f
f g x
x
instance Monad f => Interpret Free f where
retract :: Free f ~> f
retract = Free f x -> f x
Free f ~> f
forall (f :: * -> *). Monad f => Free f ~> f
retractFree
interpret :: forall (g :: * -> *). (g ~> f) -> Free g ~> f
interpret g ~> f
f Free g x
x = (g ~> f) -> Free g ~> f
forall (g :: * -> *) (f :: * -> *).
Monad g =>
(f ~> g) -> Free f ~> g
interpretFree g x -> f x
g ~> f
f Free g x
x
instance Bind f => Interpret Free1 f where
retract :: Free1 f ~> f
retract = Free1 f x -> f x
Free1 f ~> f
forall (f :: * -> *). Bind f => Free1 f ~> f
retractFree1
interpret :: forall (g :: * -> *). (g ~> f) -> Free1 g ~> f
interpret g ~> f
f Free1 g x
x = (g ~> f) -> Free1 g ~> f
forall (g :: * -> *) (f :: * -> *).
Bind g =>
(f ~> g) -> Free1 f ~> g
interpretFree1 g x -> f x
g ~> f
f Free1 g x
x
instance Applicative f => Interpret FA.Ap f where
retract :: Ap f ~> f
retract = Ap f x -> f x
forall (f :: * -> *) a. Applicative f => Ap f a -> f a
FA.retractAp
interpret :: forall (g :: * -> *). (g ~> f) -> Ap g ~> f
interpret g ~> f
f Ap g x
x = (g ~> f) -> Ap g x -> f x
forall (g :: * -> *) (f :: * -> *) a.
Applicative g =>
(forall x. f x -> g x) -> Ap f a -> g a
FA.runAp g x -> f x
g ~> f
f Ap g x
x
instance Applicative f => Interpret FAF.Ap f where
retract :: Ap f ~> f
retract = Ap f x -> f x
forall (f :: * -> *) a. Applicative f => Ap f a -> f a
FAF.retractAp
interpret :: forall (g :: * -> *). (g ~> f) -> Ap g ~> f
interpret g ~> f
f Ap g x
x = (g ~> f) -> Ap g x -> f x
forall (g :: * -> *) (f :: * -> *) a.
Applicative g =>
(forall x. f x -> g x) -> Ap f a -> g a
FAF.runAp g x -> f x
g ~> f
f Ap g x
x
instance Interpret IdentityT f where
retract :: IdentityT f ~> f
retract = IdentityT f x -> f x
forall a b. Coercible a b => a -> b
coerce
interpret :: forall (g :: k -> *). (g ~> f) -> IdentityT g ~> f
interpret g ~> f
f = g x -> f x
g ~> f
f (g x -> f x) -> (IdentityT g x -> g x) -> IdentityT g x -> f x
forall b c a. (b -> c) -> (a -> b) -> a -> c
. IdentityT g x -> g x
forall k (f :: k -> *). IdentityT f ~> f
runIdentityT
instance Pointed f => Interpret Lift f where
retract :: Lift f ~> f
retract = (x -> f x) -> (f x -> f x) -> Lift f x -> f x
forall a r (f :: * -> *). (a -> r) -> (f a -> r) -> Lift f a -> r
elimLift x -> f x
forall a. a -> f a
forall (p :: * -> *) a. Pointed p => a -> p a
point f x -> f x
forall a. a -> a
id
interpret :: forall (g :: * -> *). (g ~> f) -> Lift g ~> f
interpret g ~> f
f Lift g x
x = (x -> f x) -> (g x -> f x) -> Lift g x -> f x
forall a r (f :: * -> *). (a -> r) -> (f a -> r) -> Lift f a -> r
elimLift x -> f x
forall a. a -> f a
forall (p :: * -> *) a. Pointed p => a -> p a
point g x -> f x
g ~> f
f Lift g x
x
instance Pointed f => Interpret MaybeApply f where
retract :: MaybeApply f ~> f
retract = (f x -> f x) -> (x -> f x) -> Either (f x) x -> f x
forall a c b. (a -> c) -> (b -> c) -> Either a b -> c
either f x -> f x
forall a. a -> a
id x -> f x
forall a. a -> f a
forall (p :: * -> *) a. Pointed p => a -> p a
point (Either (f x) x -> f x)
-> (MaybeApply f x -> Either (f x) x) -> MaybeApply f x -> f x
forall b c a. (b -> c) -> (a -> b) -> a -> c
. MaybeApply f x -> Either (f x) x
forall (f :: * -> *) a. MaybeApply f a -> Either (f a) a
runMaybeApply
interpret :: forall (g :: * -> *). (g ~> f) -> MaybeApply g ~> f
interpret g ~> f
f = (g x -> f x) -> (x -> f x) -> Either (g x) x -> f x
forall a c b. (a -> c) -> (b -> c) -> Either a b -> c
either g x -> f x
g ~> f
f x -> f x
forall a. a -> f a
forall (p :: * -> *) a. Pointed p => a -> p a
point (Either (g x) x -> f x)
-> (MaybeApply g x -> Either (g x) x) -> MaybeApply g x -> f x
forall b c a. (b -> c) -> (a -> b) -> a -> c
. MaybeApply g x -> Either (g x) x
forall (f :: * -> *) a. MaybeApply f a -> Either (f a) a
runMaybeApply
instance Interpret Backwards f where
retract :: Backwards f ~> f
retract = Backwards f x -> f x
forall k (f :: k -> *). Backwards f ~> f
forwards
interpret :: forall (g :: k -> *). (g ~> f) -> Backwards g ~> f
interpret g ~> f
f = g x -> f x
g ~> f
f (g x -> f x) -> (Backwards g x -> g x) -> Backwards g x -> f x
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Backwards g x -> g x
forall k (f :: k -> *). Backwards f ~> f
forwards
instance Interpret WrappedApplicative f where
retract :: WrappedApplicative f ~> f
retract = WrappedApplicative f x -> f x
forall (f :: * -> *). WrappedApplicative f ~> f
unwrapApplicative
interpret :: forall (g :: * -> *). (g ~> f) -> WrappedApplicative g ~> f
interpret g ~> f
f = g x -> f x
g ~> f
f (g x -> f x)
-> (WrappedApplicative g x -> g x) -> WrappedApplicative g x -> f x
forall b c a. (b -> c) -> (a -> b) -> a -> c
. WrappedApplicative g x -> g x
forall (f :: * -> *). WrappedApplicative f ~> f
unwrapApplicative
instance MonadReader r f => Interpret (ReaderT r) f where
retract :: ReaderT r f ~> f
retract ReaderT r f x
x = ReaderT r f x -> r -> f x
forall r (m :: * -> *) a. ReaderT r m a -> r -> m a
runReaderT ReaderT r f x
x (r -> f x) -> f r -> f x
forall (m :: * -> *) a b. Monad m => (a -> m b) -> m a -> m b
=<< f r
forall r (m :: * -> *). MonadReader r m => m r
ask
interpret :: forall (g :: * -> *). (g ~> f) -> ReaderT r g ~> f
interpret g ~> f
f ReaderT r g x
x = g x -> f x
g ~> f
f (g x -> f x) -> (r -> g x) -> r -> f x
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ReaderT r g x -> r -> g x
forall r (m :: * -> *) a. ReaderT r m a -> r -> m a
runReaderT ReaderT r g x
x (r -> f x) -> f r -> f x
forall (m :: * -> *) a b. Monad m => (a -> m b) -> m a -> m b
=<< f r
forall r (m :: * -> *). MonadReader r m => m r
ask
instance Monoid e => Interpret (EnvT e) f where
retract :: EnvT e f ~> f
retract (EnvT e
_ f x
x) = f x
x
interpret :: forall (g :: * -> *). (g ~> f) -> EnvT e g ~> f
interpret g ~> f
f (EnvT e
_ g x
x) = g x -> f x
g ~> f
f g x
x
instance Interpret Reverse f where
retract :: Reverse f ~> f
retract = Reverse f x -> f x
forall k (f :: k -> *). Reverse f ~> f
getReverse
interpret :: forall (g :: k -> *). (g ~> f) -> Reverse g ~> f
interpret g ~> f
f = g x -> f x
g ~> f
f (g x -> f x) -> (Reverse g x -> g x) -> Reverse g x -> f x
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Reverse g x -> g x
forall k (f :: k -> *). Reverse f ~> f
getReverse
class (c a, d a) => AndC c d a
instance (c a, d a) => AndC c d a
instance (Interpret s f, Interpret t f) => Interpret (ComposeT s t) f where
retract :: ComposeT s t f ~> f
retract = (t f ~> f) -> s (t f) ~> f
forall {k} (t :: (k -> *) -> k -> *) (f :: k -> *) (g :: k -> *).
Interpret t f =>
(g ~> f) -> t g ~> f
forall (g :: * -> *). (g ~> f) -> s g ~> f
interpret t f x -> f x
t f ~> f
forall {k} (t :: (k -> *) -> k -> *) (f :: k -> *).
Interpret t f =>
t f ~> f
retract (s (t f) x -> f x)
-> (ComposeT s t f x -> s (t f) x) -> ComposeT s t f x -> f x
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ComposeT s t f x -> s (t f) x
forall (f :: (* -> *) -> * -> *) (g :: (* -> *) -> * -> *)
(m :: * -> *) a.
ComposeT f g m a -> f (g m) a
getComposeT
interpret :: forall (g :: * -> *). (g ~> f) -> ComposeT s t g ~> f
interpret g ~> f
f = (t g ~> f) -> s (t g) ~> f
forall {k} (t :: (k -> *) -> k -> *) (f :: k -> *) (g :: k -> *).
Interpret t f =>
(g ~> f) -> t g ~> f
forall (g :: * -> *). (g ~> f) -> s g ~> f
interpret ((g ~> f) -> t g ~> f
forall {k} (t :: (k -> *) -> k -> *) (f :: k -> *) (g :: k -> *).
Interpret t f =>
(g ~> f) -> t g ~> f
forall (g :: * -> *). (g ~> f) -> t g ~> f
interpret g x -> f x
g ~> f
f) (s (t g) x -> f x)
-> (ComposeT s t g x -> s (t g) x) -> ComposeT s t g x -> f x
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ComposeT s t g x -> s (t g) x
forall (f :: (* -> *) -> * -> *) (g :: (* -> *) -> * -> *)
(m :: * -> *) a.
ComposeT f g m a -> f (g m) a
getComposeT
instance Interpret t f => Interpret (HLift t) f where
retract :: HLift t f ~> f
retract = \case
HPure f x
x -> f x
x
HOther t f x
x -> t f x -> f x
t f ~> f
forall {k} (t :: (k -> *) -> k -> *) (f :: k -> *).
Interpret t f =>
t f ~> f
retract t f x
x
interpret :: forall (g :: k -> *). (g ~> f) -> HLift t g ~> f
interpret g ~> f
f = \case
HPure g x
x -> g x -> f x
g ~> f
f g x
x
HOther t g x
x -> (g ~> f) -> t g ~> f
forall {k} (t :: (k -> *) -> k -> *) (f :: k -> *) (g :: k -> *).
Interpret t f =>
(g ~> f) -> t g ~> f
forall (g :: k -> *). (g ~> f) -> t g ~> f
interpret g x -> f x
g ~> f
f t g x
x
instance Interpret t f => Interpret (HFree t) f where
retract :: HFree t f ~> f
retract = \case
HReturn f x
x -> f x
x
HJoin t (HFree t f) x
x -> (HFree t f ~> f) -> t (HFree t f) ~> f
forall {k} (t :: (k -> *) -> k -> *) (f :: k -> *) (g :: k -> *).
Interpret t f =>
(g ~> f) -> t g ~> f
forall (g :: k -> *). (g ~> f) -> t g ~> f
interpret HFree t f x -> f x
HFree t f ~> f
forall {k} (t :: (k -> *) -> k -> *) (f :: k -> *).
Interpret t f =>
t f ~> f
retract t (HFree t f) x
x
newtype WrapHF t f a = WrapHF { forall {k} {k} (t :: k -> k -> *) (f :: k) (a :: k).
WrapHF t f a -> t f a
unwrapHF :: t f a }
deriving (Int -> WrapHF t f a -> ShowS
[WrapHF t f a] -> ShowS
WrapHF t f a -> String
(Int -> WrapHF t f a -> ShowS)
-> (WrapHF t f a -> String)
-> ([WrapHF t f a] -> ShowS)
-> Show (WrapHF t f a)
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
forall k k (t :: k -> k -> *) (f :: k) (a :: k).
Show (t f a) =>
Int -> WrapHF t f a -> ShowS
forall k k (t :: k -> k -> *) (f :: k) (a :: k).
Show (t f a) =>
[WrapHF t f a] -> ShowS
forall k k (t :: k -> k -> *) (f :: k) (a :: k).
Show (t f a) =>
WrapHF t f a -> String
$cshowsPrec :: forall k k (t :: k -> k -> *) (f :: k) (a :: k).
Show (t f a) =>
Int -> WrapHF t f a -> ShowS
showsPrec :: Int -> WrapHF t f a -> ShowS
$cshow :: forall k k (t :: k -> k -> *) (f :: k) (a :: k).
Show (t f a) =>
WrapHF t f a -> String
show :: WrapHF t f a -> String
$cshowList :: forall k k (t :: k -> k -> *) (f :: k) (a :: k).
Show (t f a) =>
[WrapHF t f a] -> ShowS
showList :: [WrapHF t f a] -> ShowS
Show, ReadPrec [WrapHF t f a]
ReadPrec (WrapHF t f a)
Int -> ReadS (WrapHF t f a)
ReadS [WrapHF t f a]
(Int -> ReadS (WrapHF t f a))
-> ReadS [WrapHF t f a]
-> ReadPrec (WrapHF t f a)
-> ReadPrec [WrapHF t f a]
-> Read (WrapHF t f a)
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
forall k k (t :: k -> k -> *) (f :: k) (a :: k).
Read (t f a) =>
ReadPrec [WrapHF t f a]
forall k k (t :: k -> k -> *) (f :: k) (a :: k).
Read (t f a) =>
ReadPrec (WrapHF t f a)
forall k k (t :: k -> k -> *) (f :: k) (a :: k).
Read (t f a) =>
Int -> ReadS (WrapHF t f a)
forall k k (t :: k -> k -> *) (f :: k) (a :: k).
Read (t f a) =>
ReadS [WrapHF t f a]
$creadsPrec :: forall k k (t :: k -> k -> *) (f :: k) (a :: k).
Read (t f a) =>
Int -> ReadS (WrapHF t f a)
readsPrec :: Int -> ReadS (WrapHF t f a)
$creadList :: forall k k (t :: k -> k -> *) (f :: k) (a :: k).
Read (t f a) =>
ReadS [WrapHF t f a]
readList :: ReadS [WrapHF t f a]
$creadPrec :: forall k k (t :: k -> k -> *) (f :: k) (a :: k).
Read (t f a) =>
ReadPrec (WrapHF t f a)
readPrec :: ReadPrec (WrapHF t f a)
$creadListPrec :: forall k k (t :: k -> k -> *) (f :: k) (a :: k).
Read (t f a) =>
ReadPrec [WrapHF t f a]
readListPrec :: ReadPrec [WrapHF t f a]
Read, WrapHF t f a -> WrapHF t f a -> Bool
(WrapHF t f a -> WrapHF t f a -> Bool)
-> (WrapHF t f a -> WrapHF t f a -> Bool) -> Eq (WrapHF t f a)
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
forall k k (t :: k -> k -> *) (f :: k) (a :: k).
Eq (t f a) =>
WrapHF t f a -> WrapHF t f a -> Bool
$c== :: forall k k (t :: k -> k -> *) (f :: k) (a :: k).
Eq (t f a) =>
WrapHF t f a -> WrapHF t f a -> Bool
== :: WrapHF t f a -> WrapHF t f a -> Bool
$c/= :: forall k k (t :: k -> k -> *) (f :: k) (a :: k).
Eq (t f a) =>
WrapHF t f a -> WrapHF t f a -> Bool
/= :: WrapHF t f a -> WrapHF t f a -> Bool
Eq, Eq (WrapHF t f a)
Eq (WrapHF t f a) =>
(WrapHF t f a -> WrapHF t f a -> Ordering)
-> (WrapHF t f a -> WrapHF t f a -> Bool)
-> (WrapHF t f a -> WrapHF t f a -> Bool)
-> (WrapHF t f a -> WrapHF t f a -> Bool)
-> (WrapHF t f a -> WrapHF t f a -> Bool)
-> (WrapHF t f a -> WrapHF t f a -> WrapHF t f a)
-> (WrapHF t f a -> WrapHF t f a -> WrapHF t f a)
-> Ord (WrapHF t f a)
WrapHF t f a -> WrapHF t f a -> Bool
WrapHF t f a -> WrapHF t f a -> Ordering
WrapHF t f a -> WrapHF t f a -> WrapHF t f a
forall a.
Eq a =>
(a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
forall k k (t :: k -> k -> *) (f :: k) (a :: k).
Ord (t f a) =>
Eq (WrapHF t f a)
forall k k (t :: k -> k -> *) (f :: k) (a :: k).
Ord (t f a) =>
WrapHF t f a -> WrapHF t f a -> Bool
forall k k (t :: k -> k -> *) (f :: k) (a :: k).
Ord (t f a) =>
WrapHF t f a -> WrapHF t f a -> Ordering
forall k k (t :: k -> k -> *) (f :: k) (a :: k).
Ord (t f a) =>
WrapHF t f a -> WrapHF t f a -> WrapHF t f a
$ccompare :: forall k k (t :: k -> k -> *) (f :: k) (a :: k).
Ord (t f a) =>
WrapHF t f a -> WrapHF t f a -> Ordering
compare :: WrapHF t f a -> WrapHF t f a -> Ordering
$c< :: forall k k (t :: k -> k -> *) (f :: k) (a :: k).
Ord (t f a) =>
WrapHF t f a -> WrapHF t f a -> Bool
< :: WrapHF t f a -> WrapHF t f a -> Bool
$c<= :: forall k k (t :: k -> k -> *) (f :: k) (a :: k).
Ord (t f a) =>
WrapHF t f a -> WrapHF t f a -> Bool
<= :: WrapHF t f a -> WrapHF t f a -> Bool
$c> :: forall k k (t :: k -> k -> *) (f :: k) (a :: k).
Ord (t f a) =>
WrapHF t f a -> WrapHF t f a -> Bool
> :: WrapHF t f a -> WrapHF t f a -> Bool
$c>= :: forall k k (t :: k -> k -> *) (f :: k) (a :: k).
Ord (t f a) =>
WrapHF t f a -> WrapHF t f a -> Bool
>= :: WrapHF t f a -> WrapHF t f a -> Bool
$cmax :: forall k k (t :: k -> k -> *) (f :: k) (a :: k).
Ord (t f a) =>
WrapHF t f a -> WrapHF t f a -> WrapHF t f a
max :: WrapHF t f a -> WrapHF t f a -> WrapHF t f a
$cmin :: forall k k (t :: k -> k -> *) (f :: k) (a :: k).
Ord (t f a) =>
WrapHF t f a -> WrapHF t f a -> WrapHF t f a
min :: WrapHF t f a -> WrapHF t f a -> WrapHF t f a
Ord, (forall a b. (a -> b) -> WrapHF t f a -> WrapHF t f b)
-> (forall a b. a -> WrapHF t f b -> WrapHF t f a)
-> Functor (WrapHF t f)
forall a b. a -> WrapHF t f b -> WrapHF t f a
forall a b. (a -> b) -> WrapHF t f a -> WrapHF t f b
forall k (t :: k -> * -> *) (f :: k) a b.
Functor (t f) =>
a -> WrapHF t f b -> WrapHF t f a
forall k (t :: k -> * -> *) (f :: k) a b.
Functor (t f) =>
(a -> b) -> WrapHF t f a -> WrapHF t f b
forall (f :: * -> *).
(forall a b. (a -> b) -> f a -> f b)
-> (forall a b. a -> f b -> f a) -> Functor f
$cfmap :: forall k (t :: k -> * -> *) (f :: k) a b.
Functor (t f) =>
(a -> b) -> WrapHF t f a -> WrapHF t f b
fmap :: forall a b. (a -> b) -> WrapHF t f a -> WrapHF t f b
$c<$ :: forall k (t :: k -> * -> *) (f :: k) a b.
Functor (t f) =>
a -> WrapHF t f b -> WrapHF t f a
<$ :: forall a b. a -> WrapHF t f b -> WrapHF t f a
Functor, (forall m. Monoid m => WrapHF t f m -> m)
-> (forall m a. Monoid m => (a -> m) -> WrapHF t f a -> m)
-> (forall m a. Monoid m => (a -> m) -> WrapHF t f a -> m)
-> (forall a b. (a -> b -> b) -> b -> WrapHF t f a -> b)
-> (forall a b. (a -> b -> b) -> b -> WrapHF t f a -> b)
-> (forall b a. (b -> a -> b) -> b -> WrapHF t f a -> b)
-> (forall b a. (b -> a -> b) -> b -> WrapHF t f a -> b)
-> (forall a. (a -> a -> a) -> WrapHF t f a -> a)
-> (forall a. (a -> a -> a) -> WrapHF t f a -> a)
-> (forall a. WrapHF t f a -> [a])
-> (forall a. WrapHF t f a -> Bool)
-> (forall a. WrapHF t f a -> Int)
-> (forall a. Eq a => a -> WrapHF t f a -> Bool)
-> (forall a. Ord a => WrapHF t f a -> a)
-> (forall a. Ord a => WrapHF t f a -> a)
-> (forall a. Num a => WrapHF t f a -> a)
-> (forall a. Num a => WrapHF t f a -> a)
-> Foldable (WrapHF t f)
forall a. Eq a => a -> WrapHF t f a -> Bool
forall a. Num a => WrapHF t f a -> a
forall a. Ord a => WrapHF t f a -> a
forall m. Monoid m => WrapHF t f m -> m
forall a. WrapHF t f a -> Bool
forall a. WrapHF t f a -> Int
forall a. WrapHF t f a -> [a]
forall a. (a -> a -> a) -> WrapHF t f a -> a
forall m a. Monoid m => (a -> m) -> WrapHF t f a -> m
forall b a. (b -> a -> b) -> b -> WrapHF t f a -> b
forall a b. (a -> b -> b) -> b -> WrapHF t f a -> b
forall k (t :: k -> * -> *) (f :: k) a.
(Foldable (t f), Eq a) =>
a -> WrapHF t f a -> Bool
forall k (t :: k -> * -> *) (f :: k) a.
(Foldable (t f), Num a) =>
WrapHF t f a -> a
forall k (t :: k -> * -> *) (f :: k) a.
(Foldable (t f), Ord a) =>
WrapHF t f a -> a
forall k (t :: k -> * -> *) (f :: k) m.
(Foldable (t f), Monoid m) =>
WrapHF t f m -> m
forall k (t :: k -> * -> *) (f :: k) a.
Foldable (t f) =>
WrapHF t f a -> Bool
forall k (t :: k -> * -> *) (f :: k) a.
Foldable (t f) =>
WrapHF t f a -> Int
forall k (t :: k -> * -> *) (f :: k) a.
Foldable (t f) =>
WrapHF t f a -> [a]
forall k (t :: k -> * -> *) (f :: k) a.
Foldable (t f) =>
(a -> a -> a) -> WrapHF t f a -> a
forall k (t :: k -> * -> *) (f :: k) m a.
(Foldable (t f), Monoid m) =>
(a -> m) -> WrapHF t f a -> m
forall k (t :: k -> * -> *) (f :: k) b a.
Foldable (t f) =>
(b -> a -> b) -> b -> WrapHF t f a -> b
forall k (t :: k -> * -> *) (f :: k) a b.
Foldable (t f) =>
(a -> b -> b) -> b -> WrapHF t f a -> b
forall (t :: * -> *).
(forall m. Monoid m => t m -> m)
-> (forall m a. Monoid m => (a -> m) -> t a -> m)
-> (forall m a. Monoid m => (a -> m) -> t a -> m)
-> (forall a b. (a -> b -> b) -> b -> t a -> b)
-> (forall a b. (a -> b -> b) -> b -> t a -> b)
-> (forall b a. (b -> a -> b) -> b -> t a -> b)
-> (forall b a. (b -> a -> b) -> b -> t a -> b)
-> (forall a. (a -> a -> a) -> t a -> a)
-> (forall a. (a -> a -> a) -> t a -> a)
-> (forall a. t a -> [a])
-> (forall a. t a -> Bool)
-> (forall a. t a -> Int)
-> (forall a. Eq a => a -> t a -> Bool)
-> (forall a. Ord a => t a -> a)
-> (forall a. Ord a => t a -> a)
-> (forall a. Num a => t a -> a)
-> (forall a. Num a => t a -> a)
-> Foldable t
$cfold :: forall k (t :: k -> * -> *) (f :: k) m.
(Foldable (t f), Monoid m) =>
WrapHF t f m -> m
fold :: forall m. Monoid m => WrapHF t f m -> m
$cfoldMap :: forall k (t :: k -> * -> *) (f :: k) m a.
(Foldable (t f), Monoid m) =>
(a -> m) -> WrapHF t f a -> m
foldMap :: forall m a. Monoid m => (a -> m) -> WrapHF t f a -> m
$cfoldMap' :: forall k (t :: k -> * -> *) (f :: k) m a.
(Foldable (t f), Monoid m) =>
(a -> m) -> WrapHF t f a -> m
foldMap' :: forall m a. Monoid m => (a -> m) -> WrapHF t f a -> m
$cfoldr :: forall k (t :: k -> * -> *) (f :: k) a b.
Foldable (t f) =>
(a -> b -> b) -> b -> WrapHF t f a -> b
foldr :: forall a b. (a -> b -> b) -> b -> WrapHF t f a -> b
$cfoldr' :: forall k (t :: k -> * -> *) (f :: k) a b.
Foldable (t f) =>
(a -> b -> b) -> b -> WrapHF t f a -> b
foldr' :: forall a b. (a -> b -> b) -> b -> WrapHF t f a -> b
$cfoldl :: forall k (t :: k -> * -> *) (f :: k) b a.
Foldable (t f) =>
(b -> a -> b) -> b -> WrapHF t f a -> b
foldl :: forall b a. (b -> a -> b) -> b -> WrapHF t f a -> b
$cfoldl' :: forall k (t :: k -> * -> *) (f :: k) b a.
Foldable (t f) =>
(b -> a -> b) -> b -> WrapHF t f a -> b
foldl' :: forall b a. (b -> a -> b) -> b -> WrapHF t f a -> b
$cfoldr1 :: forall k (t :: k -> * -> *) (f :: k) a.
Foldable (t f) =>
(a -> a -> a) -> WrapHF t f a -> a
foldr1 :: forall a. (a -> a -> a) -> WrapHF t f a -> a
$cfoldl1 :: forall k (t :: k -> * -> *) (f :: k) a.
Foldable (t f) =>
(a -> a -> a) -> WrapHF t f a -> a
foldl1 :: forall a. (a -> a -> a) -> WrapHF t f a -> a
$ctoList :: forall k (t :: k -> * -> *) (f :: k) a.
Foldable (t f) =>
WrapHF t f a -> [a]
toList :: forall a. WrapHF t f a -> [a]
$cnull :: forall k (t :: k -> * -> *) (f :: k) a.
Foldable (t f) =>
WrapHF t f a -> Bool
null :: forall a. WrapHF t f a -> Bool
$clength :: forall k (t :: k -> * -> *) (f :: k) a.
Foldable (t f) =>
WrapHF t f a -> Int
length :: forall a. WrapHF t f a -> Int
$celem :: forall k (t :: k -> * -> *) (f :: k) a.
(Foldable (t f), Eq a) =>
a -> WrapHF t f a -> Bool
elem :: forall a. Eq a => a -> WrapHF t f a -> Bool
$cmaximum :: forall k (t :: k -> * -> *) (f :: k) a.
(Foldable (t f), Ord a) =>
WrapHF t f a -> a
maximum :: forall a. Ord a => WrapHF t f a -> a
$cminimum :: forall k (t :: k -> * -> *) (f :: k) a.
(Foldable (t f), Ord a) =>
WrapHF t f a -> a
minimum :: forall a. Ord a => WrapHF t f a -> a
$csum :: forall k (t :: k -> * -> *) (f :: k) a.
(Foldable (t f), Num a) =>
WrapHF t f a -> a
sum :: forall a. Num a => WrapHF t f a -> a
$cproduct :: forall k (t :: k -> * -> *) (f :: k) a.
(Foldable (t f), Num a) =>
WrapHF t f a -> a
product :: forall a. Num a => WrapHF t f a -> a
Foldable, Functor (WrapHF t f)
Foldable (WrapHF t f)
(Functor (WrapHF t f), Foldable (WrapHF t f)) =>
(forall (f :: * -> *) a b.
Applicative f =>
(a -> f b) -> WrapHF t f a -> f (WrapHF t f b))
-> (forall (f :: * -> *) a.
Applicative f =>
WrapHF t f (f a) -> f (WrapHF t f a))
-> (forall (m :: * -> *) a b.
Monad m =>
(a -> m b) -> WrapHF t f a -> m (WrapHF t f b))
-> (forall (m :: * -> *) a.
Monad m =>
WrapHF t f (m a) -> m (WrapHF t f a))
-> Traversable (WrapHF t f)
forall k (t :: k -> * -> *) (f :: k).
Traversable (t f) =>
Functor (WrapHF t f)
forall k (t :: k -> * -> *) (f :: k).
Traversable (t f) =>
Foldable (WrapHF t f)
forall k (t :: k -> * -> *) (f :: k) (m :: * -> *) a.
(Traversable (t f), Monad m) =>
WrapHF t f (m a) -> m (WrapHF t f a)
forall k (t :: k -> * -> *) (f :: k) (f :: * -> *) a.
(Traversable (t f), Applicative f) =>
WrapHF t f (f a) -> f (WrapHF t f a)
forall k (t :: k -> * -> *) (f :: k) (m :: * -> *) a b.
(Traversable (t f), Monad m) =>
(a -> m b) -> WrapHF t f a -> m (WrapHF t f b)
forall k (t :: k -> * -> *) (f :: k) (f :: * -> *) a b.
(Traversable (t f), Applicative f) =>
(a -> f b) -> WrapHF t f a -> f (WrapHF t f b)
forall (t :: * -> *).
(Functor t, Foldable t) =>
(forall (f :: * -> *) a b.
Applicative f =>
(a -> f b) -> t a -> f (t b))
-> (forall (f :: * -> *) a. Applicative f => t (f a) -> f (t a))
-> (forall (m :: * -> *) a b.
Monad m =>
(a -> m b) -> t a -> m (t b))
-> (forall (m :: * -> *) a. Monad m => t (m a) -> m (t a))
-> Traversable t
forall (m :: * -> *) a.
Monad m =>
WrapHF t f (m a) -> m (WrapHF t f a)
forall (f :: * -> *) a.
Applicative f =>
WrapHF t f (f a) -> f (WrapHF t f a)
forall (m :: * -> *) a b.
Monad m =>
(a -> m b) -> WrapHF t f a -> m (WrapHF t f b)
forall (f :: * -> *) a b.
Applicative f =>
(a -> f b) -> WrapHF t f a -> f (WrapHF t f b)
$ctraverse :: forall k (t :: k -> * -> *) (f :: k) (f :: * -> *) a b.
(Traversable (t f), Applicative f) =>
(a -> f b) -> WrapHF t f a -> f (WrapHF t f b)
traverse :: forall (f :: * -> *) a b.
Applicative f =>
(a -> f b) -> WrapHF t f a -> f (WrapHF t f b)
$csequenceA :: forall k (t :: k -> * -> *) (f :: k) (f :: * -> *) a.
(Traversable (t f), Applicative f) =>
WrapHF t f (f a) -> f (WrapHF t f a)
sequenceA :: forall (f :: * -> *) a.
Applicative f =>
WrapHF t f (f a) -> f (WrapHF t f a)
$cmapM :: forall k (t :: k -> * -> *) (f :: k) (m :: * -> *) a b.
(Traversable (t f), Monad m) =>
(a -> m b) -> WrapHF t f a -> m (WrapHF t f b)
mapM :: forall (m :: * -> *) a b.
Monad m =>
(a -> m b) -> WrapHF t f a -> m (WrapHF t f b)
$csequence :: forall k (t :: k -> * -> *) (f :: k) (m :: * -> *) a.
(Traversable (t f), Monad m) =>
WrapHF t f (m a) -> m (WrapHF t f a)
sequence :: forall (m :: * -> *) a.
Monad m =>
WrapHF t f (m a) -> m (WrapHF t f a)
Traversable, Typeable, (forall x. WrapHF t f a -> Rep (WrapHF t f a) x)
-> (forall x. Rep (WrapHF t f a) x -> WrapHF t f a)
-> Generic (WrapHF t f a)
forall x. Rep (WrapHF t f a) x -> WrapHF t f a
forall x. WrapHF t f a -> Rep (WrapHF t f a) x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
forall k k (t :: k -> k -> *) (f :: k) (a :: k) x.
Rep (WrapHF t f a) x -> WrapHF t f a
forall k k (t :: k -> k -> *) (f :: k) (a :: k) x.
WrapHF t f a -> Rep (WrapHF t f a) x
$cfrom :: forall k k (t :: k -> k -> *) (f :: k) (a :: k) x.
WrapHF t f a -> Rep (WrapHF t f a) x
from :: forall x. WrapHF t f a -> Rep (WrapHF t f a) x
$cto :: forall k k (t :: k -> k -> *) (f :: k) (a :: k) x.
Rep (WrapHF t f a) x -> WrapHF t f a
to :: forall x. Rep (WrapHF t f a) x -> WrapHF t f a
Generic, Typeable (WrapHF t f a)
Typeable (WrapHF t f a) =>
(forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> WrapHF t f a -> c (WrapHF t f a))
-> (forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c (WrapHF t f a))
-> (WrapHF t f a -> Constr)
-> (WrapHF t f a -> DataType)
-> (forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c (WrapHF t f a)))
-> (forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c (WrapHF t f a)))
-> ((forall b. Data b => b -> b) -> WrapHF t f a -> WrapHF t f a)
-> (forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> WrapHF t f a -> r)
-> (forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> WrapHF t f a -> r)
-> (forall u. (forall d. Data d => d -> u) -> WrapHF t f a -> [u])
-> (forall u.
Int -> (forall d. Data d => d -> u) -> WrapHF t f a -> u)
-> (forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> WrapHF t f a -> m (WrapHF t f a))
-> (forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> WrapHF t f a -> m (WrapHF t f a))
-> (forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> WrapHF t f a -> m (WrapHF t f a))
-> Data (WrapHF t f a)
WrapHF t f a -> Constr
WrapHF t f a -> DataType
(forall b. Data b => b -> b) -> WrapHF t f a -> WrapHF t f a
forall a.
Typeable a =>
(forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> a -> c a)
-> (forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c a)
-> (a -> Constr)
-> (a -> DataType)
-> (forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c a))
-> (forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c a))
-> ((forall b. Data b => b -> b) -> a -> a)
-> (forall r r'.
(r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> a -> r)
-> (forall r r'.
(r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> a -> r)
-> (forall u. (forall d. Data d => d -> u) -> a -> [u])
-> (forall u. Int -> (forall d. Data d => d -> u) -> a -> u)
-> (forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> a -> m a)
-> (forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> a -> m a)
-> (forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> a -> m a)
-> Data a
forall u. Int -> (forall d. Data d => d -> u) -> WrapHF t f a -> u
forall u. (forall d. Data d => d -> u) -> WrapHF t f a -> [u]
forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> WrapHF t f a -> r
forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> WrapHF t f a -> r
forall k k (t :: k -> k -> *) (f :: k) (a :: k).
(Typeable f, Typeable a, Typeable t, Typeable k, Typeable k,
Data (t f a)) =>
Typeable (WrapHF t f a)
forall k k (t :: k -> k -> *) (f :: k) (a :: k).
(Typeable f, Typeable a, Typeable t, Typeable k, Typeable k,
Data (t f a)) =>
WrapHF t f a -> Constr
forall k k (t :: k -> k -> *) (f :: k) (a :: k).
(Typeable f, Typeable a, Typeable t, Typeable k, Typeable k,
Data (t f a)) =>
WrapHF t f a -> DataType
forall k k (t :: k -> k -> *) (f :: k) (a :: k).
(Typeable f, Typeable a, Typeable t, Typeable k, Typeable k,
Data (t f a)) =>
(forall b. Data b => b -> b) -> WrapHF t f a -> WrapHF t f a
forall k k (t :: k -> k -> *) (f :: k) (a :: k) u.
(Typeable f, Typeable a, Typeable t, Typeable k, Typeable k,
Data (t f a)) =>
Int -> (forall d. Data d => d -> u) -> WrapHF t f a -> u
forall k k (t :: k -> k -> *) (f :: k) (a :: k) u.
(Typeable f, Typeable a, Typeable t, Typeable k, Typeable k,
Data (t f a)) =>
(forall d. Data d => d -> u) -> WrapHF t f a -> [u]
forall k k (t :: k -> k -> *) (f :: k) (a :: k) r r'.
(Typeable f, Typeable a, Typeable t, Typeable k, Typeable k,
Data (t f a)) =>
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> WrapHF t f a -> r
forall k k (t :: k -> k -> *) (f :: k) (a :: k) r r'.
(Typeable f, Typeable a, Typeable t, Typeable k, Typeable k,
Data (t f a)) =>
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> WrapHF t f a -> r
forall k k (t :: k -> k -> *) (f :: k) (a :: k) (m :: * -> *).
(Typeable f, Typeable a, Typeable t, Typeable k, Typeable k,
Data (t f a), Monad m) =>
(forall d. Data d => d -> m d) -> WrapHF t f a -> m (WrapHF t f a)
forall k k (t :: k -> k -> *) (f :: k) (a :: k) (m :: * -> *).
(Typeable f, Typeable a, Typeable t, Typeable k, Typeable k,
Data (t f a), MonadPlus m) =>
(forall d. Data d => d -> m d) -> WrapHF t f a -> m (WrapHF t f a)
forall k k (t :: k -> k -> *) (f :: k) (a :: k) (c :: * -> *).
(Typeable f, Typeable a, Typeable t, Typeable k, Typeable k,
Data (t f a)) =>
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c (WrapHF t f a)
forall k k (t :: k -> k -> *) (f :: k) (a :: k) (c :: * -> *).
(Typeable f, Typeable a, Typeable t, Typeable k, Typeable k,
Data (t f a)) =>
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> WrapHF t f a -> c (WrapHF t f a)
forall k k (t :: k -> k -> *) (f :: k) (a :: k) (t :: * -> *)
(c :: * -> *).
(Typeable f, Typeable a, Typeable t, Typeable k, Typeable k,
Data (t f a), Typeable t) =>
(forall d. Data d => c (t d)) -> Maybe (c (WrapHF t f a))
forall k k (t :: k -> k -> *) (f :: k) (a :: k) (t :: * -> * -> *)
(c :: * -> *).
(Typeable f, Typeable a, Typeable t, Typeable k, Typeable k,
Data (t f a), Typeable t) =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c (WrapHF t f a))
forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> WrapHF t f a -> m (WrapHF t f a)
forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> WrapHF t f a -> m (WrapHF t f a)
forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c (WrapHF t f a)
forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> WrapHF t f a -> c (WrapHF t f a)
forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c (WrapHF t f a))
forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c (WrapHF t f a))
$cgfoldl :: forall k k (t :: k -> k -> *) (f :: k) (a :: k) (c :: * -> *).
(Typeable f, Typeable a, Typeable t, Typeable k, Typeable k,
Data (t f a)) =>
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> WrapHF t f a -> c (WrapHF t f a)
gfoldl :: forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> WrapHF t f a -> c (WrapHF t f a)
$cgunfold :: forall k k (t :: k -> k -> *) (f :: k) (a :: k) (c :: * -> *).
(Typeable f, Typeable a, Typeable t, Typeable k, Typeable k,
Data (t f a)) =>
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c (WrapHF t f a)
gunfold :: forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c (WrapHF t f a)
$ctoConstr :: forall k k (t :: k -> k -> *) (f :: k) (a :: k).
(Typeable f, Typeable a, Typeable t, Typeable k, Typeable k,
Data (t f a)) =>
WrapHF t f a -> Constr
toConstr :: WrapHF t f a -> Constr
$cdataTypeOf :: forall k k (t :: k -> k -> *) (f :: k) (a :: k).
(Typeable f, Typeable a, Typeable t, Typeable k, Typeable k,
Data (t f a)) =>
WrapHF t f a -> DataType
dataTypeOf :: WrapHF t f a -> DataType
$cdataCast1 :: forall k k (t :: k -> k -> *) (f :: k) (a :: k) (t :: * -> *)
(c :: * -> *).
(Typeable f, Typeable a, Typeable t, Typeable k, Typeable k,
Data (t f a), Typeable t) =>
(forall d. Data d => c (t d)) -> Maybe (c (WrapHF t f a))
dataCast1 :: forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c (WrapHF t f a))
$cdataCast2 :: forall k k (t :: k -> k -> *) (f :: k) (a :: k) (t :: * -> * -> *)
(c :: * -> *).
(Typeable f, Typeable a, Typeable t, Typeable k, Typeable k,
Data (t f a), Typeable t) =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c (WrapHF t f a))
dataCast2 :: forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c (WrapHF t f a))
$cgmapT :: forall k k (t :: k -> k -> *) (f :: k) (a :: k).
(Typeable f, Typeable a, Typeable t, Typeable k, Typeable k,
Data (t f a)) =>
(forall b. Data b => b -> b) -> WrapHF t f a -> WrapHF t f a
gmapT :: (forall b. Data b => b -> b) -> WrapHF t f a -> WrapHF t f a
$cgmapQl :: forall k k (t :: k -> k -> *) (f :: k) (a :: k) r r'.
(Typeable f, Typeable a, Typeable t, Typeable k, Typeable k,
Data (t f a)) =>
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> WrapHF t f a -> r
gmapQl :: forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> WrapHF t f a -> r
$cgmapQr :: forall k k (t :: k -> k -> *) (f :: k) (a :: k) r r'.
(Typeable f, Typeable a, Typeable t, Typeable k, Typeable k,
Data (t f a)) =>
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> WrapHF t f a -> r
gmapQr :: forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> WrapHF t f a -> r
$cgmapQ :: forall k k (t :: k -> k -> *) (f :: k) (a :: k) u.
(Typeable f, Typeable a, Typeable t, Typeable k, Typeable k,
Data (t f a)) =>
(forall d. Data d => d -> u) -> WrapHF t f a -> [u]
gmapQ :: forall u. (forall d. Data d => d -> u) -> WrapHF t f a -> [u]
$cgmapQi :: forall k k (t :: k -> k -> *) (f :: k) (a :: k) u.
(Typeable f, Typeable a, Typeable t, Typeable k, Typeable k,
Data (t f a)) =>
Int -> (forall d. Data d => d -> u) -> WrapHF t f a -> u
gmapQi :: forall u. Int -> (forall d. Data d => d -> u) -> WrapHF t f a -> u
$cgmapM :: forall k k (t :: k -> k -> *) (f :: k) (a :: k) (m :: * -> *).
(Typeable f, Typeable a, Typeable t, Typeable k, Typeable k,
Data (t f a), Monad m) =>
(forall d. Data d => d -> m d) -> WrapHF t f a -> m (WrapHF t f a)
gmapM :: forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> WrapHF t f a -> m (WrapHF t f a)
$cgmapMp :: forall k k (t :: k -> k -> *) (f :: k) (a :: k) (m :: * -> *).
(Typeable f, Typeable a, Typeable t, Typeable k, Typeable k,
Data (t f a), MonadPlus m) =>
(forall d. Data d => d -> m d) -> WrapHF t f a -> m (WrapHF t f a)
gmapMp :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> WrapHF t f a -> m (WrapHF t f a)
$cgmapMo :: forall k k (t :: k -> k -> *) (f :: k) (a :: k) (m :: * -> *).
(Typeable f, Typeable a, Typeable t, Typeable k, Typeable k,
Data (t f a), MonadPlus m) =>
(forall d. Data d => d -> m d) -> WrapHF t f a -> m (WrapHF t f a)
gmapMo :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> WrapHF t f a -> m (WrapHF t f a)
Data)
instance Show1 (t f) => Show1 (WrapHF t f) where
liftShowsPrec :: forall a.
(Int -> a -> ShowS)
-> ([a] -> ShowS) -> Int -> WrapHF t f a -> ShowS
liftShowsPrec Int -> a -> ShowS
sp [a] -> ShowS
sl Int
d (WrapHF t f a
x) = (Int -> t f a -> ShowS) -> String -> Int -> t f a -> ShowS
forall a. (Int -> a -> ShowS) -> String -> Int -> a -> ShowS
showsUnaryWith ((Int -> a -> ShowS) -> ([a] -> ShowS) -> Int -> t f a -> ShowS
forall a.
(Int -> a -> ShowS) -> ([a] -> ShowS) -> Int -> t f a -> ShowS
forall (f :: * -> *) a.
Show1 f =>
(Int -> a -> ShowS) -> ([a] -> ShowS) -> Int -> f a -> ShowS
liftShowsPrec Int -> a -> ShowS
sp [a] -> ShowS
sl) String
"WrapHF" Int
d t f a
x
instance Eq1 (t f) => Eq1 (WrapHF t f) where
liftEq :: forall a b.
(a -> b -> Bool) -> WrapHF t f a -> WrapHF t f b -> Bool
liftEq a -> b -> Bool
eq (WrapHF t f a
x) (WrapHF t f b
y) = (a -> b -> Bool) -> t f a -> t f b -> Bool
forall a b. (a -> b -> Bool) -> t f a -> t f b -> Bool
forall (f :: * -> *) a b.
Eq1 f =>
(a -> b -> Bool) -> f a -> f b -> Bool
liftEq a -> b -> Bool
eq t f a
x t f b
y
instance Ord1 (t f) => Ord1 (WrapHF t f) where
liftCompare :: forall a b.
(a -> b -> Ordering) -> WrapHF t f a -> WrapHF t f b -> Ordering
liftCompare a -> b -> Ordering
c (WrapHF t f a
x) (WrapHF t f b
y) = (a -> b -> Ordering) -> t f a -> t f b -> Ordering
forall a b. (a -> b -> Ordering) -> t f a -> t f b -> Ordering
forall (f :: * -> *) a b.
Ord1 f =>
(a -> b -> Ordering) -> f a -> f b -> Ordering
liftCompare a -> b -> Ordering
c t f a
x t f b
y
instance HFunctor t => HFunctor (WrapHF t) where
hmap :: forall (f :: k -> *) (g :: k -> *).
(f ~> g) -> WrapHF t f ~> WrapHF t g
hmap f ~> g
f (WrapHF t f x
x) = t g x -> WrapHF t g x
forall {k} {k} (t :: k -> k -> *) (f :: k) (a :: k).
t f a -> WrapHF t f a
WrapHF ((f ~> g) -> t f ~> t g
forall {k} {k1} (t :: (k -> *) -> k1 -> *) (f :: k -> *)
(g :: k -> *).
HFunctor t =>
(f ~> g) -> t f ~> t g
forall (f :: k -> *) (g :: k -> *). (f ~> g) -> t f ~> t g
hmap f x -> g x
f ~> g
f t f x
x)
instance Inject t => Inject (WrapHF t) where
inject :: forall (f :: k -> *). f ~> WrapHF t f
inject = t f x -> WrapHF t f x
forall {k} {k} (t :: k -> k -> *) (f :: k) (a :: k).
t f a -> WrapHF t f a
WrapHF (t f x -> WrapHF t f x) -> (f x -> t f x) -> f x -> WrapHF t f x
forall b c a. (b -> c) -> (a -> b) -> a -> c
. f x -> t f x
forall {k} (t :: (k -> *) -> k -> *) (f :: k -> *).
Inject t =>
f ~> t f
forall (f :: k -> *). f ~> t f
inject
instance HBind t => HBind (WrapHF t) where
hbind :: forall (f :: k -> *) (g :: k -> *).
(f ~> WrapHF t g) -> WrapHF t f ~> WrapHF t g
hbind f ~> WrapHF t g
f (WrapHF t f x
x) = t g x -> WrapHF t g x
forall {k} {k} (t :: k -> k -> *) (f :: k) (a :: k).
t f a -> WrapHF t f a
WrapHF ((f ~> t g) -> t f ~> t g
forall {k} (t :: (k -> *) -> k -> *) (f :: k -> *) (g :: k -> *).
HBind t =>
(f ~> t g) -> t f ~> t g
forall (f :: k -> *) (g :: k -> *). (f ~> t g) -> t f ~> t g
hbind (WrapHF t g x -> t g x
forall {k} {k} (t :: k -> k -> *) (f :: k) (a :: k).
WrapHF t f a -> t f a
unwrapHF (WrapHF t g x -> t g x) -> (f x -> WrapHF t g x) -> f x -> t g x
forall b c a. (b -> c) -> (a -> b) -> a -> c
. f x -> WrapHF t g x
f ~> WrapHF t g
f) t f x
x)
hjoin :: forall (f :: k -> *). WrapHF t (WrapHF t f) ~> WrapHF t f
hjoin (WrapHF t (WrapHF t f) x
x) = t f x -> WrapHF t f x
forall {k} {k} (t :: k -> k -> *) (f :: k) (a :: k).
t f a -> WrapHF t f a
WrapHF ((WrapHF t f ~> t f) -> t (WrapHF t f) ~> t f
forall {k} (t :: (k -> *) -> k -> *) (f :: k -> *) (g :: k -> *).
HBind t =>
(f ~> t g) -> t f ~> t g
forall (f :: k -> *) (g :: k -> *). (f ~> t g) -> t f ~> t g
hbind WrapHF t f x -> t f x
WrapHF t f ~> t f
forall {k} {k} (t :: k -> k -> *) (f :: k) (a :: k).
WrapHF t f a -> t f a
unwrapHF t (WrapHF t f) x
x)