[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 variables in polymorphic function's type when some of arguments 
have polymorphic types and only types of arguments are given.



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


[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:

http://darcs.serpentine.com/suffixtree/dist/doc/html/Data-SuffixTree.html

I've tested it on multi-megabyte input strings.


I think I found a bug:
import qualified Data.SuffixTree as T

 T.countRepeats ab (T.construct abab)
1

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


[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 mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[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 
http://research.microsoft.com/~simonpj/papers/control/ for Haskell 
implementation.


But in this case Cont may be enough. If you don't like passing `exit' 
explicitly, you can put in into Reader monad. This is the idea:



import Control.Monad.Cont
import Control.Monad.Reader

type Abortable r a = ReaderT (r - Cont r r) (Cont r) a

runAbortable :: Abortable a a - a
runAbortable m = runCont (callCC $ \exit - runReaderT m exit) id

abort :: r - Abortable r a
abort x = do
  exit - ask
  lift (exit x)
  undefined -- this hack is needed to make abort polymorphic

test a b c = do
  x - if a then abort a else return 1
  y - if b then abort b else return False
  z - foo c   -- calling foo without explicit abort continuation
  return $ show (x, y, z)
  where foo True = abort c
foo False = return 5.39

run m = putStrLn (runAbortable m)

main = do run (test False False False)
  run (test False False True)
  run (test False True False)
  run (test True False False)

--

This implementation is a bit hackish, since it uses undefined to make 
abort polymorphic in return type. You can use rank-2 types to avoid it, 
see http://www.vex.net/~trebla/tmp/ContMonad.lhs by Albert C. Lai.


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


[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 above.
But you suggested using 'control' which is obviously a delimited control 
operator and that is what I was trying to say.


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


[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 this
func1' :: (X|Y) - (B|C) -- i want sth. like this. (| means or)

OCaml has a feature called 'polymorphic variants' that allows exactly 
this. You may want to google 'polymorphic variants in haskell'.


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


[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 Network.XmlRpc.Server
import Happstack.Server.SimpleHTTP
import Control.Monad.Trans
import Data.ByteString.Lazy.Char8

add :: Int - Int - IO Int
add x y = return (x + y)

handler = do
  Body body - rqBody `fmap` askRq
  liftIO $ handleCall (methods [(examples.add, fun add)]) (unpack body)

main = simpleHTTP (Conf 8080 Nothing) handler

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


[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 constrcutor names, pack some things
together, or similar.

Is there a way to configure their output?

And for the vacuum-ubigraph option, I like it's output generally, however
while creating the expression tree, is doesn't respect my structures. If
there is a flag or so to fix this issue, I'd appreciate it. The Problem is
like the following:

data Expr = Sum Expr Expr | Mult Expr Expr | Single Int
e = Sum (Single 2) (Mult (Single 3) (Single 4))

And it orients the tree in such a way that Mult looks like the root node,
instead of Sum, as I would expect.



Hi,
I can answer only about vacuum-ubigraph.
Regarding expression tree: the problem is Ubigraph doesn't know anything 
about the tree. It uses physical simulation to determine the optimum 
graph layout, the Mult node has the most links attached to it, that's 
why it's located at the center of the graph. As far as I can tell from 
Ubigraph docs, this cannot be tweaked. Theoretically one can change the 
shape of the graph visualization by introducing invisible links and/or 
nodes.


And no, there's no way to tweak the vacuum-ubigraph output without 
modifying its code.

Thanks,
Ozgur Akgun





___
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: 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 layout determination process?

Best,
Ozgur



Ozgur,
I've just compared the way vacuum-ubigraph visualizes binary trees to 
the random_binary_tree demo and found that I had missed an important 
edge attribute called oriented, it seems to produce the output you want.


I hope to upload the new package version soon, meanwhile you can do the 
following (assuming you use Linux):


cabal unpack vacuum-ubigraph
patch -d vacuum-ubigraph-0.1.0.3/ -p 1  vacuum-ubigraph-oriented.patch
cd vacuum-ubigraph-0.1.0.3
cabal configure  cabal build  cabal install
diff -rupN vacuum-ubigraph-0.1.0.3/System/Vacuum/Ubigraph.hs vacuum-ubigraph-0.1.0.4/System/Vacuum/Ubigraph.hs
--- vacuum-ubigraph-0.1.0.3/System/Vacuum/Ubigraph.hs	2010-05-13 11:04:39.0 +0300
+++ vacuum-ubigraph-0.1.0.4/System/Vacuum/Ubigraph.hs	2010-05-13 10:51:47.0 +0300
@@ -58,6 +58,7 @@ view a = do
e - U.newEdge srv a b
U.setEdgeAttribute srv e stroke dotted
U.setEdgeAttribute srv e arrow true
+   U.setEdgeAttribute srv e oriented true
 
   srv = U.defaultServer
 
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[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 hidden?


There's no reason whatsoever other than vacuum-ubigraph was born rather 
hastily and never maintained after that. Its complete history is in the 
vacuum-cairo announcement thread:


http://www.mail-archive.com/haskell-cafe@haskell.org/msg57214.html

As you can see, Don Stewart pointed me at Hubigraph, too. If it was on 
Hackage, probably the right thing to do would be to drop the hidden 
module and use Hubigraph.




As far as I know, there is another wrapper for Ubigraph in Haskell,
Hubigraph[1], but it's not on hackage. (licensing issues?) Your module
contains all the basics, and should be enough in general.

[1] http://ooxo.org/hubigraph/index.html

Best,
Ozgur



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


[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 Hubigraph, about the latter
being uploaded to Hackage, and got the positive response.

I'm updating vacuum-hubigraph package now, hope to upload the new 
version soon.


Regards,
Gleb.

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


[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 _) = VColor color
setColor _ s = s

 myview = customView (defaultOptions { nodeStyle = myNodeStyle }) 
defaultServer


 main = myview $ cycle [1..5]

Any feedback appreciated.

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


[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 is also able to animate graph *mutations*, as shown by the 
various demos on Ubigraph's website. How cool would it be if we could 
tell vacuum-ubigraph: here, show this tree, and then show how the tree 
changes when we apply this function on it. We could see how [1,2,3] is 
transformed into a ring when cycle is applied on it, or we could see how 
a list is consumed node by node when a foldr is applied.


I have no idea how difficult this is or how to begin, so I thought I'd 
throw the idea out here. Perhaps it is appealing enough that someone 
picks it up and implements it. :-)


Martijn.


[1] http://hackage.haskell.org/package/vacuum
[2] http://www.youtube.com/watch?v=oujaqo9GAmA
[3] http://ubietylab.net/ubigraph/content/Demos/index.html
[4] http://hackage.haskell.org/package/vacuum-ubigraph


Hello, Martijn.

I'm glad you found vacuum-ubigraph useful.

I have to tell you that it was hacked in a hour or so based on the code 
from vacuum-cairo. I'm in no way an expert in GHC runtime internals.


The spec of application visualization as you propose it is unclear: in 
what sense the list [1,2,3] is transformed to a ring, given that only 
values 1,2,3 are shared, not cons-cells? Can this definition of 
transformation be extrapolated to a function like parseXml :: [Char] - 
XmlTree?


As to 'list consumed by foldr', things seem even more unclear. I'm under 
impression that Vacuum allows inspection of representation of static 
values, and here we need the history of evaluation, with information 
which nodes and when get collected as garbage. I doubt this is possible, 
but we'll have to wait until Matt Morrow or anyone else more 
knowledgeable than me comments.


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


[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 (Int, Bool)
--testNotOk = do f - return id
--   return (f 42, f True)

Try uncommenting the 'testNotOk' definition.

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


[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 give an example, please?


testOk = let f = id in (f 42, f True)

--testNotOk :: Monad m =  m (Int, Bool)
--testNotOk = do f- return id
--   return (f 42, f True)

Try uncommenting the 'testNotOk' definition.


There's no later here at all.

Two seperate definitions in a Haskell program act as if they have always been 
defined, are defined, and always will be defined, they are not dealt with in 
sequence (except for pattern matching but that doesn't apply here).

Instead, what's going on here is scoping.  The f in testOk is a different f to 
the one in testNotOkay, distinguished by their scope.

Finally, this is not how you use a let in a do expression, here's how you 
should do it:

testOk2 :: Monad m =  m (Int, Bool)
testOk2 = do let f = id
  return (f 42, f True)



I don't understand, I'm afraid. Michael Lazarev asked for example on the 
difference between let-bound and lambda-bound values. testNotOk 
definition mirrors the structure of the testOk definition, but testNotOk 
is, pardon my pun, not ok, because f is let-bound and, therefore, 
monomorphic, while f in the first definition is polymorphic.


I never implied that definitions are processed in some sort of sequence, 
nor I stated that the two f's are somehow related.


Thanks

Tom Davie



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


[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 for that.





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


[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: 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. Therefore the current choice 
in the worst of both worlds.


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


[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, I'm not sure the way to 
compose iterators shown in example_2.py is the only option. Actually I'd love 
to see a better solution, because it would remove a lot of bloat from my 
code ;)




You may want to look at Lua coroutines, which are more powerful than 
Python iterators. Your example_1.py is very similiar to the example in 
the Coroutines Tutorial [1].


[1] http://lua-users.org/wiki/CoroutinesTutorial

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


[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 see that 'x' is ignored, both True and False are returned, hence 
 x is preserved in one answer and not preserved in another.


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


[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 of all subsets. Every element x of the input list 
divides the powerset in 2 halves, the first one contains x, the second 
one doesn't. Filtering on the non-deterministic predicate (\x - return 
True `mplus` return False) in the List monad does exactly that.


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


[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 remain the same. I would further like to define
Triangular, which I will do incorrectly for consistency.

  data Triangular = One | Three | Six

I could not accommodate this definition using your scheme, correct?



A variation on scheme proposed by Ross Mellgren earlier in this thread.
It's a bit tedious but allows for definition of arbitrary subsets thus 
it may work for you:


{-# LANGUAGE GADTs, EmptyDataDecls  #-}

data One
data Two
data Three
data Four

data Foo a where
FOne :: Foo One
FTwo :: Foo Two
FThree :: Foo Three
FFour :: Foo Four


class IsEven a
instance IsEven Two
instance IsEven Four

class IsOdd a
instance IsOdd One
instance IsOdd Three

class IsLessThanThree a
instance IsLessThanThree One
instance IsLessThanThree Two

quux :: IsEven a = Foo a - String
quux FTwo = 2
quux FFour = 4

bzzt :: IsLessThanThree a = Foo a - String
bzzt FOne = 1
bzzt FTwo = 2




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


[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 this.


What are my options?


If my guess is correct (sorry if it's not), you want the code to be 
polymorhic so that you don't have to write the shape of the stack twice. 
Then the way out is to annotate the type of 'empty':


test1 = first . p 2 . p 3 $ (empty :: ((), Void))

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


[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 mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/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 checked GHC docs before posting.

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


[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 System.Console.Readline

main = do readline prompt
  putStrLn You cannot see this, because I've crashed. Amen

I'm running Windows 2003 Server, GHC-6.6, Emacs 22.0.50.1.

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


[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
http://www.haskell.org/mailman/listinfo/haskell-cafe


[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}
} in return print ;
  print (1%5) ;
  print 5.0
}
---


I guess you intended to call printNumber in the quoted snippet?
There's a way to use GHC's extensions to do what you want, let me 
illustrate with simpler example:


{-# LANGUAGE RankNTypes #-}
{-# LANGUAGE ImpredicativeTypes #-}

t1 () = do f - (return id :: IO (forall a. a-a))
   return (f foo, f True)

However, I would call this style unnatural and unnecessary. What's wrong 
with plain 'let' or 'where' that work without any extensions?


t2 () = do let f = id
   return (f foo, f True)


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


[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 that you fixed the typo 
the first example compiles, but I think you will be surprised with its 
output:

1 % 5
5 % 1
As you can see, the type of printNumber is still monomorphic for the 
reasons explained by Ryan Ingram and Lennart Augustsson. It's only the 
peculiarity of the numeric classes in Haskell that makes two your 
examples different - the constant `5.0' has type `(Fractional t) = t', 
and (Ratio a) is an instance of Fractional.


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


[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 [SN True, SN foo, SN 42], because 
for all x SN x has type SomeNum.


In the second case, SN can be applied only to polymorphic values, SN 
True or SN foo won't compile.


The only thing that both types have in common - they are both useless. 
Polymorphic and existential types must have more structure to be useful 
- you cannot _construct_ SomeNum #2 and you cannot do anything to the 
value you _extract_ from SomeNum #1.


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


[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 SN1
SN1 :: a - SomeNum1
*Main :t SN2
SN2 :: (forall a. a) - SomeNum2

This is not the whole story, types of the bound variables you get on 
pattern matching differ too, but this makes the short explanation a bit 
longer :).


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


[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 what is going on or how I should fix this.



The discussion [1] seems to be related.

[1] http://hackage.haskell.org/trac/ghc-test/ticket/2855

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


[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 using GHC 6.10.1 on an Athlon 64 X2 (32 bits
system).  The error message reads:

  test: internal error: schedule: invalid what_next field
  (GHC version 6.10.1 for i386_unknown_linux)
  Please report this as a GHC bug:  http://www.haskell.org/ghc/reportabug


Interesting. Looks like a bug in the single-threaded runtime to me: I 
can reproduce this crash only when compiling without the `-threaded' flag.


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


[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 = m  return ()

and use it like this:
when condition $ ignore doSmth

[1]http://neilmitchell.blogspot.com/2008/12/mapm-mapm-and-monadic-statements.html

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


[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-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[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:

{-# LANGUAGE GADTs #-}
{-# LANGUAGE NoImplicitPrelude #-}

import Prelude(Monad, Char)
data IO a where
GetChar :: IO Char
Bind :: IO a - (a - IO b) - IO b

getChar = GetChar
(=) = Bind

It is perfectly possible to construct IO actions as values of this data 
type and execute them by some function evalIO :: IO - Prelude.IO with 
the obvious definition. Now the question arises: do you think

getChar = \x - getChar would be optimized to getChar by compiler?
If no, why would GHC want to do this optimization for standard IO?




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


[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, the value of getChar is GetChar.
The value of 'getChar = \x - getChar' is 'Bind GetChar (\x - 
GetChar'. 'x' is not used anywhere, but this doesn't change the fact 
that these are totally different values, no sane compiler would prove 
them equal.


For some monads, the evaluation of 'a = \x - b' yields b, but it's 
not true in general.


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


[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?



Perhaps my example doesn't work, so I'll try another example.
As you know, (=) is just an (overloaded) higher-order function.
Let's consider another higher-order function, map. The expression
 map (\x - 42) [1..3]
evaluates to [42, 42, 42].
As you can see, the function (\x - 42) passed to map ignores its first 
argument. Would you expect the compiler to discard the call to map?


Can you see the analogy? The shapes of the two expressions, map (\x - 
42) [1..3] and (=) getChar (\x - getChar) are similar.


(=) is a combinator just like map, you cannot optimize it away in general.

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


[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 (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


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


[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 is needlessly verbose, the following 
instance suffices:

 instance Eq a = Eq (CatList a) where
 a == b = viewCL a == viewCL b

___
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-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 three dimensions. 
Attached is quick and dirty hack based on your code and Ubigraph server 
(http://ubietylab.net/ubigraph/).


The demo video (apologies for poor quality): 
http://www.youtube.com/watch?v=3mMH1cHWB6c


If someone finds it fun enough, I'll cabalize it and upload to Hackage.
module Ubigraph where

import Network.XmlRpc.Client

type Url = String
type VertexId = Int
type EdgeId = Int

defaultServer = http://127.0.0.1:20738/RPC2;

void :: IO Int - IO ()
void m = m  return ()

clear :: Url - IO ()
clear url = void (remote url ubigraph.clear)

newVertex :: Url - IO VertexId
newVertex url = remote url ubigraph.new_vertex

newEdge :: Url - VertexId - VertexId - IO EdgeId
newEdge url = remote url ubigraph.new_edge

removeVertex :: Url - VertexId - IO ()
removeVertex url vid = void (remote url ubigraph.remove_vertex vid)

removeEgde :: Url - EdgeId - IO ()
removeEgde url eid= void (remote url ubigraph.remove_edge eid)


zeroOnSuccess :: IO Int - IO Bool
zeroOnSuccess = fmap (==0) 

newVertexWithId :: Url - VertexId - IO Bool
newVertexWithId url vid = zeroOnSuccess (remote url ubigraph.new_vertex_w_id vid)

newEdgeWithId :: Url - EdgeId - VertexId - VertexId - IO Bool
newEdgeWithId url eid x y = zeroOnSuccess (remote url ubigraph.new_edge_w_id eid x y)

setVertexAttribute :: Url - VertexId - String - String - IO Bool
setVertexAttribute url vid attr val = zeroOnSuccess (remote url ubigraph.set_vertex_attribute vid attr val)

setEdgeAttribute :: Url - VertexId - String - String - IO Bool
setEdgeAttribute url eid attr val = zeroOnSuccess (remote url ubigraph.set_edge_attribute eid attr val)
module VacuumUbigraph where

import GHC.Vacuum
import Data.Char
import Text.Printf
import Data.List

import qualified Data.IntMap as IntMap
import qualified Data.IntSet as IntSet

import qualified Ubigraph as U

nodeStyle n =
case nodeName n of
  :  - ((:), cube, #ff)

  -- atomic stuff is special
  k | k `elem` [S# ,I# ,W#
   ,I8# ,I16# ,I32# ,I64#
   ,W8# ,W16# ,W32# ,W64#] - (showLit n, sphere, #00ff00)
  -- chars
  C# - (show . chr . fromIntegral . head . nodeLits $ n, sphere, #00ff00)
  D# - (Double, sphere, #009900)
  F# - (Float, sphere, #009900)

  -- bytestrings
  PS- (printf ByteString[%d,%d] (nodeLits n !! 1) (nodeLits n !! 2), cube, #ff)
  Chunk - (printf Chunk[%d,%d] (nodeLits n !! 1) (nodeLits n !! 2), cube, #ff)

  -- otherwise just the constructor and local fields
  c   | z  0 -
(c ++ show (take (fromIntegral z) $ nodeLits n), cube, #99)
  | otherwise - (c, cube, #99)
where z = itabLits (nodeInfo n)
where
  showLit n = show (head $ nodeLits n)

view a = do
  U.clear srv
  mapM_ renderNode nodes
  mapM_ renderEdge edges
where  
  g = vacuum a
  alist = toAdjList g
  nodes = nub $ map fst alist ++ concatMap snd alist
  edges = concatMap (\(n, ns) - map ((,) n) ns) alist

  style nid = maybe (..., cube, #ff) nodeStyle (IntMap.lookup nid g)

  renderNode nid = do
   U.newVertexWithId srv nid
   let (label, shape, color) = style nid
   U.setVertexAttribute srv nid label label
   U.setVertexAttribute srv nid shape shape
   U.setVertexAttribute srv nid color color
  
  renderEdge (a, b) = do
   e - U.newEdge srv a b
   U.setEdgeAttribute srv e stroke dotted
   U.setEdgeAttribute srv e arrow true

  srv = U.defaultServer

___
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 monad, datatypes for 
shapes etc.


BTW, it seems that you didn't notice the complete source code attached 
to my first message. Like I said it's just a quick and dirty hack, all 
real job is done by vacuum, Ubigraph server and a bit of code 
copy-pasted from vacuum-cairo.


___
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

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 packages failed to install:
HUBIGraph-0.1 depends on haxr-3000.1.1.2 which failed to install.
haxr-3000.1.1.2 failed during the building phase. The exception was:
exit: ExitFailure 1

Any ideas?



I've just run into this problem as well. It seems that haxr doesn't 
build with HTTP-4000, though its cabal file doesn't specify the upper bound.


___
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:

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 linking errors from 
ghci (though interactive loading of the same module from source works fine):


Prelude :m + System.Vacuum.Ubigraph
Prelude System.Vacuum.Ubigraph view 42
Loading package syb ... linking ... done.
Loading lots of packages skipped
Loading package vacuum-0.0.6 ... linking ... done.
Loading package haxr-3000.1.1.2 ... linking ... done.
Loading package vacuum-ubigraph-0.1.0.2 ... linking ... interactive: 
/home/gleb/.cabal/lib/vacuum-ubigraph-0.1.0.2/ghc-6.10.1/HSvacuum-ubigraph-0.1.0.2.o: 
unknown symbol `vacuumzmubigraphzm0zi1zi0zi2_GraphicsziUbigraph_lvl_closure'

ghc: unable to load package `vacuum-ubigraph-0.1.0.2'
Prelude System.Vacuum.Ubigraph

Non-working package is here: 
http://hackage.haskell.org/cgi-bin/hackage-scripts/package/vacuum-ubigraph-0.1.0.1.


Any hints appreciated.

___
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

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@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe