[Haskell-cafe] Re: Do expression definition

2010-09-13 Thread Gleb Alexeyev
On 09/13/2010 12:23 PM, Michael Lazarev wrote: 2010/9/13 Henning Thielemannlemm...@henning-thielemann.de: It means that variables bound by let, may be instantiated to different types later. Can you give an example, please? testOk = let f = id in (f 42, f True) --testNotOk :: Monad m = m

[Haskell-cafe] Re: Do expression definition

2010-09-13 Thread Gleb Alexeyev
On 09/13/2010 12:38 PM, Thomas Davie wrote: On 13 Sep 2010, at 10:28, Gleb Alexeyev wrote: On 09/13/2010 12:23 PM, Michael Lazarev wrote: 2010/9/13 Henning Thielemannlemm...@henning-thielemann.de: It means that variables bound by let, may be instantiated to different types later. Can you

[Haskell-cafe] Re: Do expression definition

2010-09-13 Thread Gleb Alexeyev
On 09/13/2010 12:45 PM, Gleb Alexeyev wrote: is, pardon my pun, not ok, because f is let-bound and, therefore, monomorphic This line doesn't make sense, I was too hasty to hit the 'Send' button, I meant to write 'lambda-bound', of course, apologies

[Haskell-cafe] Re: tweak vacuum-* output

2010-05-14 Thread Gleb Alexeyev
Ozgur Akgun wrote: In this case I think you should either make it a separate package, or don't hide it in this module. It looks like an easy way to call Ubigraph from Hhaskell, and there is no apparent alternative (in hackage) so why hide it? I've contacted Kohei Ozaki, the author of

[Haskell-cafe] Re: tweak vacuum-* output

2010-05-14 Thread Gleb Alexeyev
The new version (0.2.0.1) is on Hackage. vacuum-ubigraph now depends on Hubigraph, basic customization is now possible, e.g.: import System.Vacuum.Ubigraph import Graphics.Ubigraph myNodeStyle n = map (setColor #ff) $ defaultNodeStyle n where setColor color (VColor _) =

[Haskell-cafe] Re: tweak vacuum-* output

2010-05-13 Thread Gleb Alexeyev
Ozgur Akgun wrote: Thanks for the answer. I see your point, that Ubigraph does some magic* to place vertices and edges. This makes me wonder, how they generate the binary tree demo: http://ubietylab.net/ubigraph/content/Demos/random_binary_tree.html Is there a way to disable this optimal graph

[Haskell-cafe] Re: tweak vacuum-* output

2010-05-13 Thread Gleb Alexeyev
Ozgur Akgun wrote: A little bit of topic, but why is the module Graphics.Ubigraph hidden in your package? I've been trying to use Ubigraph directly, and your module helped me a lot. (I just patched the cabal file to expose Graphics.Ubigraph as well) Is there a specific reason for it to be

[Haskell-cafe] Re: tweak vacuum-* output

2010-05-12 Thread Gleb Alexeyev
Ozgur Akgun wrote: Hi all, I am using vacuum-opengl and vacuum-ubigraph to visualise and analyse some of my data structures. They are quite helpful most of the time, however sometimes I feel the need to tweak the generated output -- such as removing the auto-generted identifiers from

[Haskell-cafe] Re: Remote invocations in Haskell?

2010-03-25 Thread Gleb Alexeyev
Yves Parès wrote: Okay, well, apparently I have to rely on an external HTTP server. This is not very simple, is there another more suitable way to get RPC working in haskell? Apparently it is possible to use Happstack as webserver, here's example I came up with: import

[Haskell-cafe] Re: Strange typing?

2010-03-22 Thread Gleb Alexeyev
Ozgur Akgun wrote: Is there any way to limit a functions type, not by a data type but by a group of constructors of a data type? If not, what would be the *right* thing to do to achieve this level of type safety? data DT1 = X | Y | Z data DT2 = A | B | C | D func1 :: DT1 - DT2 -- instead of

[Haskell-cafe] Re: Visualizing function application

2010-01-18 Thread Gleb Alexeyev
Martijn van Steenbergen wrote: Dear café, I am deeply impressed with Vacuum[1][2], Ubigraph[3] and especially their combination[4]. I can trivially and beautifully visualize the ASTs that my parser produces. I can visualize zippers of the ASTs and confirm that sharing is optimal. Ubigraph

[Haskell-cafe] Re: A Question of Restriction

2009-07-27 Thread Gleb Alexeyev
Brian Troutwine wrote: Do you have any reason not to do the above? Yes, the subset types that I wish to define are not clean partitions, though my example does suggest this. Let's say that the definition of Foo is now data Foo = One | Two | Three | Four | Five | Six while Odd and Even

[Haskell-cafe] Re: powerSet = filterM (const [True, False]) ... is this obfuscated haskell?

2009-07-17 Thread Gleb Alexeyev
Thomas Hartman wrote: on haskell reddit today powerSet = filterM (const [True, False]) Does it help if we inline the 'const' function and rewrite [True, False] in monadic notation as (return True `mplus` return False)? powerSet = filterM (\x - return True `mplus` return False). You can

[Haskell-cafe] Re: powerSet = filterM (const [True, False]) ... is this obfuscated haskell?

2009-07-17 Thread Gleb Alexeyev
On Jul 17, 2009 1:40pm, Thomas Hartman wrote: my question to all 3 (so far) respondants is, how does your explanation explain that the result is the power set? I guess you forgot to reply to the cafe. Well, to me the modified definition I posted looks like the essence of powerset, the set

[Haskell-cafe] Re: Laziness enhances composability: an example

2009-07-10 Thread Gleb Alexeyev
Marcin Kosiba wrote: Hi, To illustrate what I meant I'm attaching two examples. In example_1.py I've written code the way I think would be elegant (but it doesn't work). In example_2.py I've written code so that it works, but it isn't elegant. I know I'm abusing Python iterators here. Also,

[Haskell-cafe] Re: curious about sum

2009-06-18 Thread Gleb Alexeyev
Thomas Davie wrote: No, I think it's extremely useful. It highlights that numbers can both be lazy and strict, and that the so called useless lazy sum, is in fact, useful. But lazy sum should have beed defined in terms of foldr, not foldl. And foldl is not strict enough for strict sum.

[Haskell-cafe] Re: Trouble with type signatures and type families

2009-04-22 Thread Gleb Alexeyev
You may want to read the comments at http://hackage.haskell.org/trac/ghc/ticket/1897. ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe

[Haskell-cafe] Re: ANNOUNCE: vacuum-cairo: a cairo frontend to vacuum for live Haskell data visualization

2009-04-02 Thread Gleb Alexeyev
Don Stewart wrote: Did you use hubigraph? http://ooxo.org/hubigraph/ This cabalized project doesn't appear to be on hackage! Oh, I wasn't aware of hubigraph until now. Ubigraph has very simple XML-RPC-based API so I used it directly. Hubigraph, of course, looks nicer with its custom

[Haskell-cafe] Re: ANNOUNCE: vacuum-cairo: a cairo frontend to vacuum for live Haskell data visualization

2009-04-02 Thread Gleb Alexeyev
Daryoush Mehrtash wrote: When I try to install the hubigraph I get the following error: skip Network/XmlRpc/Client.hs:113:23: Not in scope: type constructor or class `ConnError' Network/XmlRpc/Client.hs:113:51: Not in scope: type constructor or class `ConnError' cabal: Error: some

[Haskell-cafe] Re: ANNOUNCE: vacuum-cairo: a cairo frontend to vacuum for live Haskell data visualization

2009-04-02 Thread Gleb Alexeyev
Don Stewart wrote: Please upload!! I've run into 2 problems while trying to do this. The first one - haxr won't build with HTTP-4000, so I had to edit haxr.cabal and add the upper version bound for HTTP. The second one is puzzling me. I've cabal-installed the package, but keep getting

[Haskell-cafe] Re: ANNOUNCE: vacuum-cairo: a cairo frontend to vacuum for live Haskell data visualization

2009-04-02 Thread Gleb Alexeyev
Iavor Diatchki wrote: Hi, The linking problem might be due to a bug in the cabal file: if you have modules that are not exposed, you still need to list them in the other-modules section. This was the problem, thanks! ___ Haskell-Cafe mailing list

[Haskell-cafe] Re: ANNOUNCE: vacuum-cairo: a cairo frontend to vacuum for live Haskell data visualization

2009-04-01 Thread Gleb Alexeyev
Don Stewart wrote: I am pleased to announce the release of vacuum-cairo, a Haskell library for interactive rendering and display of values on the GHC heap using Matt Morrow's vacuum library. Awesome stuff, kudos to you and Matt Morrow! I thought it'd be fun to visualize data structures in

[Haskell-cafe] Re: Interesting problem from Bird (4.2.13)

2009-03-06 Thread Gleb Alexeyev
Gleb Alexeyev wrote: instance Eq a = Eq (CatList a) where a == b = case (viewCL a, viewCL b) of (Just (x, xs), Just (y, ys)) - x==y xs == ys (Nothing, Nothing) - True _- False I just realized that my solution

[Haskell-cafe] Re: Interesting problem from Bird (4.2.13)

2009-03-04 Thread Gleb Alexeyev
Here's my attempt though it's not really different from using built-in lists: viewCL CatNil = Nothing viewCL (Wrap a) = Just (a, CatNil) viewCL (Cat a b) = case viewCL a of Nothing - viewCL b Just (x, xs) - Just (x, Cat xs b) instance Eq a = Eq

[Haskell-cafe] Re: evaluation semantics of bind

2009-02-05 Thread Gleb Alexeyev
Gregg Reynolds wrote: However, consider: getChar = \x - getChar An optimizer can see that the result of the first getChar is discarded and replace the entire expression with one getChar without changing the formal semantics. Let's imagine that IO datatype is defined thus: {-#

[Haskell-cafe] Re: evaluation semantics of bind

2009-02-05 Thread Gleb Alexeyev
Gregg Reynolds wrote: I must be misunderstanding something. I don't know if it would be optimized out, but I see no reason why it couldn't be. There's no data dependency, right? Of course there is data dependency. In my example, where IO is defined as a (generalized) algebraic datatype,

[Haskell-cafe] Re: evaluation semantics of bind

2009-02-05 Thread Gleb Alexeyev
Gregg Reynolds wrote: Are you saying that using equations to add a level of indirection prevents optimization? I still don't see it - discarding x doesn't change the semantics, so a good compiler /should/ do this. How is this different from optimizing out application of a constant function?

[Haskell-cafe] Re: 1,000 packages, so let's build a few!

2009-02-02 Thread Gleb Alexeyev
Duncan Coutts wrote: Gleb Alexeyev did the majority of the work on this one. I'm most grateful to him for heeding my recent calls for more volunteers for Cabal hacking. I guess you're overstating my contribution a little, but thanks :). ___ Haskell

[Haskell-cafe] Re: Changing type of 'when'

2009-01-28 Thread Gleb Alexeyev
Maurí­cio wrote: ? It is easy for 'when' to ignore the result of the first computation, and this would not break existing code, and also save a lot of return ()s. As Neil Mitchell pointed out[1], ignoring results implicitly may indicate an error. Perhaps it's cleaner to define ignore m =

[Haskell-cafe] Re: how to implement daemon start and stop directives?

2009-01-23 Thread Gleb Alexeyev
Ertugrul Soeylemez wrote: And to prove that IORefs do lead to a pointer race condition and hence are insecure, try the following code: main :: IO () main = do ref - newIORef False forkIO $ forever $ modifyIORef ref not forever $ readIORef ref = print It crashes for me. I'm

[Haskell-cafe] Re: Type family problem

2009-01-21 Thread Gleb Alexeyev
Sjoerd Visscher wrote: When I try this bit of code: class C1 a where type F a :: * x :: F a y :: F a x = y I get this error: Couldn't match expected type `F a1' against inferred type `F a' In the expression: y In the definition of `x': x = y I can't figure out

[Haskell-cafe] Re: Existencial quantification and polymorphic datatypes (actually, components...)

2009-01-20 Thread Gleb Alexeyev
Mauricio wrote: But how is this: data SomeNum = forall a. SN a different from: data SomeNum = SN (forall a. a) In the first case the constructor SN can be applied to the monomorphic value of any type, it effectively hides the type of the argument. For example, you can have a list like

[Haskell-cafe] Re: Existencial quantification and polymorphic datatypes (actually, components...)

2009-01-20 Thread Gleb Alexeyev
I just thought that the shorter explanation could do better: the difference is in the types of the constructor functions. Code: {-# LANGUAGE ExistentialQuantification #-} {-# LANGUAGE RankNTypes #-} data SomeNum1 = forall a. SN1 a data SomeNum2 = SN2 (forall a. a) ghci session: *Main :t

[Haskell-cafe] Re: Type errors, would extensions help?

2009-01-16 Thread Gleb Alexeyev
Mauricio wrote: After you pointed my dumb mistake, I was able to build the first example -- without any of the extensions! Haskell can be misterious some times. Strange enough, I can't get the original (and, to my eyes, equal) problem to work. Indeed Haskell can be misterious sometimes. Now

[Haskell-cafe] Re: some ideas for Haskell', from Python

2009-01-15 Thread Gleb Alexeyev
Manlio Perillo wrote: import System.Posix.Files as PF Try this: import qualified System.Posix.Files as PF The problem you described should go away. ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org

[Haskell-cafe] Re: Type errors, would extensions help?

2009-01-15 Thread Gleb Alexeyev
Mauricio wrote: Hi, I have this problem trying to define a function inside a do expression. I tried this small code to help me check. This works well: --- import Data.Ratio ; main = do { printNumber - let { print :: (Num n,Show n) = n - IO () ; print n = do { putStrLn $ show n}

[Haskell-cafe] Re: Ambiguous type variable woes

2008-11-24 Thread Gleb Alexeyev
Jacques Carette wrote: -- This does not however help at all! The only way I have found of 'fixing' this requires annotating the code itself, which I most definitely do not want to do because I specifically want the code to be polymorphic in that way. But GHC 6.8.2 does not want to let me do

[Haskell-cafe] Re: How to abort a computation within Continuation Monad?

2007-11-21 Thread Gleb Alexeyev
Derek Elkins wrote: As Derek Elkins has written, one of the options is to use delimited continuations, see http://research.microsoft.com/~simonpj/papers/control/ for Haskell implementation. I made no such suggestion. I didn't mean that you suggested using implementation referenced

[Haskell-cafe] Re: How to abort a computation within Continuation Monad?

2007-11-20 Thread Gleb Alexeyev
Dimitry Golubovsky wrote: If I have callCC $ \exit - do foo ... I cannot jump to `exit' from within foo unless `exit' is given to foo as an argument. As Derek Elkins has written, one of the options is to use delimited continuations, see

[Haskell-cafe] Re: [ANN] An efficient lazy suffix tree library

2007-08-28 Thread Gleb Alexeyev
Bryan O'Sullivan wrote: ChrisK wrote: That is almost certainly because the algorithm expects the source string to have a unique character at its end. Chris is correct. I'll ensure that the docs make this clear. Apologies, I should have thought of this myself. Thanks.

[Haskell-cafe] Re: [ANN] An efficient lazy suffix tree library

2007-08-27 Thread Gleb Alexeyev
Bryan O'Sullivan wrote: I just posted a library named suffixtree to Hackage. http://www.serpentine.com/software/suffixtree/ It implements Giegerich and Kurtz's lazy construction algorithm, with a few tweaks for better performance and resource usage. API docs:

[Haskell-cafe] Re: Impredicativity confusion

2007-08-22 Thread Gleb Alexeyev
Dimitrios Vytiniotis wrote: I hope this helps more than confuses, It really does, thank you. To understand your explanation completely I have to study 'Boxy types' paper thoroughly, but from the user's point of view everything is clear - GHC currently cannot correctly instantiate type

[Haskell-cafe] readline crashes in Emacs buffer on Windows

2007-05-15 Thread Gleb Alexeyev
Hello Cafe! I asked about this problem on IRC channel but with little luck. The problem boils down to the following: readline crashes on any input if the calling program runs in the Emacs buffer. To reproduce this bug, load the code below into ghci using haskell-mode and run main. import

[Haskell-cafe] GHC 6.6 hangs

2007-04-11 Thread Gleb Alexeyev
Dmitry Antonyuk (lomeo) came up with a piece of code that hung GHC 6.6: newtype Foo a = Foo (Foo a - a) bar x@(Foo f) = f x baz = bar (Foo bar) See the original discussion (in Russian) at: http://lomeo.livejournal.com/35674.html ___ Haskell-Cafe

[Haskell-cafe] Re: GHC 6.6 hangs

2007-04-11 Thread Gleb Alexeyev
Neil Mitchell wrote: It's a documented bug in GHC: http://www.haskell.org/ghc/docs/latest/html/users_guide/bugs.html#bugs-ghc GHC's inliner can be persuaded into non-termination using the standard way to encode recursion via a data type Thanks Neil! Sorry for the noise, I should have