> {-# LANGUAGE DeriveFunctor, Rank2Types, ExistentialQuantification #-}
Any inductive type is defined like so
> newtype Ind f = Ind {flipinduct :: forall r. (f r -> r) -> r}
> induction = flip flipinduct
induction
has type (f a -> a) -> Ind f -> a
. There is a dual concept to this called coinduction.
> data CoInd f = forall r. Coinduction (r -> f r) r
> coinduction = Coinduction
coinduction
has type (a -> f a) -> a -> CoInd f
. Notice how induction
and coinduction
are dual. As an example of inductive and coinductive datatypes, look at this functor.
> data StringF rec = Nil | Cons Char rec deriving Functor
Without recursion, Ind StringF
is a finite string and CoInd StringF
is a finite or infinite string (if we use recursion, they are both finite or infinite or undefined strings). In general, it is possible to convert Ind f -> CoInd f
for any Functor f
. For example, we can wrap a functor value around a coinductive type
> wrap :: (Functor f) => f (CoInd f) -> CoInd f
> wrap fc = coinduction igo Nothing where
> --igo :: Maybe (CoInd f) -> f (Maybe (CoInd f))
> igo Nothing = fmap Just fc
> igo (Just (Coinduction step seed)) = fmap (Just . Coinduction step) $ step seed
This operation adds an extra operation (pattern matching Maybe
) for each step. This means it gives O(n)
overhead.
We can use induction on Ind f
and wrap
to get CoInd f
.
> convert :: (Functor f) => Ind f -> CoInd f
> convert = induction wrap
This is O(n^2)
. (Getting the first layer is O(1)
, but the nth element is O(n)
due to the nested Maybe
s, making this O(n^2)
total.)
Dually, we can define cowrap
, which takes an inductive type, and reveals its top Functor layer.
> cowrap :: (Functor f) => Ind f -> f (Ind f)
> cowrap = induction igo where
> --igo :: f (f (Ind f)) -> f (Ind f)
> igo = fmap (\fInd -> Ind $ \fold -> fold $ fmap (`flipinduct` fold) fInd)
induction
is always O(n)
, so so is cowrap
.
We can use coinduction
to produce CoInd f
from cowrap
and Ind f
.
> convert' :: (Functor f) => Ind f -> CoInd f
> convert' = coinduction cowrap
This is again O(n)
everytime we get an element, for a total of O(n^2)
.
My question is, without using recursion (directly or indirectly), can we convert Ind f
to CoInd f
in O(n)
time?
I know how to do it with recursion (convert Ind f
to Fix f
and then Fix f
to CoInd f
(the initial conversion is O(n)
, but then each element from CoInd f
is O(1)
, making the second conversion O(n)
total, and O(n) + O(n) = O(n)
)), but I would like to see if its possible without.
Observe that convert
and convert'
never used recursion, directly or indirectly. Nifty, ain't it!
(f a -> a) -> Ind a -> a
." Should beInd f
. – Toreyinduction :: (f a -> a) -> (Ind a -> a) ≈ (f a -> a, Ind a) -> a
, so shouldn't it's dual be either(Ind a -> a) -> (f a -> a)
ora -> (f a -> a, Ind a)
? – Toreyf :: f a -> a
,cata f
:: Mu f -> a is the unique f-algebra homomorphism from the initial f-algebra (Mu f) to a. This is how you get(f a -> a) -> Mu f -> a
.flip
that and you can literally take that as the definition of Mu f! As for ana/coinduction, Given an f-coalgebra (f :: a -> f a), we haveana f :: a -> Nu f
. So(a -> f a) -> a -> Nu f
. The arrows that get turned around were 'f' and thecata f
/ana f
arrows, not the meta-theoretic ones. When you dualize the def. of monad to make comonad, same thing happens. – Firewardenmap
asmap = reverse . map' [] where {map' seed [] = seed; map' seed (x : xs) = map' (x : seed) xs}
. – Agleam