[Haskell-cafe] No need for integer literals

Henning Thielemann iakd0 at clusterf.urz.uni-halle.de
Fri Nov 19 12:21:48 EST 2004


In addition to Paul Hudak's "The Haskell School of Expression", Appendix A
"Built-in types are not special" I want to note that there is also hardly
a need for integer literals. :-]


module Digits where

infixl 9 #

(#) :: a -> (a -> b) -> b
x # f = f x

int :: Num a => a
int = 0

d0, d1, d2, d3, d4, d5, d6, d7, d8, d9 :: (Enum a, Num a) => a -> a

d0 n = n+n+n+n+n+n+n+n+n+n
d1 = succ . d0
d2 = succ . d1
d3 = succ . d2
d4 = succ . d3
d5 = succ . d4
d6 = succ . d5
d7 = succ . d6
d8 = succ . d7
d9 = succ . d8

test :: (Enum a, Num a) => a
test = int#d1#d4#d2#d8#d5#d7 * int#d2#d1



More information about the Haskell-Cafe mailing list