[Haskell-cafe] How to input Unicode string in Haskell program?

2013-02-21 Thread Semyon Kholodnov
Imagine we have this simple program:

module Main(main) where

main = do
x - getLine
putStrLn x

Now I want to run it somehow, enter résumé 履歴書 резюме and see this
string printed back as résumé 履歴書 резюме. Now, the first problem is
that my computer runs Windows, which means that I can't use ghci
:main or result of ghc main.hs to enter such an outrageous string
— Windows console is locked to one specific local code page, and no
codepage contains Latin-1, Cyrillic and Kanji symbols at the same
time.

But there is also WinGHCi. So I do :main, copy-paste this string
into the window (It works! Because Windows has Unicode for 20 years
now), but the output is all messed up. In a rather curious way,
actually: the input string is converted to UTF-8 byte string, and its
bytes are treated as being characters from my local code page.

So, it appears that I have no way to enter Unicode strings into my
Haskell programs by hands, I should read them from files. That's sad,
and I refuse to think I am the first one with such a problem, so I
assume there is a solution/workaround. Now would someone please tell
me this solution? Except from Just stick to 127 letters of ASCII, of
course.

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


Re: [Haskell-cafe] Parser left recursion

2013-02-21 Thread S. Doaitse Swierstra
As mentioned before, the way to handle this specific problem is to use either  
the pChainl or pChainr parser combinators, as e.g. found on:

http://hackage.haskell.org/packages/archive/uu-parsinglib/2.7.4.1/doc/html/Text-ParserCombinators-UU-Derived.html

and many similar libraries. So one can write:

pExpr = pChainl ( (+) $ pSym ' ')) pFactor
pFactor = iI '(' pExpr ')' Ii | pInteger | pIdentifier 

What is even nicer is that one can easily extend this to deal with many 
different operators:

pExpr = foldr nextop [((+),'+'), ((*), '*'))] pGactor
where nextop (sem,sym) = pChainl sem $ pSym sym))

It is obvious how to extend this further into operators with the same priority 
or being right associative. See furthermore:

@inproceedings{Fokker95:0,
  title = {Functional Parsers},
  author = {Jeroen Fokker},
  year = {1995},
  tags = {parsing},
  researchr = {http://dutieq.st.ewi.tudelft.nl/publication/Fokker95%3A0},
  cites = {0},
  citedby = {0},
  pages = {1-23},
  booktitle = {Advanced Functional Programming, First International Spring 
School on Advanced Functional Programming Techniques, Båstad, Sweden, May 
24-30, 1995, Tutorial Text},
  editor = {Johan  Jeuring and Erik Meijer},
  volume = {925},
  series = {Lecture Notes in Computer Science},
  publisher = {Springer},
  isbn = {3-540-59451-5},
}

Most left recursion stems from the fact that conventional CFG notation is 
sufficient, but unfortunately not ideally suited, to express oft occurring 
patterns. This is where parser combinators come in: they allow one to express 
what one wants to say instead of having to encode it using recursion, etc.

If you have a really nasty grammar where left recursion removal by hand would 
ruin your grammar, you may use a transform like the LeftCornerTransform as used 
e.g. in the ChristmasTree package, which removes the problem of exponential 
time behaviour of reading Haskell data types with infix operators. See: 
http://hackage.haskell.org/package/ChristmasTree-0.2, and which has been 
described in:

@article{DBLP
:journals/entcs/BaarsSV10,
  author= {Arthur I. Baars and
   S. Doaitse Swierstra and
   Marcos Viera},
  title = {Typed Transformations of Typed Grammars: The Left Corner
   Transform},
  journal   = {Electr. Notes Theor. Comput. Sci.},
  volume= {253},
  number= {7},
  year  = {2010},
  pages = {51-64},
  ee= {http://dx.doi.org/10.1016/j.entcs.2010.08.031},
  bibsource = {DBLP, http://dblp.uni-trier.de}
}

Doaitse



On Feb 20, 2013, at 8:13 , Martin Drautzburg martin.drautzb...@web.de wrote:

 Hello all,
 
 this was previously asked on haskell-beginners, but only partially answered.
 
 As an exercise I am writing a parser roughly following the expamples in 
 Graham 
 Hutton's book. The language contains things like:
 
 data Exp = Lit Int -- literal integer
 | Plus Exp Exp
 
 My naive parser enters an infinite recursion, when I try to parse 1+2. I do 
 understand why:
 
 hmm, this expression could be a plus, but then it must start with an 
 expression, lets check. 
 
 and it tries to parse expression again and again considers Plus.
 
 Twan van Laarhoven told me that:
 
 Left-recursion is always a problem for recursive-descend parsers.
 
 and suggested to do something like:
 
parseExp = do
  lit - parseLit
  pluses - many (parsePlusToken * parseLit)
  return (combinePlusesWithLit lit pluses)
 
combinePlusesWithLit = foldr Plus -- or foldl
 
 This indeed does the trick, but only when the first token is a Lit (literal 
 integer). 
 
 I then added the possibility to optionally put things in parentheses. But 
 then  
 I cannot parse (1+2)+3. The original code fails, because (1+2) is not a 
 Lit and when I allow an expression as the first argument to + I get 
 infinite 
 recursion again.
 
 I am generally confused, that saying a plus expression is an integer 
 followed 
 by many plus somethings is not what the language says. So this requires a 
 lot of paying attention to get right. I'd much rather say a plus 
 expression 
 is two expressions with a '+' in between.
 
 I do know for sure, that it is possible to parse (1+2)+3 (ghci does it just 
 fine). But I seem to be missing a trick.
 
 Can anyone shed some light on this?
 
 -- 
 Martin
 
 ___
 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] question about: --hyperlink-source

2013-02-21 Thread Doaitse Swierstra
I ran into the problem that for the packages which I install using

cabal install

The generated html does not contain links to the sources. This issue was raised 
before in:

http://stackoverflow.com/questions/1587635/haddock-for-cabal-installed-modules

I have been looking into the documentation available, but could not find a way 
to set this e.g. as a default in some .haddock file. 

Am I overlooking something?

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


Re: [Haskell-cafe] ANN: data-fix-cse -- Common subexpression elimination for EDSLs

2013-02-21 Thread Emil Axelsson

This should be possible using higher-order terms, as in

http://hackage.haskell.org/packages/archive/compdata/latest/doc/html/Data-Comp-Multi-Term.html

The only complication I see is that the Dag nodes would get 
heterogeneous types requiring existential quantification with a 
`Typeable` constraint. A better representation might be typed ASGs [1]


Syntactic has typed ASTs and it has a module that does something similar 
to data-fix-cse (uses a combination of stable names and hashing), but it 
needs some fixing up.


/ Emil

[1]: http://dl.acm.org/citation.cfm?id=2426909


2013-02-20 01:58, Conal Elliott skrev:

Do you think the approach can be extended for non-regular (nested)
algebraic types (where the recursive data type is sometimes at a
different type instance)? For instance, it's very handy to use GADTs to
capture embedded language types in host language (Haskell) types, which
leads to non-regularity.



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


Re: [Haskell-cafe] question about: --hyperlink-source

2013-02-21 Thread Ivan Lazar Miljenovic
On 21 February 2013 21:18, Doaitse Swierstra doai...@swierstra.net wrote:
 I ran into the problem that for the packages which I install using

 cabal install

 The generated html does not contain links to the sources. This issue was 
 raised before in:

 http://stackoverflow.com/questions/1587635/haddock-for-cabal-installed-modules

 I have been looking into the documentation available, but could not find a 
 way to set this e.g. as a default in some .haddock file.

 Am I overlooking something?

I don't think this is currently possible:
https://github.com/haskell/cabal/issues/510


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



-- 
Ivan Lazar Miljenovic
ivan.miljeno...@gmail.com
http://IvanMiljenovic.wordpress.com

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


Re: [Haskell-cafe] How to input Unicode string in Haskell program?

2013-02-21 Thread MigMit
Have you tried running ghci inside Emacs?

Отправлено с iPhone

21.02.2013, в 13:58, Semyon Kholodnov joker...@gmail.com написал(а):

 Imagine we have this simple program:
 
 module Main(main) where
 
 main = do
x - getLine
putStrLn x
 
 Now I want to run it somehow, enter résumé 履歴書 резюме and see this
 string printed back as résumé 履歴書 резюме. Now, the first problem is
 that my computer runs Windows, which means that I can't use ghci
 :main or result of ghc main.hs to enter such an outrageous string
 — Windows console is locked to one specific local code page, and no
 codepage contains Latin-1, Cyrillic and Kanji symbols at the same
 time.
 
 But there is also WinGHCi. So I do :main, copy-paste this string
 into the window (It works! Because Windows has Unicode for 20 years
 now), but the output is all messed up. In a rather curious way,
 actually: the input string is converted to UTF-8 byte string, and its
 bytes are treated as being characters from my local code page.
 
 So, it appears that I have no way to enter Unicode strings into my
 Haskell programs by hands, I should read them from files. That's sad,
 and I refuse to think I am the first one with such a problem, so I
 assume there is a solution/workaround. Now would someone please tell
 me this solution? Except from Just stick to 127 letters of ASCII, of
 course.
 
 ___
 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] PhD Studentship in Nottingham

2013-02-21 Thread Graham Hutton
Dear all,

The School of Computer Science at the University of Nottingham
is currently advertising a PhD position on applying functional
programming techniques to optimisation problems:

   http://www.cs.nott.ac.uk/~ajp/PhD-opportunities.htm

This would be a great position for someone who is interested
in applying FP ideas to real-world problems.  The closing
date for applications is 28th February 2013.  If you have
any queries about the position, please contact Andrew
Parkes andrew.par...@nottingham.ac.uk.

Best wishes,

Graham

--  
Prof Graham Hutton
Functional Programming Lab
School of Computer Science
University of Nottingham, UK
http://www.cs.nott.ac.uk/~gmh


This message and any attachment are intended solely for the addressee and may 
contain confidential information. If you have received this message in error, 
please send it back to me, and immediately delete it.   Please do not use, copy 
or disclose the information contained in this message or in any attachment.  
Any views or opinions expressed by the author of this email do not necessarily 
reflect the views of the University of Nottingham.

This message has been checked for viruses but the contents of an attachment
may still contain software viruses which could damage your computer system:
you are advised to perform your own checks. Email communications with the
University of Nottingham may be monitored as permitted by UK legislation.

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


Re: [Haskell-cafe] How to input Unicode string in Haskell program?

2013-02-21 Thread Erik Hesselink
You can also set the locale encoding for a handle (e.g.
System.IO.stdin) from code using `System.IO.hSetEncoding` [0].

Erik

[0] 
http://hackage.haskell.org/packages/archive/base/latest/doc/html/System-IO.html#v:hSetEncoding

On Thu, Feb 21, 2013 at 12:07 PM, Alexander V Vershilov
alexander.vershi...@gmail.com wrote:
 The problem is that Prelude.getLine uses current locale to load characters:
 for example if you have utf8 locale, then everything works out of the box:

 $ runhaskell 1.hs
 résumé 履歴書 резюме
 résumé 履歴書 резюме

 But if you change locale you'll have error:

 LANG=C runhaskell 1.hs
 résumé 履歴書 резюме
 1.hs: stdin: hGetLine: invalid argument (invalid byte sequence)

 To force haskell use UTF8 you can load string as byte sequence and convert
 it to UTF-8
 charecters for example by

 import qualified Data.ByteString as S
 import qualified Data.Text.Encoding as T

 main = do
 x - fmap T.decodeUtf8 S.getLine

 now code will work even with different locale, and you'll load UTF8 from
 shell
  independenty of user input's there

 --
 Alexander


 On 21 February 2013 13:58, Semyon Kholodnov joker...@gmail.com wrote:

 Imagine we have this simple program:

 module Main(main) where

 main = do
 x - getLine
 putStrLn x

 Now I want to run it somehow, enter résumé 履歴書 резюме and see this
 string printed back as résumé 履歴書 резюме. Now, the first problem is
 that my computer runs Windows, which means that I can't use ghci
 :main or result of ghc main.hs to enter such an outrageous string
 — Windows console is locked to one specific local code page, and no
 codepage contains Latin-1, Cyrillic and Kanji symbols at the same
 time.

 But there is also WinGHCi. So I do :main, copy-paste this string
 into the window (It works! Because Windows has Unicode for 20 years
 now), but the output is all messed up. In a rather curious way,
 actually: the input string is converted to UTF-8 byte string, and its
 bytes are treated as being characters from my local code page.

 So, it appears that I have no way to enter Unicode strings into my
 Haskell programs by hands, I should read them from files. That's sad,
 and I refuse to think I am the first one with such a problem, so I
 assume there is a solution/workaround. Now would someone please tell
 me this solution? Except from Just stick to 127 letters of ASCII, of
 course.

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




 --
 Alexander

 ___
 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] Fwd: How to input Unicode string in Haskell program?

2013-02-21 Thread Semyon Kholodnov
-- Forwarded message --
From: Semyon Kholodnov joker...@gmail.com
Date: Thu, 21 Feb 2013 16:26:58 +0400
Subject: Re: [Haskell-cafe] How to input Unicode string in Haskell program?
To: Alexander V Vershilov alexander.vershi...@gmail.com

I know that this problem doesn't exist on Linux. But I work on
Windows. And I use WinGHCi primarily, because it has RTF component in
it which shows Unicode. But it turns out WinGHCi merely sends commands
and receives results to/from ghci.exe. And it does it in a weird way:
it sets ghci's console code pages to current system codepages (ACP),
reads results from ghci as ACP, but sends commands to it as UTF8.
Which got interpreted as ACP.

Now, however, I have a fix for WinGHCi: in StartGHCI.c one should replace

SetConsoleOutputCP(GetACP());
SetConsoleCP(GetACP());

with

SetConsoleOutputCP(CP_UTF8);
SetConsoleCP(CP_UTF8);

and in Utf8.c, in UnicodeToLocalCodePage() body, WideCharToMultiByte(
CP_ACP has to be replaced with WideCharToMultiByte( CP_UTF8, and in
LocalCodePageToUnicode() body, MultiByteToWideChar( CP_ACP has to be
replaced with MultiByteToWideChar( CP_UTF8. After recompiling,
everything works great:

Prelude x - getLine
résumé 履歴書 резюме
Prelude putStrLn x
résumé 履歴書 резюме
Prelude

Is there any way to ask for this fix to be included in WinGHCi and
Haskell Platform?

2013/2/21, Alexander V Vershilov alexander.vershi...@gmail.com:
 The problem is that Prelude.getLine uses current locale to load characters:
 for example if you have utf8 locale, then everything works out of the box:

 $ runhaskell 1.hs
 résumé 履歴書 резюме
 résumé 履歴書 резюме

 But if you change locale you'll have error:

 LANG=C runhaskell 1.hs
 résumé 履歴書 резюме
 1.hs: stdin: hGetLine: invalid argument (invalid byte sequence)

 To force haskell use UTF8 you can load string as byte sequence and convert
 it to UTF-8
 charecters for example by

 import qualified Data.ByteString as S
 import qualified Data.Text.Encoding as T

 main = do
 x - fmap T.decodeUtf8 S.getLine

 now code will work even with different locale, and you'll load UTF8 from
 shell
  independenty of user input's there

 --
 Alexander


 On 21 February 2013 13:58, Semyon Kholodnov joker...@gmail.com wrote:

 Imagine we have this simple program:

 module Main(main) where

 main = do
 x - getLine
 putStrLn x

 Now I want to run it somehow, enter résumé 履歴書 резюме and see this
 string printed back as résumé 履歴書 резюме. Now, the first problem is
 that my computer runs Windows, which means that I can't use ghci
 :main or result of ghc main.hs to enter such an outrageous string
 — Windows console is locked to one specific local code page, and no
 codepage contains Latin-1, Cyrillic and Kanji symbols at the same
 time.

 But there is also WinGHCi. So I do :main, copy-paste this string
 into the window (It works! Because Windows has Unicode for 20 years
 now), but the output is all messed up. In a rather curious way,
 actually: the input string is converted to UTF-8 byte string, and its
 bytes are treated as being characters from my local code page.

 So, it appears that I have no way to enter Unicode strings into my
 Haskell programs by hands, I should read them from files. That's sad,
 and I refuse to think I am the first one with such a problem, so I
 assume there is a solution/workaround. Now would someone please tell
 me this solution? Except from Just stick to 127 letters of ASCII, of
 course.

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




 --
 Alexander


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


Re: [Haskell-cafe] Unused definitions across modules in a package

2013-02-21 Thread Felipe Almeida Lessa
On Wed, Feb 20, 2013 at 9:20 PM, Ivan Lazar Miljenovic
ivan.miljeno...@gmail.com wrote:
 My (getting-long-in-the-tooth-and-could-do-with-a-rewrite) SourceGraph
 package does identify these definitions.

What a coincidence, then!  I was trying to use SourceGraph for other
reasons but it didn't work for my codebase.  I haven't investigated
with it couldn't parse the files, though, and I use many extensions.

Nice to know that it supports this feature =).

Cheers,

-- 
Felipe.

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


[Haskell-cafe] ANNOUNCE: mcpi-0.0.0.2 (The MineCraft-Pi API in Haskell)

2013-02-21 Thread Doug Burke
I have released versions 0.0.0.1 and 0.0.0.2 (the latter being
documentation improvements but it hasn't yet been built) of mcpi:

  http://hackage.haskell.org/package/mcpi
  https://github.com/DougBurke/hmcpi

It is a very simple, and very incomplete, interface to MineCraft: Pi edition

  http://pi.minecraft.net/

Now I just need to find out how to get ghc 7.4.2 on my Raspberry Pi (oops,
I mean the Raspberry Pi I told my wife I bought as a Christmas gift for the
kids) so that I can use this from ghci.

Any comments and improvements are more than welcome,
Doug
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] generalized, tail-recursive left fold that can

2013-02-21 Thread Roman Cheplyaka
Thanks, I see now where my mistake was.

Laziness (or call by name) is needed to make the step from

  (\e a z - a (f z e))
(head l)
(foldr (\e a z - a (f z e)) id (tail l) z)
(f z (head l))

to

  \z - foldr (\e a z - a (f z e)) id (tail l) (f z (head l))

without evaluating foldr further.

Roman

* o...@okmij.org o...@okmij.org [2013-02-20 04:23:34-]
 
   That said, to express foldl via foldr, we need a higher-order
   fold. There are various problems with higher-order folds, related to
   the cost of building closures. The problems are especially severe 
   in strict languages or strict contexts. Indeed,
   
   foldl_via_foldr f z l = foldr (\e a z - a (f z e)) id l z
   
   first constructs the closure and then applies it to z. The closure has
   the same structure as the list -- it is isomorphic to the
   list. However, the closure representation of a list takes typically
   quite more space than the list. So, in strict languages, expressing
   foldl via foldr is a really bad idea. It won't work for big lists.
 
  If we unroll foldr once (assuming l is not empty), we'll get
 
\z - foldr (\e a z - a (f z e)) id (tail l) (f z (head l))
 
  which is a (shallow) closure. In order to observe what you describe (a
  closure isomorphic to the list) we'd need a language which does
  reductions inside closures.
 
 I should've elaborated this point.
 
 Let us consider monadic versions of foldr and foldl. First, monads,
 sort of emulate strict contexts, making it easier to see when
 closures are constructed. Second, we can easily add tracing.
 
 
 import Control.Monad.Trans
 
 -- The following is just the ordinary foldr, with a specialized
 -- type for the seed: m z
 foldrM :: Monad m =
   (a - m z - m z) - m z - [a] - m z
 -- The code below is identical to that of foldr
 foldrM f z [] = z
 foldrM f z (h:t) = f h (foldrM f z t)
 
 -- foldlM is identical Control.Monad.foldM 
 -- Its code is shown below for reference.
 foldlM, foldlM' :: Monad m =
   (z - a - m z) - z - [a] - m z
 foldlM f z []= return z
 foldlM f z (h:t) = f z h = \z' - foldlM f z' t
 
 t1 = foldlM (\z a - putStrLn (foldlM:  ++ show a) 
  return (a:z)) [] [1,2,3]
 
 {-
 foldlM: 1
 foldlM: 2
 foldlM: 3
 [3,2,1]
 -}
 
 -- foldlM' is foldlM expressed via foldrM
 foldlM' f z l = 
 foldrM (\e am - am = \k - return $ \z - f z e = k)
(return return) l = \f - f z
 
 -- foldrM'' is foldlM' with trace printing
 foldlM'' :: (MonadIO m, Show a) =
   (z - a - m z) - z - [a] - m z
 foldlM'' f z l = 
 foldrM (\e am - liftIO (putStrLn $ foldR:  ++ show e) 
 am = \k - return $ \z - f z e = k)
(return return) l = \f - f z
 
 
 t2 = foldlM'' (\z a - putStrLn (foldlM:  ++ show a) 
return (a:z)) [] [1,2,3]
 
 {-
 foldR: 1
 foldR: 2
 foldR: 3
 foldlM: 1
 foldlM: 2
 foldlM: 3
 [3,2,1]
 -}
 
 
 As we can see from the trace printing, first the whole list is
 traversed by foldR and the closure is constructed. Only after foldr
 has finished, the closure is applied to z ([] in our case), and
 foldl's function f gets a chance to work. The list is effectively
 traversed twice, which means the `copy' of the list has to be
 allocated -- that is, the closure that incorporates the calls to
 f e1, f e2, etc. 
 

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


[Haskell-cafe] websockets client

2013-02-21 Thread Stephen Olsen
Are there any good websockets client libraries for haskell. I've been searching 
for one but can only come up with server implementations.

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


Re: [Haskell-cafe] websockets client

2013-02-21 Thread Yuras Shumovich
Hi,

websockets package has basic support for client-side applications:
http://hackage.haskell.org/packages/archive/websockets/0.7.2.1/doc/html/Network-WebSockets.html#g:12

AFAIK it is the only available option right now (except implementing it
yourself.)

Thanks,
Yuras

On Thu, 2013-02-21 at 16:09 -0500, Stephen Olsen wrote:
 Are there any good websockets client libraries for haskell. I've been 
 searching for one but can only come up with server implementations.
 
 ___
 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] websockets client

2013-02-21 Thread Patrick Mylund Nielsen
Yes, Jasper's websockets has a client in recent versions that works really
nicely since server and client have the same APIs.

The example was a little hidden:
https://github.com/jaspervdj/websockets/blob/master/example/client.hs




On Thu, Feb 21, 2013 at 10:09 PM, Stephen Olsen steve.ol...@gmail.comwrote:

 Are there any good websockets client libraries for haskell. I've been
 searching for one but can only come up with server implementations.

 ___
 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] GHC panicking when using -fext-core -O2

2013-02-21 Thread Christian Gosch

Hi Cafe,

when I try to create core files with the above options, ghc panics with 
this message:


ghc: panic! (the 'impossible' happened)
  (GHC version 7.6.2 for x86_64-unknown-linux):
make_exp (App _ (Coercion _))

Please report this as a GHC bug: http://www.haskell.org/ghc/reportabug


I tried this with 7.4.1 and with 7.6.2.
Does anyone have an idea why this could happen, without looking at the 
code I am trying to compile?


Thanks for any hint,
Christian


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