[Haskell-cafe] Re: Question on rank-N polymorphism

2009-06-09 Thread oleg

Ryan Ingram discussed a question of writing
 fs f g = (f fst, g snd)

so that fs ($ (1, 2)) type checks.

This is not that difficult:

 {-# LANGUAGE RankNTypes, MultiParamTypeClasses -#}
 {-# LANGUAGE FunctionalDependencies, FlexibleInstances #-}

 class Apply f x y | f x - y where
 apply :: f - x - y

 instance Apply (x-y) x y where
 apply = ($)

 data Fst = Fst
 data Snd = Snd

 instance Apply Fst (x,y) x where
 apply _ = fst

 instance Apply Snd (x,y) y where
 apply _ = snd

The function in question:

 fs3 f = (apply f Fst, apply f Snd)

-- One of Wouter Swierstra's examples
-- examples = (fs id, fs repeat, fs (\x - [x]), fs ((,)id))

 data Id a = Id

 instance Apply (Id a) Fst ((a,a) - a) where
 apply _ _ = fst

 instance Apply (Id a) Snd ((a,a) - a) where
 apply _ _ = snd

 ex1 = fs3 Id

Now, Ryan's main example

 newtype Pair a b = Pair (forall w. (((a,b) - w) - w))

 instance Apply (Pair a b) Fst a where
 apply (Pair f) _ = f fst

 instance Apply (Pair a b) Snd b where
 apply (Pair f) _ = f snd

 ex4 = fs3 (Pair ($ (1, 2)))
 -- (1,2)


Incidentally, a different variation of this example is discussed in
http://okmij.org/ftp/Computation/extra-polymorphism.html

Indeed, such a selection from a pair occurs quite often...





___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Deprecated packages on Hackage?

2009-06-09 Thread Ketil Malde
Erik de Castro Lopo mle...@mega-nerd.com writes:

 Finally, if a package is deprecated it might be usefult to have
 a reason as well so the hackage entry might say:
 
Deprecated : true (replaced by package XXX)
 
 or
 
Deprecated : true (needs maintainer)

Or just Deprecated: (reason)?.  Couldn't the presence of a Deprecated
field be sufficient - the true seems gratuitious to me.

One could also have something like Superseeds and Superseeded-by, of
course, if that turns out to be the usual reasons for deprecation.

And in a later post:

 Well there is at least one package (network-dns) where the maintainter
 doesn't want to maintain it any more but would be happy for someone
 else to take it over.

 It would be nice if something like this could be represented in the
 package metadata.

Absence of a Maintainer field?  One problem is that the last
uploaded package is likely to have an active maintainer, and when the
maintainer disappears, he or she is unlikely to do a last update
changing the status.

Perhaps we could have automated emails to maintainers twice a year or
so?

-k
-- 
If I haven't seen further, it is by standing in the footprints of giants
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] How to compile base?

2009-06-09 Thread Jochem Berndsen
Henk-Jan van Tuyl wrote:
 I tried to compile base-4.0.0.0 (on Windows XP) as follows:
   [...]\base\4.0.0.0runhaskell Setup configure
   command line: module `Prelude' is not loaded
 It seems that Base needs another way to compile, how?
 

AFAIK base is shipped with GHC, and cannot be compiled separately.
GHC 6.10.1 ships with base-4.0.0.0, later versions in the 6.10.x series
may have a somewhat later version.

Regards,

-- 
Jochem Berndsen | joc...@functor.nl
GPG: 0xE6FABFAB
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Incremental XML parsing with namespaces?

2009-06-09 Thread Krzysztof Skrzętnicki
On Mon, Jun 8, 2009 at 20:39, John Millikinjmilli...@gmail.com wrote:
 I'm trying to convert an XML document, incrementally, into a sequence
 of XML events. A simple example XML document:

 doc xmlns=org:myproject:mainns xmlns:x=org:myproject:otherns
    titleDoc title/title
    x:refabc1234/x:ref
    html xmlns=http://www.w3.org/1999/xhtml;bodyHello world!/body/html
 /doc

 The document can be very large, and arrives in chunks over a socket,
 so I need to be able to feed the text data into a parser and receive
 a list of XML events per chunk. Chunks can be separated in time by
 intervals of several minutes to an hour, so pausing processing for the
 arrival of the entire document is not an option. The type signatures
 would be something like:

 type Namespace = String
 type LocalName = String

 data Attribute = Attribute Namespace LocalName String

 data XMLEvent =
    EventElementBegin Namespace LocalName [Attribute] |
    EventElementEnd Namespace LocalName |
    EventContent String |
   EventError String

 parse :: Parser - String - (Parser, [XMLEvent])

 I've looked at HaXml, HXT, and hexpat, and unless I'm missing
 something, none of them can achieve this:

 + HaXml and hexpat seem to disregard namespaces entirely -- that is,
 the root element is parsed to doc instead of
 (org:myproject:mainns, doc), and the second child is x:ref
 instead of (org:myproject:otherns, ref). Obviously, this makes
 parsing mixed-namespace documents effectively impossible. I found an
 email from 2004[1] that mentions a filter for namespace support in
 HaXml, but no further information and no working code.

I would recommend hexpat to do the job. Contrary to what you are
saying, hexpat does offer namespace handling:
http://hackage.haskell.org/packages/archive/hexpat/0.8/doc/html/Text-XML-Expat-Namespaced.html
Perhaps you need more than that?

Personally I found hexpat to be fast, space efficient and easy to use.

Here is the representation I got for your example. Please note the
namespaces in right places.
*  (toNamespaced ( toQualified t'))
Element {eName = NName {nnNamespace = Just org:myproject:mainns,
nnLocalPart = doc}, eAttrs = [(NName {nnNamespace = Just
http://www.w3.org/2000/xmlns/;, nnLocalPart =
x},org:myproject:otherns),(NName {nnNamespace = Just
org:myproject:mainns, nnLocalPart =
xmlns},org:myproject:mainns)], eChildren = [Text \n,Text 
,Element {eName = NName {nnNamespace = Just org:myproject:mainns,
nnLocalPart = title}, eAttrs = [], eChildren = [Text Doc
title]},Text \n,Text ,Element {eName = NName {nnNamespace =
Just org:myproject:otherns, nnLocalPart = ref}, eAttrs = [],
eChildren = [Text abc1234]},Text \n,Text ,Element {eName =
NName {nnNamespace = Just http://www.w3.org/1999/xhtml;, nnLocalPart
= html}, eAttrs = [(NName {nnNamespace = Just
http://www.w3.org/1999/xhtml;, nnLocalPart =
xmlns},http://www.w3.org/1999/xhtml;)], eChildren = [Element {eName
= NName {nnNamespace = Just http://www.w3.org/1999/xhtml;,
nnLocalPart = body}, eAttrs = [], eChildren = [Text Hello
world!]}]},Text \n]}

Best regards

Krzysztof Skrzętnicki
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] Dutch HUG meeting tonight in Amsterdam

2009-06-09 Thread Chris Eidhof

Hi everyone,

Tonight there will be another meeting of the Dutch Haskell Users'  
Group! This time we'll meet in Amsterdam, in the library. On the wiki  
[1] you can find the details of how to reach it. We'll be at the top  
floor and shouldn't be hard to recognize. The meeting is set to begin  
at 19:30.


Everybody's welcome, from beginners to advanced haskellers. Even if  
you never programmed in Haskell before it'll probably be a lot of fun.  
See you tonight! There are a lot of international people joining, so  
no knowledge of Dutch is necessary.


If you're joining, also be sure to subscribe to our mailinglist [2].

See you tonight!

-chris

[1]: http://www.haskell.org/haskellwiki/Dutch_HUG
[2]: http://groups.google.com/group/dutch-hug
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Incremental XML parsing with namespaces?

2009-06-09 Thread Krzysztof Skrzętnicki
And just to provide an example of working program:

---
module Main where

import Text.XML.Expat.Qualified
import Text.XML.Expat.Namespaced
import Text.XML.Expat.Tree

import qualified Data.ByteString.Lazy as BSL

main = do
f - BSL.readFile doc1.xml
let (tree,error) = parseTree Nothing f
case error of
Nothing - putStrLn Here you are:   (print . toNamespaced .
toQualified $ (tree :: Node String String))
Just err - putStrLn Error!  print err
---


$ ./hexpat-test
Here you are:
Element {eName = NName {nnNamespace = Just org:myproject:mainns,
nnLocalPart = doc}, eAttrs = [(NName {nnNamespace = Just
http://www.w3.org/2000/xmlns/;, nnLocalPart =
x},org:myproject:otherns),(NName {nnNamespace = Just
org:myproject:mainns, nnLocalPart =
xmlns},org:myproject:mainns)], eChildren = [Text \n,Text 
,Element {eName = NName {nnNamespace = Just org:myproject:mainns,
nnLocalPart = title}, eAttrs = [], eChildren = [Text Doc
title]},Text \n,Text ,Element {eName = NName {nnNamespace =
Just org:myproject:otherns, nnLocalPart = ref}, eAttrs = [],
eChildren = [Text abc1234]},Text \n,Text ,Element {eName =
NName {nnNamespace = Just http://www.w3.org/1999/xhtml;, nnLocalPart
= html}, eAttrs = [(NName {nnNamespace = Just
http://www.w3.org/1999/xhtml;, nnLocalPart =
xmlns},http://www.w3.org/1999/xhtml;)], eChildren = [Element {eName
= NName {nnNamespace = Just http://www.w3.org/1999/xhtml;,
nnLocalPart = body}, eAttrs = [], eChildren = [Text Hello
world!]}]},Text \n]}
# we mess with doc1.xml and exchange /doc for /do
$ ./hexpat-test
Error!
XMLParseError mismatched tag (XMLParseLocation {xmlLineNumber = 5,
xmlColumnNumber = 2, xmlByteIndex = 205, xmlByteCount = 0})


Best regards

Krzysztof Skrzętnicki

2009/6/9 Krzysztof Skrzętnicki gte...@gmail.com:
 On Mon, Jun 8, 2009 at 20:39, John Millikinjmilli...@gmail.com wrote:
 I'm trying to convert an XML document, incrementally, into a sequence
 of XML events. A simple example XML document:

 doc xmlns=org:myproject:mainns xmlns:x=org:myproject:otherns
    titleDoc title/title
    x:refabc1234/x:ref
    html xmlns=http://www.w3.org/1999/xhtml;bodyHello 
 world!/body/html
 /doc

 The document can be very large, and arrives in chunks over a socket,
 so I need to be able to feed the text data into a parser and receive
 a list of XML events per chunk. Chunks can be separated in time by
 intervals of several minutes to an hour, so pausing processing for the
 arrival of the entire document is not an option. The type signatures
 would be something like:

 type Namespace = String
 type LocalName = String

 data Attribute = Attribute Namespace LocalName String

 data XMLEvent =
    EventElementBegin Namespace LocalName [Attribute] |
    EventElementEnd Namespace LocalName |
    EventContent String |
   EventError String

 parse :: Parser - String - (Parser, [XMLEvent])

 I've looked at HaXml, HXT, and hexpat, and unless I'm missing
 something, none of them can achieve this:

 + HaXml and hexpat seem to disregard namespaces entirely -- that is,
 the root element is parsed to doc instead of
 (org:myproject:mainns, doc), and the second child is x:ref
 instead of (org:myproject:otherns, ref). Obviously, this makes
 parsing mixed-namespace documents effectively impossible. I found an
 email from 2004[1] that mentions a filter for namespace support in
 HaXml, but no further information and no working code.

 I would recommend hexpat to do the job. Contrary to what you are
 saying, hexpat does offer namespace handling:
 http://hackage.haskell.org/packages/archive/hexpat/0.8/doc/html/Text-XML-Expat-Namespaced.html
 Perhaps you need more than that?

 Personally I found hexpat to be fast, space efficient and easy to use.

 Here is the representation I got for your example. Please note the
 namespaces in right places.
 *  (toNamespaced ( toQualified t'))
 Element {eName = NName {nnNamespace = Just org:myproject:mainns,
 nnLocalPart = doc}, eAttrs = [(NName {nnNamespace = Just
 http://www.w3.org/2000/xmlns/;, nnLocalPart =
 x},org:myproject:otherns),(NName {nnNamespace = Just
 org:myproject:mainns, nnLocalPart =
 xmlns},org:myproject:mainns)], eChildren = [Text \n,Text 
 ,Element {eName = NName {nnNamespace = Just org:myproject:mainns,
 nnLocalPart = title}, eAttrs = [], eChildren = [Text Doc
 title]},Text \n,Text     ,Element {eName = NName {nnNamespace =
 Just org:myproject:otherns, nnLocalPart = ref}, eAttrs = [],
 eChildren = [Text abc1234]},Text \n,Text     ,Element {eName =
 NName {nnNamespace = Just http://www.w3.org/1999/xhtml;, nnLocalPart
 = html}, eAttrs = [(NName {nnNamespace = Just
 http://www.w3.org/1999/xhtml;, nnLocalPart =
 xmlns},http://www.w3.org/1999/xhtml;)], eChildren = [Element {eName
 = NName {nnNamespace = Just http://www.w3.org/1999/xhtml;,
 nnLocalPart = body}, eAttrs = [], eChildren = [Text Hello
 world!]}]},Text \n]}

 Best regards

 Krzysztof Skrzętnicki

___
Haskell-Cafe 

[Haskell-cafe] Unification for rank-N types

2009-06-09 Thread Vladimir Reshetnikov
Hi,

I have the following code:
---
{-# LANGUAGE RankNTypes #-}

f :: ((forall a. a - a) - b) - b
f x = x id

g :: (forall c. Eq c = [c] - [c]) - ([Bool],[Int])
g y = (y [True], y [1])

h :: ([Bool],[Int])
h = f g
---

GHC rejects it:
Couldn't match expected type `forall a. a - a'
   against inferred type `forall c. (Eq c) = [c] - [c]'
  Expected type: forall a. a - a
  Inferred type: forall c. (Eq c) = [c] - [c]
In the first argument of `f', namely `g'
In the expression: f g

But, intuitively, this code is type-safe, and actually I can convince
the typechecker in it with the following workaround:
---
h :: ([Bool],[Int])
h = let g' = (\(x :: forall a. a - a) - g x) in f g'
---

So, is the current behavior of GHC correct ot it is a bug?
How unification for rank-N types should proceed?

Thanks,
Vladimir
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] Convert IO Int to Int

2009-06-09 Thread ptrash

Hi,

I am using the System.Random method randomRIO. How can I convert its output
to an Int?

Thanks...
-- 
View this message in context: 
http://www.nabble.com/Convert-IO-Int-to-Int-tp23940249p23940249.html
Sent from the Haskell - Haskell-Cafe mailing list archive at Nabble.com.

___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Convert IO Int to Int

2009-06-09 Thread Tobias Olausson
You can not convert an IO Int to Int, or at least, you shouldn't.
However, you can do as follows:

test :: IO ()
test = do
   int - randomRIO -- or whatever it is called
   print $ useInt int

useInt :: Int - Int
useInt x = x+10

//Tobias

2009/6/9 ptrash ptr...@web.de:

 Hi,

 I am using the System.Random method randomRIO. How can I convert its output
 to an Int?

 Thanks...
 --
 View this message in context: 
 http://www.nabble.com/Convert-IO-Int-to-Int-tp23940249p23940249.html
 Sent from the Haskell - Haskell-Cafe mailing list archive at Nabble.com.

 ___
 Haskell-Cafe mailing list
 Haskell-Cafe@haskell.org
 http://www.haskell.org/mailman/listinfo/haskell-cafe




-- 
Tobias Olausson
tob...@gmail.com
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Convert IO Int to Int

2009-06-09 Thread Jochem Berndsen
ptrash wrote:
 Hi,
 
 I am using the System.Random method randomRIO. How can I convert its output
 to an Int?
 
 Thanks...

You cannot [1], you should read up on monads and I/O in Haskell, for example
http://haskell.org/haskellwiki/IO_inside

[1] Yes, you can, but no, you don't want to.

Regards,

-- 
Jochem Berndsen | joc...@functor.nl
GPG: 0xE6FABFAB
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Convert IO Int to Int

2009-06-09 Thread Yusaku Hashimoto


On 2009/06/09, at 19:33, Tobias Olausson wrote:


You can not convert an IO Int to Int, or at least, you shouldn't.
However, you can do as follows:

test :: IO ()
test = do
   int - randomRIO -- or whatever it is called
   print $ useInt int

useInt :: Int - Int
useInt x = x+10


Or, you can lift pure function into IO. the below test' function  
almost same as above test function. (But I used randomIO instead of  
randomRIO because it seemed to be a typo :-)


test' = print = fmap useInt randomIO

I think it is more handy than using do notation, when you want to do  
something simple with monads. And converting IO Int to IO anything is  
much easier and safer than converting IO Int to Int.


ghci :m +System.Random Data.Char
ghci :t fmap (+1) randomIO
fmap (+1) randomIO :: (Num a, Random a) = IO a
ghci :t fmap show randomIO
fmap show randomIO :: IO String
ghci :t fmap chr randomIO
fmap Data.Char.chr randomIO :: IO Char
ghci :t fmap (+) randomIO
fmap (+) randomIO :: (Num a, Random a) = IO (a - a)

Thanks,
Hashimoto



//Tobias

2009/6/9 ptrash ptr...@web.de:


Hi,

I am using the System.Random method randomRIO. How can I convert  
its output

to an Int?

Thanks...
--
View this message in context: http://www.nabble.com/Convert-IO-Int- 
to-Int-tp23940249p23940249.html
Sent from the Haskell - Haskell-Cafe mailing list archive at  
Nabble.com.


___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe





--
Tobias Olausson
tob...@gmail.com
___
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] Re: Unification for rank-N types

2009-06-09 Thread Vladimir Reshetnikov
One more example:

This does not type-check:
---
{-# LANGUAGE RankNTypes, ImpredicativeTypes #-}

f :: [forall a. t a - t a] - t b - t b
f = foldr (.) id
---

Couldn't match expected type `forall a. f a - f a'
   against inferred type `b - c'
In the first argument of `foldr', namely `(.)'

But this, very similar, does type-check:
---
{-# LANGUAGE RankNTypes, ImpredicativeTypes #-}

f :: [forall a. t a - t a] - t b - t b
f = foldr (\g - (.) g) id
---

What is the reason for this?

Thanks,
Vladimir


On 6/9/09, Vladimir Reshetnikov v.reshetni...@gmail.com wrote:
 Hi,

 I have the following code:
 ---
 {-# LANGUAGE RankNTypes #-}

 f :: ((forall a. a - a) - b) - b
 f x = x id

 g :: (forall c. Eq c = [c] - [c]) - ([Bool],[Int])
 g y = (y [True], y [1])

 h :: ([Bool],[Int])
 h = f g
 ---

 GHC rejects it:
 Couldn't match expected type `forall a. a - a'
against inferred type `forall c. (Eq c) = [c] - [c]'
   Expected type: forall a. a - a
   Inferred type: forall c. (Eq c) = [c] - [c]
 In the first argument of `f', namely `g'
 In the expression: f g

 But, intuitively, this code is type-safe, and actually I can convince
 the typechecker in it with the following workaround:
 ---
 h :: ([Bool],[Int])
 h = let g' = (\(x :: forall a. a - a) - g x) in f g'
 ---

 So, is the current behavior of GHC correct ot it is a bug?
 How unification for rank-N types should proceed?

 Thanks,
 Vladimir

___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] Re: A generics question

2009-06-09 Thread Henry Laxen
Sterling Clover s.clover at gmail.com writes:

 
 Try it with the following type signature and it should work fine:
 
 convert :: (Data a) = Int - a - a
 
 Of course, as has been noted, SYB is a rather big sledgehammer for  
 the insect in question.
 
 Cheers,
 S.
 


Thank you Sterling.  That is the answer I was looking for.  I was trying out
things from the various Scrap your Boilerplate papers, and got stuck doing
something that I thought should be easy.  Now it makes sense.  Thanks again.
Best wishes,
Henry Laxen

___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Convert IO Int to Int

2009-06-09 Thread ptrash

Ok, thanks for the information.
-- 
View this message in context: 
http://www.nabble.com/Convert-IO-Int-to-Int-tp23940249p23942344.html
Sent from the Haskell - Haskell-Cafe mailing list archive at Nabble.com.

___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] Combine to List to a new List

2009-06-09 Thread ptrash

Hi,

I have the following two lists:

a = [1,2,3]
b = [A,B,C]

I want a combination of the to lists:

c = [(1,A), (2, B), (3, C)]

How can I do this?

I have tried

c = [(x,y) | x - a, y - b] 

But this  just returns me a list with every possible combination of the 2
lists.

Thanks...


-- 
View this message in context: 
http://www.nabble.com/Combine-to-List-to-a-new-List-tp23942440p23942440.html
Sent from the Haskell - Haskell-Cafe mailing list archive at Nabble.com.

___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Combine to List to a new List

2009-06-09 Thread Andrew Wagner
Try c = zip a b

On Tue, Jun 9, 2009 at 9:05 AM, ptrash ptr...@web.de wrote:


 Hi,

 I have the following two lists:

 a = [1,2,3]
 b = [A,B,C]

 I want a combination of the to lists:

 c = [(1,A), (2, B), (3, C)]

 How can I do this?

 I have tried

 c = [(x,y) | x - a, y - b]

 But this  just returns me a list with every possible combination of the 2
 lists.

 Thanks...


 --
 View this message in context:
 http://www.nabble.com/Combine-to-List-to-a-new-List-tp23942440p23942440.html
 Sent from the Haskell - Haskell-Cafe mailing list archive at Nabble.com.

 ___
 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


RE: [Haskell-cafe] Combine to List to a new List

2009-06-09 Thread Dimitris Vekris

Probably you might need the zip function.Check 
here:http://haskell.org/ghc/docs/latest/html/libraries/base/Prelude.html#v:zip

 Date: Tue, 9 Jun 2009 06:05:57 -0700
 From: ptr...@web.de
 To: haskell-cafe@haskell.org
 Subject: [Haskell-cafe] Combine to List to a new List
 
 
 Hi,
 
 I have the following two lists:
 
 a = [1,2,3]
 b = [A,B,C]
 
 I want a combination of the to lists:
 
 c = [(1,A), (2, B), (3, C)]
 
 How can I do this?
 
 I have tried
 
 c = [(x,y) | x - a, y - b] 
 
 But this  just returns me a list with every possible combination of the 2
 lists.
 
 Thanks...
 
 
 -- 
 View this message in context: 
 http://www.nabble.com/Combine-to-List-to-a-new-List-tp23942440p23942440.html
 Sent from the Haskell - Haskell-Cafe mailing list archive at Nabble.com.
 
 ___
 Haskell-Cafe mailing list
 Haskell-Cafe@haskell.org
 http://www.haskell.org/mailman/listinfo/haskell-cafe

_
Windows Live™: Keep your life in sync. Check it out!
http://windowslive.com/explore?ocid=TXT_TAGLM_WL_t1_allup_explore_012009___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Combine to List to a new List

2009-06-09 Thread ptrash

Hey, cool. Thanks!
-- 
View this message in context: 
http://www.nabble.com/Combine-to-List-to-a-new-List-tp23942440p23942633.html
Sent from the Haskell - Haskell-Cafe mailing list archive at Nabble.com.

___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Applying Data.Map

2009-06-09 Thread michael rice
Hi Toby,

Thanks for the helpful comments. I'd gotten used to arithmetic operator 
sections (+2), (*2), etc. but hadn't picked up on the generality of using them 
with *any* infix function. I can also see the benefit of using List.Group. 
However, I'm uncertain about how to import just fromList and ! from with the 
imports I'm using

import Data.Map (Map)   (fromList,!)  ???
import qualified Data.Map as Map  (fromList,!) ???

Michael

--- On Mon, 6/8/09, Toby Hutton toby.hut...@gmail.com wrote:

From: Toby Hutton toby.hut...@gmail.com
Subject: Re: [Haskell-cafe] Applying Data.Map
To: michael rice nowg...@yahoo.com
Cc: haskell-cafe@haskell.org
Date: Monday, June 8, 2009, 8:57 PM

Although in this example using Data.Map is overkill, if the alphabet was very 
large then Data.Map probably would be the way to go. In that case I'd use:
map head . group . sort instead of nub . sort


since it's noticeably quicker for large lists.  This is because nub needs to 
preserve the order of input, removing redundancies, but you're sorting it 
anyway.
Also, in map (\c - m Map.! c) s you can use the 'section' (m Map.!) instead.  
e.g., map (m Map.!) s


The Map.! is ugly though.  As you're only using fromList and (!) from Data.Map, 
I'd just import those explicitly since they don't clash with Prelude.  Then 
you'd have map (m !) s


Toby.

On Tue, Jun 9, 2009 at 4:59 AM, michael rice nowg...@yahoo.com wrote:


I wrote a Haskell solution for the Prolog problem stated below. I had written a 
function SQUISH before discovering that NUB does the same thing. While the 
solution works, I thought maybe I could apply some functions in the Data.Map 
module, and so wrote a second version of SERIALIZE, one no longer needing 
TRANSLATE. Using the Data.Map module is probably overkill for this particular 
problem, but wanted to familiarize myself with Map type. Suggestions welcome. 
Prolog code also included below for those interested.



Michael 



===

{-


 From Prolog By Example, Coelho, Cotta, Problem 42, pg. 63



   Verbal statement:
   Generate a list of serial numbers for the items of a given
 list,
   the members of which are to be numbered in alphabetical order.



   For example, the list [p,r,o,l,o,g] must generate [4,5,3,2,3,1]


-}

{-


Prelude :l
 serialize
[1 of 1] Compiling Main ( serialize.hs, interpreted )


Ok, modules loaded: Main.
*Main serialize prolog


[4,5,3,2,3,1]
*Main


-} 

===Haskell code==



import Data.Char
import Data.List


import Data.Map (Map)
import qualified Data.Map as
 Map

{-


translate :: [Char] - [(Char,Int)] - [Int]
translate [] _ = []


translate (x:xs) m = (fromJust (lookup x m)) : (translate xs m )
-}



{-
serialize :: [Char] - [Int]


serialize s = let c = nub $ sort s
  n = [1..(length c)]


  in translate s (zip c n)
-}



serialize :: [Char] - [Int]

serialize s = let c = nub $ sort s

  n = [1..(length c)]
  m = Map.fromList $ zip c n


  in map (\c - m Map.! c) s 



Prolog code



serialize(L,R) :- pairlists(L,R,A),arrange(A,T),
  numbered(T,1,N).


    ?  - typo?
pairlists([X|L],[Y|R],[pair(X,Y)|A]) :- pairlist(L,R,A).


pairlists([],[],[]). 

arrange([X|L],tree(T1,X,T2)) :- partition(L,X,L1,L2),


    arrange(L1,T1),
    arrange(L2,T2).


arrange([],_).

partition([X|L],X,L1,L2) :- partition(L,X,L1,L2).


partition([X|L],Y,[X|L1],L2) :- before(X,Y),
    partition(L,Y,L1,L2).


partition([X|L],Y,L1,[X|L2]) :- before(Y,X),
    partition(L,Y,L1,L2).


partition([],_,[],[]).

before(pair(X1,Y1),pair(X2,Y2)) :- X1X2.



numbered(tree(T1,pair(X,N1),T2),N0,N) :- numbered(T1,N0,N1),


 N2 is N1+1,
 numbered(T2,N2,N).


numbered(void,N,N).

Prolog examples


Execution:

?- serialize([p,r,o,l,o,g]).


   [4,5,3,2,3,1]
?- serialize ([i,n,t,.,a,r,t,i,f,i,c,i,a,l]).


  [5,7,9,1,2,8,9,5,4,5,3,5,2,6]




  
___

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


Re: [Haskell-cafe] Combine to List to a new List

2009-06-09 Thread Mattias Bengtsson
On Tue, 2009-06-09 at 06:05 -0700, ptrash wrote:
 Hi,
 
 I have the following two lists:
 
 a = [1,2,3]
 b = [A,B,C]
 
 I want a combination of the to lists:
 
 c = [(1,A), (2, B), (3, C)]
 
 How can I do this?

What you want is a function with the following type signature:
[t1] - [t2] - [(t1,t2)]

Search for that in hoogle[1] and you get the function zip as a
result[2] (as already told in this thread).
Hoogle is your friend (and helps you help yourself)! :)

1: http://haskell.org/hoogle/
2: http://haskell.org/hoogle/?hoogle=%5Ba%5D+-%3E+%5Bb%5D+-%3E+%5B%28a%
2Cb%29%5D

___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Applying Data.Map

2009-06-09 Thread Thomas ten Cate
On Tue, Jun 9, 2009 at 15:23, michael ricenowg...@yahoo.com wrote:
 import Data.Map (Map)   (fromList,!)  ???
 import qualified Data.Map as Map  (fromList,!) ???

Because ! is an operator, you need to enclose it in parentheses. Also,
the (Map) in the import is already the list of things you are
importing; you can just add to that. So do the following:

Import these without qualification:
 import Data.Map (Map, fromList, (!))
Import everything else (actually including Map, fromList and (!)) with
qualification Map:
 import qualified Data.Map as Map

Cheers,

Thomas
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Convert IO Int to Int

2009-06-09 Thread ptrash

Hmm...it am not getting through it. I just want to generate a random number
and then compare it with other numbers. Something like

r = randomRIO (1, 10)
if (r  5) then... else ...
-- 
View this message in context: 
http://www.nabble.com/Convert-IO-Int-to-Int-tp23940249p23943301.html
Sent from the Haskell - Haskell-Cafe mailing list archive at Nabble.com.

___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Convert IO Int to Int

2009-06-09 Thread Magnus Therning
On Tue, Jun 9, 2009 at 2:52 PM, ptrashptr...@web.de wrote:

 Hmm...it am not getting through it. I just want to generate a random number
 and then compare it with other numbers. Something like

 r = randomRIO (1, 10)
 if (r  5) then... else ...

You have to do it inside the IO monad, something like

myFunc  = do
r - randomRIO (1, 10
if r  5
then ...
else ...

/M

-- 
Magnus Therning(OpenPGP: 0xAB4DFBA4)
magnus@therning.org  Jabber: magnus@therning.org
http://therning.org/magnus identi.ca|twitter: magthe
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Convert IO Int to Int

2009-06-09 Thread Henning Thielemann


On Tue, 9 Jun 2009, ptrash wrote:


I am using the System.Random method randomRIO. How can I convert its output
to an Int?


in general:
http://haskell.org/haskellwiki/How_to_get_rid_of_IO

about randomIO:
http://haskell.org/haskellwiki/Avoiding_IO#State_monad
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Convert IO Int to Int

2009-06-09 Thread Daniel Fischer
Am Dienstag 09 Juni 2009 15:57:24 schrieb Magnus Therning:
 On Tue, Jun 9, 2009 at 2:52 PM, ptrashptr...@web.de wrote:
  Hmm...it am not getting through it. I just want to generate a random
  number and then compare it with other numbers. Something like
 
  r = randomRIO (1, 10)
  if (r  5) then... else ...

 You have to do it inside the IO monad, something like

 myFunc  = do
 r - randomRIO (1, 10
 if r  5
 then ...
 else ...

 /M

Or make the source of the pseudo-random numbers explicit:

import System.Random

function :: (RandomGen g, Random a) = g - other args - result
function gen whatever
| r  5 = blah newgen something
| r  3 = blub newgen somethingElse
| otherwise = bling
  where
(r,newgen) = randomR (lo,hi) gen

and finally, when the programme is run:

main = do
args - getArgs
sg - getStdGen
foo - thisNThat
print $ function sg foo

If you're doing much with random generators, wrap it in a State monad.
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Incremental XML parsing with namespaces?

2009-06-09 Thread Henning Thielemann

John Millikin wrote:

On Mon, Jun 8, 2009 at 3:39 PM, Henning
Thielemannlemm...@henning-thielemann.de wrote:

I think you could use the parser as it is and do the name parsing later.
Due to lazy evaluation both parsers would run in an interleaved way.


I've been trying to figure out how to get this to work with lazy
evaluation, but haven't made much headway. Tips? The only way I can
think of to get incremental parsing working is to maintain explicit
state, but I also can't figure out how to achieve this with the
parsers I've tested (HaXml, HXT, hexpat).


Can you please look at
   http://code.haskell.org/~thielema/tagchup/example/Escape.hs
   http://code.haskell.org/~thielema/tagchup/example/Strip.hs

You just have to replace Text.XML.Basic.Name.LowerCase by 
Text.XML.Basic.Name.Qualified for use of qualified names.


--
Mit freundlichen Gruessen
Henning Thielemann

Viele Gruesse
Henning

Martin-Luther-Universitaet Halle-Wittenberg, Institut fuer Informatik

Tel. +49 - 345 - 55 24773
Fax  +49 - 345 - 55 27333
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Applying Data.Map

2009-06-09 Thread michael rice
In the import statements, it wasn't clear to me that I could import types as 
well as functions, and Map is a type. All clear now.

Thanks.

Michael

--- On Tue, 6/9/09, Thomas ten Cate ttenc...@gmail.com wrote:

From: Thomas ten Cate ttenc...@gmail.com
Subject: Re: [Haskell-cafe] Applying Data.Map
To: michael rice nowg...@yahoo.com
Cc: haskell-cafe@haskell.org
Date: Tuesday, June 9, 2009, 9:40 AM

On Tue, Jun 9, 2009 at 15:23, michael ricenowg...@yahoo.com wrote:
 import Data.Map (Map)   (fromList,!)  ???
 import qualified Data.Map as Map  (fromList,!) ???

Because ! is an operator, you need to enclose it in parentheses. Also,
the (Map) in the import is already the list of things you are
importing; you can just add to that. So do the following:

Import these without qualification:
 import Data.Map (Map, fromList, (!))
Import everything else (actually including Map, fromList and (!)) with
qualification Map:
 import qualified Data.Map as Map

Cheers,

Thomas



  ___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] How to improve below code?

2009-06-09 Thread Neil Brown

Andy Stewart wrote:

So have a better solution to avoid write above ugly code

How about:


data Page a =
   Page {pageName  :: IORef String
,pageId:: Int
,pageBuffer:: a
,pageBox   :: VBox
}

class PageBuffer a where
 pageBufferClone :: a - IO (a, VBox)

pageClone :: PageBuffer a = Page a - IO (Page a)
pageClone page = do
 -- Get common information for clone page.
 name - pageGetName page
 let id = pageId page
 pb = pageBuffer page

 -- Get clone information for dynamic interface. 
 (pBuffer, pBox) - pageBufferClone pb


 -- Return clone page.
 pageNewInternal name id pBuffer pBox



I'm not totally sure if that will work without seeing the rest of your 
code.  But it seems neater, and no GADTs in sight.  If you need to store 
Page StringBuffer in a list with Page ImageBuffer you will have a 
problem, so perhaps you could spell out what else you need to do with 
these Page items in your application?


Thanks,

Neil.
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] How to improve below code?

2009-06-09 Thread Andy Stewart
Hi all,

I have below source code, i use Dynamic for `pageBuffer`.
In implement of function `pageClone`, after `case pt of`, i need write 
like this, and this code looks ugly, if `PageTyep` have 100 type, i need
write those ugly code 100 times.

case pt of
  TStringBuffer - pageBufferClone (x :: StringBuffer)
  TImageBuffer  - pageBufferClone (x :: ImageBuffer)
  TVideoBuffer  - pageBufferClone (x :: TVideoBuffer)
  TMixBuffer- pageBufferClone (x :: TMixBuffer)
  
So have a better solution to avoid write above ugly code?

Someone suggestion me use GADTs instead, but i don't know how to write correct
GADTs code replace current version, if GADTs is best way, someone can
explain it detail? It's better if someone give me demo code.

-- Source Code start 
--
data PageType = TStringBuffer | TImageBuffer | TVideoBuffer | TMixBuffer
 deriving (Eq, Show, Read)

data Page =
Page {pageName  :: IORef String
 ,pageId:: Int
 ,pageType  :: PageType
 ,pageBuffer:: Dynamic
 ,pageBox   :: VBox
 }

class PageBuffer a where
pageBufferClone :: a - IO (Dynamic, VBox)

-- | Page clone interface.
pageClone :: Page - IO Page
pageClone page = do
  -- Get common information for clone page.
  name - pageGetName page
  let id = pageId page
  pt = pageType page
  pb = pageBuffer page

  -- Get clone information for dynamic interface. 
  (pBuffer, pBox) - 
  case fromDynamic pb of
Just x - 
case pt of
  TStringBuffer - pageBufferClone (x :: StringBuffer)
  TImageBuffer  - pageBufferClone (x :: ImageBuffer)
  TVideoBuffer  - pageBufferClone (x :: TVideoBuffer)
  TMixBuffer- pageBufferClone (x :: TMixBuffer)
Nothing - pageCloneEmpty

  -- Return clone page.
  pageNewInternal name id pt pBuffer pBox
-- Source Code end   
--

Thanks!

  -- Andy


___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Convert IO Int to Int

2009-06-09 Thread Krzysztof Skrzętnicki
On Tue, Jun 9, 2009 at 16:14, Daniel Fischerdaniel.is.fisc...@web.de wrote:
 Am Dienstag 09 Juni 2009 15:57:24 schrieb Magnus Therning:
 On Tue, Jun 9, 2009 at 2:52 PM, ptrashptr...@web.de wrote:
  Hmm...it am not getting through it. I just want to generate a random
  number and then compare it with other numbers. Something like
 
  r = randomRIO (1, 10)
  if (r  5) then... else ...

 You have to do it inside the IO monad, something like

     myFunc  = do
         r - randomRIO (1, 10
         if r  5
             then ...
             else ...

 /M

 Or make the source of the pseudo-random numbers explicit:

 import System.Random

 function :: (RandomGen g, Random a) = g - other args - result
 function gen whatever
    | r  5     = blah newgen something
    | r  3     = blub newgen somethingElse
    | otherwise = bling
      where
        (r,newgen) = randomR (lo,hi) gen

 and finally, when the programme is run:

 main = do
    args - getArgs
    sg - getStdGen
    foo - thisNThat
    print $ function sg foo

 If you're doing much with random generators, wrap it in a State monad.

To avoid reinventing the wheel one can use excellent package available
on Hackage:
http://hackage.haskell.org/cgi-bin/hackage-scripts/package/MonadRandom

 The die function simulates the roll of a die, picking a number between 1 and 
 6, inclusive, and returning it in the Rand monad.
 Notice that this code will work with any source of random numbers g.

 die :: (RandomGen g) = Rand g Int
 die = getRandomR (1,6)

 The dice function uses replicate and sequence to simulate the roll of n dice.

 dice :: (RandomGen g) = Int - Rand g [Int]
 dice n = sequence (replicate n die)

 To extract a value from the Rand monad, we can can use evalRandIO.

 main = do
   values - evalRandIO (dice 2)
   putStrLn (show values)

Best regards

Krzysztof Skrzętnicki
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Convert IO Int to Int

2009-06-09 Thread jerzy . karczmarczuk
Magnus Therning writes: 


ptrash  wrote:



...am not getting through it. I just want to generate a random number
and then compare it with other numbers. Something like 


r = randomRIO (1, 10)
if (r  5) then... else ...


You have to do it inside the IO monad, something like 


myFunc  = do
r - randomRIO (1, 10


This may continue forever...
With nice references to monads, to uns...@#*!, etc. ... 


We may say, as many tutorials do : this is not what you want! (which I
hate ; you are not my conscience, whoever you are...), or just give some
code, not always readable... 


Perhaps I belong to a minority here, but I strongly believe that at
THIS level, the first thing to do - unless I am dead wrong - is to explain
to our friend ptrash (who could find a less gothic pseudo) that in a pure
functional programming, the construction
r = whatEver(par1,par2)
being a function call, cannot give just a random number, something which
is not (intuitively) determined, and changes with every call, despite the
constancy of the arguments. 


For most of us, acquainted with the stuff, it becomes trivial, but if
somebody doesn't know that a classical pseudo-random generator modifies a
seed, and in such a way involves a side effect, then sending him to the
monadic heaven is dangerous. 


Please, tell him first about random streams, which he can handle without
IO. Or, about ergodic functions (hashing contraptions which transform ANY
parameter into something unrecognizable). When he says : I know all that,
THEN hurt him badly with monads. 


Jerzy Karczmarczuk
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re[2]: [Haskell-cafe] Convert IO Int to Int

2009-06-09 Thread Bulat Ziganshin
Hello jerzy,

Tuesday, June 9, 2009, 8:23:04 PM, you wrote:

 Please, tell him first about random streams, which he can handle without
 IO. Or, about ergodic functions (hashing contraptions which transform ANY
 parameter into something unrecognizable). When he says : I know all that,
 THEN hurt him badly with monads. 

i think that for someone coming from imperative programming teeling
about IO monad is the easiest way. and then he will learn how to do it
FP way


-- 
Best regards,
 Bulatmailto:bulat.zigans...@gmail.com

___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] please comment on my parser, can I do this cleaner?

2009-06-09 Thread Thomas Hartman
All I want to do is split on commas, but not the commas inside () or  tags.

I have been wanting to master parsec for a long time and this simple
exercise looked like a good place to start.

The code below does the right thing. Am I missing any tricks to make
this simpler/neater?

Thanks, thomas.

thart...@ubuntu:~/perlArenacat splitEm.
splitEm.hs   splitEm.hs~  splitEm.pl   splitEm.pl~
thart...@ubuntu:~/perlArenacat splitEm.hs
{-# LANGUAGE ScopedTypeVariables #-}
import Text.ParserCombinators.Parsec
import Text.ParserCombinators.Parsec.Char
import Text.PrettyPrint (vcat, render, text)
import Data.List.Split hiding (sepBy, chunk)
import Text.ParserCombinators.Parsec.Token

import Debug.Trace
import Debug.Trace.Helpers

-- this works, but is there a neater/cleaner way?
main = ripInputsXs (toEof splitter) splitter [ goodS, badS ]

-- I need a way to split on commas, but not the commas inside '' or
'()' characters
goodS = *2FOO2,1,*3(SigB8:0:2,BAR),*2Siga2:0,Sigb8,7,6,5,0
badS = *2)FOO2,1,*3(SigB8:0:2,BAR),*2Siga2:0,Sigb8,7,6,5,0
-- the first  matches a ), so reject this


splitter = do
  chunks :: [String] - toEof (many chunk)
  let pieces = map concat $ splitOn [,] chunks
  return pieces -- chunks
  where
atom = string ,
   | ( many1 $ noneOf () )
chunk = parenExpr |  atom
parenExpr :: GenParser Char st [Char]
parenExpr = let paren p = betweenInc (char '(' ) (char ')' ) p
| betweenInc (char '' ) (char '' )
p
in paren $ option  $ do ps - many1 $ parenExpr | atom
  return . concat $ ps

betweenInc o' c' p' = do
  o - o'
  p - p'
  c - c'
  return $ [o] ++ p ++ [c]

toEof p' = do
r - p'
eof
return r






ripInputs prs prsName xs = mapM_ (putStrLn . show . parse prs prsName ) xs
ripInputsXs prs prsName xs = mapM_ (putStrLn . showXs . parse prs prsName ) xs
  where showXs v = case v of
  Left e - show e
  Right xs - render . vcat . map text $ xs
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] nubBy seems broken in recent GHCs

2009-06-09 Thread Cale Gibbard
2009/6/6 Bertram Felgenhauer bertram.felgenha...@googlemail.com:
 Interesting. This was changed in response to

    http://hackage.haskell.org/trac/ghc/ticket/2528

 | Tue Sep  2 11:29:50 CEST 2008  Simon Marlow marlo...@gmail.com
 |   * #2528: reverse the order of args to (==) in nubBy to match nub
 |   This only makes a difference when the (==) definition is not
 |   reflexive, but strictly speaking it does violate the report definition
 |   of nubBy, so we should fix it.

 It turns out that 'elem' differs from the report version and should
 have its comparison reversed. Of course that would only ever matter
 for broken Eq instances.

 However, the report also states that the nubBy function may assume that
 the given predicate defines an equivalence relation.

    http://haskell.org/onlinereport/list.html#sect17.6

 So I'm not sure there's anything to be fixed here - although backing
 out the above patch probably won't hurt anybody.

 Bertram

Yeah, while most Eq instances really do define an equivalence relation
(at least extensionally), and the Report authors probably thought in
terms of an equivalence relation (even going so far as to say that
nubBy can assume its parameter is one, which I think was a mistake), I
think nubBy has a much more general use. It does a generalised kind of
sieving, specifically,

nubBy f xs is the unique subsequence of xs that:
1) Has the property that if x and y are elements such that x occurs
before y in it, then f x y is False.
2) The sequence of indices of selected elements is lexicographically
minimum for all subsequences satisfying condition 1. (That is, it
always picks the earliest elements possible.)

I think this is how it ought to be specified.

Similarly, groupBy f xs is (and should be) the unique list of
contiguous sublists of xs such that:
1) concat (groupBy f xs) = xs
2) If x is the head of any of the sublists and y is any other element
of that sublist, then f x y
3) The sequence of lengths of the sublists is lexicographically
maximum for all lists satisfying the first two properties (That is, it
always prefers adding elements to an earlier group to starting a new
group.)

 - Cale
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Convert IO Int to Int

2009-06-09 Thread Jorge Branco Branco Aires

Bulat Ziganshin wrote:

Hello jerzy,

Tuesday, June 9, 2009, 8:23:04 PM, you wrote:

  

Please, tell him first about random streams, which he can handle without
IO. Or, about ergodic functions (hashing contraptions which transform ANY
parameter into something unrecognizable). When he says : I know all that,
THEN hurt him badly with monads. 



i think that for someone coming from imperative programming teeling
about IO monad is the easiest way. and then he will learn how to do it
FP way
  
I came from a imperative programming background. I didn't feel like this 
help me at all back then. At least in the beginning you want to detach 
yourself from an imperative style, not try to simulate it with some 
weird structure that you don't really understand.


More generally I really wish IO hadn't been the first Monad I played 
with. It's so close to a Functor, yet in my mind Functors were simple, 
just structures that could be mapped, and Monads were these mysterious 
things that allowed you to get away with side effects and that once you 
were inside you could never get out.


Jorge
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] please comment on my parser, can I do this cleaner?

2009-06-09 Thread Daniel Fischer
Am Dienstag 09 Juni 2009 20:29:09 schrieb Thomas Hartman:
 All I want to do is split on commas, but not the commas inside () or 
 tags.

 I have been wanting to master parsec for a long time and this simple
 exercise looked like a good place to start.

 The code below does the right thing. Am I missing any tricks to make
 this simpler/neater?

 Thanks, thomas.

 thart...@ubuntu:~/perlArenacat splitEm.
 splitEm.hs   splitEm.hs~  splitEm.pl   splitEm.pl~
 thart...@ubuntu:~/perlArenacat splitEm.hs
 {-# LANGUAGE ScopedTypeVariables #-}
 import Text.ParserCombinators.Parsec
 import Text.ParserCombinators.Parsec.Char
 import Text.PrettyPrint (vcat, render, text)
 import Data.List.Split hiding (sepBy, chunk)
 import Text.ParserCombinators.Parsec.Token

 import Debug.Trace
 import Debug.Trace.Helpers

 -- this works, but is there a neater/cleaner way?
 main = ripInputsXs (toEof splitter) splitter [ goodS, badS ]

 -- I need a way to split on commas, but not the commas inside '' or
 '()' characters
 goodS = *2FOO2,1,*3(SigB8:0:2,BAR),*2Siga2:0,Sigb8,7,6,5,0
 badS = *2)FOO2,1,*3(SigB8:0:2,BAR),*2Siga2:0,Sigb8,7,6,5,0
 -- the first  matches a ), so reject this


 splitter = do
   chunks :: [String] - toEof (many chunk)
   let pieces = map concat $ splitOn [,] chunks
   return pieces -- chunks
   where
 atom = string ,
| ( many1 $ noneOf () )
 chunk = parenExpr |  atom

I think that does not do what you want.

For input FOO,BAR,BAZ, chunks is [FOO,BAR,BAZ], that won't be split; as far 
as I can 
see, it splits only on commas directly following a parenExpr (or at the 
beginning of the 
input or directly following another splitting comma).

 parenExpr :: GenParser Char st [Char]
 parenExpr = let paren p = betweenInc (char '(' ) (char ')' ) p
 | betweenInc (char '' ) (char '' )
 p
 in paren $ option  $ do ps - many1 $ parenExpr | atom
   return . concat $ ps

 betweenInc o' c' p' = do
   o - o'
   p - p'
   c - c'
   return $ [o] ++ p ++ [c]

 toEof p' = do
 r - p'
 eof
 return r






 ripInputs prs prsName xs = mapM_ (putStrLn . show . parse prs prsName ) xs
 ripInputsXs prs prsName xs = mapM_ (putStrLn . showXs . parse prs prsName )
 xs where showXs v = case v of
   Left e - show e
   Right xs - render . vcat . map text $ xs

I can offer (sorry for the names, and I don't know if what that does is really 
what you 
want):


keepSepBy :: Parser a - Parser a - Parser [a]
keepSepBy p sep = (do
r - p
(do s - sep
xs - keepSepBy p sep
return (r:s:xs)) | return [r])
| return []

twain :: Parser a - Parser a - Parser [a] - Parser [a]
twain open close list = do
o - open
l - list
c - close
return (o:l++[c])

comma :: Parser String
comma = string ,

simpleChar :: Parser Char
simpleChar = noneOf (),

suite :: Parser String
suite = many1 simpleChar

atom :: Parser String
atom = fmap concat $ many1 (parenExp | suite)

parenGroup :: Parser String
parenGroup = fmap concat $ keepSepBy atom comma

parenExp :: Parser String
parenExp = twain (char '') (char '') parenGroup
| twain (char '(') (char ')') parenGroup

chunks :: Parser [String]
chunks = sepBy atom comma

splitter = do
cs - chunks
eof
return cs

goodS = *2FOO2,1,*3(SigB8:0:2,BAR),*2Siga2:0,Sigb8,7,6,5,0
badS = *2)FOO2,1,*3(SigB8:0:2,BAR),*2Siga2:0,Sigb8,7,6,5,0

goodRes = parse splitter splitter goodS
badRes = parse splitter splitter badS


___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Convert IO Int to Int

2009-06-09 Thread Luke Palmer
2009/6/9 Krzysztof Skrzętnicki gte...@gmail.com

 On Tue, Jun 9, 2009 at 16:14, Daniel Fischerdaniel.is.fisc...@web.de
 wrote:
  If you're doing much with random generators, wrap it in a State monad.

 To avoid reinventing the wheel one can use excellent package available
 on Hackage:
 http://hackage.haskell.org/cgi-bin/hackage-scripts/package/MonadRandom


Please do!  Prefer MonadRandom to explicit generator passing:
http://lukepalmer.wordpress.com/2009/01/17/use-monadrandom/.  Keep
computations in MonadRandom, and pull them out with evalRandomIO at the last
second.

Luke


 http://hackage.haskell.org/cgi-bin/hackage-scripts/package/MonadRandom

  The die function simulates the roll of a die, picking a number between 1
 and 6, inclusive, and returning it in the Rand monad.
  Notice that this code will work with any source of random numbers g.
 
  die :: (RandomGen g) = Rand g Int
  die = getRandomR (1,6)
 
  The dice function uses replicate and sequence to simulate the roll of n
 dice.
 
  dice :: (RandomGen g) = Int - Rand g [Int]
  dice n = sequence (replicate n die)
 
  To extract a value from the Rand monad, we can can use evalRandIO.
 
  main = do
values - evalRandIO (dice 2)
putStrLn (show values)

 Best regards

 Krzysztof Skrzętnicki
 ___
 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


Re: [Haskell-cafe] How to improve below code?

2009-06-09 Thread Ryan Ingram
On Tue, Jun 9, 2009 at 7:21 AM, Neil Brownnc...@kent.ac.uk wrote:
 data Page a =
   Page {pageName      :: IORef String
        ,pageId        :: Int
        ,pageBuffer    :: a
        ,pageBox       :: VBox
        }

 class PageBuffer a where
  pageBufferClone :: a - IO (a, VBox)

 pageClone :: PageBuffer a = Page a - IO (Page a)
 pageClone page = do
  -- Get common information for clone page.
  name - pageGetName page
  let id = pageId page
     pb = pageBuffer page

  -- Get clone information for dynamic interface.  (pBuffer, pBox) -
 pageBufferClone pb

  -- Return clone page.
  pageNewInternal name id pBuffer pBox

Actually you can avoid the type parameter on a using an existential:

 {-# LANGUAGE ExistentialQuantification #-}
 data Page = forall a. PageBuffer a =
   Page {pageName  :: IORef String
,pageId:: Int
,pageBuffer:: a
,pageBox   :: VBox
}

Now you can still use [Page].  You can't do pageBuffer p, though,
you'll get this fun error message:
Cannot use record selector `pageBuffer' as a function due to
escaped type variables
Probable fix: use pattern-matching syntax instead

Instead you need to do
case p of Page{pageBuffer = x} - ...something with x...

This will bring the PageBuffer context into scope, inside of the case statement.

  -- ryan
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] FlexibleContexts and FlexibleInstances

2009-06-09 Thread Niklas Broberg
Dear all,

This post is partly a gripe about how poor the formal documentation
for various GHC extensions is, partly a gripe about how GHC blurs the
lines between syntactic and type-level issues as well as between
various extensions, and partly a gripe about how the Haskell 98 report
is sometimes similarly blurred where syntax is concerned (or not). All
these things make the life of a poor parser implementor quite
miserable at times. All in good jest of course, but with an edge of
truth, especially regarding (lack of) formal documentation.

The issue at hand which has caused my frustration is the
FlexibleContexts [1] and FlexibleInstances [2] extensions, which lift
restrictions imposed by Haskell 98 on the forms of contexts and
instances that may be defined. Great extensions both of them - but
what do they do, really really?

The following toy program requires MultiParamTypeClasses OR
FlexibleContexts in order to be accepted by GHC(i):

 f :: (T a b) = a - Int
 f _ = 0

This of course assumes that we import the definition of T, we *must*
have MultiParamTypeClasses enabled if we want to declare T. Both
extensions thus enable classes with more than one argument to appear
in contexts.

Changing the program to

 f :: (T a ()) = a - Int
 f _ = 0

i.e. changing the second argument to T to () instead, means we now
*must* have FlexibleInstances, in order to allow the non-tyvar
argument. This is nothing surprising, this is what FlexibleInstances
are supposed to do. But the question is, is this a syntactic issue or
a typing issue? In GHC proper this doesn't really matter much, as long
as it is caught *somewhere* then all is dandy. GHC's parser lets
everything pass, and it's the type checker that balks at this program.
But for someone like me with *only* a parser, this is a question that
needs a clear answer. Looking at the online report, the productions
regarding contexts are

context -  class
|   ( class1 , ... , classn )   (n=0)
class   -  qtycls tyvar
|   qtycls ( tyvar atype1 ... atypen )  (n=1)
qtycls  -  [ modid . ] tycls
tycls   -  conid
tyvar   -  varid

Ok, so clearly the () is a syntactic extension enabled by
FlexibleContexts, as it is not a tyvar nor a tyvar applied to a
sequence of types. So this is something that a parser should handle.
FlexibleContexts also enables similar parses of contexts in other
places, for instance in class declarations, for which the Haskell 98
report says

topdecl -  class [scontext =] tycls tyvar [where cdecls]
scontext-  simpleclass
|   ( simpleclass1 , ... , simpleclassn )   (n=0)
simpleclass -  qtycls tyvar

The difference here is that the simpleclass doesn't allow the tyvar
applied to a sequence of types bit. FlexibleContexts lifts that
restriction too, so there should be no difference between the two
kinds of contexts. So the new formal productions for flexible contexts
should be something like

fcontext-  fclass
|   ( fclass1 , ... , fclassn ) (n=0)
fclass  -  qtycls type1 ... typen  (n=1)

topdecl -  data [fcontext =] simpletype = constrs [deriving]
|   newtype [fcontext =] simpletype = newconstr [deriving]
|   class [fcontext =] tycls tyvar [where cdecls]
|   instance [fcontext =] qtycls inst [where idecls]

gendecl -  vars :: [fcontext =] type

Does this seem correct?

Now let's turn to FlexibleInstances, which similarly lifts
restrictions, only to instance declarations instead of contexts. The
Haskell 98 report says on instance declarations:

topdecl -  instance [scontext =] qtycls inst [where idecls]
inst-  gtycon
|   ( gtycon tyvar1 ... tyvark )(k=0, tyvars distinct)
|   ( tyvar1 , ... , tyvark )   (k=2, tyvars distinct)
|   [ tyvar ]
|   ( tyvar1 - tyvar2 )(tyvar1 and tyvar2 distinct)

Note the re-appearance of scontext, which is the same as above. The
instance head must be a type constructor, possibly applied to a number
of type variables, or one of three built-in syntactic cases. This is
where I consider the Haskell 98 report blurry - the fact that the
tyvars must be distinct, is that truly a syntactic issue? It might be,
it's certainly something that could be checked syntactically. But when
you take into account that with the proper extensions, they no longer
need to be distinct, at what level would we expect such a check to
happen? My gut feeling is that this check for distinctness is
something that a type checker might do better than a parser, though
it's not clear cut by any means. But since I don't do any other kind
of name resolution or checking in my parser even if it would be
possible (e.g. multiple declarations of the same symbol), I would find
it a bit anomalous to check this too.

Turning on FlexibleInstances, we shouldn't need to follow any of the
above restrictions on 

Re: [Haskell-cafe] Incremental XML parsing with namespaces?

2009-06-09 Thread Iavor Diatchki
Hi,
you may also want to look at:
http://hackage.haskell.org/cgi-bin/hackage-scripts/package/xml
It knows about namespaces and, also, it's parser is lazy.
-Iavor


On Mon, Jun 8, 2009 at 11:39 AM, John Millikinjmilli...@gmail.com wrote:
 I'm trying to convert an XML document, incrementally, into a sequence
 of XML events. A simple example XML document:

 doc xmlns=org:myproject:mainns xmlns:x=org:myproject:otherns
    titleDoc title/title
    x:refabc1234/x:ref
    html xmlns=http://www.w3.org/1999/xhtml;bodyHello world!/body/html
 /doc

 The document can be very large, and arrives in chunks over a socket,
 so I need to be able to feed the text data into a parser and receive
 a list of XML events per chunk. Chunks can be separated in time by
 intervals of several minutes to an hour, so pausing processing for the
 arrival of the entire document is not an option. The type signatures
 would be something like:

 type Namespace = String
 type LocalName = String

 data Attribute = Attribute Namespace LocalName String

 data XMLEvent =
    EventElementBegin Namespace LocalName [Attribute] |
    EventElementEnd Namespace LocalName |
    EventContent String |
   EventError String

 parse :: Parser - String - (Parser, [XMLEvent])

 I've looked at HaXml, HXT, and hexpat, and unless I'm missing
 something, none of them can achieve this:

 + HaXml and hexpat seem to disregard namespaces entirely -- that is,
 the root element is parsed to doc instead of
 (org:myproject:mainns, doc), and the second child is x:ref
 instead of (org:myproject:otherns, ref). Obviously, this makes
 parsing mixed-namespace documents effectively impossible. I found an
 email from 2004[1] that mentions a filter for namespace support in
 HaXml, but no further information and no working code.

 + HXT looks promising, because I see explicit mention in the
 documentation of recording and propagating namespaces. However, I
 can't figure out if there's an incremental mode. A page on the wiki[2]
 suggests that SAX is supported in the html tag soup parser, but I
 want incremental parsing of *valid* documents. If incremental parsing
 is supported by the standard arrow interface, I don't see any
 obvious way to pull events out into a list -- I'm a Haskell newbie,
 and still haven't quite figured out monads yet, let alone Arrows.

 Are there any libraries that support namespace-aware incremental parsing?

 [1] http://www.haskell.org/pipermail/haskell-cafe/2004-June/006252.html
 [2] 
 http://www.haskell.org/haskellwiki/HXT/Conversion_of_Haskell_data_from/to_XML
 ___
 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


Re: [Haskell-cafe] please comment on my parser, can I do this cleaner?

2009-06-09 Thread Thomas Hartman
Thanks. It seems my original parser also works against FOO,BAR,BAZ if
you only modify

atom = string ,
           | ( many1 $ noneOf (), ) -- add ,

Indeed, what to call the thingies in a parser is a source of some
personal consternation.

What is a token, what is an atom, what is an expr? It all seems to be
somewhat ad hoc.

 2009/6/9 Daniel Fischer daniel.is.fisc...@web.de:
 Am Dienstag 09 Juni 2009 20:29:09 schrieb Thomas Hartman:
 All I want to do is split on commas, but not the commas inside () or 
 tags.

 I have been wanting to master parsec for a long time and this simple
 exercise looked like a good place to start.

 The code below does the right thing. Am I missing any tricks to make
 this simpler/neater?

 Thanks, thomas.

 thart...@ubuntu:~/perlArenacat splitEm.
 splitEm.hs   splitEm.hs~  splitEm.pl   splitEm.pl~
 thart...@ubuntu:~/perlArenacat splitEm.hs
 {-# LANGUAGE ScopedTypeVariables #-}
 import Text.ParserCombinators.Parsec
 import Text.ParserCombinators.Parsec.Char
 import Text.PrettyPrint (vcat, render, text)
 import Data.List.Split hiding (sepBy, chunk)
 import Text.ParserCombinators.Parsec.Token

 import Debug.Trace
 import Debug.Trace.Helpers

 -- this works, but is there a neater/cleaner way?
 main = ripInputsXs (toEof splitter) splitter [ goodS, badS ]

 -- I need a way to split on commas, but not the commas inside '' or
 '()' characters
 goodS = *2FOO2,1,*3(SigB8:0:2,BAR),*2Siga2:0,Sigb8,7,6,5,0
 badS = *2)FOO2,1,*3(SigB8:0:2,BAR),*2Siga2:0,Sigb8,7,6,5,0
 -- the first  matches a ), so reject this


 splitter = do
   chunks :: [String] - toEof (many chunk)
   let pieces = map concat $ splitOn [,] chunks
   return pieces -- chunks
   where
     atom = string ,
            | ( many1 $ noneOf () )
     chunk = parenExpr |  atom

 I think that does not do what you want.

 For input FOO,BAR,BAZ, chunks is [FOO,BAR,BAZ], that won't be split; as 
 far as I can
 see, it splits only on commas directly following a parenExpr (or at the 
 beginning of the
 input or directly following another splitting comma).

     parenExpr :: GenParser Char st [Char]
     parenExpr = let paren p = betweenInc (char '(' ) (char ')' ) p
                                 | betweenInc (char '' ) (char '' )
 p
                 in paren $ option  $ do ps - many1 $ parenExpr | atom
                                           return . concat $ ps

 betweenInc o' c' p' = do
   o - o'
   p - p'
   c - c'
   return $ [o] ++ p ++ [c]

 toEof p' = do
         r - p'
         eof
         return r






 ripInputs prs prsName xs = mapM_ (putStrLn . show . parse prs prsName ) xs
 ripInputsXs prs prsName xs = mapM_ (putStrLn . showXs . parse prs prsName )
 xs where showXs v = case v of
           Left e - show e
           Right xs - render . vcat . map text $ xs

 I can offer (sorry for the names, and I don't know if what that does is 
 really what you
 want):


 keepSepBy :: Parser a - Parser a - Parser [a]
 keepSepBy p sep = (do
    r - p
    (do s - sep
        xs - keepSepBy p sep
        return (r:s:xs)) | return [r])
    | return []

 twain :: Parser a - Parser a - Parser [a] - Parser [a]
 twain open close list = do
    o - open
    l - list
    c - close
    return (o:l++[c])

 comma :: Parser String
 comma = string ,

 simpleChar :: Parser Char
 simpleChar = noneOf (),

 suite :: Parser String
 suite = many1 simpleChar

 atom :: Parser String
 atom = fmap concat $ many1 (parenExp | suite)

 parenGroup :: Parser String
 parenGroup = fmap concat $ keepSepBy atom comma

 parenExp :: Parser String
 parenExp = twain (char '') (char '') parenGroup
            | twain (char '(') (char ')') parenGroup

 chunks :: Parser [String]
 chunks = sepBy atom comma

 splitter = do
    cs - chunks
    eof
    return cs

 goodS = *2FOO2,1,*3(SigB8:0:2,BAR),*2Siga2:0,Sigb8,7,6,5,0
 badS = *2)FOO2,1,*3(SigB8:0:2,BAR),*2Siga2:0,Sigb8,7,6,5,0

 goodRes = parse splitter splitter goodS
 badRes = parse splitter splitter badS


 ___
 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] Re: I love purity, but it's killing me.

2009-06-09 Thread Chung-chieh Shan
Paul L nine...@gmail.com wrote in article 
856033f20906082224s2b7d5391gdc7a4ed913004...@mail.gmail.com in 
gmane.comp.lang.haskell.cafe:
 The open question is whether there exists such a
 solution that's both elegant and efficient at maintain proper sharing
 in the object language.

What is your criterion for efficient?

 We certainly can get rid of all interpretive overheads by either
 having a tagless interpreter (as in Oleg and Shan's paper), or by
 direct compilation.

(BTW, the paper is by Jacques Carette, Oleg Kiselyov, and Chung-chieh
Shan.)

 But so far I don't see how a tagless interpreter
 could handle sharing when it can't be distinguished in the host
 language.

Indeed, I would agree with those on this thread who have stated that
sharing should be distinguished in the host language.

-- 
Edit this signature at http://www.digitas.harvard.edu/cgi-bin/ken/sig
We want our revolution, and we want it now! -- Marat/Sade
We want our revolution, and we'll take it at such time as  
 you've gotten around to delivering it  -- Haskell programmer

___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] help with a question

2009-06-09 Thread haonan21

I'm very new to haskell hugs and would appreciate it if someone could help me
out here. I've been giving 2 questions. 

1.) A and B are two sets of integers. Implement a function to obtain the
integers that belong to both sets.
Test your function fully.

2.) Define and test a function f, which, if A is a set of {x, y, z} then
f(A) = {{},{x}, {y}, {z}, {x, y}, {x,z}, {y,z}, {x, y, z}}

Manage to get the first one.
interset::[Int]-[Int]-[Int]

interset x [] = []

interset [] y = []

interset x@(xs:xt) y@(ys:yt) =
 if xs == ys
 then as:(interset at yt)
 else interset at y

Totally have no clue for the 2nd question. could someone help me out ? 

Many thanks!
-- 
View this message in context: 
http://www.nabble.com/help-with-a-question-tp23946402p23946402.html
Sent from the Haskell - Haskell-Cafe mailing list archive at Nabble.com.

___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] help with a question

2009-06-09 Thread Michael Vanier

haonan21 wrote:

I'm very new to haskell hugs and would appreciate it if someone could help me
out here. I've been giving 2 questions. 


1.) A and B are two sets of integers. Implement a function to obtain the
integers that belong to both sets.
Test your function fully.

2.) Define and test a function f, which, if A is a set of {x, y, z} then
f(A) = {{},{x}, {y}, {z}, {x, y}, {x,z}, {y,z}, {x, y, z}}

Manage to get the first one.
interset::[Int]-[Int]-[Int]

interset x [] = []

interset [] y = []

interset x@(xs:xt) y@(ys:yt) =
 if xs == ys
 then as:(interset at yt)
 else interset at y

Totally have no clue for the 2nd question. could someone help me out ? 


Many thanks!
  

Haonan,

This looks like homework, but I can offer a few suggestions.  Your 
interset function uses as and at where I think you mean xs and 
xt and the else case is wrong (you need to test the code!).  Anyway, 
it looks like you're assuming that the lists are in ascending order, and 
I don't see that in the problem specification -- it won't work if that 
isn't the case.  More interestingly, you should look at the List (or 
Data.List) library; it contains a library function which can solve your 
problem in one line.  As for the second function, that's a classic 
problem used for teaching recursion: find all subsets of a given list.  
The way to solve it is to first ask what the solution is for the empty 
set (which should be obvious).  Then assume that you have the solution 
for the tail of the list ({y, z}).  How would you use this and the head 
of the list (x) to generate the full solution?


HTH,

Mike



___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Re: Building network package on Windows

2009-06-09 Thread Bryan O'Sullivan
On Mon, Jun 8, 2009 at 10:18 PM, Iavor Diatchki iavor.diatc...@gmail.comwrote:


 OK, I think that I found and fixed the problem.  As Thomas pointed
 out, the configure script is not wrong.  The problem turned out to be
 the foreign import for getnameinfo (this was the missing symbol).


So it was the name mangling! Great, thanks for the patch. It's applied.
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe