Send Beginners mailing list submissions to
        beginners@haskell.org

To subscribe or unsubscribe via the World Wide Web, visit
        http://www.haskell.org/mailman/listinfo/beginners
or, via email, send a message with subject or body 'help' to
        beginners-requ...@haskell.org

You can reach the person managing the list at
        beginners-ow...@haskell.org

When replying, please edit your Subject line so it is more specific
than "Re: Contents of Beginners digest..."


Today's Topics:

   1.  Haskell Generic Function Question (William Gilbert)
   2. Re:  Haskell Generic Function Question (Paul Visschers)
   3.  Re: Haskell Generic Function Question (Ertugrul Soeylemez)
   4. Re:  Haskell Generic Function Question (Thomas Friedrich)
   5. Re:  Haskell Generic Function Question (Jeff Wheeler)
   6.  Case Expressions (Nathan Holden)
   7. Re:  Case Expressions (Brent Yorgey)
   8. Re:  Haskell Generic Function Question (Jan Jakubuv)
   9. Re:  Case Expressions (Dean Herington)
  10. Re:  Case Expressions (Thomas Friedrich)


----------------------------------------------------------------------

Message: 1
Date: Thu, 28 May 2009 11:50:36 -0400
From: William Gilbert <gilber...@gmail.com>
Subject: [Haskell-beginners] Haskell Generic Function Question
To: beginners@haskell.org
Message-ID:
        <a928161a0905280850r7751f0d4m1b41cda7eb32...@mail.gmail.com>
Content-Type: text/plain; charset=ISO-8859-1

I am trying to write a function that will covert either an integer or
an int into a list containing its digits.

ex. toIntegralList 123 -> [1,2,3]

I have written the following definition that tries to use read to
generically cast a string value to an Integral type that is the same
as the Integral passed in:

toIntegralList :: (Integral a) => a -> [a]
toIntegralList x = map (\c -> read [c] :: a) (show x)

I understand it would be very simple to just create two functions, one
that converts an Int and one that converts an Integer, however I was
wondering if there were any way to accomplish what I am trying to do
here.

Thanks In Advance,
Bryan


------------------------------

Message: 2
Date: Thu, 28 May 2009 18:49:15 +0200
From: Paul Visschers <m...@paulvisschers.net>
Subject: Re: [Haskell-beginners] Haskell Generic Function Question
To: William Gilbert <gilber...@gmail.com>
Cc: beginners@haskell.org
Message-ID: <4a1ec08b.3060...@paulvisschers.net>
Content-Type: text/plain; charset=ISO-8859-1

I assume the problem is that the function doesn't compile. This should work:
> toIntegralList :: (Read a, Show a) => a -> [a]
> toIntegralList x = map (\c -> read [c]) (show x)
This adds the required Read and Show instances, which are necessary
because of the read and show functions, respectively. Also note that I
have omitted your extra type annotation, which also causes an compile error.

The problem with this functions is that you can use it on a lot of stuff
that isn't a number, and you'll get a runtime read error, to remedy
this, just reinsert the Integral type class requirement:
> toIntegralList :: (Integral a, Read a, Show a) => a -> [a]
> toIntegralList x = map (\c -> read [c]) (show x)

Hope this helps,
Paul

William Gilbert wrote:
> I am trying to write a function that will covert either an integer or
> an int into a list containing its digits.
> 
> ex. toIntegralList 123 -> [1,2,3]
> 
> I have written the following definition that tries to use read to
> generically cast a string value to an Integral type that is the same
> as the Integral passed in:
> 
> toIntegralList :: (Integral a) => a -> [a]
> toIntegralList x = map (\c -> read [c] :: a) (show x)
> 
> I understand it would be very simple to just create two functions, one
> that converts an Int and one that converts an Integer, however I was
> wondering if there were any way to accomplish what I am trying to do
> here.
> 
> Thanks In Advance,
> Bryan
> _______________________________________________
> Beginners mailing list
> Beginners@haskell.org
> http://www.haskell.org/mailman/listinfo/beginners


------------------------------

Message: 3
Date: Thu, 28 May 2009 18:55:06 +0200
From: Ertugrul Soeylemez <e...@ertes.de>
Subject: [Haskell-beginners] Re: Haskell Generic Function Question
To: beginners@haskell.org
Message-ID: <20090528185506.1e62c...@tritium.xx>
Content-Type: text/plain; charset=US-ASCII

William Gilbert <gilber...@gmail.com> wrote:

> I am trying to write a function that will covert either an integer or
> an int into a list containing its digits.
>
> ex. toIntegralList 123 -> [1,2,3]
>
> I have written the following definition that tries to use read to
> generically cast a string value to an Integral type that is the same
> as the Integral passed in:
>
> toIntegralList :: (Integral a) => a -> [a]
> toIntegralList x = map (\c -> read [c] :: a) (show x)
>
> I understand it would be very simple to just create two functions, one
> that converts an Int and one that converts an Integer, however I was
> wondering if there were any way to accomplish what I am trying to do
> here.

Of course you can use read and show for that, but personally I find it
more appropriate to write the algorithm yourself.  It will be faster and
give you a much more useful digit ordering, namely starting with the
least significant digit:

  toDigits :: Integral i => i -> i -> [i]
  toDigits base = takeWhile (>0) . map (`rem` base) . iterate (`div` base)

  toDecimalDigits :: Integral i => i -> [i]
  toDecimalDigits = toDigits 10

  fromDigits :: Num a => a -> [a] -> a
  fromDigits base = foldr (\d c -> base*c + d) 0

  fromDecimalDigits :: Num a => [a] -> a
  fromDecimalDigits = fromDigits 10


Greets,
Ertugrul.


-- 
nightmare = unsafePerformIO (getWrongWife >>= sex)
http://blog.ertes.de/




------------------------------

Message: 4
Date: Thu, 28 May 2009 13:05:12 -0400
From: Thomas Friedrich <i...@suud.de>
Subject: Re: [Haskell-beginners] Haskell Generic Function Question
To: William Gilbert <gilber...@gmail.com>
Cc: beginners@haskell.org
Message-ID: <4a1ec448.9040...@suud.de>
Content-Type: text/plain; charset=ISO-8859-1; format=flowed

Hi William,

I would also strongly success not to make the detour using read and 
show.  Keep things simple.  Here is my suggestion:

toDigit x = case f x of
              (0,b) -> [b]
              (a,b) -> toDigit a    ++ [b]

f = \x -> (x `quot` 10, x `mod` 10)

Best,
Thomas




William Gilbert wrote:
> I am trying to write a function that will covert either an integer or
> an int into a list containing its digits.
>
> ex. toIntegralList 123 -> [1,2,3]
>
> I have written the following definition that tries to use read to
> generically cast a string value to an Integral type that is the same
> as the Integral passed in:
>
> toIntegralList :: (Integral a) => a -> [a]
> toIntegralList x = map (\c -> read [c] :: a) (show x)
>
> I understand it would be very simple to just create two functions, one
> that converts an Int and one that converts an Integer, however I was
> wondering if there were any way to accomplish what I am trying to do
> here.
>
> Thanks In Advance,
> Bryan
> _______________________________________________
> Beginners mailing list
> Beginners@haskell.org
> http://www.haskell.org/mailman/listinfo/beginners
>   



------------------------------

Message: 5
Date: Thu, 28 May 2009 12:18:22 -0500
From: Jeff Wheeler <j...@nokrev.com>
Subject: Re: [Haskell-beginners] Haskell Generic Function Question
To: beginners@haskell.org
Message-ID: <1243531102.10719.2.ca...@ulysses>
Content-Type: text/plain

On Thu, 2009-05-28 at 13:05 -0400, Thomas Friedrich wrote:

> toDigit x = case f x of
>               (0,b) -> [b]
>               (a,b) -> toDigit a    ++ [b]
> 
> f = \x -> (x `quot` 10, x `mod` 10)

Your function f is almost the same as divMod in Prelude. Also, using a
lambda function seems odd; this is simpler:

> f x = (x `quot` 10, x `mod` 10)

Anyways, because that's essentially just divMod, toDigit can be
simplified thusly:

> toDigit x = case x `divMod` 10 of
>     (0, b) -> [b]
>     (a, b) -> toDigit a ++ [b]

Jeff Wheeler



------------------------------

Message: 6
Date: Thu, 28 May 2009 17:53:43 -0400
From: Nathan Holden <nathanmhol...@gmail.com>
Subject: [Haskell-beginners] Case Expressions
To: beginners@haskell.org
Message-ID:
        <305228b20905281453m227462f2iab0b4337ff8a5...@mail.gmail.com>
Content-Type: text/plain; charset="iso-8859-1"

I've been playing with my musical interval problem from before, and I got a
little further, but I came up with a problem.

I have two types-- Interval and BasicInterval.

Interval has 12 constructors, Unison, MinorSecond, MajorSecond, MinorThird,
et cetera.
BasicInterval has 8 constructors, BasicUnison, Second, Third, Fourth, and so
on.

I want to be able to convert between them somewhat;

I have function interToBasic, which at the moment looks like:

interToBasic :: Interval -> BasicInterval
interToBasic a = if (b == 1 || b == 2) then Second
                          else if (b == 3 || b == 4) then Third
..
where b = fromEnum a

What I wanted to do, and figure is probably doable, but I can't seem to find
it, is to say something like

case (fromEnum a) of
   1 || 2 -> Second
   3 || 4 -> Third
..

Is this doable? If so, what's the syntax?
-------------- next part --------------
An HTML attachment was scrubbed...
URL: 
http://www.haskell.org/pipermail/beginners/attachments/20090528/02601f12/attachment-0001.html

------------------------------

Message: 7
Date: Thu, 28 May 2009 18:27:31 -0400
From: Brent Yorgey <byor...@seas.upenn.edu>
Subject: Re: [Haskell-beginners] Case Expressions
To: beginners@haskell.org
Message-ID: <20090528222731.ga7...@seas.upenn.edu>
Content-Type: text/plain; charset=us-ascii

On Thu, May 28, 2009 at 05:53:43PM -0400, Nathan Holden wrote:
> 
> interToBasic :: Interval -> BasicInterval
> interToBasic a = if (b == 1 || b == 2) then Second
>                           else if (b == 3 || b == 4) then Third
> ..
> where b = fromEnum a
> 
> What I wanted to do, and figure is probably doable, but I can't seem to find
> it, is to say something like
> 
> case (fromEnum a) of
>    1 || 2 -> Second
>    3 || 4 -> Third
> ..
> 
> Is this doable? If so, what's the syntax?

You can do this with pattern guards, like so:

interToBasic a | b == 1 || b == 2  = Second
               | b == 3 || b == 4  = Third
               ...
  where b = fromEnum a

You could also use b `elem` [1,2] as an alternative to b == 1 || b ==
2 (especially nice when there are more than two options).

-Brent


------------------------------

Message: 8
Date: Thu, 28 May 2009 18:01:58 +0100
From: Jan Jakubuv <j...@hw.ac.uk>
Subject: Re: [Haskell-beginners] Haskell Generic Function Question
To: William Gilbert <gilber...@gmail.com>
Cc: beginners@haskell.org
Message-ID: <20090528170158.ga24...@lxultra2.macs.hw.ac.uk>
Content-Type: text/plain; charset=us-ascii

Hi Bryan,

I think that it isn't a very good idea to use `read/show` to do some numeric
computations. You can use standard functions `div` and `mod` which work with
any Integrals.

    digits :: (Integral a) => a -> [a]
    digits 0 = []
    digits n = digits (n `div` 10) ++ [n `mod` 10]

This code behaves differently on 0 then your one (also on negative numbers).
You can fix it easily, and moreover, you may want to use `divMod` and some
accumulator to improve efficiency:

    digits2 :: (Integral a) => a -> [a]
    digits2 0 = [0]
    digits2 n = digits2' n [] where
        digits2' 0 acc = acc
        digits2' n acc = let (r,d) = divMod n 10 in digits2' r (d:acc)

I hope I understood well what you were asking about ;-)

Btw, to make your code working I needed to write it as:

    toIntegralList :: (Read a, Integral a) => a -> [a]
    toIntegralList (x :: a)  = map (\c -> read [c] :: a) (show x)

Sincerely,
  Jan.

On Thu, May 28, 2009 at 11:50:36AM -0400, William Gilbert wrote:
> I am trying to write a function that will covert either an integer or
> an int into a list containing its digits.
> 
> ex. toIntegralList 123 -> [1,2,3]
> 
> I have written the following definition that tries to use read to
> generically cast a string value to an Integral type that is the same
> as the Integral passed in:
> 
> toIntegralList :: (Integral a) => a -> [a]
> toIntegralList x = map (\c -> read [c] :: a) (show x)
> 
> I understand it would be very simple to just create two functions, one
> that converts an Int and one that converts an Integer, however I was
> wondering if there were any way to accomplish what I am trying to do
> here.
> 
> Thanks In Advance,
> Bryan
> _______________________________________________
> Beginners mailing list
> Beginners@haskell.org
> http://www.haskell.org/mailman/listinfo/beginners


-- 
Heriot-Watt University is a Scottish charity
registered under charity number SC000278.



------------------------------

Message: 9
Date: Fri, 29 May 2009 01:40:07 -0400
From: Dean Herington <heringtonla...@mindspring.com>
Subject: Re: [Haskell-beginners] Case Expressions
To: beginners@haskell.org
Message-ID: <a06240802c64524439...@[192.168.1.106]>
Content-Type: text/plain; charset="us-ascii" ; format="flowed"

And I'm not sure what going via integers (via `fromEnum`) buys you.  Why not:

interToBasic :: Interval -> BasicInterval
interToBasic a
     | a `elem` [MinorSecond, MajorSecond] = Second
     | a `elem` [MinorThird, MajorThird] = Third
...

Dean

At 6:27 PM -0400 5/28/09, Brent Yorgey wrote:
>On Thu, May 28, 2009 at 05:53:43PM -0400, Nathan Holden wrote:
>>
>  > interToBasic :: Interval -> BasicInterval
>  > interToBasic a = if (b == 1 || b == 2) then Second
>>                            else if (b == 3 || b == 4) then Third
>>  ..
>>  where b = fromEnum a
>>
>>  What I wanted to do, and figure is probably doable, but I can't seem to find
>>  it, is to say something like
>>
>>  case (fromEnum a) of
>>     1 || 2 -> Second
>>     3 || 4 -> Third
>>  ..
>>
>>  Is this doable? If so, what's the syntax?
>
>You can do this with pattern guards, like so:
>
>interToBasic a | b == 1 || b == 2  = Second
>              | b == 3 || b == 4  = Third
>              ...
>   where b = fromEnum a
>
>You could also use b `elem` [1,2] as an alternative to b == 1 || b ==
>2 (especially nice when there are more than two options).
>
>-Brent


------------------------------

Message: 10
Date: Fri, 29 May 2009 10:27:26 -0400
From: Thomas Friedrich <i...@suud.de>
Subject: Re: [Haskell-beginners] Case Expressions
To: Nathan Holden <nathanmhol...@gmail.com>
Cc: beginners@haskell.org
Message-ID: <4a1ff0ce.2090...@suud.de>
Content-Type: text/plain; charset=ISO-8859-1; format=flowed

Hi Nathan,

do you mean something like the following?

data Interval = Unison
              | MinorSecond
              | MajorSecond
              | MinorThird
              | MajorThird
                deriving (Show)

data BasicInterval = BasicUnison
                   | Second
                   | Third
                   | Fourth
                     deriving (Show)

inter2basic :: Interval -> BasicInterval
inter2basic x = case x of
                  Unison -> BasicUnison
                  MinorSecond -> Second
                  MajorSecond -> Second
                  MinorThird -> Third
                  MajorThird -> Third


Happy Hacking,
Thomas



Nathan Holden wrote:
> I've been playing with my musical interval problem from before, and I 
> got a little further, but I came up with a problem.
>
> I have two types-- Interval and BasicInterval.
>
> Interval has 12 constructors, Unison, MinorSecond, MajorSecond, 
> MinorThird, et cetera.
> BasicInterval has 8 constructors, BasicUnison, Second, Third, Fourth, 
> and so on.
>
> I want to be able to convert between them somewhat;
>
> I have function interToBasic, which at the moment looks like:
>
> interToBasic :: Interval -> BasicInterval
> interToBasic a = if (b == 1 || b == 2) then Second
>                           else if (b == 3 || b == 4) then Third
> ..
> where b = fromEnum a
>
> What I wanted to do, and figure is probably doable, but I can't seem 
> to find it, is to say something like
>
> case (fromEnum a) of
>    1 || 2 -> Second
>    3 || 4 -> Third
> ..
>
> Is this doable? If so, what's the syntax?
> ------------------------------------------------------------------------
>
> _______________________________________________
> Beginners mailing list
> Beginners@haskell.org
> http://www.haskell.org/mailman/listinfo/beginners
>   



------------------------------

_______________________________________________
Beginners mailing list
Beginners@haskell.org
http://www.haskell.org/mailman/listinfo/beginners


End of Beginners Digest, Vol 11, Issue 19
*****************************************

Reply via email to