[Haskell-cafe] Learn You a Haskell for Great Good - a few doubts

Alexander Solla alex.solla at gmail.com
Thu Mar 3 22:00:08 CET 2011


On Wed, Mar 2, 2011 at 10:09 PM, Karthick Gururaj <
karthick.gururaj at gmail.com> wrote:

> Hello,
>
> I'm learning Haskell from the extremely well written (and well
> illustrated as well!) tutorial - http://learnyouahaskell.com/chapters.
> I have couple of questions from my readings so far.
>
> In "typeclasses - 101"
> (http://learnyouahaskell.com/types-and-typeclasses#typeclasses-101),
> there is a paragraph that reads:
> Enum members are sequentially ordered types - they can be enumerated.
> The main advantage of the Enum typeclass is that we can use its types
> in list ranges. They also have defined successors and predecesors,
> which you can get with the succ and pred functions. Types in this
> class: (), Bool, Char, Ordering, Int, Integer, Float and Double.
>
> What is the "()" type? Does it refer to a tuple? How can tuple be
> ordered, let alone be enum'd?
>

Any set can be put into an order.  That's the well-ordering principle.
 Basically, the most natural order for pairs is the lexicographical order.
 There are instances of the form:

instance (Ord a, Ord b) => Ord (a,b)

in GHC.Enum (if you're using GHC).  You can also create Enum instances for
pairs, but at least one of the "sides" must be bounded.  Otherwise, the
enumeration will have an uncomputable order-type (something like the order
type of the rationals). Check out http://en.wikipedia.org/wiki/Order_type if
you're interested in what all that "order type" stuff means.

I wrote  an instance for this very purpose the other day:


-- An intuitive way to think about this is in terms of tables. Given
datatypes
--
-- @
-- data X = A | B | C | D deriving ('Bounded', 'Enum', 'Eq', 'Ord', 'Show')
-- data Y = E | F | G     deriving ('Bounded', 'Enum', 'Eq', 'Ord', 'Show')
-- @
--
-- we can form the table
--
-- @
-- (A, E)   (A, F)   (A, G)
-- (B, E)   (B, F)   (B, G)
-- (C, E)   (C, F)   (C, G)
-- (D, E)   (D, F)   (D, G)
-- @
--
-- in a natural lexicographical order.  We simply require that there be a
finite
-- number of columns, and allow an unbounded number of rows (in so far as
the
-- lazy evaluation mechanism allows them).  In even more practical terms, we
require
-- a finite number of columns because we use that number to perform
arithmetic.

instance ( Bounded b
         , Enum a
         , Enum b
         ) => Enum (a, b) where
              toEnum k = let n = 1 + fromEnum (maxBound :: b) -- Enums are 0
indexed, but we want to
                             a = toEnum ((k `div` n))         -- divide by
the number of elements in a row to find the row and
                             b = toEnum ((k `mod` n))         -- get the
remainder to find the column.
                          in (a,b)

              fromEnum (a, b) = let n = 1 + fromEnum (maxBound :: b)
                                    i = fromEnum a
                                    j = fromEnum b
                                 in (i*n + j)

-- | This instance of 'Enum' is defined in terms of the previous instance.
 We
-- use the natural equivalence of the types @(a,b,c)@ and @(a,(b,c))@ and
use
-- the previous definition.  Again, notice that all elements but the first
must
-- be bounded.
instance ( Bounded b
         , Bounded c
         , Enum a
         , Enum b
         , Enum c
         ) => Enum (a, b, c) where
                   fromEnum (a, b, c) = fromEnum (a, (b,c))
                   toEnum k = let (a, (b, c)) = toEnum k
                               in (a, b,  c)






> So tuples are in "Ord" type class atleast. What is the ordering logic?
>
>
Lexicographical.  Dictionary order.

Another question, on the curried functions - specifically for infix
> functions. Suppose I need a function that takes an argument and adds
> five to it. I can do:
> Prelude> let addFive = (+) 5
> Prelude> addFive 4
> 9
>
> The paragraph: "Infix functions can also be partially applied by using
> sections. To section an infix function, simply surround it with
> parentheses and only supply a parameter on one side. That creates a
> function that takes one parameter and then applies it to the side
> that's missing an operand": describes a different syntax. I tried that
> as well:
>
> Prelude> let addFive' = (+5)
> Prelude> addFive' 3
> 8
>
> Ok. Works. But on a non-commutative operation like division, we get:
> Prelude> let x = (/) 20.0
> Prelude> x 10
> 2.0
> Prelude> let y = (/20.0)
> Prelude> y 10
> 0.5
>
> So a curried infix operator fixes the first argument and a "sectioned
> infix" operator fixes the second argument?
>

I guess, except you can section infix operators the other way:

> let twentyover = (20 /)
> twentyover 5
4.0
-------------- next part --------------
An HTML attachment was scrubbed...
URL: <http://www.haskell.org/pipermail/haskell-cafe/attachments/20110303/cf78409e/attachment.htm>


More information about the Haskell-Cafe mailing list