Re: [Haskell-cafe] Why cannot ghc find a existng module ?

2010-05-11 Thread zaxis

`ghc-pkg list` finds two random packages.  After `ghc-pkg unregsiter` the one
installed by cabal in ~/.ghc/, all works normally now!

%ghc-pkg list|grep -i random
random-1.0.0.2


zaxis wrote:
 
 I have reinstall ghc, xmonad and xmonad-contrib but it still doesnot work!
 
 %ghc-pkg list|grep xmonad 
 xmonad-0.9.1
 xmonad-contrib-0.9.1
 
 %cat
 /usr/lib/ghc-6.12.1/package.conf.d/xmonad-contrib-0.9.1-e073c906e3b29eb062e632e9bb989664.conf|grep
 LayoutHints
  XMonad.Layout.LayoutCombinators XMonad.Layout.LayoutHints
 
 %ls
 /usr/lib/ghc-6.12.1/site-local/xmonad-contrib-0.9.1/XMonad/Layout/LayoutHints.hi
   
 ../site-local/xmonad-contrib-0.9.1/XMonad/Layout/LayoutHints.hi
 
 LayoutHints is indeed there. But ghc still cannot find it !
 
 Thanks for your suggestion. i will try #xmonad and xmond mailinglist
 later!
 
 
 Ivan Lazar Miljenovic wrote:
 
 zaxis z_a...@163.com writes:
 
 It seems that it is not a xmonad problem as xmond just call ghc
 directly.
 
 Well, yes, except that it might be something else to do with your
 config, etc. and as such the xmonad mailing list is probably more
 relevant.
 
 -- 
 Ivan Lazar Miljenovic
 ivan.miljeno...@gmail.com
 IvanMiljenovic.wordpress.com
 ___
 Haskell-Cafe mailing list
 Haskell-Cafe@haskell.org
 http://www.haskell.org/mailman/listinfo/haskell-cafe
 
 
 
 


-
e^(π⋅i) + 1 = 0
-- 
View this message in context: 
http://old.nabble.com/Why-cannot-ghc-find-a-existng-module---tp28507704p28521179.html
Sent from the Haskell - Haskell-Cafe mailing list archive at Nabble.com.

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


Re: [Haskell-cafe] Why cannot ghc find a existng module ?

2010-05-11 Thread David Virebayre
On Tue, May 11, 2010 at 10:10 AM, zaxis z_a...@163.com wrote:

 `ghc-pkg list` finds two random packages.  After `ghc-pkg unregsiter` the one
 installed by cabal in ~/.ghc/, all works normally now!

I stopped counting the number of times I've reinstalled GHC because I
forgot to tell cabal to install a package globally. I really should
modify the config file.

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


Re: [Haskell-cafe] Why cannot ghc find a existng module ?

2010-05-11 Thread Ivan Lazar Miljenovic
David Virebayre dav.vire+hask...@gmail.com writes:

 On Tue, May 11, 2010 at 10:10 AM, zaxis z_a...@163.com wrote:

 `ghc-pkg list` finds two random packages.  After `ghc-pkg unregsiter` the one
 installed by cabal in ~/.ghc/, all works normally now!

 I stopped counting the number of times I've reinstalled GHC because I
 forgot to tell cabal to install a package globally. I really should
 modify the config file.

No, this isn't the problem here.  The problem is that zaxis should
never have installed the second random library in the first place,
because it is a boot library of GHC.

-- 
Ivan Lazar Miljenovic
ivan.miljeno...@gmail.com
IvanMiljenovic.wordpress.com
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] Haskell meeting in Leipzig, Germany, June 4

2010-05-11 Thread Johannes Waldmann
The Fifth Haskell in Leipzig meeting will be held on June 4,
see http://www.iba-cg.de/hal5.html .

You can still submit proposals (and wishes)
for tutorials and talks (deadline: May 14).

For instance, we'd love to hear about recent advances
in Haskell IDEs (eclipsefp? leksah?), and parallel/multicore
programming is always a hot topic as well.

The primary language is German but we can switch to English
if requested/agreed upon by audience and speaker.

Best regards, Johannes Waldmann, HTWK Leipzig.
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] How efficient is read?

2010-05-11 Thread Gwern Branwen
On Tue, May 11, 2010 at 12:16 AM, Tom Hawkins tomahawk...@gmail.com wrote:

 The tarball was missing its Rules.hs; as it happens, GHC has a module
 named Rules.hs as well, hence the confusing error. I've uploaded a
 fresh one that should work.

 Thanks.  This builds and installs fine.

 But I think there is something wrong with the generated parser.  It
 doesn't look for (..) groupings.  For example:

 data Something = Something Int (Maybe String)
  deriving Show {-! derive : Parse !-}

 There is nothing in the generated parser to look for parens around the
 Maybe in case it is a (Just string).

 Am I missing something?

I don't know. If you could check whether the original Drift has that
error as well, then I suspect Drift's author, Meachem, would be
interested to know. (I only maintain drift-cabalized as a packaging
fork; I tried not to change any actual functionality.)

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


Re: [Haskell-cafe] How efficient is read?

2010-05-11 Thread Malcolm Wallace

data Something = Something Int (Maybe String)
 deriving Show {-! derive : Parse !-}

There is nothing in the generated parser to look for parens around the
Maybe in case it is a (Just string).


Sorry, that will be my fault.  I contributed the rules for deriving  
Parse to DrIFT.  I am on holiday right now, but will try to take a  
look shortly.


Regards,
Malcolm

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


[Haskell-cafe] Functions of type foo :: f a - g a

2010-05-11 Thread Gordon J. Uszkay
I would like to build a class that includes a method to move data from one 
arbitrary functor to another, a natural transformation.   The structures might 
be more than just functors, but I can start with that.  I ran into some 
practical issues with resolving the type variables for my multiparameter type 
class, which I can resolve with functional dependencies.   I can also not 
isolate the natural transformation from my overall operation, muddling it with 
the element transformation.  I was wondering if anyone had any words of advice, 
example  or warning about this kind of function or method in general?

Class (Functor f, Functor g) = Foo f g a where
  foo :: f a - g a
  bar :: (a-b) - g a - g b

Thanks,

Gordon J. Uszkay, McMaster University
uszka...@mcmaster.ca



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


Re: [Haskell-cafe] Functions of type foo :: f a - g a

2010-05-11 Thread John Meacham
On Tue, May 11, 2010 at 02:01:05PM -0400, Gordon J. Uszkay wrote:
 I would like to build a class that includes a method to move data from one 
 arbitrary functor to another, a natural transformation.   The structures 
 might be more than just functors, but I can start with that.  I ran into some 
 practical issues with resolving the type variables for my multiparameter type 
 class, which I can resolve with functional dependencies.   I can also not 
 isolate the natural transformation from my overall operation, muddling it 
 with the element transformation.  I was wondering if anyone had any words of 
 advice, example  or warning about this kind of function or method in general?
 
 Class (Functor f, Functor g) = Foo f g a where
   foo :: f a - g a
   bar :: (a-b) - g a - g b

A couple points,

  * why is 'a' a member of the type class head? Functors don't care
about what is stored inside the type, so your class shouldn't either
if it is a transformer from functor to functor.
  * isn't bar exactly the same as 'fmap' for g?

A better way might be

class (Functor f, Functor g) = FunctorPair f g where
transformFunctor :: f a - g a

though, I am not sure what your use is, there isn't an obvious instance
to me, but I don't know what your motivating task is.

John

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


Re: [Haskell-cafe] Functions of type foo :: f a - g a

2010-05-11 Thread Edward Kmett
On Tue, May 11, 2010 at 2:01 PM, Gordon J. Uszkay uszka...@mcmaster.cawrote:

 I would like to build a class that includes a method to move data from one
 arbitrary functor to another, a natural transformation.   The structures
 might be more than just functors, but I can start with that.  I ran into
 some practical issues with resolving the type variables for my
 multiparameter type class, which I can resolve with functional dependencies.
   I can also not isolate the natural transformation from my overall
 operation, muddling it with the element transformation.  I was wondering if
 anyone had any words of advice, example  or warning about this kind of
 function or method in general?

 Class (Functor f, Functor g) = Foo f g a where
  foo :: f a - g a
  bar :: (a-b) - g a - g b


In general I would shy away from encoding natural transformations as a
typeclass describing one family of morphisms of the form f a - g a. I would
avoid it because the choice of function f a - g a isn't really canonical.
There are many potentially valid such functions.

foo :: Maybe a - [a]
foo (Just a) = [a]
foo Nothing = []

bar :: Maybe a - [a]
bar (Just a) = repeat a
bar Nothing = []

baz :: Maybe a - [a]
baz _ = Nothing

quux n :: Int - Maybe a - [a]
quux (Just a) = replicate a n
quux Nothing = Nothing

With that in mind an arguably better approach would be to define a natural
transformation as:

type Nat f g = forall a. f a - g a

or even

type f :~ g = forall a. f a - g a

and pass them around explicitly then you can encode things like:

hylohttp://hackage.haskell.org/packages/archive/category-extras/0.53.5/doc/html/Control-Morphism-Hylo.html#v%3Ahylo::
Functorhttp://hackage.haskell.org/packages/archive/base/4.2.0.1/doc/html/Control-Monad.html#t%3AFunctorf
=
Algebrahttp://hackage.haskell.org/packages/archive/category-extras/0.53.5/doc/html/Control-Functor-Algebra.html#t%3AAlgebrag
b - (f
:~http://hackage.haskell.org/packages/archive/category-extras/0.53.5/doc/html/Control-Functor-Extras.html#t%3A%3A%7E%3Eg)
-
Coalgebrahttp://hackage.haskell.org/packages/archive/category-extras/0.53.5/doc/html/Control-Functor-Algebra.html#t%3ACoalgebraf
a - a - b

hylo f e g = f . e . fmap (hylo f e g). g

This is important because there can exist such natural transformations that
need data out of your current environment: i.e. the natural transformation
((,) x), the quux example above, etc.

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


Re: [Haskell-cafe] Functions of type foo :: f a - g a

2010-05-11 Thread C. McCann
On Tue, May 11, 2010 at 2:06 PM, John Meacham j...@repetae.net wrote:
 A better way might be

 class (Functor f, Functor g) = FunctorPair f g where
        transformFunctor :: f a - g a

 though, I am not sure what your use is, there isn't an obvious instance
 to me, but I don't know what your motivating task is.

Furthermore, to select an instance at this point both Functors must be
known in context of use, which exhausts pretty much the entire
informational content of the instance--raising the question of what
benefit is drawn from a type class at all, as opposed to simply
passing around functions of type f a - g a as needed. Consider that
fmap doesn't require a multi-parameter type class for each pair a, b,
it just takes a function (a - b).

The only way a type class would make sense here, I think, is with a
fundep uniquely determining a particular natural transformation based
on one of the Functors, at which point I'm not sure that the concept
of natural transformation is what you're actually trying to model.

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


[Haskell-cafe] comprehending monad execution

2010-05-11 Thread rick
All:

I've been analyzing monads for a while now and have a question on execution. I 
suspect I've missed something basic.

In the snippet below the ghc debugger shows that in just one single step 
Discriminate has been substituted for g.
Even with :trace turned on in the debugger there is no evidence of an execution 
step to carry out the substitution.
This leads me to assume a compile time operation identifies Discriminate as a 
substitute for g.

Could someone correct my assumption or explain how this works?

Note: this snippet was extracted from [1].

 {-# LANGUAGE EmptyDataDecls, Rank2Types #-}
 module LEM where
 import Control.Monad.Identity

 data F -- no constructors

 data Discriminate a b = L a | R b
 instance Monad (Discriminate e) where
 return = R
 R x = f = f x
 L x = f = L x

 h :: (forall m. Monad m = ((a - m F) - m F)) - a
 h g = case g (\x - L x) of
 R x - error Not reachable
 L x - x

 -- A proof term for a - NOT NOT a
 lift :: forall a m. Monad m = a - ((a - m F) - m F)
 lift x = \k - k x

 t = h $ lift True 


ghci trace ...

C:\haskell\lemghci lem.lhs
GHCi, version 6.8.3: http://www.haskell.org/ghc/ :? for help
Loading package base ... linking ... done.
[1 of 1] Compiling LEM ( lem.lhs, interpreted )
Ok, modules loaded: LEM.
*LEM :b h
Breakpoint 0 activated at lem.lhs:(14,2)-(16,17)
*LEM :trace t
Loading package mtl-1.1.0.1 ... linking ... done.
Stopped at lem.lhs:(14,2)-(16,17)
_result :: a = _
[lem.lhs:(14,2)-(16,17)] *LEM :step
Stopped at lem.lhs:(14,8)-(16,17)
_result :: a = _
g :: (a - Discriminate a F) - Discriminate a F = _
[lem.lhs:(14,8)-(16,17)] *LEM :hist
-1 : h (lem.lhs:(14,2)-(16,17))
-2 : t (lem.lhs:22:6-18)
end of history
[lem.lhs:(14,8)-(16,17)] *LEM


My previous analysis includes running single step execution on Wadler's I monad 
here [2], 
where I am able to observe execution of the I monad.

[essence.lhs:32:33-37] *Essence :hist
-1 : unitI (essence.lhs:7:34)
-2 : unitI (essence.lhs:7:2-34)
-3 : interp (essence.lhs:32:26-38)
-4 : interp (essence.lhs:(31,2)-(39,44))
-5 : test (essence.lhs:54:41-51)
-6 : showval (essence.lhs:(26,2)-(28,45))
-7 : showI (essence.lhs:9:34-42)
-8 : showI (essence.lhs:9:2-42)
-9 : test (essence.lhs:54:34-52)
-10 : test (essence.lhs:54:2-52)
end of history

[1] http://okmij.org/ftp/Computation/lem.html
[2] http://homepages.inf.ed.ac.uk/wadler/papers/essence/essence.ps

Thanks much in advance for your help.

Rick



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


[Haskell-cafe] hSetEncoding on socket handles

2010-05-11 Thread David Powell
Greetings,

I am having trouble sending unicode characters as utf8 over a socket handle.
Despite setting the encoding on the socket handle to utf8, it still seems to
use some other encoding when writing to the socket.  It works correctly when
writing to stdout, but not to a socket handle.  I am using ghc 6.12.1 and
network-2.2.1.7.  I can get it to work using System.IO.UTF8, but I was under
the impression this was no longer necessary?

I also don't seem to understand the interaction between hSetEncoding and
hSetBinaryMode because if I set the binary mode to 'False' and the encoding
to
utf8 on the socket, then when writing to the socket the string seems to be
truncated at the first non-ascii codepoint.

Here is a test snippet, which can be used with netcat as a listening server
(ie. nc -l 1234).

 import System.IO
 import Network
 main = do
  let a=λ
  s - connectTo 127.0.0.1 (PortNumber 1234)
  hSetEncoding s utf8
  hSetEncoding stdout utf8
  hPutStrLn s a
  putStrLn a
  hClose s

Thanks,

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


Re: [Haskell-cafe] Speed of Error handling with Continuations vs. Eithers

2010-05-11 Thread wren ng thornton

Max Cantor wrote:

Based on some discussions in #haskell, it seemed to be a consensus
that using a modified continuation monad for Error handling instead
of Eithers would be a significant optimization since it would
eliminate a lot of conditional branching (everytime = is called
in the Either monad, there is a conditional.  


I implemented a ErrCPS monad which does exactly that, but the speed
has been disappointing.  It runs almost exactly 3x slower than a
drop in replacement using the MonadError instance of Either from mtl.



I have noticed speedup in my CPS version of Maybe[1] (kidnapped from the 
Wiki) so the difference is curious. Jan-Willem's comments about closures 
are significant when doing CPS work, but I'd expect Maybe and Either to 
perform similarly, whatever their performance is. It's been a while 
since I've benchmarked MaybeCPS, so perhaps I now have the slowdown too. 
Let's look at the code and see if we can find other differences...


[1] 
http://community.haskell.org/~wren/wren-extras/src/Control/Monad/MaybeCPS.hs



Here's one big difference:


newtype ErrCPS e m a = ErrCPS { runErrCPS ::
forall r . (e - m r) --  error handler
- (a - m r) --  success handler
- m r }


The analogous version I use is:

newtype MaybeCPS a = MaybeCPS
(forall r. (a - Maybe r) - Maybe r)

While I also offer a transformer version of MaybeCPS, the transformer 
*does* suffer from significant slowdown. Also, for MaybeCPS it's better 
to leave the handlers inline in client code rather than to abstract them 
out; that helps to keep things concrete. So perhaps you should first try 
a direct CPS translation:


newtype ErrCPS e a = ErrCPS
(forall r. (a - Either e r) - Either e r)

runErrCPS :: ErrCPS e a - Either e a
runErrCPS (ErrCPS f) = f return

I'd be curious if this version suffers the same slowdown.

--
Live well,
~wren
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] Tsuru Capital is hiring

2010-05-11 Thread Simon Cranshaw
We are looking to hire a programmer that has experience programming in a
functional language, and is familiar with Haskell.

There is a wide range of tools and applications that we want to build over
time, including graphical interfaces and profiling tools for our trading
system, parsers for new market feeds, and algorithms for trading strategies.
If you have experience in any one of these areas it's a definite bonus.

You will be working with a small team of developers, and from time to time
will be working along side Traders to assist in tool development.

Annual compensation will be in the region of USD150k with potential for
growth.

The team is based in Tokyo but there are projects that could be done
remotely so feel free to apply for this type of work also.

http://tsurucapital.com/en/jobs.html#programmer
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Speed of Error handling with Continuations vs. Eithers

2010-05-11 Thread wren ng thornton

wren ng thornton wrote:

Here's one big difference:


newtype ErrCPS e m a = ErrCPS { runErrCPS ::
forall r . (e - m r) --  error handler
- (a - m r) --  success handler
- m r }


The analogous version I use is:

newtype MaybeCPS a = MaybeCPS
(forall r. (a - Maybe r) - Maybe r)

While I also offer a transformer version of MaybeCPS, the transformer 
*does* suffer from significant slowdown. Also, for MaybeCPS it's better 
to leave the handlers inline in client code rather than to abstract them 
out; that helps to keep things concrete. So perhaps you should first try 
a direct CPS translation:


newtype ErrCPS e a = ErrCPS
(forall r. (a - Either e r) - Either e r)

runErrCPS :: ErrCPS e a - Either e a
runErrCPS (ErrCPS f) = f return

I'd be curious if this version suffers the same slowdown.



With this change [1] I can't notice any difference for your 
benchmark[2]. Then again, all the runTest calls take 0 msec and I've had 
no luck making the computation take much time; perhaps your computer can 
detect a difference.


You may want to see what standard benchmarking tools like Microbench[3] 
or the magnificent Criterion[4] have to say. I'd do it myself, but I 
haven't had a chance to reinstall everything since getting my new 
computer (due to the installation issues on newer versions of OSX).



[1] 
http://community.haskell.org/~wren/wren-extras/src/Control/Monad/ErrCPS.hs


[2] 
http://community.haskell.org/~wren/wren-extras/test/Control/Monad/ErrCPS/MaxCantorBenchmark.hs


[3] http://hackage.haskell.org/package/microbench

[4] http://hackage.haskell.org/package/criterion

--
Live well,
~wren
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe