This may be a GHC bug, but even though in the module Data.TypeLevel.Num.Reps has the header

{-# LANGUAGE EmptyDataDecls, TypeOperators #-}

I still get an error with both ghc and ghci version 6.8.2 unless I throw in the -XTypeOperators flag.

> cat Go.hs
import Data.TypeLevel.Num.Reps
main = return (undefined :: D2 :+ D1) >> print "Done"

> ghc --make Go.hs
[1 of 1] Compiling Main             ( Go.hs, Go.o )

Go.hs:3:31:
    Illegal operator `:+' in type `D2 :+ D1'
      (Use -XTypeOperators to allow operators in types)

> ghc --make -XTypeOperators Go.hs
[1 of 1] Compiling Main             ( Go.hs, Go.o )
Linking Go ...

> ghc --version
The Glorious Glasgow Haskell Compilation System, version 6.8.2

Dan

Alfonso Acosta wrote:
Don't expect anything astonishing yet, but an initial version of the
library can be found at

http:/code.haskell.org/type-level

To make reviewing easier I have put the haddock-generated documentation at

http://code.haskell.org/~fons/type-level/doc/

Some remarks:

* Only Positive and Natural numerals in decimal representation are
supported. It would be cool to add support for Integers though.

* The code is based on Oleg's implimentation of type-level binaries
http://okmij.org/ftp/Computation/resource-aware-prog/BinaryNumber.hs

* exponentiation/log and GCD is not implemented yet

* multiplication is not relational and thus division is broken. I
tried porting Oleg's multiplication algorithm without success.

* Aliases (in binary, octal decimal and hexadecimal form) for
type-level values and their value-level reflection functions are
generated with TH.
  That implies:
    * Long compilation time depending on your system
    * Although errors will always be reported in decimal form, the end
user can input values using other bases (only for values in the range
of generated aliases of course)

* It would be cool to have "real" support for other bases apart from decimals
  * It would imply having unlimited size of input for other bases
(right now if we want to input a value out of the alises limit,
decimal reprentation is mandatory)
  * However, is it feasible? How could it be done without needing to
implement the operations for each base? WOuld it be possible to
"overload" the type-level operators so that they worked with different
representations and mixed representation arguments?

* Booleans are not implemented (Wolfgang?)

I would be happy to hear any suggestions, get code reviews and/or contributions.

Cheers,

Fons








On Feb 7, 2008 11:17 AM, Wolfgang Jeltsch <[EMAIL PROTECTED]> wrote:
Am Donnerstag, 7. Februar 2008 02:47 schrieb Alfonso Acosta:
The other library I use for type-level programming is HList. It has
type-level booleans already so you might what to take a look at it if
you're not already familiar with it.
Thanks I'll have a look at it.
I have to admit that I don't like the names HBool, HTrue and HFalse.  What do
they mean?  Heterogenous booleans?  Heterogenous truth?  Why it's "Bool"
instead of "Boolean" and therefore not conforming to the Prelude convention?

Heterogenous lists are not directly about type level computation.  A HList
type is usually inhabited.  On the other hand, types which denote type level
naturals or type-level booleans are empty data types.  So type level booleans
should go into some type level programming library like the one Alfonso and I
want to create.  HList should then use these booleans.  This is at least my
opinion.

Best wishes,
Wolfgang

_______________________________________________
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

Reply via email to