Send Beginners mailing list submissions to
[email protected]
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
[email protected]
You can reach the person managing the list at
[email protected]
When replying, please edit your Subject line so it is more specific
than "Re: Contents of Beginners digest..."
Today's Topics:
1. Re: definition of combinator (Michael Mossey)
2. Re: definition of combinator (Heinrich Apfelmus)
3. pretty-printing data (Michael Mossey)
4. partitions made of unique parts (I. J. Kennedy)
5. Re: partitions made of unique parts (Daniel Fischer)
6. Re: partitions made of unique parts (Daniel Fischer)
7. Re: pretty-printing data (Magnus Therning)
8. Type Class Woes .. (Tom Poliquin)
9. Re: Type Class Woes .. (Javier M Mora)
----------------------------------------------------------------------
Message: 1
Date: Mon, 24 Aug 2009 10:45:06 -0700
From: Michael Mossey <[email protected]>
Subject: Re: [Haskell-beginners] definition of combinator
To: beginners <[email protected]>
Message-ID: <[email protected]>
Content-Type: text/plain; charset=ISO-8859-1; format=flowed
Brandon S. Allbery KF8NH wrote:
> On Aug 23, 2009, at 20:44 , Michael Mossey wrote:
>> Although I can use libraries like Parsec, I don't really understand
>> what a combinator is, theoretically. There is an article here
>
>
> Example: in Parsec, "many" is a combinator which takes a parser as an
> argument and produces a parser that matches multiple successive copies
> of whatever the argument matches. It doesn't need to know anything
> about its argument except that it's a parser. This kind of function
> lets you build up complex but general parsers from smaller pieces.
>
What makes it a "combinator" and not a general function? The fact that it
takes only a function (parser) as input (no data) and produces only a
function? Is any function that takes only functions and produces a function
called a combinator?
Thanks,
Mike
------------------------------
Message: 2
Date: Tue, 25 Aug 2009 10:02:19 +0200
From: Heinrich Apfelmus <[email protected]>
Subject: [Haskell-beginners] Re: definition of combinator
To: [email protected]
Message-ID: <[email protected]>
Content-Type: text/plain; charset=ISO-8859-1
Michael Mossey wrote:
>
> Brandon S. Allbery KF8NH wrote:
>>
>> Example: in Parsec, "many" is a combinator which takes a parser as an
>> argument and produces a parser that matches multiple successive copies
>> of whatever the argument matches. It doesn't need to know anything
>> about its argument except that it's a parser. This kind of function
>> lets you build up complex but general parsers from smaller pieces.
>
> What makes it a "combinator" and not a general function? The fact that
> it takes only a function (parser) as input (no data) and produces only a
> function? Is any function that takes only functions and produces a
> function called a combinator?
The term "combinator" is just another name for "function", but with a
special connotation. It mainly applies to functions building and
combining values of an abstract data type.
In particular, parsers are abstract. They are defined by the following
combinators
return :: a -> P a
(>>=) :: P a -> (a -> P b) -> P b
symbol :: P Char
mzero :: P a
mplus :: P a -> P a -> P a
and an observation function like
run :: P a -> String -> Maybe a
The above functions are called combinators because they make new parsers
from old ones. In contrast, run turns a parser into something else, so
it's not called "combinator".
Regards,
apfelmus
--
http://apfelmus.nfshost.com
------------------------------
Message: 3
Date: Sat, 29 Aug 2009 07:22:06 -0700
From: Michael Mossey <[email protected]>
Subject: [Haskell-beginners] pretty-printing data
To: [email protected]
Message-ID: <[email protected]>
Content-Type: text/plain; charset=ISO-8859-1; format=flowed
For debugging purposes I'm interested in pretty-printing data; to start
with, lists of algebraic data types. Basically I'd like 'show' with the
ability to put each entry of a list on a separate line, and indented. Note
that the algebraic data might have an inner list as one of its elements, so
this is a non-obvious formatting problem.
I believe I can make instances of Show, can I not? Is there something
called showList which I can use to code my own method of showing lists of a
particular type? My understanding is that I can't make [a] an instance of
Show; hence they provided showList.
So basically, I'm wondering if a pretty-printing (for data!) library
already exists, or whether I should try to make instances of Show.
Thanks,
Mike
------------------------------
Message: 4
Date: Sat, 29 Aug 2009 10:43:02 -0500
From: "I. J. Kennedy" <[email protected]>
Subject: [Haskell-beginners] partitions made of unique parts
To: [email protected]
Message-ID:
<[email protected]>
Content-Type: text/plain; charset=UTF-8
The following function finds all the partitions of an integer that are
made of unique parts.
It works, but I'm not happy with it--seems too complex. Is there a
more haskelly (clever)
way to implement this?
-- parts n finds all the partitions of n having unique parts
-- helper function parts' n r m finds partitions of n from a set
r of remaining possible parts,
-- with a minimum part of m.
parts n = parts' n [1..n] 1 where
parts' 0 _ _ = [[]] -- there's always one way ([])
to get a sum of 0
parts' n [] _ = [] -- if n /= 0, there are no
possible partitions of the empty list
parts' n remaining atleast = [(x:y) | x <- filter (>= atleast)
remaining, y <- (parts' (n-x) (remaining \\ [x])) x]
*Main> parts 11
[[1,2,3,5],[1,2,8],[1,3,7],[1,4,6],[1,10],[2,3,6],[2,4,5],[2,9],[3,8],[4,7],[5,6],[11]]
------------------------------
Message: 5
Date: Sat, 29 Aug 2009 18:39:18 +0200
From: Daniel Fischer <[email protected]>
Subject: Re: [Haskell-beginners] partitions made of unique parts
To: [email protected]
Message-ID: <[email protected]>
Content-Type: text/plain; charset="utf-8"
Am Samstag 29 August 2009 17:43:02 schrieb I. J. Kennedy:
> The following function finds all the partitions of an integer that are
> made of unique parts.
> It works, but I'm not happy with it--seems too complex. Is there a
> more haskelly (clever)
> way to implement this?
>
> -- parts n finds all the partitions of n having unique parts
> -- helper function parts' n r m finds partitions of n from a set
> r of remaining possible parts,
> -- with a minimum part of m.
>
> parts n = parts' n [1..n] 1 where
> parts' 0 _ _ = [[]] -- there's always one way ([])
> to get a sum of 0
> parts' n [] _ = [] -- if n /= 0, there are no
> possible partitions of the empty list
> parts' n remaining atleast = [(x:y) | x <- filter (>= atleast)
> remaining, y <- (parts' (n-x) (remaining \\ [x])) x]
>
>
> *Main> parts 11
> [[1,2,3,5],[1,2,8],[1,3,7],[1,4,6],[1,10],[2,3,6],[2,4,5],[2,9],[3,8],[4,7]
>,[5,6],[11]]
You don't have to have a list of possible parts, the possible parts follow from
the
minimum:
parts :: Int -> [[Int]] -- or (Num a, Ord a) => a -> [[a]]
parts 0 = [[]]
parts n
| n < 0 = []
| otherwise = mpart n 1
where
-- mpart m k partitions m into distinct parts of size at least k
mpart m k
| m < k = []
| m <= 2*k = [[m]]
| otherwise = map (k:) (mpart (m-k) (k+1)) ++ mpart m (k+1)
------------------------------
Message: 6
Date: Sat, 29 Aug 2009 19:39:42 +0200
From: Daniel Fischer <[email protected]>
Subject: Re: [Haskell-beginners] partitions made of unique parts
To: [email protected]
Message-ID: <[email protected]>
Content-Type: text/plain; charset="utf-8"
Am Samstag 29 August 2009 17:43:02 schrieb I. J. Kennedy:
> The following function finds all the partitions of an integer that are
> made of unique parts.
> It works, but I'm not happy with it--seems too complex. Is there a
> more haskelly (clever)
> way to implement this?
>
> -- parts n finds all the partitions of n having unique parts
> -- helper function parts' n r m finds partitions of n from a set
> r of remaining possible parts,
> -- with a minimum part of m.
>
> parts n = parts' n [1..n] 1 where
> parts' 0 _ _ = [[]] -- there's always one way ([])
> to get a sum of 0
> parts' n [] _ = [] -- if n /= 0, there are no
> possible partitions of the empty list
> parts' n remaining atleast = [(x:y) | x <- filter (>= atleast)
> remaining, y <- (parts' (n-x) (remaining \\ [x])) x]
>
>
> *Main> parts 11
> [[1,2,3,5],[1,2,8],[1,3,7],[1,4,6],[1,10],[2,3,6],[2,4,5],[2,9],[3,8],[4,7],[5,6],[11]]
Another thing: In your list of possible parts, you keep values smaller than the
minimum
value and values larger than the remaining value to be partitioned. This leads
to horrible
performance (1 second to partition 20 and 20 minutes to partition 30 on my box)
since you
have to scan through unnecessarily long lists and you try to partition negative
numbers.
In particular the latter cripples performance, inserting a guard
 parts' n remaining atleast
| n < 0 = []
| otherwise = [(x:y) | x <- filter (>= atleast) remaining
, y <- (parts' (n-x) (remaining \\ [x]))
(x)]
into the last clause of parts' brings the time for parts 30 down to 0.06
seconds, for
parts 70 to 2.06 seconds :) (still about 100 times slower than the code from my
previous
post).
------------------------------
Message: 7
Date: Sat, 29 Aug 2009 23:09:15 +0100
From: Magnus Therning <[email protected]>
Subject: Re: [Haskell-beginners] pretty-printing data
To: Michael Mossey <[email protected]>
Cc: [email protected]
Message-ID:
<[email protected]>
Content-Type: text/plain; charset=UTF-8
On Sat, Aug 29, 2009 at 3:22 PM, Michael Mossey<[email protected]> wrote:
> For debugging purposes I'm interested in pretty-printing data; to start
> with, lists of algebraic data types. Basically I'd like 'show' with the
> ability to put each entry of a list on a separate line, and indented. Note
> that the algebraic data might have an inner list as one of its elements, so
> this is a non-obvious formatting problem.
>
> I believe I can make instances of Show, can I not? Is there something called
> showList which I can use to code my own method of showing lists of a
> particular type? My understanding is that I can't make [a] an instance of
> Show; hence they provided showList.
>
> So basically, I'm wondering if a pretty-printing (for data!) library already
> exists, or whether I should try to make instances of Show.
Take a look at the pretty-printing libraries available on Hackage.
I've personally used two of them, pretty and wl-pprint. I'm fairly
sure both of them define pretty-printing for lists, but I don't know
whether it's done the way you want.
/M
--
Magnus Therning (OpenPGP: 0xAB4DFBA4)
magnusï¼ therningï¼org Jabber: magnusï¼ therningï¼org
http://therning.org/magnus identi.ca|twitter: magthe
------------------------------
Message: 8
Date: Sat, 29 Aug 2009 23:57:25 -0700
From: Tom Poliquin <[email protected]>
Subject: [Haskell-beginners] Type Class Woes ..
To: [email protected]
Message-ID: <[email protected]>
Content-Type: text/plain; charset="us-ascii"
I've been writing Haskell programs (even useful ones :-) )
for awhile and I thought it was time to experiment with my own
type classes. I chose the (contrived toy) problem of computing the volume
of various fruits.
First I wrote the code using algebraic data types ..
(shown below); then I 'converted' it to use type classes
(also shown below)
The type class version gives me the errors ..
Main.hs:12:16: Not in scope: type constructor or class `Banana'
Main.hs:15:16: Not in scope: type constructor or class `Watermelon'
.. which makes sense since Banana and Watermelon are
'data constructors' and not 'type constructors'. The problem is I'm
not sure how to get around it .. If I try putting
data Orange = Orange
data Banana = Banana ..
then what does 'initFruit' return .. ?
it can't return [Fruit FruitType] anymore ..
It seems like this should be a simple problem.
I'm clearly not 'getting it'.
Any help greatly appreciated,
Tom
----------
Algegraic Data Type Version (works)
----------
module Main where
data Fruit a = F {radius::Double, len::Double, fType::a}
data FruitType = Orange | Apple | Banana | Watermelon
deriving Show
initFruit :: [Fruit FruitType]
initFruit = [
(F 3.0 0.0 Orange),
(F 3.0 0.0 Apple),
(F 3.0 2.0 Banana),
(F 40.0 20.0 Watermelon)
]
volume :: Fruit FruitType -> Double
volume F{radius=r,len=l,fType=Orange} = (4.0/3.0) * pi * r * r * r
volume F{radius=r,len=l,fType=Apple} = (4.0/3.0) * pi * r * r * r
volume F{radius=r,len=l,fType=Banana} = pi * (r * r) * l
volume F{radius=r,len=l,fType=Watermelon} = (4.0/3.0) * pi * (2.0 * r)
* l * (0.5 * l)
----------
-- Main --
----------
main = do
fruit <- return $ initFruit
mapM (\f@(F{fType=t}) -> putStrLn ("Volume -> " ++ show t ++
" = " ++ show (volume f))) fruit
Volume -> Orange = 113.09733552923255
Volume -> Apple = 113.09733552923255
Volume -> Banana = 56.548667764616276
Volume -> Watermelon = 67020.64327658225
----------
Type Class Version (fails)
----------
module Main where
data Fruit a = F {radius::Double, len::Double, fType::a}
data FruitType = Orange | Apple | Banana | Watermelon
class Volume a where
volume :: (FruitType a) => Fruit a -> Double
-- default spherical fruit ..
volume F{radius=r,len=l} = (4.0/3.0) * pi * r * r * r
instance Volume Banana where
volume F{radius=r,len=l} = pi * (r * r) * l
instance Volume Watermelon where
volume F{radius=r,len=l} = (4.0/3.0) * pi * (2.0 * r) * l * (0.5 * l)
initFruit :: [Fruit FruitType]
initFruit = [
(F 3.0 0.0 Orange),
(F 3.0 0.0 Apple),
(F 3.0 2.0 Banana),
(F 40.0 20.0 Watermelon)
]
----------
-- Main --
----------
main = do
fruit <- return $ initFruit
mapM (\f@(F{fType=t}) -> putStrLn ("Volume -> " ++ show t ++
" = " ++ show (volume f))) fruit
Main.hs:12:16: Not in scope: type constructor or class `Banana'
Main.hs:15:16: Not in scope: type constructor or class `Watermelon'
------------------------------
Message: 9
Date: Sun, 30 Aug 2009 11:11:23 +0200
From: Javier M Mora <[email protected]>
Subject: Re: [Haskell-beginners] Type Class Woes ..
To: [email protected]
Message-ID: <[email protected]>
Content-Type: text/plain; charset=ISO-8859-1; format=flowed
Tom Poliquin escribió:
> ----------
> Type Class Version (fails)
> ----------
>
> module Main where
>
> data Fruit a = F {radius::Double, len::Double, fType::a}
>
> data FruitType = Orange | Apple | Banana | Watermelon
>
> class Volume a where
> volume :: (FruitType a) => Fruit a -> Double
> -- default spherical fruit ..
> volume F{radius=r,len=l} = (4.0/3.0) * pi * r * r * r
>
> instance Volume Banana where
> volume F{radius=r,len=l} = pi * (r * r) * l
The problem here is you only can instance datatypes. The datatype here
is FruitType. Banana is a DataConstructor.
How to fix it?
(I'm newbie too, so you have to think more with my answer)
A posibility is create a data type for each frute:
-----
[...]
class FruitType a where
volume :: Fruit a -> Double
-- default spherical
volume F{radius=r,len=l} = (4.0/3.0) * pi * r * r * r
data Orange = Orange
data Apple = Apple
data Banana = Banana
data Watermelon = Watermelon
instance FruitType Orange where
instance FruitType Apple where
instance FruitType Banana where
volume F{radius=r,len=l} = pi * (r * r) * l
instance FruitType Watermelon where
volume F{radius=r,len=l} = (4.0/3.0) * pi * (2.0 * r) * l * (0.5 * l)
[...]
-----
But, you can't later define a list with mixed types because the first
one is "::Fruit Orange" and the second is "::Fruit Apple"
----- WRONG vvv
initFruit :: FruitType a => [Fruit a]
initFruit = [
(F 3.0 0.0 Orange),
(F 3.0 0.0 Apple),
(F 3.0 2.0 Banana),
(F 40.0 20.0 Watermelon)
]
----- WRONG ^^^
The second posibilitie is use patterns. So, I'm sorry this example is
very similar to your first attempt:
----- SECOND ATTEMPT
module Main where
data Fruit a = F {radius::Double, len::Double, fType::a}
data FruitType = Orange | Apple | Banana | Watermelon
deriving Show
class Volume a where
volume:: a -> Double
instance Volume (Fruit FruitType) where
volume F{radius=r,len=l,fType=Banana} = pi * (r * r) * l
volume F{radius=r,len=l,fType=Watermelon} = (4.0/3.0) * pi * (2.0 *
r) * l * (0.5 * l)
volume F{radius=r,len=l} = (4.0/3.0) * pi * r * r * r
initFruit :: [Fruit FruitType]
initFruit = [
(F 3.0 0.0 Orange),
(F 3.0 0.0 Apple),
(F 3.0 2.0 Banana),
(F 40.0 20.0 Watermelon)
]
----------
-- Main --
----------
main = do
fruit <- return $ initFruit
mapM (\f@(F{fType=t}) -> putStrLn ("Volume -> " ++ show t ++
" = " ++ show (volume f))) fruit
But, you need define "FlexibleInstances" add on because:
"instance Volume (Fruit FruitType)"
is not standard Haskell
THIRD IDEA. Make a wrapper volume function:
-----
module Main where
data Fruit a = F {radius::Double, len::Double, fType::a}
data FruitType = Orange | Apple | Banana | Watermelon
deriving Show
class Volume a where
volume:: a -> Double -> Double -> Double
instance Volume FruitType where
volume Banana r l = pi * (r * r) * l
volume Watermelon r l = (4.0/3.0) * pi * (2.0 * r) * l * (0.5 * l)
volume _ r l = (4.0/3.0) * pi * r * r * r
volumeFruit F{radius=r,len=l,fType=f} = volume f r l
initFruit :: [Fruit FruitType]
initFruit = [
(F 3.0 0.0 Orange),
(F 3.0 0.0 Apple),
(F 3.0 2.0 Banana),
(F 40.0 20.0 Watermelon)
]
----------
-- Main --
----------
main = do
let fruit = initFruit
mapM (\f@(F{fType=t}) -> putStrLn ("Volume -> " ++ show t ++
" = " ++ show (volumeFruit f))) fruit
-----
So. This problem is more interesting that I thought.
Javier M Mora.
PD. initFruit is a Pure Function. I prefer the "let" construction.
------------------------------
_______________________________________________
Beginners mailing list
[email protected]
http://www.haskell.org/mailman/listinfo/beginners
End of Beginners Digest, Vol 14, Issue 13
*****************************************