Re: [Haskell-cafe] An experimental Zipper using Thrists and first-class Labels. Help or thoughts?

2010-07-26 Thread Jason Dagit
On Mon, Jul 26, 2010 at 10:59 PM, Jason Dagit  wrote:

>
>  ($) is application, but in the space of functions it is identity.  So, if
> you think the elements in your thrist as being values in the space of
> functions, you're asking for a right fold that is like, v1 `id` (v2 `id` (v3
> `id` ...), which I hope you agree doesn't make that much sense.
>

I just realized a better way to phrase this analogy is that id and ($) are
0, and (.) is (+).

So your foldr expands like:
v1 `0` (v2 `0` (v3 `0`  (vn `0` 0) ... )

But if you use (.), it expands like:
v1 + (v2 + (v3 + ... (vn + 0) ... )

I guess you could pick id = ($) = 1, and (.) = (*).  I think the analogy
works equally well, but I might be forgetting something simple.  Either way,
I bet you get what I'm rambling about so I'll stop now :)

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


Re: [Haskell-cafe] An experimental Zipper using Thrists and first-class Labels. Help or thoughts?

2010-07-26 Thread Jason Dagit
On Mon, Jul 26, 2010 at 9:00 PM, Brandon Simmons <
brandon.m.simm...@gmail.com> wrote:

> I had the idea for a simple generic Zipper data structure that I
> thought would be possible to implement using type-threaded lists
> provided by Gabor Greif's thrist package:
>
>http://hackage.haskell.org/package/thrist
>
> ...and the fclabels package by Sebastiaan Visser, Erik Hesselink,
> Chris Eidhof and Sjoerd Visscher:
>
>http://hackage.haskell.org/package/fclabels
>
> It would (ideally) work as follows:
>
> - the zipper would consist simply of a tuple:
>   (type threaded list of constructor sections , current "context")
> - in the type threaded list we store functions (constructor with hole
> -> complete constructor), so the
>"one hole context" is represented as a lambda expression where the
> free variable will be filled
>by the current "context" (the snd of the tuple)
> - we "go down" through our structure by passing to our `moveTo`
> function a first-class label
>corresponding to the constructor we want to descend into. `moveTo`
> uses this both as a "getter"
>to extract the next level down from the current level, and as a
> "setter" to form the lambda expression
>which acts as the "constructor with a piece missing"
> - "going up" means popping the head off the thrist and applying it to
> the current context, making that
>the new context, exiting the zipper would be a fold in the same manner
>
>
> After throwing together a quick attempt I realized that I'm not sure
> if it would be possible to make the `moveUp` function type-check and
> be usable. I'm still new to GADTs, existential types, template haskell
> etc. and am stuck.
>
> Here is the code I wrote up, which doesn't currently compile:
>
>
> --  START CODE
> ---
>
> {-# LANGUAGE TypeOperators, GADTs #-}
> module ZipperGenerator
>(
>  viewC   --lets user pattern match against context
>, moveTo
>, moveUp
>, genZippers
>, zipper
>, unzipper
>, (:->)
>, ZipperGenerator
>, Zipper
>) where
>
> -- these provide the secret sauce
> import Data.Record.Label
> import Data.Thrist
> import Language.Haskell.TH
>
>
> type ZipperGenerator = [Name] -> Q [Dec]
>
> -- the Template Haskell function that does the work of generating
> -- first-class labels used to move about the zipper:
> genZippers :: ZipperGenerator
> genZippers = mkLabels
>
> -- hide the innards:
> newtype Zipper t c = Z (Thrist (->) c t, c)
>
> -- returns the current "context" (our location in the zipper) for pattern
> -- matching and inspection:
> viewC :: Zipper t c -> c
> viewC (Z(_,c)) = c
>
> -- takes a first-class label corresponding to the record in the current
> context
> -- that we would like to move to:
> moveTo :: (c :-> c') -> Zipper t c -> Zipper t c'
> moveTo lb (Z(thr,c)) = Z (Cons (\a-> set lb a c) thr , get lb c)
>
>
> -- backs up a level in the zipper, returning `Nothing` if we are already at
> the
> -- top level:
> moveUp :: Zipper t c -> Maybe (Zipper t b)
> moveUp (Z (Nil,_)) = Nothing
> moveUp (Z (Cons f thr,c)) = Just $ Z (thr, f c)
>
> -- create zipper with focus on topmost constructor level:
> zipper :: t -> Zipper t t
> zipper t = Z (Nil,t)
>
> -- close zipper
> unzipper :: Zipper t c -> t
> unzipper (Z(thr,c)) = undefined --foldThrist ($) id thr c
>

Hmm...I think you just need to change ($) to (.).  I haven't tested it.
 But, if you have Thrist (->) c t, then what you have is a transformation
from c to t, or more simply, c -> t.  So, conceptually at least, you just
need to compose the elements in your Thrist.  ($) is application, but in the
space of functions it is identity.  So, if you think the elements in your
thrist as being values in the space of functions, you're asking for a right
fold that is like, v1 `id` (v2 `id` (v3 `id` ...), which I hope you agree
doesn't make that much sense.  So try this:
unzipper (Z(thr,c)) = foldThrist (.) id thr c

In the darcs source we use our own custom thrists for storing sequences of
patches.  We have two variants, forward lists (FL) and reverse lists (RL).
 In our parlance, we have foldlFL defined thusly:
foldlFL :: (forall w y. a -> b w y -> a) -> a -> FL b x z -> a
foldlFL _ x NilFL = x
foldlFL f x (y:>:ys) = foldlFL f (f x y) ys

We don't use Control.Arrow, so in our notation the 'b' in the type signature
plays the same role as (~>) but in prefix notation, of course.  And we use
(:>:) instead of Cons.  It's supposed to look like normal list cons but with
an arrow pointing forward.  The cons for RL is (:<:).  Perhaps we should use
arrow though, as I think that looks pretty nice.

For comparison, here is the definition of foldThrist:
foldThrist :: (forall i j k . (i ~> j) -> (j ~> k) -> (i ~> k))
-> c ~> c
-> Thrist (~>) a c
-> a ~> c
foldThrist _ v Nil = v
foldThrist f v (Cons h t) = h `f` (foldThrist f v t)

As you can see, our fold is a left fold and the thrist fold is a right fold.
 I don't th

Re: [Haskell-cafe] Re: ANN: weighted-regexp-0.1.0.0

2010-07-26 Thread Sebastian Fischer


On Jul 27, 2010, at 6:57 AM, Sebastian Fischer wrote:

Maybe I'll add it [noMatch] to the next version. I only need a  
better string representation ;)


Ha! It's already provided by character classes:

ghci> accept (fromString "[]") "abc"
False

I'll add

noMatch :: RegExp c
noMatch = psym "[]" (const False)

Sebastian



--
Underestimating the novelty of the future is a time-honored tradition.
(D.G.)



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


Re: [Haskell-cafe] 1st attempt at concurrency

2010-07-26 Thread Jason Dagit
2010/7/26 Günther Schmidt 

> Dear Felipe,
>
> thank you for the code and for the correction :).
>
> As usual I come across interesting stuff when I have no immediate need for
> it and when I do I can't find it anymore.
>
> I am looking for something slightly more abstracted and iirc there recently
> was a post about the pi-calculus which seemed elegant even though the author
> told me himself it was not meant for any RW use.
>
> But I believe the Galois boys have created a lib, called orc?, for this
> purpose. I think I'll check into that and see how it goes.
>

BTW, Galois also employs women, not just boys/men.  "Galois folks" would be
more appropriate and gender inclusive.

And yes, Orc is pretty cool and should be perfectly suited for what you're
doing as fetching data from websites was one of the original use cases for
Orc.

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


[Haskell-cafe] Re: ANN: weighted-regexp-0.1.0.0

2010-07-26 Thread Sebastian Fischer

Hi Sjoerd,

It seems that only shift needs the reg field of the RegW datatype.  
So you can also replace the reg field with a shift field. This makes  
the regexp parser extensible, as there is no longer a dependence on  
the (closed) datatype Reg:



data RegW w c = RegW { active :: !Bool,
  empty :: !w,
  final_ :: !w,
  shift :: w -> c -> RegW w c }


Interesting observation. However, such an encoding would prevent the  
definition of some other functions on RegExp. More specifically, there  
are Show and Eq instances for the QuickCheck tests.


For example it is then easy to define the parser that matches  
nothing, which is the identity element of alt:



noMatch :: RegExp c
noMatch = RegExp noMatchW

noMatchW :: Semiring w => RegW w c
noMatchW = RegW False zero zero $ \_ _ -> noMatchW


Note that you can also define it with the current interface:

noMatch :: RegExp c
noMatch = psym "(Big Lambda)" (const False)

Maybe I'll add it to the next version. I only need a better string  
representation ;)



But otherwise I do wonder if the parser needs to be extensible.


I have some ideas for extending the matcher. For example /a{2,5}/ is  
currently translated into /aa(a(a(a)?)?)?/ but it may be possible to  
handle it without such blowup. I also want to add substring matching,  
i.e., the possibility to find out against which strings parenthesized  
parts of the regexp were matched.


But as the closed Reg type is not exported I can freely change it  
along with any matcher extension.


For example some XML Schema implementations that are based on finite  
automata have special cases for the xs:all construct, which matches  
a list of elements, each occurring once in any order. But I tried a  
straightforward implementation and it works fine:



eachOnce :: [RegExp c] -> RegExp c
eachOnce [] = eps
eachOnce ps = eachOnce' ps [] where
 eachOnce' [] _ = noMatch
 eachOnce' (p:ps) qs = (p `seq_` eachOnce (ps ++ qs)) `alt`  
eachOnce' ps (p:qs)


Neat! That's also worth adding. I find

eachOnce :: [RegExp c] -> RegExp c
eachOnce = foldr alt noMatch . map (foldr seq_ eps) . permutations

even clearer but your version is *much* better as it uses nesting to  
combine all alternatives that start with the same regexp.


Thanks!
Sebastian


--
Underestimating the novelty of the future is a time-honored tradition.
(D.G.)



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


Re: [Haskell-cafe] Chart package segfaults when rendering to window

2010-07-26 Thread Thomas DuBuisson
Can you boil this down to some simple example code?  Are you using a
recent version of Chart?  And your definition of "latest" gtk2hs is
11, right?  How about your gtk+ C library, it what? 2.20?

Cheers,
Thomas

On Mon, Jul 26, 2010 at 9:39 PM,   wrote:
> Seems to be ok rendering to png files.
>
> I was wondering if anybody has been using Chart and may have seen the
> same thing.

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


[Haskell-cafe] Chart package segfaults when rendering to window

2010-07-26 Thread briand
Seems to be ok rendering to png files.

I was wondering if anybody has been using Chart and may have seen the
same thing.

I'm running ghc 6.12.1 and the latest and greatest gtk2hs :-)

Thanks,

Brian

p.s. the amplitude modulation
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] An experimental Zipper using Thrists and first-class Labels. Help or thoughts?

2010-07-26 Thread Brandon Simmons
I had the idea for a simple generic Zipper data structure that I
thought would be possible to implement using type-threaded lists
provided by Gabor Greif's thrist package:

http://hackage.haskell.org/package/thrist

...and the fclabels package by Sebastiaan Visser, Erik Hesselink,
Chris Eidhof and Sjoerd Visscher:

http://hackage.haskell.org/package/fclabels

It would (ideally) work as follows:

- the zipper would consist simply of a tuple:
   (type threaded list of constructor sections , current "context")
- in the type threaded list we store functions (constructor with hole
-> complete constructor), so the
"one hole context" is represented as a lambda expression where the
free variable will be filled
by the current "context" (the snd of the tuple)
- we "go down" through our structure by passing to our `moveTo`
function a first-class label
corresponding to the constructor we want to descend into. `moveTo`
uses this both as a "getter"
to extract the next level down from the current level, and as a
"setter" to form the lambda expression
which acts as the "constructor with a piece missing"
- "going up" means popping the head off the thrist and applying it to
the current context, making that
the new context, exiting the zipper would be a fold in the same manner


After throwing together a quick attempt I realized that I'm not sure
if it would be possible to make the `moveUp` function type-check and
be usable. I'm still new to GADTs, existential types, template haskell
etc. and am stuck.

Here is the code I wrote up, which doesn't currently compile:


--  START CODE ---

{-# LANGUAGE TypeOperators, GADTs #-}
module ZipperGenerator
(
  viewC   --lets user pattern match against context
, moveTo
, moveUp
, genZippers
, zipper
, unzipper
, (:->)
, ZipperGenerator
, Zipper
) where

-- these provide the secret sauce
import Data.Record.Label
import Data.Thrist
import Language.Haskell.TH


type ZipperGenerator = [Name] -> Q [Dec]

-- the Template Haskell function that does the work of generating
-- first-class labels used to move about the zipper:
genZippers :: ZipperGenerator
genZippers = mkLabels

-- hide the innards:
newtype Zipper t c = Z (Thrist (->) c t, c)

-- returns the current "context" (our location in the zipper) for pattern
-- matching and inspection:
viewC :: Zipper t c -> c
viewC (Z(_,c)) = c

-- takes a first-class label corresponding to the record in the current context
-- that we would like to move to:
moveTo :: (c :-> c') -> Zipper t c -> Zipper t c'
moveTo lb (Z(thr,c)) = Z (Cons (\a-> set lb a c) thr , get lb c)


-- backs up a level in the zipper, returning `Nothing` if we are already at the
-- top level:
moveUp :: Zipper t c -> Maybe (Zipper t b)
moveUp (Z (Nil,_)) = Nothing
moveUp (Z (Cons f thr,c)) = Just $ Z (thr, f c)

-- create zipper with focus on topmost constructor level:
zipper :: t -> Zipper t t
zipper t = Z (Nil,t)

-- close zipper
unzipper :: Zipper t c -> t
unzipper (Z(thr,c)) = undefined --foldThrist ($) id thr c

--  END CODE ---


Thanks,
Brandon Simmons
http://coder.bsimmons.name/blog/
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Haskell Forum

2010-07-26 Thread aditya siram
We have a Google group. Doesn't that qualify?
-deech

On Mon, Jul 26, 2010 at 9:59 PM, Kurt Häusler wrote:

> Hi,
> I think it might be valuable to have a web forum. Not as a different
> interface to the same community, but as a different community.
> Perhaps the sort of people that prefer mailing lists and the sort of people
> that prefer web forums are different after all, and a community that grows
> up around a forum could serve different needs and exhibit different
> characteristics to that of the mailing list.
>
> It would not be fragmentation, it would be growth, and I imagine there
> would be a degree of overlap.
>
> For me the choice of mailing list or web forum depends on the topic, and
> how I want to use it, I think for me, when it comes to feeling part of a
> Haskell community a web forum may suit better than the mailing list, so I
> would like to try it.
>
> For me mailing lists are great for focussed technical questions and
> discussions, but less useful for building a community. A web forum tends to
> be less sterile and allows more personality to show through and I guess it
> allows a bit more of the culture surrounding the core tech to flourish, as
> members begin to form images of each other. Definitely not for many of you I
> am sure, but I think if the goal is to nourish a culture and encourage a
> true community rather than just technical Q&A, then a web forum would be an
> intriguing option.
>
> But a different interface to the same community doesn't make much sense.
> And let us try and find a Haskell based software solution for it, I thought
> phpBB was a joke in the OP.
>
>
>
> ___
> 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] Haskell Forum

2010-07-26 Thread Kurt Häusler
Hi,
I think it might be valuable to have a web forum. Not as a different interface 
to the same community, but as a different community.
Perhaps the sort of people that prefer mailing lists and the sort of people 
that prefer web forums are different after all, and a community that grows up 
around a forum could serve different needs and exhibit different 
characteristics to that of the mailing list.

It would not be fragmentation, it would be growth, and I imagine there would be 
a degree of overlap.

For me the choice of mailing list or web forum depends on the topic, and how I 
want to use it, I think for me, when it comes to feeling part of a Haskell 
community a web forum may suit better than the mailing list, so I would like to 
try it.

For me mailing lists are great for focussed technical questions and 
discussions, but less useful for building a community. A web forum tends to be 
less sterile and allows more personality to show through and I guess it allows 
a bit more of the culture surrounding the core tech to flourish, as members 
begin to form images of each other. Definitely not for many of you I am sure, 
but I think if the goal is to nourish a culture and encourage a true community 
rather than just technical Q&A, then a web forum would be an intriguing option.

But a different interface to the same community doesn't make much sense. And 
let us try and find a Haskell based software solution for it, I thought phpBB 
was a joke in the OP.



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


[Haskell-cafe] Announce snm-0.0.2: The Simple Nice-Looking Manual Generator

2010-07-26 Thread Johnny Morrice
Hi list,

Recently, I've been working on a compiler/programming language
project.[2]

I became rather unstuck when I started spending more time documenting
the semantics instead of actually getting to work on the implementation.

Hence this program!

snm allows you to write clean, web-friendly reports, user guides and
manuals without having to edit fickle html.

snm allows you to structure your document in a modular fashion.

snm document sections are written in yaml and are easy to write and
understand.

snm is a generator of small, valid xhtml files.

Read the snm user guide here:
http://www.killersmurf.com/static/snm_help.html

snm uses Yaml and generates XHTML, so it's a little like John
MacFarlane's yst[1], but yst is for making websites, while snm is
exclusively for creating structured reports.

It still has a lot of problems, not to mention no support for images, or
multiple pages, but I'm finding it usable (enough to document itself!)
so I thought it best to share :)

Sorry if I have left typos, it's very late

Have fun,
   Johnny


[1] John MacFarlane's yst: http://hackage.haskell.org/package/yst
[2] Yon aforementioned programming language project, in case anyone
fancies a peep.  Demoted to reference #2, on account of it not yet
compiling code :) http://github.com/elginer/Obelisk

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


Re: [Haskell-cafe] hGetContents: resource exhausted

2010-07-26 Thread Brandon S Allbery KF8NH
-BEGIN PGP SIGNED MESSAGE-
Hash: SHA1

On 7/26/10 21:01 , Donn Cave wrote:
> Much easier (but not guaranteed to help) you might be able to
> see the actual error, at the system call level, if you can trace
> system calls.  The utility for this varies by platform, but
> e.g. "strace" or "ktrace".

On Solaris it's truss.

- -- 
brandon s. allbery [linux,solaris,freebsd,perl]  allb...@kf8nh.com
system administrator  [openafs,heimdal,too many hats]  allb...@ece.cmu.edu
electrical and computer engineering, carnegie mellon university  KF8NH
-BEGIN PGP SIGNATURE-
Version: GnuPG v2.0.10 (Darwin)
Comment: Using GnuPG with Mozilla - http://enigmail.mozdev.org/

iEYEARECAAYFAkxOQw4ACgkQIn7hlCsL25WYwQCgxNsPquHR3fyqZxTAGJTeYlfQ
+wEAn38Z6Phapm4vMgmgp1/0Y/GDqu2Y
=KanW
-END PGP SIGNATURE-
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Is 'flip' really necessary?

2010-07-26 Thread Bill Atkins
Seconded.

On Monday Jul 26, 2010, at 6:24 PM, Edward Z. Yang wrote:

> IMO, if you really want a wildcard, just write a lambda...
> 
>\x -> foo 1 x 3
> 
> Cheers,
> Edward
> ___
> 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] Is 'flip' really necessary?

2010-07-26 Thread Brandon S Allbery KF8NH
-BEGIN PGP SIGNED MESSAGE-
Hash: SHA1

On 7/26/10 17:53 , aditya siram wrote:
> It seems confusing to alias a function without adding any functionality just
> to make things slightly easier to read. Instead wouldn't it be better if
> this idiom were documented on haskell.org ?

And yet much of Applicative is exactly that.  (It even started out being
called "idioms".)

- -- 
brandon s. allbery [linux,solaris,freebsd,perl]  allb...@kf8nh.com
system administrator  [openafs,heimdal,too many hats]  allb...@ece.cmu.edu
electrical and computer engineering, carnegie mellon university  KF8NH
-BEGIN PGP SIGNATURE-
Version: GnuPG v2.0.10 (Darwin)
Comment: Using GnuPG with Mozilla - http://enigmail.mozdev.org/

iEYEARECAAYFAkxONH0ACgkQIn7hlCsL25XLsgCcDLhDWBfkHcAGgc7145NuY08/
N4IAmgPHachdFS28mOGHeYD7yy1A3px2
=NLVp
-END PGP SIGNATURE-
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] hGetContents: resource exhausted

2010-07-26 Thread Donn Cave
Quoth Lally Singh ,
...
> I've got my own source build of ghc.  Is there anything I can put in
> to track down what's going on?

Much easier (but not guaranteed to help) you might be able to
see the actual error, at the system call level, if you can trace
system calls.  The utility for this varies by platform, but
e.g. "strace" or "ktrace".

Donn Cave, d...@avvanta.com

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


Re: [Haskell-cafe] hGetContents: resource exhausted

2010-07-26 Thread Lally Singh
On Mon, Jul 26, 2010 at 7:59 AM, Ben Millwood  wrote:
> On Mon, Jul 26, 2010 at 10:47 AM, Magnus Therning  wrote:
>> On Sun, Jul 25, 2010 at 23:47, Lally Singh  wrote:
>>> Hey all,
>>>
>>>  This is on OpenSolaris.  Simple attempts to build cabal packages
>>> give me this error, and I don't know what it means.  Here's an
>>> example:
>>> [07/25 18:51::la...@sol type-level]$ runghc Setup.hs configure
>>> Configuring type-level-0.2.4...
>>> Setup.hs: fd:8: hGetContents: resource exhausted (Resource temporarily
>>> unavailable)
>>> Setup.hs: fd:8: resource exhausted
>>>
>>> Does anyone know what this means?  I'm trying to just get the llvm
>>> bindings installed (requiring mtl & type-level).
>>
>> A quick guess: you're running out of filedescriptors.
>>
>
> The error gives the descriptor number as 8, so I don't think that's
> terribly likely :)
> Resource temporarily unavailable is the string that corresponds to the
> EAGAIN error, which is typically presented by operations that would
> block being used in non-blocking mode. I have no idea what would cause
> it to be a fatal error in a hGetContents call.

I checked that my ulimit was > 8 :-)  It was 256, I knocked it up to
65,535, but that didn't help.

I've got my own source build of ghc.  Is there anything I can put in
to track down what's going on?

Thanks for all the help folks,

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


Re: [Haskell-cafe] Instances for Set of Functor, Traversable?

2010-07-26 Thread Lennart Augustsson
Try to make Set an instance of Functor and you'll see why it isn't.
It's very annoying.

On Mon, Jul 26, 2010 at 11:55 PM, Gregory Crosswhite
 wrote:
> Is there a specific reason why Set doesn't have instances for Functor
> and Traversable?  Or have they just not been written yet?  :-)
>
> Cheers,
> Greg
>
> ___
> 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] Haskell Forum

2010-07-26 Thread Richard O'Keefe

On Jul 27, 2010, at 8:12 AM, Nick Bowler wrote:

> On 20:56 Mon 26 Jul , Andrew Coppin wrote:
>> My personal preference would be for NNTP. It seems to handle threading 
>> much better. You can easily "kill" threads you're not interested in, and 
>> thereafter not bother downloading them. You can use several different 
>> client programs. And so on. However, last time I voiced this opinion, 
>> people started talking about something called "usenet", which I've never 
>> heard of...
> 
> Conveniently, all of the haskell mailing lists have an NNTP interface
> available.  Add news.gmane.org as a server in your newsreader and
> subscribe to gmane.comp.lang.haskell.cafe.

I often find messages in this mailing list with such detailed and
valuable information that I want to print them, take them away,
and study them for a couple of days.  From Mail, nothing could be
simpler.  Visiting gmane with Google Chromium, all I can ever print
is the first screen or so of a pane.

I am *sick* of web browsers that cannot or will not print the whole
of a frame.  You'd think Google Chromium would do better, but no.
It does try to help by *printing* scroll bars, though...

Mailing list => simple yes trouble no.
Browser based => simple no trouble yes.

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


Re: [Haskell-cafe] data type declaration

2010-07-26 Thread Richard O'Keefe

On Jul 27, 2010, at 3:02 AM, Brandon S Allbery KF8NH wrote:
> As I understand it:
> 1) carrying [contexts] around complicates Haskell98 (and now Haskell2010)
> compatibility (also see below);

Like the availability of so many other features,
this one could be controlled by a language pragma.

> 2) GADTs do what you want, since they don't have backward compatibility 
> baggage.

They are also more complex than is needed for the problem at hand.
> 
> As to the current proposal, I think nobody's certain what would happen to
> older programs if data were changed to carry contexts around --- someone
> might be relying on the current behavior, and changing it might produce
> runtime oddness instead of a compile-time error --- whereas making contexts
> illegal will produce an easily-fixed error message in all relevant cases.

Does anyone know why `data' contexts were broken in the first place?

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


Re: [Haskell-cafe] Is 'flip' really necessary?

2010-07-26 Thread Nils Schweinsberg

On 26.07.2010 23:55, Ozgur Akgun wrote:

I think it is pretty cool as well. But I think there is a problem with
viewing it as a wildcard.

let's say we define the following:

(??) = flip

foo :: a -> b -> c
foo ?? x :: a -> c

Perfect!

But saying ?? can be used as a wildcard might in the following wrong
perception:

foo x ?? :: b -> c -- WRONG


This looks interesting. I played around with this for a bit:


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

class Wildcard f v r | f -> v r where
(??) :: f -> v -> r

instance Wildcard (a -> b -> c) b (a -> c) where
(??) = flip

instance Wildcard (b -> c) b c where
(??) = id

f :: String -> Int -> String
f s i = s ++ show i

a :: String -> String
a = (f ?? 5)

b :: Int -> String
b = (f "Int: " ??)



Sadly, this won't typecheck:


pattern.hs:19:0:
Couldn't match expected type `Int' against inferred type `[Char]'
  Expected type: Int
  Inferred type: String
When using functional dependencies to combine
  Wildcard (b -> c) b c,
arising from the dependency `f -> a r'
in the instance declaration at pattern.hs:12:9
  Wildcard (String -> Int -> String) Int (String -> String),
arising from a use of `??' at pattern.hs:19:5-10
When generalising the type(s) for `a'


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


[Haskell-cafe] Re: ANN: weighted-regexp-0.1.0.0

2010-07-26 Thread Sjoerd Visscher
Hi Sebastian,

I enjoyed this paper very much. Writing papers in the style of a play seems to 
work very well! (although I think you should spice it up more if your want to 
get it on Broadway)

It seems that only shift needs the reg field of the RegW datatype. So you can 
also replace the reg field with a shift field. This makes the regexp parser 
extensible, as there is no longer a dependence on the (closed) datatype Reg:

> data RegW w c = RegW { active :: !Bool,
>empty :: !w,
>final_ :: !w,
>shift :: w -> c -> RegW w c }

For example it is then easy to define the parser that matches nothing, which is 
the identity element of alt:

> noMatch :: RegExp c
> noMatch = RegExp noMatchW
> 
> noMatchW :: Semiring w => RegW w c
> noMatchW = RegW False zero zero $ \_ _ -> noMatchW

But otherwise I do wonder if the parser needs to be extensible. For example 
some XML Schema implementations that are based on finite automata have special 
cases for the xs:all construct, which matches a list of elements, each 
occurring once in any order. But I tried a straightforward implementation and 
it works fine:

> eachOnce :: [RegExp c] -> RegExp c
> eachOnce [] = eps
> eachOnce ps = eachOnce' ps [] where
>   eachOnce' [] _ = noMatch
>   eachOnce' (p:ps) qs = (p `seq_` eachOnce (ps ++ qs)) `alt` eachOnce' ps 
> (p:qs)

*Main> accept (eachOnce (map char ['a'..'z'])) $ reverse ['a'..'z']
True
(0.05 secs, 8706356 bytes)

greetings,
Sjoerd




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


Re: [Haskell-cafe] 1st attempt at concurrency

2010-07-26 Thread Günther Schmidt

Dear Felipe,

thank you for the code and for the correction :).

As usual I come across interesting stuff when I have no immediate need 
for it and when I do I can't find it anymore.


I am looking for something slightly more abstracted and iirc there 
recently was a post about the pi-calculus which seemed elegant even 
though the author told me himself it was not meant for any RW use.


But I believe the Galois boys have created a lib, called orc?, for this 
purpose. I think I'll check into that and see how it goes.


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


Re: [Haskell-cafe] 1st attempt at parallelizing

2010-07-26 Thread Felipe Lessa
2010/7/26 Felipe Lessa :
> downloader :: TChan (Maybe Page) -> TChan (Page, Info) -> IO ()
> downloader in out = do
>  mp <- atomically (readTChan in)
>  case mp of
>    Nothing -> return ()
>    Just p -> download p >>= atomically . writeTChan out

Oops!  Of course there should be recursion here!  (This is a bug the
typechecker probably wouldn't catch.)

downloader :: TChan (Maybe Page) -> TChan (Page, Info) -> IO ()
downloader in out = do
 mp <- atomically (readTChan in)
 case mp of
   Nothing -> return ()
   Just p -> download p >>= atomically . writeTChan out >> downloader in out

Cheers,

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


Re: [Haskell-cafe] Typeclasses question in "Real World Haskell" book

2010-07-26 Thread Richard O'Keefe

On Jul 27, 2010, at 1:16 AM, Angel de Vicente wrote:
> data JValue = JString String
> | JNumber Double
> | JBool Bool
> | JNull
> | JObject [(String, JValue)]
> | JArray [JValue]
> deriving (Eq, Ord, Show)
> 
> type JSONError = String
> 
> class JSON a where
>toJValue :: a -> JValue
>fromJValue :: JValue -> Either JSONError a

The type class JSON is the class of types (a)
that have been provided with functions functions to
convert between (a) and JValue.

toJValueconverts an (a) to a JValue.
fromJValue  tries to convert a JValue to
an (a), returning Right x if
it succeeds, or Left ".." if
it fails, for some error message.

So the JSON type class is useful when every value of
type (a) can be faithfully represented by some JValue,
but not every JValue represents an (a).

For example, we might say
instance (JSON a, JSON b) => JSON (a,b)
  where

toJValue (x,y) = JArray [toJValue x, toJValue y]

fromJValue (JArray [u,v]) =
case (fromJValue u, fromJValue v) of
  (Right x, Right y) -> Right (x,y)
  (Right _, Left er) -> Left er
  (Left er, _)   -> Left er
fromJValue _ = Left "not a 2-element array"

> instance JSON JValue where
>toJValue = id
>fromJValue = Right

A JValue can be converted to a JValue by doing nothing.
A JValue can be converted back to a JValue again by doing
nothing, BUT we must say that the conversion succeeded by
wrapping the result in Right.
> 
> instance JSON Bool where
>toJValue = JBool
>fromJValue (JBool b) = Right b
>fromJValue _ = Left "not a JSON boolean"

A Bool can be converted to a JValue by wrapping it in JBool.
A JBool can be converted back to a Bool by unwrapping it
and then wrapping the result in Right.
But any JValue other than a JBool cannot be converted to a
Bool.  (Actually, this is was a choice; other choices could
have been made.)  Since we can't do it, we have to say _that_
we didn't (Left) and _why_ ("not a JSON boolean").

> I don't understand how the JSON typeclass is defined, in particular the
> fromJValue definition.

There's a simple pattern for "communication" types like XML or
JSON or UBF or for that matter byte strings.  Roughly speaking

class Communicable t
  where
to_exchange_format   :: t -> Maybe Exchange
from_exchange_format :: Exchange -> Maybe t

Variations on this are
 - where one direction of conversion must never fail,
   so the "Maybe" disappears
 - where the designer chose to require reasons for failure,
   so that Maybe is replaced by Either String.

> For instance, when defining the instance for Bool types, then I
> understand that both functions (toJValue and fromJValue) will be called
> upon when we supply a Bool type, but then the (JBool b) type in function 
> fromJValue doesn't match

Ah.  What you may be missing here is that Haskell resolves the
types of functions taking into account ALL information about
them,
>>> INCLUDING THE RESULT <<<

So if we do
let boo = True
jay = toJValue boo
lea = fromJValue jay
...
then the call of toJValue is resolved thanks to the type of its
*argument* and the call to fromJValue is not resolved.  But if
we do
let boo = True
jay = toJValue boo
lea :: Bool
lea = fromJValue jay
then the call of fromJValue is resolved thanks to the (now!) known
type of its *result*.

> toJValue is no problem, but I cannot understand how fromJValue is
> supposed to work, and the comments in the online book
> (http://book.realworldhaskell.org/read/using-typeclasses.html) don't
> help with this either.
> 
> *Main> :load ch6
> [1 of 1] Compiling Main ( ch6.hs, interpreted )
> Ok, modules loaded: Main.
> *Main> toJValue False
> JBool False
> *Main> :type it
> it :: JValue
> *Main> fromJValue False
> 
> :1:11:
>Couldn't match expected type `JValue' against inferred type `Bool'
>In the first argument of `fromJValue', namely `False'

This is hardly surprising, because you have an explicit declaration
that says

fromJValue :: JValue -> Either JSONError a

so the argument of fromJValue may only be a JValue, and False is
not a JValue.

> *Main> fromJValue (JBool False)
> 
> :1:0:
>Ambiguous type variable `a' in the constraint:
>  `JSON a' arising from a use of `fromJValue' at :1:0-23
>Probable fix: add a type signature that fixes these type variable(s)
> *Main>
> 
> 
> 
> Any pointers?

Yes.  That last error message you quoted told you exactly what to
do.  It said, in effect, that the only thing wrong with
fromJValue (JBool False)
is that it doesn't know what the result type (a) should be,
except that it must involve *some* instance of JSON,
and it recommen

Re: [Haskell-cafe] 1st attempt at parallelizing

2010-07-26 Thread Felipe Lessa
2010/7/26 Günther Schmidt :
> Hi all,

Hello!

> I'm spidering web pages, the implementation currently is synchronous. I'd
> like to parallelize this for speed-up, ie. get up to 6 pages in parallel and
> recycle those threads.

This is usually called concurrent programming, not parallel.

> Now I have come across good examples for this on the web before, but I doubt
> I'd find it again right away.
>
> I'd appreciate some good pointers.

There's a simple way of doing this with Chans, for example:

import Control.Applicative
import Control.Concurrent.STM
import Control.Monad
import qualified Data.Map as M

data Page = ...
data Info = ...

download :: Page -> IO Info
download = ...

getOneByOne :: [Page] -> IO (M.Map Page Info)
getOneByOne = M.fromList <$> mapM (\p -> (,) p <$> download p)

downloader :: TChan (Maybe Page) -> TChan (Page, Info) -> IO ()
downloader in out = do
  mp <- atomically (readTChan in)
  case mp of
Nothing -> return ()
Just p -> download p >>= atomically . writeTChan out

getConcurrent :: Int -> [Page] -> IO [M.Map Page Info]
getConcurrent n xs = do
  in <- newTChanIO
  out <- newTChanIO
  replicateM_ n (forkIO $ downloader in out) -- create n threads
  mapM (writeTChan in . Just) xs
  replicateM_ n (writeTChan in Nothing) -- kill n threads
  M.fromList <$> mapM (\_ -> readTChan out) xs


This code doesn't take exceptions into account, which you should, but
this works.  Well, I guess, didn't try, if it compiles then it should
;).

HTH,

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


Re: [Haskell-cafe] Is 'flip' really necessary?

2010-07-26 Thread Edward Z. Yang
IMO, if you really want a wildcard, just write a lambda...

\x -> foo 1 x 3

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


Re: [Haskell-cafe] Instances for Set of Functor, Traversable?

2010-07-26 Thread Henning Thielemann


On Mon, 26 Jul 2010, Gregory Crosswhite wrote:


Is there a specific reason why Set doesn't have instances for Functor
and Traversable?


Sure, fmap needs an Ord restriction for the element type, which is not 
possible for the plain Functor constructor class. E.g. in

   fmap (const 'a') set
 all result elements will coincide. If you need such an fmap, try
  http://hackage.haskell.org/package/rmonad .
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] 1st attempt at parallelizing

2010-07-26 Thread Günther Schmidt

Hi all,

I'm spidering web pages, the implementation currently is synchronous. 
I'd like to parallelize this for speed-up, ie. get up to 6 pages in 
parallel and recycle those threads.


Now I have come across good examples for this on the web before, but I 
doubt I'd find it again right away.


I'd appreciate some good pointers.

Günther

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


[Haskell-cafe] Instances for Set of Functor, Traversable?

2010-07-26 Thread Gregory Crosswhite
Is there a specific reason why Set doesn't have instances for Functor
and Traversable?  Or have they just not been written yet?  :-)

Cheers,
Greg

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


Re: [Haskell-cafe] Is 'flip' really necessary?

2010-07-26 Thread Ozgur Akgun
I think it is pretty cool as well. But I think there is a problem with
viewing it as a wildcard.

let's say we define the following:

(??) = flip

foo :: a -> b -> c
foo ?? x :: a -> c

Perfect!

But saying ?? can be used as a wildcard might in the following wrong
perception:

foo x ?? :: b -> c -- WRONG

Just a small concern. Other than that, very neat!

On 26 July 2010 21:42, Nils  wrote:

> On 26.07.2010 08:33, David Virebayre wrote:
>
>> listeEtagTot = concatMap (`listeEtagArm` cfgTypesTringle) listeArmOrd
>>
>
> You can use flip as a "wildcard" aswell:
>
> > listeEtagTot = concatMap (listeEtagArm `flip` cfgTypesTringle)
> listeArmOrd
>
> Makes it even more readable in my opinion, since this really "shows" you
> where the value belongs to.
>
> ___
> Haskell-Cafe mailing list
> Haskell-Cafe@haskell.org
> http://www.haskell.org/mailman/listinfo/haskell-cafe
>



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


Re: [Haskell-cafe] Is 'flip' really necessary?

2010-07-26 Thread aditya siram
It seems confusing to alias a function without adding any functionality just
to make things slightly easier to read. Instead wouldn't it be better if
this idiom were documented on haskell.org?

-deech

On Mon, Jul 26, 2010 at 4:47 PM, Vo Minh Thu  wrote:

> 2010/7/26 Vo Minh Thu :
> > 2010/7/26 Daniel Fischer :
> >> On Monday 26 July 2010 23:25:27, Max Rabkin wrote:
> >>>
> >>> It took me a fair while (I'm talking on the order of half a minute) to
> >>> figure out what that meant, but it's pretty cool.
> >>
> >> Yeah, really neat.
> >>
> >>> Maybe a different
> >>> name would be better? How about (??) or "it"?
> >>>
> >>> > listeEtagTot = concatMap (listeEtagArm ?? cfgTypesTringle)
> listeArmOrd
> >>> > listeEtagTot = concatMap (listeEtagArm `it` cfgTypesTringle)
> >>> > listeArmOrd
> >>
> >> I think (??) is far better.
> >> Additionally, it doesn't run into problems with ghci's magical `it'.
> >
> > (__) is quite good :)
>
> Well, I meant `__`
>
> Cheers,
> Thu
> ___
> 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] new Cabal user question -- installing to Haskell Platform on Windows network drive?

2010-07-26 Thread Rogan Creswick
On Mon, Jul 26, 2010 at 2:06 PM, Peter Schmitz  wrote:
> I have recently installed the Haskell Platform (for the first time) to a MS
> Windows network drive; e.g.:
>
> H:\aaa\bbb\Haskell Platform\2010.1.0.0\
>
> I did so without admin privs.
>
> It has ghc-6.12.1
>
> I need to not install to C:.
>
> I would like to install and use Gtk2Hs and Glade on the Platform also.

There are instructions in the INSTALL doc here:

 * http://code.haskell.org/gtk2hs/INSTALL

Generally, you don't need to (explicitly) download anything when using
cabal-install, cabal install does that for you.  However, when
libraries implemented in other languages are used, such as with
gtk2hs, you will need to manually install something.  That's where the
windows "gtk+ libraries" come in.  You can download them from here:

http://www.gtk.org/download-windows.html

That url is mentioned in the INSTALL document linked to above, and the
document also describes what you need to download and install.  I
don't know if it is possible to do that without admin access though
(I've never tried).

Once you have the gtk+ libraries installed it should just be a matter
of running 'cabal update' (to get the latest updates from hackage) and
then running a handfull of 'cabal install ' commands.

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


Re: [Haskell-cafe] Is 'flip' really necessary?

2010-07-26 Thread Vo Minh Thu
2010/7/26 Vo Minh Thu :
> 2010/7/26 Daniel Fischer :
>> On Monday 26 July 2010 23:25:27, Max Rabkin wrote:
>>>
>>> It took me a fair while (I'm talking on the order of half a minute) to
>>> figure out what that meant, but it's pretty cool.
>>
>> Yeah, really neat.
>>
>>> Maybe a different
>>> name would be better? How about (??) or "it"?
>>>
>>> > listeEtagTot = concatMap (listeEtagArm ?? cfgTypesTringle) listeArmOrd
>>> > listeEtagTot = concatMap (listeEtagArm `it` cfgTypesTringle)
>>> > listeArmOrd
>>
>> I think (??) is far better.
>> Additionally, it doesn't run into problems with ghci's magical `it'.
>
> (__) is quite good :)

Well, I meant `__`

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


Re: [Haskell-cafe] Is 'flip' really necessary?

2010-07-26 Thread Vo Minh Thu
2010/7/26 Daniel Fischer :
> On Monday 26 July 2010 23:25:27, Max Rabkin wrote:
>>
>> It took me a fair while (I'm talking on the order of half a minute) to
>> figure out what that meant, but it's pretty cool.
>
> Yeah, really neat.
>
>> Maybe a different
>> name would be better? How about (??) or "it"?
>>
>> > listeEtagTot = concatMap (listeEtagArm ?? cfgTypesTringle) listeArmOrd
>> > listeEtagTot = concatMap (listeEtagArm `it` cfgTypesTringle)
>> > listeArmOrd
>
> I think (??) is far better.
> Additionally, it doesn't run into problems with ghci's magical `it'.

(__) is quite good :)
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Is 'flip' really necessary?

2010-07-26 Thread Daniel Fischer
On Monday 26 July 2010 23:25:27, Max Rabkin wrote:
>
> It took me a fair while (I'm talking on the order of half a minute) to
> figure out what that meant, but it's pretty cool.

Yeah, really neat.

> Maybe a different
> name would be better? How about (??) or "it"?
>
> > listeEtagTot = concatMap (listeEtagArm ?? cfgTypesTringle) listeArmOrd
> > listeEtagTot = concatMap (listeEtagArm `it` cfgTypesTringle)
> > listeArmOrd

I think (??) is far better.
Additionally, it doesn't run into problems with ghci's magical `it'.

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


Re: [Haskell-cafe] Typeclasses question in "Real World Haskell" book

2010-07-26 Thread Angel de Vicente

Hi,


And now that we are at it... In the next page, 152 there is the
following instance definition, but no explanation is (I think) given of
what it means:

instance (JSON a) =>  JSON [a] where

until then all instance definitions where of the type

instance JSON Int where ...

How should I read that definition?


As a first approximation, read it as

"for all types a which are instances of JSON, the type [a] is also an
instance of JSON, with the following methods ..."

However, instance resolution in GHC is done without taking the context
(JSON a) into account, so for GHC it reads more like

"I will view all list types as instances of the JSON class, but if you try
to use the class instance for a list type where the element type is not an
instance of JSON, the programme will not compile. Nor will it compile if
you try to define another instance of JSON for any list type [e.g. String]
- at least, if you don't turn on some language extension(s)."

That is the cause of many puzzlements and problems.



thanks for this, and for the detailed explanation on my previous 
question. I keep a frosty Canarian beer for you in the fridge for 
whenever we meet... :-)


I think that I can now move on with the rest of the book. Cheers,
Ángel de Vicente
--
http://www.iac.es/galeria/angelv/

High Performance Computing Support PostDoc
Instituto de Astrofísica de Canarias
-
ADVERTENCIA: Sobre la privacidad y cumplimiento de la Ley de Protección de 
Datos, acceda a http://www.iac.es/disclaimer.php
WARNING: For more information on privacy and fulfilment of the Law concerning 
the Protection of Data, consult http://www.iac.es/disclaimer.php?lang=en

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


Re: [Haskell-cafe] Is 'flip' really necessary?

2010-07-26 Thread Max Rabkin
On Mon, Jul 26, 2010 at 10:42 PM, Nils  wrote:
> On 26.07.2010 08:33, David Virebayre wrote:
>>
>> listeEtagTot = concatMap (`listeEtagArm` cfgTypesTringle) listeArmOrd
>
> You can use flip as a "wildcard" aswell:
>
>> listeEtagTot = concatMap (listeEtagArm `flip` cfgTypesTringle) listeArmOrd
>
> Makes it even more readable in my opinion, since this really "shows" you
> where the value belongs to.

It took me a fair while (I'm talking on the order of half a minute) to
figure out what that meant, but it's pretty cool. Maybe a different
name would be better? How about (??) or "it"?

> listeEtagTot = concatMap (listeEtagArm ?? cfgTypesTringle) listeArmOrd
> listeEtagTot = concatMap (listeEtagArm `it` cfgTypesTringle) listeArmOrd

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


Re: [Haskell-cafe] Haskell Forum

2010-07-26 Thread Magnus Therning
On 26/07/10 22:01, Andrew Coppin wrote:
> Brandon S Allbery KF8NH wrote:
>> On 7/26/10 15:56 , Andrew Coppin wrote:
>>  
>>> My personal preference would be for NNTP. It seems to handle
>>> threading much
>>> better. You can easily "kill" threads you're not interested in, and
>>> thereafter not bother downloading them. You can use several different
>>> client
>>> programs. And so on. However, last time I voiced this opinion, people
>>> started talking about something called "usenet", which I've never
>>> heard of...
>>> 
>>
>> Usenet *is* NNTP.
>>   
> 
> So I'm told. But it appears that some people believe that NNTP *is*
> Usenet, which is not the case. I use NNTP almost every single day, but
> I've never seen Usenet in my life...

So you've only ever been on private NNTP servers then, never browsed through
comp.* or sci.*?

Wikipedia has a nice article on usenet, of course:
http://en.wikipedia.org/wiki/Usenet

/M



signature.asc
Description: OpenPGP digital signature
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] new Cabal user question -- installing to Haskell Platform on Windows network drive?

2010-07-26 Thread Peter Schmitz
I have recently installed the Haskell Platform (for the first time) to a MS
Windows network drive; e.g.:

H:\aaa\bbb\Haskell Platform\2010.1.0.0\

I did so without admin privs.

It has ghc-6.12.1

I need to not install to C:.

I would like to install and use Gtk2Hs and Glade on the Platform also.

I have used Gtk2Hs and Glade in Haskell (with just ghc, not the Platform),
but I have never used Cabal or the Haskell Platform.

I see at http://www.haskell.org/gtk2hs/ that Gtk2Hs now comes in a Cabal
package ("Gtk2Hs 0.11.0 released").

The info there says you can just install "the Gtk+ libraries", and then do:
cabal install gtk2hs-buildtools
cabal install gtk

I interpret "the Gtk+ libraries" to mean "gtk: the base GUI library" package
listed at
http://www.haskell.org/gtk2hs/download/
(is that correct?).

That is a link to http://hackage.haskell.org/package/gtk
which has "gtk-0.11.0.tar.gz (Cabal source package)",
which I downloaded and unpacked to a temp directory which now contains
"gtk-0.11.0".

I've reviewed the Cabal documentation (that came with the Platform) and I'm
having a little trouble determining exactly what to do next -- the exact
commands to use for my non-C: / network drive installation. (I have not used
Cabal before.)

I would prefer to do this without admin privs, if possible.

** If anyone could help me out here with a step-by-step, I would appreciate
it.

Hopefully the procedure for glade will then be similar.

Thanks (very much) in advance.
-- Peter Schmitz
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Please report any bug of gtk2hs-0.11.0!

2010-07-26 Thread Sebastian Fischer

On Jul 26, 2010, at 6:59 PM, Andy Stewart wrote:


cabal install gtk

fails with the message

   Configuring gtk-0.11.0...
   setup: ./Graphics/UI/Gtk/General/IconTheme.chs: invalid argument
   cabal: Error: some packages failed to install:
   gtk-0.11.0 failed during the building phase. The exception was:
   ExitFailure 1


You can fix this problem with two solutions:

1) Change your locate to UTF-8.


This worked, thanks!

Sebastian

--
Underestimating the novelty of the future is a time-honored tradition.
(D.G.)



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


Re: [Haskell-cafe] Re: Haskell Forum

2010-07-26 Thread Nick Bowler
On 13:58 Mon 26 Jul , John Meacham wrote:
> There already is an NNTP <-> mailing list gateway via gmane that gives a
> nice forumy and threaded web interface for those with insufficient email
> readers. Adding a completely different interface seems unnecessary and
> fragmentary.
> 
> http://news.gmane.org/gmane.comp.lang.haskell.cafe

Ah, I didn't realise the gmane web interface supported followups (I knew
the NNTP interface did, and mentioned this elsewhere in this thread).
Looks like we've already got a web forum, then, so I guess there's
nothing to do! :)

-- 
Nick Bowler, Elliptic Technologies (http://www.elliptictech.com/)
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Re: Haskell Forum

2010-07-26 Thread Daniel Fischer
On Monday 26 July 2010 22:10:46, Evan Laforge wrote:
>  Apart from threading and attachments, are there other
> reasons you prefer a forum?

I'm a mailing list guy too, but one possible advantage of a forum is that 
it might be easier to search by topic.
Have a problem with type families?
Go to the language extensions subforum, then the type families sub-
subforum, there you are.
If you search a mailing list archive, it's not so easy and you'll likely 
miss the threads where "type families" is not in the topic because it's 
called "Need Help! Why won't this compile?".

Of course, in reality fora are not so well-structured either :)
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Haskell Forum

2010-07-26 Thread Andrew Coppin

Brandon S Allbery KF8NH wrote:

On 7/26/10 15:56 , Andrew Coppin wrote:
  

My personal preference would be for NNTP. It seems to handle threading much
better. You can easily "kill" threads you're not interested in, and
thereafter not bother downloading them. You can use several different client
programs. And so on. However, last time I voiced this opinion, people
started talking about something called "usenet", which I've never heard of...



Usenet *is* NNTP.
  


So I'm told. But it appears that some people believe that NNTP *is* 
Usenet, which is not the case. I use NNTP almost every single day, but 
I've never seen Usenet in my life...


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


Re: [Haskell-cafe] Re: Haskell Forum

2010-07-26 Thread John Meacham
On Mon, Jul 26, 2010 at 04:37:45PM -0400, Nick Bowler wrote:
> On 13:28 Mon 26 Jul , Kevin Jardine wrote:
> > On Jul 26, 10:10 pm, Evan Laforge  wrote:
> > 
> > > Interesting, I've never figured out why some people prefer forums, but
> > > you're proof that they exist :)  
> > 
> > This debate is eerily similar to several others I've seen (for
> > example, on the interactive fiction mailing list).
> > 
> > In every case I've seen, a web forum vs. mailing list debate has been
> > pointless at best and sometimes turned into a flame war. I think that
> > it's best for people who prefer a web forum to establish one and use
> > it, and for those who prefer the mailing list approach to continue to
> > use that.
> 
> It seems to me, then, that a wine-like web forum <-> mailing list
> gateway would satisfy everyone without fragmenting the community?
> 
> See http://forum.winehq.org/viewforum.php?f=2.

There already is an NNTP <-> mailing list gateway via gmane that gives a
nice forumy and threaded web interface for those with insufficient email
readers. Adding a completely different interface seems unnecessary and
fragmentary.

http://news.gmane.org/gmane.comp.lang.haskell.cafe

John


-- 
John Meacham - ⑆repetae.net⑆john⑈ - http://notanumber.net/
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Actors and message-passing a la Erlang

2010-07-26 Thread Martin Sulzmann
Not distributed (yet) but concurrent:
http://hackage.haskell.org/package/actor

The paper " Actors with Multi-headed Message Receive Patterns. COORDINATION
2008:"
describes the design rationale.

Cheers,
  Martin

On Sun, Jul 25, 2010 at 10:55 PM, Yves Parès  wrote:

> Hello !
>
> I've been studying Erlang and Scala, and I was wondering if someone has
> already implemented an actors and message passing framework for concurrent
> and distributed programs in Haskell.
>
> ___
> 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] Is 'flip' really necessary?

2010-07-26 Thread aditya siram
That's just cool. I now reverse my original statement - 'flip' does have
it's place in the pantheon of standard Haskell functions.

-deech

On Mon, Jul 26, 2010 at 3:42 PM, Nils  wrote:

> On 26.07.2010 08:33, David Virebayre wrote:
>
>> listeEtagTot = concatMap (`listeEtagArm` cfgTypesTringle) listeArmOrd
>>
>
> You can use flip as a "wildcard" aswell:
>
> > listeEtagTot = concatMap (listeEtagArm `flip` cfgTypesTringle)
> listeArmOrd
>
> Makes it even more readable in my opinion, since this really "shows" you
> where the value belongs to.
>
> ___
> 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: Haskell Forum

2010-07-26 Thread Kevin Jardine
On Jul 26, 10:37 pm, Nick Bowler  wrote:

> It seems to me, then, that a wine-like web forum <-> mailing list
> gateway would satisfy everyone without fragmenting the community?

Definitely looks like an interesting option, although since Google
groups and any decent web forum support RSS feeds, I'm not sure that
having two different streams of content would fragment the community
(any more than the many Haskell-related mailing lists do right now).

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


[Haskell-cafe] Re: Haskell Forum

2010-07-26 Thread Kevin Jardine


On Jul 26, 10:37 pm, Nick Bowler  wrote:

> It seems to me, then, that a wine-like web forum <-> mailing list
> gateway would satisfy everyone without fragmenting the community?
>
> Seehttp://forum.winehq.org/viewforum.php?f=2.
>
> --
> Nick Bowler, Elliptic Technologies (http://www.elliptictech.com/)
> ___
> Haskell-Cafe mailing list
> haskell-c...@haskell.orghttp://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] Typeclasses question in "Real World Haskell" book

2010-07-26 Thread Daniel Fischer
On Monday 26 July 2010 21:03:10, Angel de Vicente wrote:
> Hi,
>
> thanks for the answer. This is my first attempt at Typeclasses, and I
> think there is something "deep" that I don't understand...
>
> On 26/07/10 15:03, Daniel Fischer wrote:
> >> class JSON a where
> >>   toJValue :: a ->  JValue
> >>   fromJValue :: JValue ->  Either JSONError a
> >>
> >> instance JSON JValue where
> >>   toJValue = id
> >>   fromJValue = Right
> >>
> >> instance JSON Bool where
> >>   toJValue = JBool
> >>   fromJValue (JBool b) = Right b
> >>   fromJValue _ = Left "not a JSON boolean"
> >>
> >>
> >> I don't understand how the JSON typeclass is defined, in particular
> >> the fromJValue definition.
> >
> > Given a JValue and a type
> > (like Bool, JValue, String, Maybe [(Integer, ())]), fromJValue returns
> > either
>
> a JValue and a type???
>

Apparently not the best way to express it.

The function fromJValue has the type

fromJValue :: JSON a => JValue -> Either JSONError a

Read that as "for any type a being an instance of the JSON class, 
fromJValue can convert¹ a JValue to the type Either JSONError a".

For different types a, fromJValue does different things if applied to the 
same JValue, more precisely, different fromJValue functions are called.
Which version of fromJValue is called depends on the type the type variable 
a is instantiated to at the call site. (So, in some sense, fromJValue also 
takes a type as an argument.)

Perhaps looking at things in a more homely setting helps.
Consider the Enum class and the function

toEnum :: Enum a => Int -> a

What happens if you enter `toEnum 5' at the prompt?
In hugs:

Hugs> toEnum 5
ERROR - Unresolved overloading
*** Type   : Enum a => a
*** Expression : toEnum 5

you get an error, hugs complains that it doesn't know which type to choose 
for the result. And how could it, there are many types to choose from. If 
you tell hugs which type to choose, be it by an explicit type signature or 
by some calling context, it works:

Hugs> toEnum 5 :: Char
'\ENQ'
Hugs> [toEnum 42, 'k']
"*k"
Hugs> :set +t
Hugs> [toEnum 12, 42]
[12,42] :: [Integer]  -- Why Integer? ²
Hugs> [toEnum 12, 42] :: [Rational]
[12 % 1,42 % 1] :: [Rational]

¹ Actually, it doesn't 'convert' the value, rather it constructs a new 
value based on the provided one, but saying 'convert' is less cumbersome.

² [toEnum 12, 42] can have type [a] for every type a that belongs to the 
two classes Enum and Num, illustrated by the example with an explicit 
signature. hugs must choose one or it would have to throw an unresolved 
overloading error as above.
The Haskell report (in section 4.3.4) specifies that under certain 
circumstances ambiguous types [like (Enum a, Num a) => a] are defaulted.
The defaulting rules say that in this case, the ambiguous type is defaulted 
to Integer - and that's why I've used hugs here, and not ghci, because ghci 
uses extended defaulting rules and does something different:

Prelude> toEnum 5
*** Exception: Prelude.Enum.().toEnum: bad argument
Prelude> toEnum 0
()

as you can see, ghci chooses the unit type () as the default here [the 
other expressions work as in hugs] and doesn't complain about an ambiguous 
type variable as in the fromJValue example.

> >> For instance, when defining the instance for Bool types, then I
> >> understand that both functions (toJValue and fromJValue) will be
> >> called upon when we supply a Bool type, but then the (JBool b) type
> >> in function fromJValue doesn't match
> >
> > fromJValue always takes a JValue as argument. That JValue can be a
> > wrapped String, a wrapped Bool, a wrapped number (Double), ...
>
> so, fromJValue takes a JValue and a type, or only a JValue?

On the source code level, it takes only a JValue, but it needs some context 
to resolve which instance to choose. There, functions can only take values 
as arguments, not types.
On a lower implementation level, it is possible that overloaded functions 
[type class methods] take explicit type arguments, but let the compiler 
writers worry about such details :)

> I was assuming the second,

On the implementation level, in GHC, it takes a dictionary and a JValue as 
arguments, but again, that's a low-level detail you shouldn't care about.
On the Haskell code level, your assumption is correct.

> but then my misunderstanding kicks in, I guess.
> I'll try to explain myself. When defining
>
> class JSON a [...], then I thought that for an instance I would have to
> identify the type of that instance and that all functions would work on
> that type. Thus, when defining
>
> instan JSON Bool [...] I was expecting that all the function definitions
> would have as argument a Bool.

No, Bool may also appear in the result type of the functions and not in the 
argument type(s). Return ing to the Enum class, that contains

toEnum :: Enum a => Int -> a
fromEnum :: Enum a => a -> Int

in the former, the instance type is the result type of the function, in the 

Re: [Haskell-cafe] ANN: weighted-regexp-0.1.0.0

2010-07-26 Thread Felipe Lessa
Wow, great paper!  I got somewhat scared when I saw the first
description of the scene, but after I started reading I couldn't stop
anymore =D.

Thanks,

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


Re: [Haskell-cafe] Is 'flip' really necessary?

2010-07-26 Thread Nils

On 26.07.2010 08:33, David Virebayre wrote:

listeEtagTot = concatMap (`listeEtagArm` cfgTypesTringle) listeArmOrd


You can use flip as a "wildcard" aswell:

> listeEtagTot = concatMap (listeEtagArm `flip` cfgTypesTringle) 
listeArmOrd


Makes it even more readable in my opinion, since this really "shows" you 
where the value belongs to.

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


Re: [Haskell-cafe] Re: Haskell Forum

2010-07-26 Thread Nick Bowler
On 13:28 Mon 26 Jul , Kevin Jardine wrote:
> On Jul 26, 10:10 pm, Evan Laforge  wrote:
> 
> > Interesting, I've never figured out why some people prefer forums, but
> > you're proof that they exist :)  
> 
> This debate is eerily similar to several others I've seen (for
> example, on the interactive fiction mailing list).
> 
> In every case I've seen, a web forum vs. mailing list debate has been
> pointless at best and sometimes turned into a flame war. I think that
> it's best for people who prefer a web forum to establish one and use
> it, and for those who prefer the mailing list approach to continue to
> use that.

It seems to me, then, that a wine-like web forum <-> mailing list
gateway would satisfy everyone without fragmenting the community?

See http://forum.winehq.org/viewforum.php?f=2.

-- 
Nick Bowler, Elliptic Technologies (http://www.elliptictech.com/)
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] Re: Haskell Forum

2010-07-26 Thread Kevin Jardine
On Jul 26, 10:10 pm, Evan Laforge  wrote:

> Interesting, I've never figured out why some people prefer forums, but
> you're proof that they exist :)  

This debate is eerily similar to several others I've seen (for
example, on the interactive fiction mailing list).

In every case I've seen, a web forum vs. mailing list debate has been
pointless at best and sometimes turned into a flame war. I think that
it's best for people who prefer a web forum to establish one and use
it, and for those who prefer the mailing list approach to continue to
use that.

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


Re: [Haskell-cafe] Haskell Forum

2010-07-26 Thread Nick Bowler
On 20:56 Mon 26 Jul , Andrew Coppin wrote:
> My personal preference would be for NNTP. It seems to handle threading 
> much better. You can easily "kill" threads you're not interested in, and 
> thereafter not bother downloading them. You can use several different 
> client programs. And so on. However, last time I voiced this opinion, 
> people started talking about something called "usenet", which I've never 
> heard of...

Conveniently, all of the haskell mailing lists have an NNTP interface
available.  Add news.gmane.org as a server in your newsreader and
subscribe to gmane.comp.lang.haskell.cafe.

-- 
Nick Bowler, Elliptic Technologies (http://www.elliptictech.com/)
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Re: Haskell Forum

2010-07-26 Thread Evan Laforge
On Mon, Jul 26, 2010 at 12:54 PM, Kevin Jardine  wrote:
> On Jul 26, 6:45 pm, Nick Bowler  wrote:
>
>> Since when do mailing lists not have threading?  Web forums with proper
>> support for threading seem to be few and far apart.
>
> Most of the email clients I'm familiar with don't support threaded
> displays and most of the web forums I'm familiar with do (although the
> feature is not always switched on).
>
> In my experience the debate between mailing list vs. web forum can
> become very emotional (especially when discussed via a mailing list)
> and I don't think it is that productive. Some people like one, some
> people like the other. That's why I think that it is useful to give
> people a choice.

Interesting, I've never figured out why some people prefer forums, but
you're proof that they exist :)  They always seemed like a clumsy
reinvention of usenet to me.  It might be because all my email clients
are threaded.  Apart from threading and attachments, are there other
reasons you prefer a forum?

How about something like google groups, which presents a web using
forum-esque interface to mailing lists?  It threads and provides a
separate place to upload files.  You can even design a few pages to
associate with the list for introductory material, FAQs, and whatnot,
sort of like a generalization of the "sticky thread" idea from forums.

I'm pretty sure there are web-oriented interfaces to this mailing list
too... where do they fall short?
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Re: Haskell Forum

2010-07-26 Thread Brandon S Allbery KF8NH
-BEGIN PGP SIGNED MESSAGE-
Hash: SHA1

On 7/26/10 15:54 , Kevin Jardine wrote:
> On Jul 26, 6:45 pm, Nick Bowler  wrote:
> 
>> Since when do mailing lists not have threading?  Web forums with proper
>> support for threading seem to be few and far apart.
> 
> Most of the email clients I'm familiar with don't support threaded
> displays and most of the web forums I'm familiar with do (although the
> feature is not always switched on).

This is approximately the reverse of my experience.  In particular, I
haven't run across a non-threaded email client in something like 10 years.
-BEGIN PGP SIGNATURE-
Version: GnuPG v1.4.9 (Darwin)
Comment: Using GnuPG with Mozilla - http://enigmail.mozdev.org/

iEYEARECAAYFAkxN6l0ACgkQIn7hlCsL25UIQgCfeBNEwNo/IgsJAJ9vJjMIGRfB
ypQAnR0KHLmjWh5+P8Jc+frhoAo7PXWU
=tp0/
-END PGP SIGNATURE-
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Haskell Forum

2010-07-26 Thread Brandon S Allbery KF8NH
-BEGIN PGP SIGNED MESSAGE-
Hash: SHA1

On 7/26/10 15:56 , Andrew Coppin wrote:
> My personal preference would be for NNTP. It seems to handle threading much
> better. You can easily "kill" threads you're not interested in, and
> thereafter not bother downloading them. You can use several different client
> programs. And so on. However, last time I voiced this opinion, people
> started talking about something called "usenet", which I've never heard of...

Usenet *is* NNTP.
-BEGIN PGP SIGNATURE-
Version: GnuPG v1.4.9 (Darwin)
Comment: Using GnuPG with Mozilla - http://enigmail.mozdev.org/

iEYEARECAAYFAkxN6lQACgkQIn7hlCsL25VNdgCgt3dLl3e7l5jBEdZC5ogEamKB
5V0An0HDm12NbgWHjjNd8tuKaXggAwRM
=jXbn
-END PGP SIGNATURE-
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Haskell Forum

2010-07-26 Thread Andrew Coppin

Vo Minh Thu wrote:

The idea of a forum has been brought to this list a few times in the
past. Unfortunately for those who thought it was a good idea, it
didn't really catched up.

Haskellers are generaly found of the mailing-list interface.
  


I'm not particularly fond of mailing lists. It's a very unstructured way 
to manage large volumes of messages. (Plus my ISP's spam filter is 
utterly hopeless. It somehow fails to block the actual spam, and yet 
repeatedly marks Haskell Cafe messages as spam...)


My personal preference would be for NNTP. It seems to handle threading 
much better. You can easily "kill" threads you're not interested in, and 
thereafter not bother downloading them. You can use several different 
client programs. And so on. However, last time I voiced this opinion, 
people started talking about something called "usenet", which I've never 
heard of...



Beside, with stackoverflow, reddit, #haskell, the wiki, the upcoming
social hackage, ... our bases are nicely covered.
  


Kind of fragmented though, no?

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


[Haskell-cafe] Re: Haskell Forum

2010-07-26 Thread Kevin Jardine
On Jul 26, 6:45 pm, Nick Bowler  wrote:

> Since when do mailing lists not have threading?  Web forums with proper
> support for threading seem to be few and far apart.

Most of the email clients I'm familiar with don't support threaded
displays and most of the web forums I'm familiar with do (although the
feature is not always switched on).

In my experience the debate between mailing list vs. web forum can
become very emotional (especially when discussed via a mailing list)
and I don't think it is that productive. Some people like one, some
people like the other. That's why I think that it is useful to give
people a choice.

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


Re: [Haskell-cafe] Haskell Forum

2010-07-26 Thread Roman Beslik
 Hi. I personally find web-forum a more convenient and structured way 
of communication. I will help if the forum exports posts or topics as a 
feed.


Are you strictly devoted to phpBB? I think that fluxBB is a decent 
choice. Just suggesting.


On 26.07.10 16:30, Daniel Díaz wrote:
I want to open a Haskell forum based on phpBB, but I need some 
collaborators for organize its content, and moderate its use.


--
Best regards,
  Roman Beslik.

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


[Haskell-cafe] ANNOUNCE: darcs 2.5 beta 2

2010-07-26 Thread Reinier Lamers
Hi all,

The darcs team would like to announce the immediate availability of darcs 2.5
beta 2 (also known as darcs 2.4.98.2 due to Cabal restrictions). Important 
changes since darcs 2.4.4 are:

   * trackdown can now do binary search with the --bisect option
   * darcs always stores patch metadata encoded with UTF-8
   * obliterate has a -o flag to save obliterated patch
   * amend-record now supports --ask-deps
   * apply now supports --match
   * amend-record has a new --keep-date option
   * inventory-changing commands (like record and pull) now operate in
 constant time with respect to the number of patches in the repository
   * the push, pull, send and fetch commands no longer set the default
 repository by default
   * the --edit-description option is now on by default for the send command

If you have installed the Haskell Platform or cabal-install, you can install
this beta release by doing:

  $ cabal update
  $ cabal install darcs-beta

Alternatively, you can download the tarball from 
http://darcs.net/releases/darcs-2.4.98.2.tar.gz and build it by hand as 
explained in the README file. 

Kind Regards,
the darcs release manager,
Reinier Lamers


signature.asc
Description: This is a digitally signed message part.
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] datatype contexts

2010-07-26 Thread Dominique Devriese
2010/7/26 Ryan Ingram :
> There are two types of datatype contexts; haskell'98 contexts (which I
> think are terrible), and GHC existential contexts (which I like):

See also "GADT-style" data type declarations [1] and full GADT's [2],
which both behave like GHC existential contexts mentioned above: pattern
matching on them makes available the context constraint.

Dominique

Footnotes:
[1]  
http://www.haskell.org/ghc/docs/6.12.2/html/users_guide/data-type-extensions.html#gadt-style
[2]  
http://www.haskell.org/ghc/docs/6.12.2/html/users_guide/data-type-extensions.html#gadt
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Typeclasses question in "Real World Haskell" book

2010-07-26 Thread Angel de Vicente

Hi,

thanks for the answer. This is my first attempt at Typeclasses, and I 
think there is something "deep" that I don't understand...


On 26/07/10 15:03, Daniel Fischer wrote:

class JSON a where
  toJValue :: a ->  JValue
  fromJValue :: JValue ->  Either JSONError a

instance JSON JValue where
  toJValue = id
  fromJValue = Right

instance JSON Bool where
  toJValue = JBool
  fromJValue (JBool b) = Right b
  fromJValue _ = Left "not a JSON boolean"


I don't understand how the JSON typeclass is defined, in particular the
fromJValue definition.


Given a JValue and a type
(like Bool, JValue, String, Maybe [(Integer, ())]), fromJValue returns
either


a JValue and a type???


For instance, when defining the instance for Bool types, then I
understand that both functions (toJValue and fromJValue) will be called
upon when we supply a Bool type, but then the (JBool b) type in function
fromJValue doesn't match


fromJValue always takes a JValue as argument. That JValue can be a wrapped
String, a wrapped Bool, a wrapped number (Double), ...


so, fromJValue takes a JValue and a type, or only a JValue?  I was 
assuming the second, but then my misunderstanding kicks in, I guess. 
I'll try to explain myself. When defining


class JSON a [...], then I thought that for an instance I would have to 
identify the type of that instance and that all functions would work on 
that type. Thus, when defining


instan JSON Bool [...] I was expecting that all the function definitions 
would have as argument a Bool. toJValue is no problem there, but I don't 
see the fromJValue definition, since this matches against either (JBool 
b) or _ , but not a Bool...


Another misunderstading on my side: if I call fromJValue (JBool True), 
which instance ofr fromJValue should be used: instance JSON JValue or 
instance JSON Bool. If we only look at the signature of the fromJValue 
functions, then both could match?



*Main>  fromJValue False

:1:11:
  Couldn't match expected type `JValue' against inferred type `Bool'
  In the first argument of `fromJValue', namely `False'
  In the expression: fromJValue False
  In the definition of `it': it = fromJValue False


That one should be pretty clear, fromJValue expects a JValue as argument
and gets a Bool, it's like calling


Yes, but I guess you see why I try this given my misunderstanding above?


*Main>  fromJValue (JBool False)

:1:0:
  Ambiguous type variable `a' in the constraint:
`JSON a' arising from a use of `fromJValue' at
:1:0-23 Probable fix: add a type signature that fixes these
type variable(s) *Main>


That's less easy.
The compiler/interpreter doesn't know which result type to use.

fromJValue :: JSON a =>  JValue ->  Either JSONError a

with which type should a be instantiated, should it use
- JValue, in which case the result would be
Right (JBool False)

- Bool, in which case the result would be
Right False

- String, in which case the result woulde be something like
 No instance for (JValue [Char])
   arising from a use of `fromJValue' at ...

(unless you have such an instance in scope, then it would be something like
Left "not a JSON string")

- Int, in which case you'd get analogous behaviour
- ...





Any pointers?


In an actual programme, there is usually enough context to fix the type
variable a, then the compiler/interpreter knows what to do.
At the prompt or when there isn't enough context otherwise, you need to
explicitly tell the compiler/interpreter which type to use,

*Main>  fromJValue (JBool False) :: Either JSONError Bool
Right False
*Main>  fromJValue (JBool False) :: Either JSONError JValue
Right (JBool False)


Ah... OK, I think with these two examples the whole thing starts to make 
sense.


When defining

instance JSON Bool

then this doesn't mean that the functions need to work just on Bool's, 
but rather that wherever there is an "a" in the typeclass definition, 
then this should be instantiated to a Bool, correct?




And now that we are at it... In the next page, 152 there is the 
following instance definition, but no explanation is (I think) given of 
what it means:


instance (JSON a) => JSON [a] where

until then all instance definitions where of the type

instance JSON Int where ...

How should I read that definition?

Thanks for you help,
Ángel de Vicente
--
http://www.iac.es/galeria/angelv/

High Performance Computing Support PostDoc
Instituto de Astrofísica de Canarias
-
ADVERTENCIA: Sobre la privacidad y cumplimiento de la Ley de Protección de 
Datos, acceda a http://www.iac.es/disclaimer.php
WARNING: For more information on privacy and fulfilment of the Law concerning 
the Protection of Data, consult http://www.iac.es/disclaimer.php?lang=en

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

Re: [Haskell-cafe] datatype contexts

2010-07-26 Thread Gregory Crosswhite
Oh, now I see!  I knew about (and have used) existential contexts, but
somehow I hadn't made the connection that in a sense they are already
equivalent to our intuition for Haskell 98 contexts "done right".  :-) 
Thanks!

Any chance of seeing them in Haskell'11?

Cheers,
Greg

On 07/26/10 10:44, Ryan Ingram wrote:
> There are two types of datatype contexts; haskell'98 contexts (which I
> think are terrible), and GHC existential contexts (which I like):
>
> class C a where runC :: a -> Int
> data C a => T1 a = D1 a
>
> All this does is add a context to the D1 *constructor*; that is:
> -- D1 :: C a => a -> T1 a
>
> But extracting a value of this type does nothing:
>
> foo :: T1 a -> Int
> foo (D1 a) = runC a -- compile error
>
> However, putting the context on the RHS as you have done works in GHC
> and does "the right thing"; pattern matching on that constructor now
> brings the class into scope.  You can think of the datatype has having
> another field which is "proof that a is a member of C":
>
> {-# LANGUAGE ExistentialQuantification #-}
> data T2 a = C a => D2 a
> -- D2 :: C a => a -> T2 a  -- same as D1
>
> bar :: T2 a -> Int
> bar (D2 a) = runC a -- works
>
>   -- ryan
>
> On Mon, Jul 26, 2010 at 7:48 AM, Gregory Crosswhite
>  wrote:
>   
>>  I agree with prior discussion on this list that adding contexts to datatype
>> declarations seems to be more trouble than its worth, since these contexts
>> just have to be added again to every function using the datatype.  However,
>> I have often wondered:  why do function *have* to have these contexts?  What
>> would it affect in the language if we made the contexts be implicit, so that
>> if we have
>>
>>data Datatype a = Context a => Datatype a
>>
>> then for function declarations
>>
>>f :: D a -> ...
>>
>> the context "Context a" is automatically asserted by the compiler?
>>
>> Cheers,
>> Greg
>>
>> ___
>> 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] ANN: Moio, a library for compositional event-driven programming

2010-07-26 Thread Patai Gergely
Hello all,

I created a little library that provides first-class event sources and
event stream transformers, both allowing side effects. For the time
being, the code is only available on GitHub [1]. The library is called
Moio, short for 'multiple-occurrence I/O', since event sources are
effectively a generalisation of the IO monad that outputs a stream of
values over time instead of just a single result at the end of its
execution. To summarise in a short phrase, Moio could be considered as
'Rx meets Fudgets', but that's only a superficial characterisation.

Check out the example application, a simple bulletin board server, which
shows how to treat a callback-based GTK GUI and blocking I/O based
networking uniformly using the abstractions provided.

Gergely

[1] http://github.com/cobbpg/moio

-- 
http://www.fastmail.fm - Or how I learned to stop worrying and
  love email again

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


Re: [Haskell-cafe] datatype contexts

2010-07-26 Thread Ryan Ingram
There are two types of datatype contexts; haskell'98 contexts (which I
think are terrible), and GHC existential contexts (which I like):

class C a where runC :: a -> Int
data C a => T1 a = D1 a

All this does is add a context to the D1 *constructor*; that is:
-- D1 :: C a => a -> T1 a

But extracting a value of this type does nothing:

foo :: T1 a -> Int
foo (D1 a) = runC a -- compile error

However, putting the context on the RHS as you have done works in GHC
and does "the right thing"; pattern matching on that constructor now
brings the class into scope.  You can think of the datatype has having
another field which is "proof that a is a member of C":

{-# LANGUAGE ExistentialQuantification #-}
data T2 a = C a => D2 a
-- D2 :: C a => a -> T2 a  -- same as D1

bar :: T2 a -> Int
bar (D2 a) = runC a -- works

  -- ryan

On Mon, Jul 26, 2010 at 7:48 AM, Gregory Crosswhite
 wrote:
>  I agree with prior discussion on this list that adding contexts to datatype
> declarations seems to be more trouble than its worth, since these contexts
> just have to be added again to every function using the datatype.  However,
> I have often wondered:  why do function *have* to have these contexts?  What
> would it affect in the language if we made the contexts be implicit, so that
> if we have
>
>    data Datatype a = Context a => Datatype a
>
> then for function declarations
>
>    f :: D a -> ...
>
> the context "Context a" is automatically asserted by the compiler?
>
> Cheers,
> Greg
>
> ___
> 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] Techniques for ensuring parser correctness?

2010-07-26 Thread Jason Dagit
On Mon, Jul 26, 2010 at 4:14 AM, S. Doaitse Swierstra  wrote:

> I took a quick look at this file. To me it seems a mixture of a lexer and a
> parser built on top of a home brewn parser library. I see function like
> maybeWork which
> (if I interpret correctly) test whether specific conditions hold for the
> input, etc.
>

The one Eric linked to is the current parser, but it's not the one I had in
mind when I mentioned the "parsec-like" API.

I have modified the API exported by the home brewed parser to be more
parsec-like, but my changes are still in review.  You can see them here:
http://hpaste.org/fastcgi/hpaste.fcgi/view?id=28240#a28240

I have also included the PatchInfo parser on that page as it is defined in a
different module than the one Eric linked.


>
> Indeed it would be nice to have a grammatical description of the input
> format. An important question is whether you can be assured that all input
> is indeed correct, or whether any checking has to be done.
>

Most of the time darcs just consumes its own output.  Sometimes humans edit
their patches, for example to rewrite history, but this is discouraged.
Also, darcs stores hashes of files and checks them so editing patches will
fail unless those hashes are updated too.  When patches are mailed the
mailer might munge them so that's another time when it's good to do some
input validation.

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


Re: [Haskell-cafe] Haskell Forum

2010-07-26 Thread Christopher Done
I'd only really go on a Haskell forum hosted at haskell.org. If there
wlil be one, I'd moderate. Only things a forum has over a mailing list
is syntax highlighting and attachments imo. Cons are being tied to a
web site, anonymity, existence of moderators, etc. Seems a bit like
spreading the community thin. It's not *that* big.

On 26 July 2010 15:30, Daniel Díaz  wrote:
> Hi all,
>
> I want to open a Haskell forum based on phpBB, but I need some collaborators
> for organize its content, and moderate its use. When we have finished, I
> will open this forum for the entire community of Haskell!
>
> If you are interested, mail me:
> danield...@asofilak.es
>
> Thanks in advance.
>
> ___
> 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 do this with associated types?

2010-07-26 Thread Ryan Ingram
On Sun, Jul 25, 2010 at 1:53 PM, Alexey Karakulov  wrote:
> Suppose I have one piece of code like this:
>
>> class Result r e | r -> e where
>>    failure :: e -> r a
>>    success :: a -> r a
>
> Maybe instance is discarding failure information:
>
>> instance Result Maybe e where
>>     failure _ = Nothing
>>     success x = Just x

I would argue that this shouldn't successfully compile.

Your class declaration claims that given r, you can uniquely determine e.

But you've effectively defined

instance Result Maybe ()
instance Result Maybe Int
... many more instances ...

which means that isn't the case.

I wonder if there is a potential type safety failure in the compiler
with instances of this form?

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


Re: [Haskell-cafe] Please report any bug of gtk2hs-0.11.0!

2010-07-26 Thread Andy Stewart
Sebastian Fischer  writes:

> Hello,
>
> On Jul 13, 2010, at 9:15 AM, Andy Stewart wrote:
>
>> Please report any bug of gtk2hs-0.11.0, we will fix it before release
>> gtk2hs-0.11.1
>
> I have just installed the new Haskell Platform under Mac OS X 10.5. With the 
> previous installation
> of GHC 6.10.4 I managed to install  gtk2hs manually so I think I have all 
> required Unix libs.
>
> Now, I tried to install gtk2hs from Hackage but didn't succeed.
>
> cabal install gtk2hs-buildtools
>
> works fine but
>
> cabal install gtk
>
> fails with the message
>
> Configuring gtk-0.11.0...
> setup: ./Graphics/UI/Gtk/General/IconTheme.chs: invalid argument
> cabal: Error: some packages failed to install:
> gtk-0.11.0 failed during the building phase. The exception was:
> ExitFailure 1
>
> The dependencies seem to be installed properly:
>
> # ghc-pkg --user list | grep 0.11.0
> cairo-0.11.0
> gio-0.11.0
> glib-0.11.0
> pango-0.11.0
>
> Has anyone experienced this before? Googling the error message brings up a 
> related problem under
> Solaris but no solution.
It's a bug of gtk2hs-0.11.0, that IconTheme.chs contain some UTF-8
character that can't handle by gtk2hs/gtk/Gtk2HsSetup.hs 

You can fix this problem with two solutions:

1) Change your locate to UTF-8.
2) Or download darcs version of gtk2hs (darcs get 
http://code.haskell.org/gtk2hs).

Cheers,

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


Re: [Haskell-cafe] Re: Haskell Forum

2010-07-26 Thread Nick Bowler
On 08:15 Mon 26 Jul , Kevin Jardine wrote:
> Other topics I am interested in are served by both a web forum and a
> mailing list, usually with different content and participants in both.
> In my experience, routing one kind of content to another does not work
> very well because of issues of spam control, moderation, topic
> subdivisions, the ability to correct posts, and threading (usually web
> forums have these things and mailing lists do not).

Since when do mailing lists not have threading?  Web forums with proper
support for threading seem to be few and far apart.

-- 
Nick Bowler, Elliptic Technologies (http://www.elliptictech.com/)
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] monoids and monads

2010-07-26 Thread Edward Kmett
On Mon, Jul 26, 2010 at 11:55 AM, John Lato  wrote:

> Hello,
>
> I was wondering today, is this generally true?
>
> instance (Monad m, Monoid a) => Monoid (m a) where
>  mempty = return mempty
>  mappend = liftM2 mappend
>
>
Yes.


> I know it isn't a good idea to use this instance, but assuming that
> the instance head does what I mean, is it valid?  Or more generally is
> it true for applicative functors as well?  I think it works for a few
> tricky monads, but that's not any sort of proof.  I don't even know
> how to express what would need to be proven here.
>

There are multiple potential monoids that you may be interested in here.

There is the monoid formed by MonadPlus, there is the monoid formed by
wrapping a monad (or applicative) around a monoid, which usually forms part
of a right seminearring because of the left-distributive law, there are also
potentially other monoids for particular monads.

See the monad module in my monoids package:

http://hackage.haskell.org/packages/archive/monoids/0.2.0.2/doc/html/Data-Monoid-Monad.html


> Any resources for how I could develop a means to reason about this
> sort of property?
>

The types are not enough.

What you need is the associativity of Kleisli arrow composition and the two
identity laws.

The three monad laws are precisely what you need to form this monoid. There
are analogous laws for Applicative that serve the same purpose.

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


[Haskell-cafe] monoids and monads

2010-07-26 Thread John Lato
Hello,

I was wondering today, is this generally true?

instance (Monad m, Monoid a) => Monoid (m a) where
  mempty = return mempty
  mappend = liftM2 mappend

I know it isn't a good idea to use this instance, but assuming that
the instance head does what I mean, is it valid?  Or more generally is
it true for applicative functors as well?  I think it works for a few
tricky monads, but that's not any sort of proof.  I don't even know
how to express what would need to be proven here.

Any resources for how I could develop a means to reason about this
sort of property?

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


Re: [Haskell-cafe] Lists and monads

2010-07-26 Thread John Lato
> From: Kevin Jardine 
>
> As a Haskell neophyte, one of the things I find confusing is the way
> that the usual list functions (map, fold, ++, etc.) often cannot be
> used directly with monadic lists (m [a] or [m a]) but seem to require
> special purpose functions like ap, mapM etc.
>
> I suspect that things are not quite as difficult as they appear,
> however, but cannot find any tutorials on monadic list manipulation.
>

It's not really a tutorial, but have you read the Typeclassopedia,
http://haskell.org/sitewiki/images/8/85/TMR-Issue13.pdf ?

I found it very helpful to get a good understanding of functors,
applicatives, and monads, after which it became much simpler to get
good usage from Control.Monad and Control.Applicative.

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


[Haskell-cafe] Re: Iteratee package: combining enumerators

2010-07-26 Thread John Lato
Hi Max,

How about this function?

processFiles :: IterateeG [] String m a -> [FilePath] -> m
(IterateeG [] String m a)
processFiles = foldM (\i fp -> fileDriver fp (convStream decodeStrings i)

The nice thing about an enumeratee is that you can just run the outer
iteratee (fileDriver does this implicitly) and have the inner iteratee
returned.  You can then use it as input to a new
enumerator/enumeratee.

In the case where you want to treat multiple files as one long stream
of data, there's another approach (although I think the above will
work too).  If you define
enumFile :: Monad m => FilePath -> EnumeratorGMM s el m a
(which really should be in the library), which can be written
(restricted-to-IO) as:

enumFile :: FilePath -> IterateeG s el IO a -> IO (IterateeG s el IO a)
enumFile fp iter = bracket (openBinaryFile fp ReadMode) (flip
enumHandle iter) (hClose)

Now you can combine these file enumerators with (>.) like this:

enumMyFiles :: [FilePath] -> EnumeratorGMM s el IO a
enumMyFiles = foldr (>.) enumEof . map enumFile

I like this function, but nothing delimits the files in the stream, so
it's not always applicable.

Does this help?

Best,
John

On Mon, Jul 26, 2010 at 5:19 AM, Max Cantor  wrote:
> I have a series of files with binary encoded data in them, and want to create 
> an enumerator iterates on the first element at the front of all the files.  
> Something like the pseudocode: return . minimum =<< mapM (fmap (heads . 
> lines) readFile)  listOfFileNames
>
> I can use convStream to create an enumerator which runs iteratees on each 
> tuple in a single file:
>
> (convStream decodeStrings) :: Monad m => IterateeG [] String m a -> IterateeG 
> WrappedByteString Word8 m (IterateeG [] MyDataType m a)
>
> or, with the EnumerateeGMM tysyn:
>
> (convStream decodeStrings) :: Monad m => EnumerateeGMM WrappedByteString 
> Word8 [] String m a
>
> My question is if there is a simple way to combine the Enumeratees to 
> enumerate on a set of files or if I have to write an enumerator from scratch.
>
> Thank you in advance,
> Max
>
> P.S. John, apologies for the duped email, sent from the wrong address by 
> mistake.
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] ANN: weighted-regexp-0.1.0.0

2010-07-26 Thread Sebastian Fischer

Hello,

this year's ICFP features A Play on Regular Expressions where two  
Haskell programmers and an automata theory guru develop an efficient  
purely functional algorithm for matching regular expressions.


A Haskell library based on their ideas is now available from Hackage.  
For more information (and a link to the play) visit:


http://sebfisch.github.com/haskell-regexp/

Cheers,
Sebastian



--
Underestimating the novelty of the future is a time-honored tradition.
(D.G.)



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


[Haskell-cafe] Re: Haskell Forum

2010-07-26 Thread Kevin Jardine
Other topics I am interested in are served by both a web forum and a
mailing list, usually with different content and participants in both.
In my experience, routing one kind of content to another does not work
very well because of issues of spam control, moderation, topic
subdivisions, the ability to correct posts, and threading (usually web
forums have these things and mailing lists do not).

This works well in my view. Those people who prefer more structure and
features post in the forum, those who prefer more traditional mailing
lists post there, and anyone who wants to keep track of both streams
subscribes to the RSS feeds.

Personally I prefer web forums.

Kevin

On Jul 26, 5:03 pm, Magnus Therning  wrote:
> On Mon, Jul 26, 2010 at 15:47, Nick Bowler  wrote:
> > On 10:37 Mon 26 Jul     , Job Vranish wrote:
> >> I agree. A web forum would be more friendly to newcomers, easier to browse,
> >> and better organized, than the mailing list.
>
> > I don't understand this sentiment at all.  How are web forums easier to
> > browse than list archives?  Especially given that there are usually multiple
> > archives for each ML, with a variety of ways to use them (e.g., I tend to
> > use gmane with my newsreader for this purpose).
>
> Irrespective of what is easier to use, what really counts is where the
> *targets* of your post hang out.  Personally I prefer a mailing list, and I
> would only ever use a forum if I had a better chance of getting good and
> informative answers there.
>
> Another option is to import the entire haskell-cafe archive into gmail :-)
>
> >> Some people will still prefer the mailing list of course, but I think there
> >> will be enough demand to justify a forum :)
>
> > Wine has a web forum that is directly connected to their mailing lists:
> > each post on the forum is sent to the corresponding list and vice versa.
> > The web forum interface doesn't support proper threading, but it
> > otherwise seems to work OK.  Perhaps something like that would be
> > useful?
>
> This would be a good compromise.
>
> /M
>
> --
> Magnus Therning                        (OpenPGP: 0xAB4DFBA4)
> magnus@therning.org          Jabber: 
> magnus@therning.orghttp://therning.org/magnus        identi.ca|twitter: magthe
> ___
> Haskell-Cafe mailing list
> haskell-c...@haskell.orghttp://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] Haskell Forum

2010-07-26 Thread Magnus Therning
On Mon, Jul 26, 2010 at 15:47, Nick Bowler  wrote:
> On 10:37 Mon 26 Jul     , Job Vranish wrote:
>> I agree. A web forum would be more friendly to newcomers, easier to browse,
>> and better organized, than the mailing list.
>
> I don't understand this sentiment at all.  How are web forums easier to
> browse than list archives?  Especially given that there are usually multiple
> archives for each ML, with a variety of ways to use them (e.g., I tend to
> use gmane with my newsreader for this purpose).

Irrespective of what is easier to use, what really counts is where the
*targets* of your post hang out.  Personally I prefer a mailing list, and I
would only ever use a forum if I had a better chance of getting good and
informative answers there.

Another option is to import the entire haskell-cafe archive into gmail :-)

>> Some people will still prefer the mailing list of course, but I think there
>> will be enough demand to justify a forum :)
>
> Wine has a web forum that is directly connected to their mailing lists:
> each post on the forum is sent to the corresponding list and vice versa.
> The web forum interface doesn't support proper threading, but it
> otherwise seems to work OK.  Perhaps something like that would be
> useful?

This would be a good compromise.

/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] data type declaration

2010-07-26 Thread Brandon S Allbery KF8NH
-BEGIN PGP SIGNED MESSAGE-
Hash: SHA1

On 7/26/10 06:02 , John Lato wrote:
> If the behavior of class contexts on data types were changed to what
> you think it should mean, i.e. contexts specified in a data
> declaration are carried around for all uses of that type instead of
> just the data constructor, I wouldn't mind at all.  Whether this is a
> good idea or would cause other problems, I can't say.

As I understand it:
1) carrying them around complicates Haskell98 (and now Haskell2010)
compatibility (also see below);
2) GADTs do what you want, since they don't have backward compatibility baggage.

As to the current proposal, I think nobody's certain what would happen to
older programs if data were changed to carry contexts around --- someone
might be relying on the current behavior, and changing it might produce
runtime oddness instead of a compile-time error --- whereas making contexts
illegal will produce an easily-fixed error message in all relevant cases.

- -- 
brandon s. allbery [linux,solaris,freebsd,perl]  allb...@kf8nh.com
system administrator  [openafs,heimdal,too many hats]  allb...@ece.cmu.edu
electrical and computer engineering, carnegie mellon university  KF8NH
-BEGIN PGP SIGNATURE-
Version: GnuPG v2.0.10 (Darwin)
Comment: Using GnuPG with Mozilla - http://enigmail.mozdev.org/

iEYEARECAAYFAkxNo5EACgkQIn7hlCsL25WDzgCdE/QmWy/Do1M73n+rt829Dyb7
HuMAni+vw//HuanYc4LJ5uXPYdPDBmuu
=/ivE
-END PGP SIGNATURE-
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] datatype contexts

2010-07-26 Thread Gregory Crosswhite
 I agree with prior discussion on this list that adding contexts to 
datatype declarations seems to be more trouble than its worth, since 
these contexts just have to be added again to every function using the 
datatype.  However, I have often wondered:  why do function *have* to 
have these contexts?  What would it affect in the language if we made 
the contexts be implicit, so that if we have


data Datatype a = Context a => Datatype a

then for function declarations

f :: D a -> ...

the context "Context a" is automatically asserted by the compiler?

Cheers,
Greg

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


Re: [Haskell-cafe] Haskell Forum

2010-07-26 Thread Nick Bowler
On 10:37 Mon 26 Jul , Job Vranish wrote:
> I agree. A web forum would be more friendly to newcomers, easier to browse,
> and better organized, than the mailing list.

I don't understand this sentiment at all.  How are web forums easier to
browse than list archives?  Especially given that there are usually
multiple archives for each ML, with a variety of ways to use them (e.g.,
I tend to use gmane with my newsreader for this purpose).

> Some people will still prefer the mailing list of course, but I think there
> will be enough demand to justify a forum :)

Wine has a web forum that is directly connected to their mailing lists:
each post on the forum is sent to the corresponding list and vice versa.
The web forum interface doesn't support proper threading, but it
otherwise seems to work OK.  Perhaps something like that would be
useful?

-- 
Nick Bowler, Elliptic Technologies (http://www.elliptictech.com/)
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Haskell Forum

2010-07-26 Thread Job Vranish
I agree. A web forum would be more friendly to newcomers, easier to browse,
and better organized, than the mailing list.

Some people will still prefer the mailing list of course, but I think there
will be enough demand to justify a forum :)

- Job



On Mon, Jul 26, 2010 at 9:57 AM, Daniel Díaz  wrote:

> Well, I thought that it may be a more comfortable way to communicate
> between us. Specially for newcomers. Don't forget that Haskell is a growing
> community.
>
> It's just my opinion.
>
> ___
> 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: Lists and monads

2010-07-26 Thread Kevin Jardine
On Jul 26, 4:12 pm, Bill Atkins  wrote:
> The answer is still applicative.  :)

OK, then I know where to spend my reading time.

Thanks!

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


Re: [Haskell-cafe] Re: Lists and monads

2010-07-26 Thread Bill Atkins
The answer is still applicative.  :)

On Monday Jul 26, 2010, at 10:06 AM, Kevin Jardine wrote:

> On Jul 26, 3:49 pm, Kevin Jardine  wrote:
>> I find
>> myself wishing that f (m [a]) just automatically returned m f([a])
>> without me needing to do anything but I expect that there are reasons
>> why that is not a good idea.
> 
> Or is there a monadic list module where f(m [a]) = m f ([a]) ?
> 
> It occurs to me that Haskell provides the tools to construct such a
> module (I think) so probably one exists?
> 
> Kevin
> ___
> 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: Lists and monads

2010-07-26 Thread Kevin Jardine


On Jul 26, 3:49 pm, Kevin Jardine  wrote:
> I find
> myself wishing that f (m [a]) just automatically returned m f([a])
> without me needing to do anything but I expect that there are reasons
> why that is not a good idea.

Or is there a monadic list module where f(m [a]) = m f ([a]) ?

It occurs to me that Haskell provides the tools to construct such a
module (I think) so probably one exists?

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


Re: [Haskell-cafe] Typeclasses question in "Real World Haskell" book

2010-07-26 Thread Daniel Fischer
On Monday 26 July 2010 15:16:36, Angel de Vicente wrote:
> Hi,
>
> I'm stuck at page 151 of Real World Haskell and hoping that perhaps some
> of you can give me a hand here...
>
> The code that is giving me trouble is below.
>
> data JValue = JString String
>
>  | JNumber Double
>  | JBool Bool
>  | JNull
>  | JObject [(String, JValue)]
>  | JArray [JValue]
>
>deriving (Eq, Ord, Show)
>
> type JSONError = String
>
> class JSON a where
>  toJValue :: a -> JValue
>  fromJValue :: JValue -> Either JSONError a
>
> instance JSON JValue where
>  toJValue = id
>  fromJValue = Right
>
> instance JSON Bool where
>  toJValue = JBool
>  fromJValue (JBool b) = Right b
>  fromJValue _ = Left "not a JSON boolean"
>
>
> I don't understand how the JSON typeclass is defined, in particular the
> fromJValue definition.

Given a JValue and a type 
(like Bool, JValue, String, Maybe [(Integer, ())]), fromJValue returns 
either

Left errormessage

or 

Right (value of desired type)

>
> For instance, when defining the instance for Bool types, then I
> understand that both functions (toJValue and fromJValue) will be called
> upon when we supply a Bool type, but then the (JBool b) type in function
> fromJValue doesn't match

fromJValue always takes a JValue as argument. That JValue can be a wrapped 
String, a wrapped Bool, a wrapped number (Double), ...

Depending on the result type (Either JSONError a), it returns a wrapped 
value of type a [Right a] or a wrapped error message [Left JSONError]

>
> toJValue is no problem, but I cannot understand how fromJValue is
> supposed to work, and the comments in the online book
> (http://book.realworldhaskell.org/read/using-typeclasses.html) don't
> help with this either.
>
>   *Main> :load ch6
> [1 of 1] Compiling Main ( ch6.hs, interpreted )
> Ok, modules loaded: Main.
> *Main> toJValue False
> JBool False
> *Main> :type it
> it :: JValue
> *Main> fromJValue False
>
> :1:11:
>  Couldn't match expected type `JValue' against inferred type `Bool'
>  In the first argument of `fromJValue', namely `False'
>  In the expression: fromJValue False
>  In the definition of `it': it = fromJValue False

That one should be pretty clear, fromJValue expects a JValue as argument 
and gets a Bool, it's like calling

fromInteger True

> *Main> fromJValue (JBool False)
>
> :1:0:
>  Ambiguous type variable `a' in the constraint:
>`JSON a' arising from a use of `fromJValue' at
> :1:0-23 Probable fix: add a type signature that fixes these
> type variable(s) *Main>

That's less easy.
The compiler/interpreter doesn't know which result type to use.

fromJValue :: JSON a => JValue -> Either JSONError a

with which type should a be instantiated, should it use
- JValue, in which case the result would be 
Right (JBool False)

- Bool, in which case the result would be
Right False

- String, in which case the result woulde be something like
No instance for (JValue [Char])
  arising from a use of `fromJValue' at ...

(unless you have such an instance in scope, then it would be something like
Left "not a JSON string")

- Int, in which case you'd get analogous behaviour
- ...

>
>
>
> Any pointers?

In an actual programme, there is usually enough context to fix the type 
variable a, then the compiler/interpreter knows what to do.
At the prompt or when there isn't enough context otherwise, you need to 
explicitly tell the compiler/interpreter which type to use,

*Main> fromJValue (JBool False) :: Either JSONError Bool
Right False
*Main> fromJValue (JBool False) :: Either JSONError JValue
Right (JBool False)

>
> Thanks a lot,
> Ángel de Vicente

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


Re: [Haskell-cafe] Random this! ;-)

2010-07-26 Thread michael rice
Hi Lyndon,

Since the example immediately above the exercise used randomRIO, I assumed that 
randomRIO was to be used as part of the solution to the exercise.

http://en.wikibooks.org/wiki/Haskell/Understanding_monads/State

Also, it was the above mentioned example that introduced me to *liftM2*, about 
which I posted a question a couple of days ago (subject line: Heavy lift-ing).

The next topic on the wiki page is "Getting Rid of the IO" which seems to be 
the direction of your post. No doubt I'll have more questions as I plod on.

Thanks for your input,

Michael


--- On Mon, 7/26/10, Lyndon Maydwell  wrote:

From: Lyndon Maydwell 
Subject: Re: [Haskell-cafe] Random this! ;-)
To: "michael rice" 
Cc: "Max Rabkin" , "Ozgur Akgun" , 
haskell-cafe@haskell.org
Date: Monday, July 26, 2010, 8:29 AM

I find it useful to have a seed argument to nearly all random
functions rather than using ones with an IO signature. This way you
can speed up your program quite a bit and also make testing much
easier. I think that MonadRandom does this automatically too.



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


Re: [Haskell-cafe] Haskell Forum

2010-07-26 Thread Daniel Díaz
Well, I thought that it may be a more comfortable way to communicate between
us. Specially for newcomers. Don't forget that Haskell is a growing
community.

It's just my opinion.
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Please report any bug of gtk2hs-0.11.0!

2010-07-26 Thread Sebastian Fischer

Hello,

On Jul 13, 2010, at 9:15 AM, Andy Stewart wrote:


Please report any bug of gtk2hs-0.11.0, we will fix it before release
gtk2hs-0.11.1


I have just installed the new Haskell Platform under Mac OS X 10.5.  
With the previous installation of GHC 6.10.4 I managed to install  
gtk2hs manually so I think I have all required Unix libs.


Now, I tried to install gtk2hs from Hackage but didn't succeed.

cabal install gtk2hs-buildtools

works fine but

cabal install gtk

fails with the message

Configuring gtk-0.11.0...
setup: ./Graphics/UI/Gtk/General/IconTheme.chs: invalid argument
cabal: Error: some packages failed to install:
gtk-0.11.0 failed during the building phase. The exception was:
ExitFailure 1

The dependencies seem to be installed properly:

# ghc-pkg --user list | grep 0.11.0
cairo-0.11.0
gio-0.11.0
glib-0.11.0
pango-0.11.0

Has anyone experienced this before? Googling the error message brings  
up a related problem under Solaris but no solution.


Cheers,
Sebastian


--
Underestimating the novelty of the future is a time-honored tradition.
(D.G.)



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


Re: [Haskell-cafe] Typeclasses question in "Real World Haskell" book

2010-07-26 Thread S. Doaitse Swierstra
How about:

*Main> fromJValue (JBool True) :: Either JSONError Bool
Right True
*Main> 

Doaitse


On 26 jul 2010, at 15:16, Angel de Vicente wrote:

> data JValue = JString String
>| JNumber Double
>| JBool Bool
>| JNull
>| JObject [(String, JValue)]
>| JArray [JValue]
>  deriving (Eq, Ord, Show)
> 
> type JSONError = String
> 
> class JSON a where
>toJValue :: a -> JValue
>fromJValue :: JValue -> Either JSONError a
> 
> instance JSON JValue where
>toJValue = id
>fromJValue = Right
> 
> instance JSON Bool where
>toJValue = JBool
>fromJValue (JBool b) = Right b
>fromJValue _ = Left "not a JSON boolean"

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


[Haskell-cafe] Re: Lists and monads

2010-07-26 Thread Kevin Jardine
On Jul 26, 3:26 pm, Bill Atkins  wrote:
> Can you post an example of your code?

Without getting into the complexities, one simple example is a fold
where the step function returns results in a monad.
I have taken to replacing the fold in that case with a recursive
function, which surely is the wrong approach. I think foldM might do
the job but am unsure.

But as I said, that is just an example. I keep wanting to apply the
usual list tools but find that they do not work inside a monad. I find
myself wishing that f (m [a]) just automatically returned m f([a])
without me needing to do anything but I expect that there are reasons
why that is not a good idea.

Kevin



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


Re: [Haskell-cafe] Haskell Forum

2010-07-26 Thread Vo Minh Thu
2010/7/26 Daniel Díaz :
> Hi all,
>
> I want to open a Haskell forum based on phpBB, but I need some collaborators
> for organize its content, and moderate its use. When we have finished, I
> will open this forum for the entire community of Haskell!

Hi,

The idea of a forum has been brought to this list a few times in the
past. Unfortunately for those who thought it was a good idea, it
didn't really catched up.

Haskellers are generaly found of the mailing-list interface.

Beside, with stackoverflow, reddit, #haskell, the wiki, the upcoming
social hackage, ... our bases are nicely covered.

Do you know have some particular ideas that a forum would be a good
new avenue for haskellers?

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


Re: [Haskell-cafe] Actors and message-passing a la Erlang

2010-07-26 Thread Yves Parès
In fact, I noticed Holumbus.

You say that "With the help of this library it is possible to build
Erlang-Style mailboxes", but how would you solve the issue of static typing?

Besides, Holumbus depends on package 'unix', preventing it from being used
on non-unix platforms.


2010/7/26 Stefan Schmidt 

> Hi,
>
> I don't know if this solves your problem, but maybe you should take a look
> at the Holumbus-Distribution package:
>
> http://hackage.haskell.org/package/Holumbus-Distribution
>
> I've build this library because I needed a simple way to transfer messages
> between two haskell processes or threads.The current code can be found under
>
> Holumbus.Distribution.*
>
> especially the DNode and the DStreamPort modules.
>
> The modules located under Holumbus.Network are deprecated.
>
> Best Regards,
>
> Stefan
>
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] Haskell Forum

2010-07-26 Thread Daniel Díaz
Hi all,

I want to open a Haskell forum based on phpBB, but I need some collaborators
for organize its content, and moderate its use. When we have finished, I
will open this forum for the entire community of Haskell!

If you are interested, mail me:
danield...@asofilak.es

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


Re: [Haskell-cafe] Re: Lists and monads

2010-07-26 Thread Bill Atkins
Can you post an example of your code?  mapM and map are actually for pretty 
distinct purposes.

If you find yourself wanting to map over a pure list in monadic code, you 
should really look at applicative style, e.g.:

  import Control.Applicative

  data Struct =  deriving (Read)

  readStructs :: IO [Struct]
  readStructs = map read . lines <$> getContents

It lets you apply a pure function (or a composition of pure functions) to a 
monadic value.  Note that the above is exactly equivalent to:

  readStructs = do
contents <- getContents
return . map read . lines $ contents

On Monday Jul 26, 2010, at 9:13 AM, Kevin Jardine wrote:

> On Jul 26, 3:00 pm, Vo Minh Thu  wrote:
> 
>> Also, just like with IO, maybe restructuring the code to separate
>> monadic code would help.
> 
> The specific monad I am dealing with carries state around inside it.
> 
> I could revert to a pure system in many cases by simply passing the
> state as a parameter but then that defeats the point of the monad and
> clutters up my function calls.
> 
> Also, in other cases, I am using a module that defines its own monads
> and have no choice but to use them.
> 
> I think I would prefer a style of programming where monads are equal
> citizens to pure function calls. There are various hints that such a
> style of programming is possible but as I say, I have not found any
> clear tutorials on it.
> ___
> 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: Lists and monads

2010-07-26 Thread Kevin Jardine
On Jul 26, 3:19 pm, Vo Minh Thu  wrote:
>
> Maybe you missed the part of my answer hinting to applicative style?

No, I saw that but as I mentioned, I am looking for a tutorial. The
source code alone means little to me.

> LYAH has a chapter about it[0].

Thanks for the pointer. I have read LYAH before  (perhaps an earlier
version) and did not notice that chapter. I'll take a look at it.

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


Re: [Haskell-cafe] Re: Lists and monads

2010-07-26 Thread Vo Minh Thu
2010/7/26 Kevin Jardine :
> On Jul 26, 3:00 pm, Vo Minh Thu  wrote:
>
>> Also, just like with IO, maybe restructuring the code to separate
>> monadic code would help.
>
> The specific monad I am dealing with carries state around inside it.
>
> I could revert to a pure system in many cases by simply passing the
> state as a parameter but then that defeats the point of the monad and
> clutters up my function calls.
>
> Also, in other cases, I am using a module that defines its own monads
> and have no choice but to use them.
>
> I think I would prefer a style of programming where monads are equal
> citizens to pure function calls. There are various hints that such a
> style of programming is possible but as I say, I have not found any
> clear tutorials on it.

Maybe you missed the part of my answer hinting to applicative style?
LYAH has a chapter about it[0]. There are other resources about it. I
believe there is a well-known paper that introduced the idea and is
quite readable. RWH uses it with Parsec.

[0] http://learnyouahaskell.com/functors-applicative-functors-and-monoids
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] Typeclasses question in "Real World Haskell" book

2010-07-26 Thread Angel de Vicente

Hi,

I'm stuck at page 151 of Real World Haskell and hoping that perhaps some 
of you can give me a hand here...


The code that is giving me trouble is below.

data JValue = JString String
| JNumber Double
| JBool Bool
| JNull
| JObject [(String, JValue)]
| JArray [JValue]
  deriving (Eq, Ord, Show)

type JSONError = String

class JSON a where
toJValue :: a -> JValue
fromJValue :: JValue -> Either JSONError a

instance JSON JValue where
toJValue = id
fromJValue = Right

instance JSON Bool where
toJValue = JBool
fromJValue (JBool b) = Right b
fromJValue _ = Left "not a JSON boolean"


I don't understand how the JSON typeclass is defined, in particular the
fromJValue definition.

For instance, when defining the instance for Bool types, then I
understand that both functions (toJValue and fromJValue) will be called
upon when we supply a Bool type, but then the (JBool b) type in function 
fromJValue doesn't match


toJValue is no problem, but I cannot understand how fromJValue is
supposed to work, and the comments in the online book
(http://book.realworldhaskell.org/read/using-typeclasses.html) don't
help with this either.

 *Main> :load ch6
[1 of 1] Compiling Main ( ch6.hs, interpreted )
Ok, modules loaded: Main.
*Main> toJValue False
JBool False
*Main> :type it
it :: JValue
*Main> fromJValue False

:1:11:
Couldn't match expected type `JValue' against inferred type `Bool'
In the first argument of `fromJValue', namely `False'
In the expression: fromJValue False
In the definition of `it': it = fromJValue False
*Main> fromJValue (JBool False)

:1:0:
Ambiguous type variable `a' in the constraint:
  `JSON a' arising from a use of `fromJValue' at :1:0-23
Probable fix: add a type signature that fixes these type variable(s)
*Main>



Any pointers?

Thanks a lot,
Ángel de Vicente
--
http://www.iac.es/galeria/angelv/

High Performance Computing Support PostDoc
Instituto de Astrofísica de Canarias
-
ADVERTENCIA: Sobre la privacidad y cumplimiento de la Ley de Protección de 
Datos, acceda a http://www.iac.es/disclaimer.php
WARNING: For more information on privacy and fulfilment of the Law concerning 
the Protection of Data, consult http://www.iac.es/disclaimer.php?lang=en

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


[Haskell-cafe] Re: Lists and monads

2010-07-26 Thread Kevin Jardine
On Jul 26, 3:00 pm, Vo Minh Thu  wrote:

> Also, just like with IO, maybe restructuring the code to separate
> monadic code would help.

The specific monad I am dealing with carries state around inside it.

I could revert to a pure system in many cases by simply passing the
state as a parameter but then that defeats the point of the monad and
clutters up my function calls.

Also, in other cases, I am using a module that defines its own monads
and have no choice but to use them.

I think I would prefer a style of programming where monads are equal
citizens to pure function calls. There are various hints that such a
style of programming is possible but as I say, I have not found any
clear tutorials on it.
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Random this! ;-)

2010-07-26 Thread Edward Kmett
On Sun, Jul 25, 2010 at 11:39 AM, michael rice  wrote:

> Hi All,
>
> From: http://en.wikibooks.org/wiki/Haskell/Understanding_monads/State
>
>Exercises
>
>1. Implement a function rollNDiceIO :: Int -> IO [Int] that,
>   given an integer, returns a list with that number of pseudo-
>   random integers between 1 and 6.
>
>
> After a lot of learning what not to do, this is the best I could come up
> with.
>
> rollNDiceIO :: Int -> IO [Int]
> rollNDiceIO n = mapM (\x -> randomRIO(1,6)) (replicate n 1)
>
> I know, ugly, but at least I got it to work. What's a better way to
> generate this list?
>
>
An even better method lets the list be generated lazily.

import Data.Functor ((<$>))
import Random

rollDice :: IO [Int]
rollDice =  randomRs (1,6) <$> newStdGen

rollNDice :: Int -> IO [Int]
rollNDice n = take n <$> rollDice

This is important because randomRIO has to peek at an MVar to determine the
current value of the random number seed _for each die rolled_, but using
randomRs on a fresh StdGen only has does so once.

Moreover, it gives you the more general 'rollDice' funtion, which can give
you an infinite list of random dice rolls. Trying to implement that function
using the approach you used will lead to a computation that won't terminate.

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


  1   2   >