[Haskell-cafe] cpphs calls error when it finds an #error declaration

2013-08-27 Thread Niklas Hambüchen
Hi,

after some debugging of a higher-level tool I found out that when I use
cpphs as a library and the `runCpphs` function that is to produce the
preprocessed output, when it comes across the #error directive it will
terminate my program.

This is because handling #error is implemented with Haskell's `error`.

I find that slightly unfortunate since it means I cannot distinguish
betwen an #error written in the input file and a programming error
inside cpphs.

@Malcolm, would you mind a change towards throwing an exception that is
different from error so that it can be easily caught, or even better, a
change from

runCpphs :: ... -> IO String

to

runCpphs :: ... -> IO (Either String String)

or similar?

If an exception based interface is kept, it would be nice to add some
haddock to `runCpphs`; not knowing about the existence of #error, it is
easy to assume that the IO is only used for accessing the FilePath
passed in.

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


Re: [Haskell-cafe] Template Haskell

2013-08-27 Thread Niklas Hambüchen
Hi Jose,

Template Haskell doesn't parse code.

haskell-src-exts and the GHC API can do that.

Have a look at:

* ghc-mod browse (using ghc api)
* hscope (using haskell-src-exts)

On 27/08/13 15:45, Jose A. Lopes wrote:
> Hi,
> 
> Is it possible to retrieve all definitions contained in a module using
> Template Haskell ?
> 
> Thanks,
> Jose
> 

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


Re: [Haskell-cafe] Template Haskell

2013-08-27 Thread Jose A. Lopes
Thanks,
Jose
-- 
Jose Antonio Lopes
Ganeti Engineering
Google Germany GmbH
Dienerstr. 12, 80331, München

Registergericht und -nummer: Hamburg, HRB 86891
Sitz der Gesellschaft: Hamburg
Geschäftsführer: Graham Law, Christine Elizabeth Flores
Steuernummer: 48/725/00206
Umsatzsteueridentifikationsnummer: DE813741370

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


Re: [Haskell-cafe] sequence causing stack overflow on pretty small lists

2013-08-27 Thread Patrick Palka
On Mon, Aug 26, 2013 at 4:46 AM, Niklas Hambüchen  wrote:

> On #haskell we recently had a discussion about the following:
>
>import System.Random
>
>list <- replicateM 100 randomIO :: IO [Int]
>
> I would think that this gives us a list of a million random Ints. In
> fact, this is what happens in ghci. But with ghc we get:
>
>Stack space overflow: current size 8388608 bytes.
>Use `+RTS -Ksize -RTS' to increase it.
>
>
You can use ContT to force the function to use heap instead of stack space,
e.g. runContT (replicateM 100 (lift randomIO)) return
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] sequence causing stack overflow on pretty small lists

2013-08-27 Thread Niklas Hambüchen
On 27/08/13 20:37, Patrick Palka wrote:
> You can use ContT to force the function to use heap instead of stack
> space, e.g. runContT (replicateM 100 (lift randomIO)) return

That is interesting, and works.

Unfortunately its pure existence will not fix sequence, mapM etc. in base.

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


Re: [Haskell-cafe] sequence causing stack overflow on pretty small lists

2013-08-27 Thread Tom Ellis
On Mon, Aug 26, 2013 at 12:05:14PM -0700, Bryan O'Sullivan wrote:
> On Mon, Aug 26, 2013 at 1:46 AM, Niklas Hambüchen  wrote:
> > This is because sequence is implemented as
> >
> >  sequence (m:ms) = do x <- m
> >   xs <- sequence ms
> >   return (x:xs)
> >
> > and uses stack space when used on some [IO a].
> >
> 
> This problem is not due to sequence, which doesn't need to add any
> strictness here. It occurs because the functions in System.Random are
> excessively lazy. In particular, randomIO returns an unevaluated thunk.

I don't understand this.  The same stack overflow occurs with

tenmil :: Int
tenmil = 10 * 1000 * 1000

main :: IO ()
main = do  
list <- replicateM tenmil (return ()) :: IO [()] 
list `seq` return ()

"return ()" is not excessiely lazy, is it?  Could you explain further?

Tom

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


[Haskell-cafe] enumerators: exception that can't be catched

2013-08-27 Thread Yuras Shumovich
Hello,

I'm debugging an issue in "websockets" package,
https://github.com/jaspervdj/websockets/issues/42

I'm not familiar with "enumerator" package (websockets are based on it),
so I'm looking for help. The exception is throws inside "enumSocket"
enumerator using
"throwError" ( 
http://hackage.haskell.org/packages/archive/network-enumerator/0.1.5/doc/html/src/Network-Socket-Enumerator.html#enumSocket
 ), but I can't catch it with "catchError". It is propagated to "run" function:
   : recv: resource vanished (Connection reset by peer)

The question is: how is it possible? could it be a bug in "enumerator"
package?

Thanks,
Yuras


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


Re: [Haskell-cafe] enumerators: exception that can't be catched

2013-08-27 Thread Ben Doyle
This is partially guesswork, but the code to catchWSError looks dubious:

catchWsError :: WebSockets p a

 -> (SomeException -> WebSockets p a) ->
WebSockets p a  catchWsError act c = WebSockets $ do  env <- ask
   let it  = peelWebSockets env $ act  cit = peelWebSockets
env . c  lift $ it `E.catchError` citwhere  peelWebSockets
env = flip runReaderT env . unWebSockets


Look at `cit`. It runs the recovery function, then hands the
underlying Iteratee the existing environment. That's fine if `act` is
at fault, but there are Iteratee- and IO-ish things in
WebSocketsEnv---if one of `envSink` or `envSendBuilder` is causing the
exception, it'll just get re-thrown after `E.catchError`. (I think.
That's the guesswork part.)

So check how `envSendBuilder` is built up, and see if there's a way it
could throw an exception on client disconnect.



On Tue, Aug 27, 2013 at 10:28 AM, Yuras Shumovich wrote:

> Hello,
>
> I'm debugging an issue in "websockets" package,
> https://github.com/jaspervdj/websockets/issues/42
>
> I'm not familiar with "enumerator" package (websockets are based on it),
> so I'm looking for help. The exception is throws inside "enumSocket"
> enumerator using
> "throwError" (
> http://hackage.haskell.org/packages/archive/network-enumerator/0.1.5/doc/html/src/Network-Socket-Enumerator.html#enumSocket),
>  but I can't catch it with "catchError". It is propagated to "run"
> function:
>: recv: resource vanished (Connection reset by peer)
>
> The question is: how is it possible? could it be a bug in "enumerator"
> package?
>
> Thanks,
> Yuras
>
>
> ___
> 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] Template Haskell: let statement in a splice put in the "main = do" part of a program?

2013-08-27 Thread TP
adam vogt wrote:

> TH quotes limited as you've noticed. One way to generate similar code
> is to note that:
> 
> do
>   let x = y
>   z
> 
> is the same as let x = y in do z. You can generate the latter with
> something like the following file, but the `a' isn't in scope for the
> second argument to makeLetStatement. The uglier $(dyn "a") works,
> though I suppose it's more verbose than manually in-lining the
> variable a.
> 
> {-# LANGUAGE TemplateHaskell #-}
> import Language.Haskell.TH
> 
> main = $(let
> 
> makeLetStatement :: String -> ExpQ -> ExpQ
> makeLetStatement s rest = letE [ valD (varP (mkName s))
> (normalB $ stringE s) []]
> rest
> 
> in makeLetStatement "a" [| print $(dyn "a") |] )

Thanks Adam.
Unfortunately, this solution is not satisfying because the goal is to put 
only one mention to "a" in the "main" part, putting all the repetitive code 
and ExpQ's in a separate module. Tonight, I've tried hard one more time 
without more success.
Maybe I have to stick to non-let expressions in the "main" part of a script, 
when it comes to TH. It should nevertheless allow me to call functions, make 
tests, etc.

Thanks,

TP


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


Re: [Haskell-cafe] sequence causing stack overflow on pretty small lists

2013-08-27 Thread John Lato
IMHO it's perfectly reasonable to expect sequence/replicateM/mapM to be
able to handle a list of ~1e6 elements in the Unescapable Monad (i.e. IO).
All the alternate implementations in the world won't be as handy as
Prelude.sequence, and no amount of documentation will prevent people from
running into this headlong*.  So unless there's a downside to upping the
stack size limitation I'm unaware of, +1 to that suggestion from me.

John
[1] Most people are physically incapable of reading documents that explain
why what they want to do won't work.  Even if people did read the
documentation, I suspect that the people most in need of the information
would be the least likely to understand how it applies to their situation.



On Tue, Aug 27, 2013 at 9:19 PM, John Alfred Nathanael Chee <
cheech...@gmail.com> wrote:

> This is somewhat related: http://ghc.haskell.org/trac/ghc/ticket/4219
>
> This also solves the concrete problem you gave in your original post
> (in reverse order):
>
> import Control.Monad
> import System.Random
>
> sequencel :: Monad m => [m a] -> m [a]
> sequencel = foldM (\tail m -> (\x -> return $ x : tail) =<< m) []
>
> main :: IO ()
> main = print =<< sequencel (replicate 100 (randomIO :: IO Integer))
>
> Following on Reid's point, maybe it's worth noting in the
> documentation that replicateM, mapM, and sequence are not tail
> recursive for Monads that define (>>=) as strict in the first
> argument?
>
> On Tue, Aug 27, 2013 at 6:07 AM, Niklas Hambüchen  wrote:
> > On 27/08/13 20:37, Patrick Palka wrote:
> >> You can use ContT to force the function to use heap instead of stack
> >> space, e.g. runContT (replicateM 100 (lift randomIO)) return
> >
> > That is interesting, and works.
> >
> > Unfortunately its pure existence will not fix sequence, mapM etc. in
> base.
> >
> > ___
> > Libraries mailing list
> > librar...@haskell.org
> > http://www.haskell.org/mailman/listinfo/libraries
>
>
>
> --
> Love in Jesus Christ, John Alfred Nathanael Chee
> http://www.biblegateway.com/
> http://web.cecs.pdx.edu/~chee/
>
> ___
> Libraries mailing list
> librar...@haskell.org
> http://www.haskell.org/mailman/listinfo/libraries
>
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe