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.