
I've been doing some basic work on a support library for type level programming ( see http://hackage.haskell.org/trac/summer-of-code/ticket/1541 ). I know there have been similar attempts using fundeps ( Edward Kmett showed me some of his work, but I've lost the address... ) but this approach uses type families. Anyway, I would like to hear your critique! Currently I have higher order type functions and ad-hoc parametrized functions. Here's what foldl looks like: type family Foldl ( func :: * -> * -> * ) val list type instance Foldl func val ( Cons first rest ) = Foldl func ( Eval ( func val first ) ) rest type instance Foldl func val Nill = val Notice the use of Eval - this is a trick to enable us to pass around data with kind * -> *, or whatever, and then trip this into becoming a value. Here's an example, using this trick to define factorial: -- multiplication type family Times x y type instance Times x Zero = Zero type instance Times x ( Succ y ) = Sum x ( Times x y ) -- The "first order" function version of Times data TimesL x y -- Where what Eval forced TimesL to become. type instance Eval ( TimesL x y ) = Times x y -- multiplies all the elements of list of Nat together type Product l = Foldl TimesL ( Succ Zero ) l -- here list to creates a list from ( Succ Zero ) to the given number type Factorial x = Product ( ListTo x ) We can now use the function like this: *TPrelude> result ( ) :: Factorial ( Succ ( Succ ( Succ ( Zero ) ) ) ) Succ (Succ (Succ (Succ (Succ (Succ Zero))))) Using the parametrized types kinda reminds me of programming in Erlang: -- What would conventionally be the monad type class, parametized over m type family Bind m ma ( f :: * -> * ) type family Return m a type family Sequence m ma mb Here's the maybe monad: -- Monad instance type instance Bind ( Maybe t ) Nothing f = Nothing type instance Bind ( Maybe t ) ( Just a ) f = Eval ( f a ) type instance Sequence ( Maybe t ) Nothing a = Nothing type instance Sequence ( Maybe t ) ( Just a ) b = b type instance Return ( Maybe t ) a = Just a type instance Eval ( Just x ) = Just x Here's an example: *TPrelude> result ( ) :: Bind ( Maybe Nat ) ( Just Zero ) Just Just Zero For more information and to download the loose collection of module implementing this please see: http://www.killersmurf.com/projects/typelib John Morrice

There is already a library for type level number, called typelevel.
It's nice because it uses decimal representation of numbers and can
handle numbers of reasonable size.
I use it in the LLVM bindings.
-- Lennart
On Mon, Mar 30, 2009 at 1:07 AM, spoon
I've been doing some basic work on a support library for type level programming ( see http://hackage.haskell.org/trac/summer-of-code/ticket/1541 ). I know there have been similar attempts using fundeps ( Edward Kmett showed me some of his work, but I've lost the address... ) but this approach uses type families.
Anyway, I would like to hear your critique!
Currently I have higher order type functions and ad-hoc parametrized functions.
Here's what foldl looks like:
type family Foldl ( func :: * -> * -> * ) val list type instance Foldl func val ( Cons first rest ) = Foldl func ( Eval ( func val first ) ) rest type instance Foldl func val Nill = val
Notice the use of Eval - this is a trick to enable us to pass around data with kind * -> *, or whatever, and then trip this into becoming a value. Here's an example, using this trick to define factorial:
-- multiplication type family Times x y type instance Times x Zero = Zero type instance Times x ( Succ y ) = Sum x ( Times x y )
-- The "first order" function version of Times data TimesL x y
-- Where what Eval forced TimesL to become. type instance Eval ( TimesL x y ) = Times x y
-- multiplies all the elements of list of Nat together type Product l = Foldl TimesL ( Succ Zero ) l
-- here list to creates a list from ( Succ Zero ) to the given number type Factorial x = Product ( ListTo x )
We can now use the function like this:
*TPrelude> result ( ) :: Factorial ( Succ ( Succ ( Succ ( Zero ) ) ) ) Succ (Succ (Succ (Succ (Succ (Succ Zero)))))
Using the parametrized types kinda reminds me of programming in Erlang:
-- What would conventionally be the monad type class, parametized over m type family Bind m ma ( f :: * -> * ) type family Return m a type family Sequence m ma mb
Here's the maybe monad:
-- Monad instance type instance Bind ( Maybe t ) Nothing f = Nothing type instance Bind ( Maybe t ) ( Just a ) f = Eval ( f a ) type instance Sequence ( Maybe t ) Nothing a = Nothing type instance Sequence ( Maybe t ) ( Just a ) b = b type instance Return ( Maybe t ) a = Just a
type instance Eval ( Just x ) = Just x
Here's an example: *TPrelude> result ( ) :: Bind ( Maybe Nat ) ( Just Zero ) Just Just Zero
For more information and to download the loose collection of module implementing this please see: http://www.killersmurf.com/projects/typelib
John Morrice
_______________________________________________ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe

Hello,
I suppose Lennart is referring to type-level [1]. But type-level uses
functional dependencies, right?
There is also tfp [2], which uses type families. In general, how would you
say your work compares to these two?
Thanks,
Pedro
[1] http://hackage.haskell.org/cgi-bin/hackage-scripts/package/type-level
[2] http://hackage.haskell.org/cgi-bin/hackage-scripts/package/tfp
On Mon, Mar 30, 2009 at 08:22, Lennart Augustsson
There is already a library for type level number, called typelevel. It's nice because it uses decimal representation of numbers and can handle numbers of reasonable size. I use it in the LLVM bindings.
-- Lennart
On Mon, Mar 30, 2009 at 1:07 AM, spoon
wrote: I've been doing some basic work on a support library for type level programming ( see http://hackage.haskell.org/trac/summer-of-code/ticket/1541 ). I know there have been similar attempts using fundeps ( Edward Kmett showed me some of his work, but I've lost the address... ) but this approach uses type families.
Anyway, I would like to hear your critique!
Currently I have higher order type functions and ad-hoc parametrized functions.
Here's what foldl looks like:
type family Foldl ( func :: * -> * -> * ) val list type instance Foldl func val ( Cons first rest ) = Foldl func ( Eval ( func val first ) ) rest type instance Foldl func val Nill = val
Notice the use of Eval - this is a trick to enable us to pass around data with kind * -> *, or whatever, and then trip this into becoming a value. Here's an example, using this trick to define factorial:
-- multiplication type family Times x y type instance Times x Zero = Zero type instance Times x ( Succ y ) = Sum x ( Times x y )
-- The "first order" function version of Times data TimesL x y
-- Where what Eval forced TimesL to become. type instance Eval ( TimesL x y ) = Times x y
-- multiplies all the elements of list of Nat together type Product l = Foldl TimesL ( Succ Zero ) l
-- here list to creates a list from ( Succ Zero ) to the given number type Factorial x = Product ( ListTo x )
We can now use the function like this:
*TPrelude> result ( ) :: Factorial ( Succ ( Succ ( Succ ( Zero ) ) ) ) Succ (Succ (Succ (Succ (Succ (Succ Zero)))))
Using the parametrized types kinda reminds me of programming in Erlang:
-- What would conventionally be the monad type class, parametized over m type family Bind m ma ( f :: * -> * ) type family Return m a type family Sequence m ma mb
Here's the maybe monad:
-- Monad instance type instance Bind ( Maybe t ) Nothing f = Nothing type instance Bind ( Maybe t ) ( Just a ) f = Eval ( f a ) type instance Sequence ( Maybe t ) Nothing a = Nothing type instance Sequence ( Maybe t ) ( Just a ) b = b type instance Return ( Maybe t ) a = Just a
type instance Eval ( Just x ) = Just x
Here's an example: *TPrelude> result ( ) :: Bind ( Maybe Nat ) ( Just Zero ) Just Just Zero
For more information and to download the loose collection of module implementing this please see: http://www.killersmurf.com/projects/typelib
John Morrice
_______________________________________________ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe
_______________________________________________ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe

Lennart,
I think the major emphasis that John's library has is on doing things other
than numbers well in the type system, using the type family syntax to avoid
the proliferation of intermediary names that the fundep approach yields.
I think his type family approach for type-level monads for instance is
pretty neat and quite readable.
The biggest problem that I see with the approach is the general lack of
availability of currying due to Haskell not having 'polymorphic kinds'. So
he'd have to use Curry combinators that are specific to both the number of
arguments at the kinds of the arguments that a function has.
John,
http://hackage.haskell.org/cgi-bin/hackage-scripts/package/type-int
contains my old type level 2s and 16s complement integer code and some
machinery for manipulating type level lists a la HList.
-Edward Kmett
On Mon, Mar 30, 2009 at 3:22 AM, Lennart Augustsson
There is already a library for type level number, called typelevel. It's nice because it uses decimal representation of numbers and can handle numbers of reasonable size. I use it in the LLVM bindings.
-- Lennart
On Mon, Mar 30, 2009 at 1:07 AM, spoon
wrote: I've been doing some basic work on a support library for type level programming ( see http://hackage.haskell.org/trac/summer-of-code/ticket/1541 ). I know there have been similar attempts using fundeps ( Edward Kmett showed me some of his work, but I've lost the address... ) but this approach uses type families.
Anyway, I would like to hear your critique!
Currently I have higher order type functions and ad-hoc parametrized functions.
Here's what foldl looks like:
type family Foldl ( func :: * -> * -> * ) val list type instance Foldl func val ( Cons first rest ) = Foldl func ( Eval ( func val first ) ) rest type instance Foldl func val Nill = val
Notice the use of Eval - this is a trick to enable us to pass around data with kind * -> *, or whatever, and then trip this into becoming a value. Here's an example, using this trick to define factorial:
-- multiplication type family Times x y type instance Times x Zero = Zero type instance Times x ( Succ y ) = Sum x ( Times x y )
-- The "first order" function version of Times data TimesL x y
-- Where what Eval forced TimesL to become. type instance Eval ( TimesL x y ) = Times x y
-- multiplies all the elements of list of Nat together type Product l = Foldl TimesL ( Succ Zero ) l
-- here list to creates a list from ( Succ Zero ) to the given number type Factorial x = Product ( ListTo x )
We can now use the function like this:
*TPrelude> result ( ) :: Factorial ( Succ ( Succ ( Succ ( Zero ) ) ) ) Succ (Succ (Succ (Succ (Succ (Succ Zero)))))
Using the parametrized types kinda reminds me of programming in Erlang:
-- What would conventionally be the monad type class, parametized over m type family Bind m ma ( f :: * -> * ) type family Return m a type family Sequence m ma mb
Here's the maybe monad:
-- Monad instance type instance Bind ( Maybe t ) Nothing f = Nothing type instance Bind ( Maybe t ) ( Just a ) f = Eval ( f a ) type instance Sequence ( Maybe t ) Nothing a = Nothing type instance Sequence ( Maybe t ) ( Just a ) b = b type instance Return ( Maybe t ) a = Just a
type instance Eval ( Just x ) = Just x
Here's an example: *TPrelude> result ( ) :: Bind ( Maybe Nat ) ( Just Zero ) Just Just Zero
For more information and to download the loose collection of module implementing this please see: http://www.killersmurf.com/projects/typelib
John Morrice
_______________________________________________ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe
_______________________________________________ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe

Haskell not having 'polymorphic kinds'.
Is there a good description of why Haskell doesn't have polymorphic kinds?
2009/3/30 Edward Kmett
Lennart,
I think the major emphasis that John's library has is on doing things other than numbers well in the type system, using the type family syntax to avoid the proliferation of intermediary names that the fundep approach yields.
I think his type family approach for type-level monads for instance is pretty neat and quite readable.
The biggest problem that I see with the approach is the general lack of availability of currying due to Haskell not having 'polymorphic kinds'. So he'd have to use Curry combinators that are specific to both the number of arguments at the kinds of the arguments that a function has.
John,
http://hackage.haskell.org/cgi-bin/hackage-scripts/package/type-int
contains my old type level 2s and 16s complement integer code and some machinery for manipulating type level lists a la HList.
-Edward Kmett
On Mon, Mar 30, 2009 at 3:22 AM, Lennart Augustsson < lennart@augustsson.net> wrote:
There is already a library for type level number, called typelevel. It's nice because it uses decimal representation of numbers and can handle numbers of reasonable size. I use it in the LLVM bindings.
-- Lennart
On Mon, Mar 30, 2009 at 1:07 AM, spoon
wrote: I've been doing some basic work on a support library for type level programming ( see http://hackage.haskell.org/trac/summer-of-code/ticket/1541 ). I know there have been similar attempts using fundeps ( Edward Kmett showed me some of his work, but I've lost the address... ) but this approach uses type families.
Anyway, I would like to hear your critique!
Currently I have higher order type functions and ad-hoc parametrized functions.
Here's what foldl looks like:
type family Foldl ( func :: * -> * -> * ) val list type instance Foldl func val ( Cons first rest ) = Foldl func ( Eval ( func val first ) ) rest type instance Foldl func val Nill = val
Notice the use of Eval - this is a trick to enable us to pass around data with kind * -> *, or whatever, and then trip this into becoming a value. Here's an example, using this trick to define factorial:
-- multiplication type family Times x y type instance Times x Zero = Zero type instance Times x ( Succ y ) = Sum x ( Times x y )
-- The "first order" function version of Times data TimesL x y
-- Where what Eval forced TimesL to become. type instance Eval ( TimesL x y ) = Times x y
-- multiplies all the elements of list of Nat together type Product l = Foldl TimesL ( Succ Zero ) l
-- here list to creates a list from ( Succ Zero ) to the given number type Factorial x = Product ( ListTo x )
We can now use the function like this:
*TPrelude> result ( ) :: Factorial ( Succ ( Succ ( Succ ( Zero ) ) ) ) Succ (Succ (Succ (Succ (Succ (Succ Zero)))))
Using the parametrized types kinda reminds me of programming in Erlang:
-- What would conventionally be the monad type class, parametized over m type family Bind m ma ( f :: * -> * ) type family Return m a type family Sequence m ma mb
Here's the maybe monad:
-- Monad instance type instance Bind ( Maybe t ) Nothing f = Nothing type instance Bind ( Maybe t ) ( Just a ) f = Eval ( f a ) type instance Sequence ( Maybe t ) Nothing a = Nothing type instance Sequence ( Maybe t ) ( Just a ) b = b type instance Return ( Maybe t ) a = Just a
type instance Eval ( Just x ) = Just x
Here's an example: *TPrelude> result ( ) :: Bind ( Maybe Nat ) ( Just Zero ) Just Just Zero
For more information and to download the loose collection of module implementing this please see: http://www.killersmurf.com/projects/typelib
John Morrice
_______________________________________________ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe
_______________________________________________ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe
_______________________________________________ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe
-- /jve

John Van Enk wrote:
Haskell not having 'polymorphic kinds'.
Is there a good description of why Haskell doesn't have polymorphic kinds?
IANA expert but polymorphic kinds belong to a set of reasonably new influences (e.g. from dependently typed programming languages and generic programming) and they haven't been 1) polished enough to be a widely accepted standard or 2) simply haven't been implemented yet (low priority, etc). Besides that, I sometimes see polymorphic kinds in GHC error messages, so I suspect that at least parts of GHC already support them. Martijn.

I suppose having a good description of what I'd like to do might help: I'd like to be able to make an N-Tuple an instance of a type class. class Foo a where .... instance Foo (,) where .... instance Foo (,,) where .... The different kindedness of (,) and (,,) prevent this from working. /jve On Mon, Mar 30, 2009 at 2:00 PM, Martijn van Steenbergen < martijn@van.steenbergen.nl> wrote:
John Van Enk wrote:
Haskell not having 'polymorphic kinds'. Is there a good description of why Haskell doesn't have polymorphic kinds?
IANA expert but polymorphic kinds belong to a set of reasonably new influences (e.g. from dependently typed programming languages and generic programming) and they haven't been 1) polished enough to be a widely accepted standard or 2) simply haven't been implemented yet (low priority, etc).
Besides that, I sometimes see polymorphic kinds in GHC error messages, so I suspect that at least parts of GHC already support them.
Martijn.
-- /jve

Thats a bit farther down the rabbit hole than the concern in question,
though certainly related.
An example of what you could write with polymorphic kinds, inventing a
notation for polymorphic kind variables using 'x to denote a polymorphic
kind x, which could subtitute in for a kind k = * | ** | k -> k | ...
type Id (f :: 'k) = f
type Const (a :: 'a) (b :: 'b) = a
data True
data False
type family If c (x :: 'k) (y :: 'k) :: 'k
type instance If True x y = x
type instance If False x y = y
then you could safely apply Id and If types of different kinds.
class Container x where
type Elem x :: *
type SearchOffersMultipleResults x :: *
search :: x -> SearchResult x
type SearchResult x = (If (SearchOffersMultipleResults x) [] Maybe) (Elem
x)
instance Container (SomeContainer a) where
type Elem (SomeContainer a) = a
type SearchOffersMultipleResults (SomeContainer a) = True
I suppose once down this slippery slope you might consider classes that are
parameterized on types with polymorphic kinds as well, but I definitely
wouldn't start there. ;)
-Edward
On Mon, Mar 30, 2009 at 2:54 PM, John Van Enk
I suppose having a good description of what I'd like to do might help: I'd like to be able to make an N-Tuple an instance of a type class.
class Foo a where ....
instance Foo (,) where ....
instance Foo (,,) where .... The different kindedness of (,) and (,,) prevent this from working.
/jve
On Mon, Mar 30, 2009 at 2:00 PM, Martijn van Steenbergen < martijn@van.steenbergen.nl> wrote:
John Van Enk wrote:
Haskell not having 'polymorphic kinds'. Is there a good description of why Haskell doesn't have polymorphic kinds?
IANA expert but polymorphic kinds belong to a set of reasonably new influences (e.g. from dependently typed programming languages and generic programming) and they haven't been 1) polished enough to be a widely accepted standard or 2) simply haven't been implemented yet (low priority, etc).
Besides that, I sometimes see polymorphic kinds in GHC error messages, so I suspect that at least parts of GHC already support them.
Martijn.
-- /jve

I suppose having a good description of what I'd like to do might help: I'd like to be able to make an N-Tuple an instance of a type class.
class Foo a where instance Foo (,) where instance Foo (,,) where .... The different kindedness of (,) and (,,) prevent this from working.
Not that this is going to help you much, but perhaps you might want to refine the problem specification:-) Claus {-# LANGUAGE TypeFamilies #-} {-# LANGUAGE FlexibleInstances #-} {-# LANGUAGE KindSignatures #-} {-# LANGUAGE MultiParamTypeClasses #-} {-# LANGUAGE EmptyDataDecls #-} import Data.Char data Ap0 (f :: *) data Ap1 (f :: * -> *) data Ap2 (f :: * -> * -> *) data Ap3 (f :: * -> * -> * -> *) type family F a b type instance F (Ap0 b) b = b type instance F (Ap1 f) b = f b type instance F (Ap2 f) b = f b b type instance F (Ap3 f) b = f b b b class Foo a b where foo :: a -> b -> F a b unfoo :: a -> F a b -> b instance Foo (Ap0 Bool) Bool where foo _ b = b unfoo _ b = b instance Foo (Ap2 (,)) Bool where foo _ b = (b,not b) unfoo _ (a,b) = a&&b instance Foo (Ap2 (,)) Char where foo _ c = (chr (ord c+1), chr (ord c+2)) unfoo _ (a,b) = maximum [a,b] instance Foo (Ap3 (,,)) Char where foo _ c = (c, chr (ord c+1), chr (ord c+2)) unfoo _ (a,b,c) = maximum [a,b,c] f bs | unfoo (undefined::Ap2 (,)) bs = foo (undefined::Ap3 (,,)) 'a' | otherwise = foo (undefined::Ap3 (,,)) 'b' g what1 what2 bs | unfoo what1 bs = foo what2 'a' | otherwise = foo what2 '0' main = do print (f (True,False)::(Char,Char,Char)) print (g (undefined::Ap0 Bool) (undefined::Ap3 (,,)) False ::(Char,Char,Char)) print (g (undefined::Ap2 (,)) (undefined::Ap2 (,)) (True,False)::(Char,Char))

I wasn't questioning the utility of John's library.
But I saw him mentioning unary numbers and I think it's a mistake to
use those for anything practical involving even moderately sized
numbers.
I'd love to see a good type level programming library. There's a lot
of it out there, but it's never packaged in a way that is reusable as
a good library.
-- Lennart
2009/3/30 Edward Kmett
Lennart,
I think the major emphasis that John's library has is on doing things other than numbers well in the type system, using the type family syntax to avoid the proliferation of intermediary names that the fundep approach yields.
I think his type family approach for type-level monads for instance is pretty neat and quite readable.
The biggest problem that I see with the approach is the general lack of availability of currying due to Haskell not having 'polymorphic kinds'. So he'd have to use Curry combinators that are specific to both the number of arguments at the kinds of the arguments that a function has.
John,
http://hackage.haskell.org/cgi-bin/hackage-scripts/package/type-int
contains my old type level 2s and 16s complement integer code and some machinery for manipulating type level lists a la HList.
-Edward Kmett
On Mon, Mar 30, 2009 at 3:22 AM, Lennart Augustsson
wrote: There is already a library for type level number, called typelevel. It's nice because it uses decimal representation of numbers and can handle numbers of reasonable size. I use it in the LLVM bindings.
-- Lennart
On Mon, Mar 30, 2009 at 1:07 AM, spoon
wrote: I've been doing some basic work on a support library for type level programming ( see http://hackage.haskell.org/trac/summer-of-code/ticket/1541 ). I know there have been similar attempts using fundeps ( Edward Kmett showed me some of his work, but I've lost the address... ) but this approach uses type families.
Anyway, I would like to hear your critique!
Currently I have higher order type functions and ad-hoc parametrized functions.
Here's what foldl looks like:
type family Foldl ( func :: * -> * -> * ) val list type instance Foldl func val ( Cons first rest ) = Foldl func ( Eval ( func val first ) ) rest type instance Foldl func val Nill = val
Notice the use of Eval - this is a trick to enable us to pass around data with kind * -> *, or whatever, and then trip this into becoming a value. Here's an example, using this trick to define factorial:
-- multiplication type family Times x y type instance Times x Zero = Zero type instance Times x ( Succ y ) = Sum x ( Times x y )
-- The "first order" function version of Times data TimesL x y
-- Where what Eval forced TimesL to become. type instance Eval ( TimesL x y ) = Times x y
-- multiplies all the elements of list of Nat together type Product l = Foldl TimesL ( Succ Zero ) l
-- here list to creates a list from ( Succ Zero ) to the given number type Factorial x = Product ( ListTo x )
We can now use the function like this:
*TPrelude> result ( ) :: Factorial ( Succ ( Succ ( Succ ( Zero ) ) ) ) Succ (Succ (Succ (Succ (Succ (Succ Zero)))))
Using the parametrized types kinda reminds me of programming in Erlang:
-- What would conventionally be the monad type class, parametized over m type family Bind m ma ( f :: * -> * ) type family Return m a type family Sequence m ma mb
Here's the maybe monad:
-- Monad instance type instance Bind ( Maybe t ) Nothing f = Nothing type instance Bind ( Maybe t ) ( Just a ) f = Eval ( f a ) type instance Sequence ( Maybe t ) Nothing a = Nothing type instance Sequence ( Maybe t ) ( Just a ) b = b type instance Return ( Maybe t ) a = Just a
type instance Eval ( Just x ) = Just x
Here's an example: *TPrelude> result ( ) :: Bind ( Maybe Nat ) ( Just Zero ) Just Just Zero
For more information and to download the loose collection of module implementing this please see: http://www.killersmurf.com/projects/typelib
John Morrice
_______________________________________________ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe
_______________________________________________ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe
_______________________________________________ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe

On Mon, Mar 30, 2009 at 3:54 PM, Lennart Augustsson
I wasn't questioning the utility of John's library. But I saw him mentioning unary numbers and I think it's a mistake to use those for anything practical involving even moderately sized numbers.
Completely agreed. =) I only popped in because it seemed that between your response and Jose's the conversation seemed likely to devolve into an interpretation of what he was trying to do as 'just another type level number lib' and I wanted to steer things in a more productive direction.
I'd love to see a good type level programming library. There's a lot of it out there, but it's never packaged in a way that is reusable as a good library.
I started trying to package a bunch of this stuff up a year or two back, and just basically lost the will to finish because it was just too tedious to use with fundeps. Even if the lack of polymorphic kinds seems to force it into a very 'pointful' style of programming, I'd be curious to see how far it could be taken. -Edward Kmett

On Mon, 2009-03-30 at 20:54 +0100, Lennart Augustsson wrote:
I wasn't questioning the utility of John's library. But I saw him mentioning unary numbers and I think it's a mistake to use those for anything practical involving even moderately sized numbers.
Also agreed! tfp supports rational arithmetic through its decimal numbers, and in my opinion, a new library should build upon tfp, adding features like the regular prelude H.O.F.s until there is a prelude for types. - John Morrice
participants (7)
-
Claus Reinke
-
Edward Kmett
-
John Van Enk
-
José Pedro Magalhães
-
Lennart Augustsson
-
Martijn van Steenbergen
-
spoon