Logo Questions Linux Laravel Mysql Ubuntu Git Menu
 

Is it possible to iterate the application of a non-endomorphism?

In Haskell if I want to repeatedly apply an endomorphism a -> a to a value of type a I can just use iterate.

What about a function that is not an endomorphisms, but generic enough to work correctly on its return type?

Consider for example Just :: a -> Maybe a; I can write

Just . Just . Just ...

as many times as I want. Is there a way to write this shortly with something like

iterate' 3 Just :: a -> Maybe (Maybe (Maybe a))

or do we need something like dependent types to do this?

like image 610
marcosh Avatar asked Jun 11 '18 20:06

marcosh


3 Answers

It is possible with a minor tweak to the syntax you proposed: iterate' @3 Just instead of iterate' 3 Just.

This is because the result type depends on the number, so the number has to be a type literal, not a value literal. As you correctly note, doing this with arbitrary numbers would require dependent types[1], which Haskell doesn't have.

{-# OPTIONS_GHC -Wall #-}
{-# LANGUAGE TypeFamilies, KindSignatures, DataKinds,
    FlexibleInstances, UndecidableInstances, ScopedTypeVariables,
    FunctionalDependencies, TypeApplications, RankNTypes, FlexibleContexts,
    AllowAmbiguousTypes #-}

import qualified GHC.TypeLits as Lit

-- from type-natural
import Data.Type.Natural
import Data.Type.Natural.Builtin

class Iterate (n :: Nat) (f :: * -> *) (a :: *) (r :: *)
  | n f a -> r
  where
  iterate_peano :: Sing n -> (forall b . b -> f b) -> a -> r

instance Iterate 'Z f a a where
  iterate_peano SZ _ = id
instance Iterate n f (f a) r => Iterate ('S n) f a r where
  iterate_peano (SS n) f x = iterate_peano n f (f x)

iterate'
  :: forall (n :: Lit.Nat) f a r .
     (Iterate (ToPeano n) f a r, SingI n)
  => (forall b . b -> f b) -> a -> r
iterate' f a = iterate_peano (sToPeano (sing :: Sing n)) f a

If you load this in ghci, you can say

*Main> :t iterate' @3 Just
iterate' @3 Just :: a -> Maybe (Maybe (Maybe a))
*Main> iterate' @3 Just True
Just (Just (Just True))

This code uses two different type-level naturals: the built-in Nat from GHC.TypeLits and the classic Peano numerals from Data.Type.Natural. The former are needed to provide the nice iterate' @3 syntax, the latter are needed to perform the recursion (which happens in the Iterate class). I used Data.Type.Natural.Builtin to convert from a literal to the corresponding Peano numeral.

[1] However, given a specific way to consume the iterated values (e.g. if you know in advance that you'll only want to show them), you probably could adapt this code to work even for dynamic values of n. There's nothing in the type of iterate' that requires a statically known Nat; the only challenge is to prove that the result of the iteration satisfies the constraints you need.

like image 194
Roman Cheplyaka Avatar answered Sep 22 '22 22:09

Roman Cheplyaka


You can do it with template haskell, if you know the number at compile time (but unless the number is pretty large I don't think it's worth the hassle). If you don't know the number yet at compile time, you need to correctly model the return type, which we can do using a non-regular type:

data Iter f a = Iter0 a | IterS (Iter f (f a))

iterate' :: Int -> (forall x. x -> f x) -> a -> Iter f a
iterate' 0 f x = Iter0 x
iterate' n f x = IterS (iterate' (n-1) f (f x))

Iter is essentially a way of expressing the data type a | f a | f (f a) | f (f (f a)) | .... To use the result you need to recurse on Iter. Also the function has to be of the form a -> f a for some type constructor f, so you may need to do some newtype wrapping to get there. So... it's kind of a pain either way.

like image 28
luqui Avatar answered Sep 24 '22 22:09

luqui


You can do this without Template Haskell or type-level Nats. The kind of variable-depth recursive type you are building actually fits perfectly into the model of a free monad. We can use the unfold function from the free package to build up a Free structure and short-circuit when our counter reaches 0.

-- This extension is enabled so we can have nice type annotations
{-# Language ScopedTypeVariables #-}

import Control.Monad.Free (Free)
import qualified Control.Monad.Free as Free

iterate' :: forall f a. Functor f => Int -> (a -> f a) -> a -> Free f a
iterate' counter0 f x0 = Free.unfold run (counter0, x0)
  where

    -- If counter is 0, short circuit with current result
    -- Otherwise, continue computation with modified counter
    run :: (Int, a) -> Either a (f (Int, a))
    run (0      , x) = Left x
    run (counter, x) = Right (countDown counter <$> f x)

    countDown :: Int -> a -> (Int, a)
    countDown counter x = (counter - 1, x)

Now, it's easy to create and digest these types of values for any Functor.

> iterate' 3 Just True
Free (Just (Free (Just (Free (Just (Pure True))))))

> let f i = if i == 1 then Left "abort" else Right (i+1)

> iterate' 0 f 0
Pure 0
> iterate' 1 f 0
Free (Right (Pure 1))
> iterate' 2 f 0
Free (Right (Free (Left "abort")))

If your Functor also happens to be a Monad, you can use retract to collapse the recursive structure.

> Free.retract (iterate' 3 Just True)
Just True
> Free.retract (iterate' 0 f 0)
Right 0
> Free.retract (iterate' 1 f 0)
Right 1
> Free.retract (iterate' 2 f 0)
Left "abort"

I suggest reading the docs for Control.Monad.Free so you can get an idea for how these structures are created/consumed.


(Just as an aside, a -> Maybe a is an endomorphism, but it's an endomorphism in the Kleisli category of Maybe.)

like image 20
hololeap Avatar answered Sep 23 '22 22:09

hololeap