[Haskell-cafe] Re: ANN: Elerea, another FRP library

2009-04-15 Thread Achim Schneider
Patai Gergely patai_gerg...@fastmail.fm wrote:

 ...

I don't think using dirty tricks to implement FRP deserves flak, at
all, from my POV, it sounds like complaining that the IO monad is
implemented using C... meaning that if you're that close to bare
thunks, you have every right to use any means necessary to make them
behave properly.

-- 
(c) this sig last receiving data processing entity. Inspect headers
for copyright history. All rights reserved. Copying, hiring, renting,
performance and/or quoting of this signature prohibited.


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


[Haskell-cafe] Re: Best text editor

2009-04-15 Thread Achim Schneider
Jeff Wheeler j...@nokrev.com wrote:

 As one of the Yi developers, I'd love to hear some more specific
 feedback on this. Do you remember any specific Vim features that were
 missing?

Nope, but I'll be writing bug reports next time, at the very least.

-- 
(c) this sig last receiving data processing entity. Inspect headers
for copyright history. All rights reserved. Copying, hiring, renting,
performance and/or quoting of this signature prohibited.


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


Re: [Haskell-cafe] ANN: Elerea, another FRP library

2009-04-15 Thread Patai Gergely
 I don't think using dirty tricks to implement FRP deserves
 flak, at all, from my POV, it sounds like complaining that the
 IO monad is implemented using C... meaning that if you're that
 close to bare thunks, you have every right to use any means
 necessary to make them behave properly.
Dirtiness is not the problem, but the fact that it can leak out at the
present moment. I want guarantees to exclude the possibility of
undesired behaviour on the user side. Am I right thinking that the
NOINLINE pragma on unsafeDupablePerformIO prevents the problem of
multiple evaluation discussed yesterday? Or should I add NOINLINE to
primitives in Elerea.Internal too? If that guaranteed sharing, it would
certainly solve most of the problems we talked about. Apart from that,
I'm still not sure that latching works the way intended all the time,
but the fact that the breakout example works is an indication that at
least it's not hopelessly broken.

Gergely

-- 
http://www.fastmail.fm - Access all of your messages and folders
  wherever you are

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


Re: [Haskell-cafe] understanding typeable

2009-04-15 Thread Anatoly Yakovenko
So I am getting a little further, but i am seeing this bizarre behaviour:

I wrote a function that will fold over parameters and push them into a
constructor if it can
given this type:

   data Foo = FooC Int
| BarC Int
deriving (Data, Typeable, Show)

i can do this:

let a::Maybe Foo = foldFunc (Just FooC) (params $ BarC 1)
   Loading package syb ... linking ... done.
a
   Just (FooC 1)

here is the implementation

   data Child = forall a. (Typeable a, Data a) = Child a

   params::(Data a) = a - [Child]
   params = gmapQ Child

   --foldFunc :: (Typeable x, Data y) = (Maybe x) - [Child] - Maybe y
   --foldFunc :: forall y1 y.  (Typeable y1, Data y) = Maybe y1 -
[Child] - Maybe y
   foldFunc (Just ff) (ch:[]) = applyCtor ff ch
   foldFunc (Just ff) (ch:tt) = foldFunc (applyFunc ff ch) tt
   foldFunc Nothing _ = Nothing
   foldFunc (Just ff) [] = castObj ff
  where
 castObj::(Typeable y, Data x) = y - (Maybe x)
 castObj = cast

   applyCtor :: (Typeable x, Data y) = x - Child - Maybe y
   applyCtor ff (Child ch) = do
  func - castFunc ff
  return $ func ch
  where
 castFunc::(Typeable y, Data x, Data z) = y - (Maybe (x - z))
 castFunc = cast

   applyFunc :: (Typeable x, Typeable y) = x - Child - Maybe y
   applyFunc ff (Child ch) = do
  func - castFunc ff
  return $ func ch
  where
 castFunc::(Typeable y, Data x, Typeable z) = y - (Maybe (x - z))
 castFunc = cast

now this is the weird part:

--foldFunc :: (Typeable x, Data y) = (Maybe x) - [Child] - Maybe y
--foldFunc :: forall y1 y.  (Typeable y1, Data y) = Maybe y1 -
[Child] - Maybe y

if i uncomment either one of those, (shouldn't they be equivalent?), i
get an error, the first one gives me

   ParseG.hs:44:39:
   Ambiguous type variable `x' in the constraint:
 `Typeable x'
   arising from a use of `applyFunc' at ParseG.hs:44:39-53
   Probable fix: add a type signature that fixes these type variable(s)
   Failed, modules loaded: none.

the second one gives me:

   ParseG.hs:46:24:
   Could not deduce (Data y1) from the context (Typeable y1, Data y)
 arising from a use of `castObj' at ParseG.hs:46:24-33
   Possible fix:
 add (Data y1) to the context of the type signature for `foldFunc'
   In the expression: castObj ff
   In the definition of `foldFunc':
   foldFunc (Just ff) []
  = castObj ff
  where
  castObj :: (Typeable y, Data x) = y - (Maybe x)
  castObj = cast

   ParseG.hs:46:32:
   Couldn't match expected type `y' against inferred type `y1'
 `y' is a rigid type variable bound by
 the type signature for `foldFunc' at ParseG.hs:42:22
 `y1' is a rigid type variable bound by
  the type signature for `foldFunc' at ParseG.hs:42:19
   In the first argument of `castObj', namely `ff'
   In the expression: castObj ff
   In the definition of `foldFunc':
   foldFunc (Just ff) []
  = castObj ff
  where
  castObj :: (Typeable y, Data x) = y - (Maybe x)
  castObj = cast
   Failed, modules loaded: none.

So they are not equivalent, so why is that so, and why is this the
type signature of the function if i dont give one:

:t foldFunc
   foldFunc :: forall y1 y.
   (Typeable y1, Data y) =
   Maybe y1 - [Child] - Maybe y
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] ANN: Elerea, another FRP library

2009-04-15 Thread Patai Gergely
 I will test it on a couple of machines, desktops and laptops.
Try using a sensible nonzero value with threadDelay. Apparently it
brings CPU usage down under Windows while retaining smoothness. However,
increasing it from zero results in jerkiness under Linux...

 If you take a look what Yampa does: it hides signals and only
 exposes signal functions. But that means that the FRP engine
 itself could indeed use mutable variables for its signals, as
 long as during the evaluation of the circuit at time T no side
 effects should occur; the side effects should take place when
 the simulation is advanced to T+dT, which is done after the
 circuit is fully evaluated at time T.
Assuming that everything works as intended, Elerea is indeed free of
side effects. As for the underlying engine, I was also considering the
Hume language, but it has an unpleasant property that every box
(analogous to the signal functions of Yampa) has an implicit delay. In
fact, Elerea can be regarded as some kind of delayless Hume if we squint
enough.

 I'm only a bit worried about your automatic insertion of
 delays; this might break referential transparency at time T,
 since it depends on the order in which the nodes in the circuit
 are evaluated no? The latter could be problematic when doing
 evaluation in parallel on multiple cores I guess.
Oh, it's problematic enough even on a single core. ;) If the network
changes at one place, it might affect evaluation order in a way that
delays can start wandering around in dependency cycles far away. It
could be interesting to analyse the effects of this behaviour. Either
way, this is just a convenience feature for applications where it makes
little difference. I was also thinking about providing two versions of
the library: one inserting delays, and another giving an error instead.

By the way, it's also in the plans to visualise the network.

Gergely

-- 
http://www.fastmail.fm - IMAP accessible web-mail

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


[Haskell-cafe] Re: ANN: Elerea, another FRP library

2009-04-15 Thread Achim Schneider
Patai Gergely patai_gerg...@fastmail.fm wrote:

 Am I right thinking that the
 NOINLINE pragma on unsafeDupablePerformIO prevents the problem of
 multiple evaluation discussed yesterday?

From what I know and experienced, yes. Each individual unsafePerformIO
only ever evaluates its action once, and if they are prevented from
duplicating, things should work out as intended.

-- 
(c) this sig last receiving data processing entity. Inspect headers
for copyright history. All rights reserved. Copying, hiring, renting,
performance and/or quoting of this signature prohibited.


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


Re: [Haskell-cafe] Looking for the fastest Haskell primes algorithm

2009-04-15 Thread wren ng thornton

Edward Kmett wrote:

You might want to start with the Sieve of Atkin:

http://en.wikipedia.org/wiki/Sieve_of_Atkin


Also worth reading _Lazy wheel sieves and spirals of primes_:

http://www.cs.york.ac.uk/ftpdir/pub/colin/jfp97lw.ps.gz

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


[Haskell-cafe] Re: Looking for the fastest Haskell primes algorithm

2009-04-15 Thread Johannes Waldmann
for the API design, always check others before rolling your own.

E.g. the (three) functions with Prime in their name from
http://java.sun.com/javase/6/docs/api/java/math/BigInteger.html
I hope they are there for a reason.

While we're at it - do we have modPow? modInverse?

And of course check their implementation as well
(should be straightforward, but you never know).

J.W.



signature.asc
Description: OpenPGP digital signature
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] Code Golf

2009-04-15 Thread Sebastian Fischer

Fancy some Codegolf?

I wrote the following function for list diagonalization:

 diag l = foldr (.) id ((sel l . flip sel) ((:[]).(:))) []
  where
   sel = foldr (\a b c - id : mrg (a c) (b c)) (const []) . map  
(flip id)


   mrg [] ys = ys
   mrg xs [] = xs
   mrg (x:xs) (y:ys) = (x.y) : mrg xs ys

Self explanatory, isn't it? Here is a test case:

*Main take 10 $ diag [[ (m,n) | n - [1..]] | m - [1..]]
[(1,1),(1,2),(2,1),(1,3),(2,2),(3,1),(1,4),(2,3),(3,2),(4,1)]

I was trying to golf it down [^1] but my brain explodes. If you  
succeed in reducing keystrokes, I'd be happy to know!


Cheers,
Sebastian

[^1]: http://codegolf.com/
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Code Golf

2009-04-15 Thread MigMit

If I understand the problem correctly...

Prelude let diag = concat . diags where diags ((x:xs):xss) = [x] : zipWith (:) 
xs (diags xss)
Prelude take 10 $ diag [[ (m,n) | n - [1..]] | m - [1..]]
[(1,1),(1,2),(2,1),(1,3),(2,2),(3,1),(1,4),(2,3),(3,2),(4,1)]

Sebastian Fischer wrote on 15.04.2009 14:32:

Fancy some Codegolf?

I wrote the following function for list diagonalization:

  diag l = foldr (.) id ((sel l . flip sel) ((:[]).(:))) []
   where
sel = foldr (\a b c - id : mrg (a c) (b c)) (const []) . map (flip 
id)

 
mrg [] ys = ys
mrg xs [] = xs
mrg (x:xs) (y:ys) = (x.y) : mrg xs ys

Self explanatory, isn't it? Here is a test case:

*Main take 10 $ diag [[ (m,n) | n - [1..]] | m - [1..]]
[(1,1),(1,2),(2,1),(1,3),(2,2),(3,1),(1,4),(2,3),(3,2),(4,1)]

I was trying to golf it down [^1] but my brain explodes. If you succeed 
in reducing keystrokes, I'd be happy to know!


Cheers,
Sebastian

[^1]: http://codegolf.com/
___
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] Code Golf

2009-04-15 Thread Emil Axelsson

Sorry, I misread the task :)

/ Emil



Emil Axelsson skrev:

Why not:

  diag = [(x, sum-x) | sum - [2..], x - [1 .. sum-1]]

/ Emil



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


[Haskell-cafe] Data.ByteString woes

2009-04-15 Thread David Carter
Hi,

I am battling with Data.ByteString.Lazy.Char8, and currently losing.
Any help gratefully received. Here's my code:

import qualified Data.ByteString.Lazy.Char8 as B
import Text.Regex.Posix ((=~))
test = B.pack abc =~ B.pack b :: Bool

This works fine without the .Lazy, and is also fine under GHC 6.8.1,
but with GHC 6.10.1, it fails with:

No instances for (Text.Regex.Base.RegexLike.RegexLike
Text.Regex.Posix.Wrap.Regex B.ByteString,
  Text.Regex.Base.RegexLike.RegexMaker
Text.Regex.Posix.Wrap.Regex
Text.Regex.Posix.Wrap.CompOption
Text.Regex.Posix.Wrap.ExecOption
B.ByteString)

I then thought I might work around the problem by converting lazy
ByteStrings to strict ones in order to do the regex match. I
discovered toChunks, which is advertised in the documentation as type
ByteString - [ByteString], but it actually appears to be of type

toChunks :: ByteString - [Data.ByteString.Internal.ByteString]

and I can't see any way of converting a
Data.ByteString.Internal.ByteString to a (strict) ByteString.

Does anyone know whether this is (a) bug(s) in GHC, Data.ByteString,
Text.Regex.Posix or (maybe most likely) my own limited understanding?
And any ideas for fixes or workarounds (other than the obvious one of
downgrading to GHC 6.8)?

Thanks in advance

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


Re: [Haskell-cafe] Re: ANN: Elerea, another FRP library

2009-04-15 Thread Wolfgang Jeltsch
Am Mittwoch, 15. April 2009 09:03 schrieb Achim Schneider:
 I don't think using dirty tricks to implement FRP deserves flak, at
 all, from my POV, it sounds like complaining that the IO monad is
 implemented using C... meaning that if you're that close to bare
 thunks, you have every right to use any means necessary to make them
 behave properly.

It depends. Using unsafe stuff internally, might be acceptable and sometimes 
necessary. I also use unsafePerformIO in Grapefruit for implementing CSignals 
although I’m not very comfortable with this.

On the other hand, breaking referential transparency in the external interface 
is a very bad idea, in my opinion. Actually, this means that the library user 
would have to turn certain compiler optimizations off to get the intended 
behavior. Just have a look at the Haddock docs of unsafePerformIO. In my 
earlier years of Haskell programming, I thought that unsafePerformIO is not 
too bad but I had to discover that it can quickly lead to a catastrophe.

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


Re: [Haskell-cafe] Looking for the fastest Haskell primes algorithm

2009-04-15 Thread Lennart Augustsson
For isPrime you might want to implement the AKS test,
http://en.wikipedia.org/wiki/AKS_primality_test

On Tue, Apr 14, 2009 at 3:05 PM, Edward Kmett ekm...@gmail.com wrote:
 You might want to start with the Sieve of Atkin:

 http://en.wikipedia.org/wiki/Sieve_of_Atkin

 -Edward

 On Tue, Apr 14, 2009 at 8:40 AM, Niemeijer, R.A. r.a.niemei...@tue.nl
 wrote:

 Today I happened to need a large list of prime numbers. Obviously this is
 a well-known problem, so I figured there would be something on Hackage that
 I could use. Surprisingly, there isn’t, or if there is it’s not easy to
 find. Searching for prime or primes on Hackage reveals nothing. Searching
 for primes on Hayoo gives Codec.Encryption.RSA.NumberTheory, but that uses
 the inefficient one-liner implementation. The HaskellWiki article on primes
 (http://www.haskell.org/haskellwiki/Prime_numbers) has a number of
 implementations, but the faster they get, the longer and uglier they become.



 Since it’s such a common problem I’d say it would be a good idea to add a
 package to Hackage that exports

 primes :: [Integer]

 and hides the ugly implementation details. Data.Numbers.Primes seems a
 logical choice for the namespace, but I’m open to suggestions.



 The trick then is to find the most efficient implementation of primes. The
 Haskell wiki article mentions ONeillPrimes.hs as one of the fastest ones,
 but maybe there’s a faster version. So my question is: does anybody know
 what the fastest Haskell algorithm for generating primes is?

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


Re: [Haskell-cafe] Code Golf

2009-04-15 Thread Sebastian Fischer
Prelude let diag = concat . diags where diags ((x:xs):xss) = [x] :  
zipWith (:) xs (diags xss)


this has a different semantics on finite lists, so I should add a test  
case:


*Main diag [[1,2,3],[4,5,6],[7,8,9]]
[1,2,4,3,5,7,6,8,9]

Your version yields [1,2,4,3,5,7].

Actually, there are a number of implementations that implement the  
same behaviour as the original version, e.g.,


  diag = concat . foldr diags []
   where  diags [] ys   = ys
  diags (x:xs) ys   = [x] : merge xs ys

  merge [] ys   = ys
  merge xs@(_:_)   []   = map (:[]) xs
  merge (x:xs) (y:ys)   = (x:y) : merge xs ys

I'd be interested if one can *derive* from the original version a  
simpler version using clever pointfree combinators.


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


Re: [Haskell-cafe] Non-atomic atoms for type-level programming

2009-04-15 Thread Wolfgang Jeltsch
Am Dienstag, 14. April 2009 20:01 schrieb Tillmann Rendel:
 How is the need for a common import for 'data TTrue; data TFalse'
 different then the need for a common import for 'data Bool = True | False'?

Why not say

data True

data False,

instead of

data TTrue

data TFalse?

I don’t see the reason why we should insert the “T”. Data constructors are in 
a different namespace than type constructors.

By the way, the grapefruit-records package imports type-level, only to not 
define its own type-level booleans but to reuse “common” types whereas I 
considered type-level as the standard type level programming library.

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


[Haskell-cafe] Re: Data.ByteString woes

2009-04-15 Thread Achim Schneider
David Carter david.m.car...@gmail.com wrote:

 I then thought I might work around the problem by converting lazy
 ByteStrings to strict ones in order to do the regex match.

strictBS :: LB.ByteString - B.ByteString
strictBS = B.concat . LB.toChunks

lazyBS :: B.ByteString - LB.ByteString
lazyBS = LB.fromChunks . pure

-- 
(c) this sig last receiving data processing entity. Inspect headers
for copyright history. All rights reserved. Copying, hiring, renting,
performance and/or quoting of this signature prohibited.


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


Re: [Haskell-cafe] Code Golf

2009-04-15 Thread Miguel Mitrofanov

What about

diag [[1,2,3],[4],[5,6,7]]

?

What it should be?

Sebastian Fischer wrote on 15.04.2009 15:28:
Prelude let diag = concat . diags where diags ((x:xs):xss) = [x] : 
zipWith (:) xs (diags xss)


this has a different semantics on finite lists, so I should add a test 
case:


*Main diag [[1,2,3],[4,5,6],[7,8,9]]
[1,2,4,3,5,7,6,8,9]

Your version yields [1,2,4,3,5,7].

Actually, there are a number of implementations that implement the same 
behaviour as the original version, e.g.,


  diag = concat . foldr diags []
   where  diags [] ys   = ys
  diags (x:xs) ys   = [x] : merge xs ys

  merge [] ys   = ys
  merge xs@(_:_)   []   = map (:[]) xs
  merge (x:xs) (y:ys)   = (x:y) : merge xs ys

I'd be interested if one can *derive* from the original version a 
simpler version using clever pointfree combinators.


Cheers,
Sebastian
___
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] Ambiguous reified dictionaries

2009-04-15 Thread Jules Bean

Simon Peyton-Jones wrote:
 Yes, Haskell says that in any program there should be only one
 instance for any particular type (here Monoid Int).  GHC
 doesn't check that, but it should really do so.  It's not
 necessary for soundness (ie no runtime crash) but it is
 necessary for coherence (ie when you run the program the answer
 you get doesn't depend on which dictionary the typechecker
 arbitrarily chose).

Unless of course, your program implicitly depends on the coherence of 
dictionary choice for its own soundness, for example, a program using 
Data.Typeable to implement Dynamic or similar.


Jules

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


Re: [Haskell-cafe] Code Golf

2009-04-15 Thread Sebastian Fischer

diag [[1,2,3],[4],[5,6,7]]
What it should be?


*Main diag [[1,2,3],[4],[5,6,7]]
[1,2,4,3,5,6,7]

it's basically just skipping holes:

1 2 3
4
5 6 7
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Non-atomic atoms for type-level programming

2009-04-15 Thread Claus Reinke

- if type-level tags (such as 'data TTrue'/'data TFalse') are declared
   repeatedly in separate modules, they represent separate types,
   preventing shared use (your type-level predicate doesn't return
   my version of 'TTrue'/'TFalse')


How is the need for a common import for 'data TTrue; data TFalse' 
different then the need for a common import for 'data Bool = True | False'?


'Bool' is hardcoded at the language level (if/then/else), not just standard
library, not just implicitly imported Prelude, so that seems very stable - 
stable enough for a single common standard library import (unlike many

type-level programming concepts, which still require experimentation
and variation).

But even that is considered too unflexible - some users want alternative
Preludes (be it temporarily, to develop a better standard, or permanently,
for personal preferences), most authors of embedded domain-specific 
languages have wanted to replace 'Bool' and associated syntax/classes/

operations with a variant matching their needs.

Now you have several definitions of 'Bool', some of which may be
compatible with each other (say, two variants of FRP libraries that
both simply lift 'Bool' into 'Time-Bool'). How do you, as a library 
user, express that two compatible types from different sources are 
to be considered equivalent, without forcing the authors of the 
compatible definitions to collaborate on a common standard 
library for both their projects? It is not a question of possible-in-theory,

it is a question of pragmatics.

The need to go beyond common imports, temporarily (as systems
evolve) or permanently (because tree-like hierarchies do not fit
all modularization strategies), exists for 'Bool' as well as for 'TBool'.

Standard ML's answer to that kind of issue is type sharing. Haskell 
has no equivalent. Haskell has further needs in going beyond plain
hierarchical import structures, though - think of the proposals for 
class aliases, or the question of how to split up package dependencies 
without relying on orphan instances, how to depend on packages in 
specific configurations, etc. Again, the ML family of advanced module

systems has some answers to offer (and, yes, we can encode much
of those in Haskell's type system, but who does that when writing
cabal packages?).

Haskell'98, by design, had the simplest module system it could get
away with. These days, additional layers have accumulated around
this core, based on libraries and cabal packages. These layers run
into all the problems of advanced module systems, only that these
problems currently  aren't acknowledged as language design 
problems, but are treated as issues to hack around whenever 
someone is available to do the hacking.


Clearly, the advent of type-level programming necessitates the design of 
a type-level standard library, which provides standard abstractions to 
enable interoperation of custom libraries. But I don't see why the 
module system should not scale to type-level programming.


Haskell's module system is an embarrassment ignoring decades
of research, its one strong point being its simplicity. There has long
been an implicit assumption that advances in modular programming
would come either via the type class system, or via extensible records,
and that these advanced would happen within modules, without having
to evolve the module system beyond simple namespace management.

In practice, cabal and hackage have changed all that, introducing a
de-facto module configuration system on top of the existing modules, 
with an evolving design.


My typed non-atomic atoms don't fix any of that, but they do seem
to offer a workaround for a single issue that has been around for years,
and has led to several trac tickets and type-level library awkwardnesses.
For instance, it isn't necessary to pre-define hundreds of constant literals 
for a type-level numeric library if they can be generated in client code,

nor is it necessary to hand-define or template-generate an ordering
relation on constructors (which some type-level libraries depend on)
if it can be defined once and for all.

Non of this means that it wouldn't be good to have a standard
library for type-level programming - in fact, I'd expect a revised 
Data.Label to become a small part of such standard!-)


Claus

ps. If you want to know more about my view on module systems
   for functional languages, have a look at chapter 4 of
   http://community.haskell.org/~claus/publications/phd.html ,
   titled Module Systems for Functional Languages. 

   It is slightly dated by now -lots of things have happened in program 
   (de-)composition research since 1997, when that was written-, but 
   the basis for Haskell's module system is much more ancient that that, 
   so it might be interesting for new Haskellers to see just how old

   some of Haskell's advanced ideas really are;-)


___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org

Re: [Haskell-cafe] Code Golf

2009-04-15 Thread Jan Christiansen

Hi,

On 15.04.2009, at 13:28, Sebastian Fischer wrote:

Actually, there are a number of implementations that implement the  
same behaviour as the original version, e.g.,


 diag = concat . foldr diags []
  where



 diags [] ys   = ys
 diags (x:xs) ys   = [x] : merge xs ys

 merge [] ys   = ys
 merge xs@(_:_)   []   = map (:[]) xs
 merge (x:xs) (y:ys)   = (x:y) : merge xs ys



I think your first implementation is a slightly unreadable : )  
implementation of this version but uses functional lists instead of  
standard lists. If we replace some of the lists by functional lists we  
get the following


diag :: [[a]] - [a]
diag = toList . concatFL . foldr diags2 []
 where
diags [] ys = ys
diags (x:xs) ys = (x:) : merge xs ys

merge [] ys = ys
merge xs@(_:_) [] = map (:) xs
merge (x:xs) (y:ys) = ((x:) . y) : merge xs ys

with the following definitions

concatFL :: [[a] - [a]] - [a] - [a]
concatFL = foldr (.) id

toList :: ([a] - [a]) - [a]
toList fl = fl []

Additionally we can move the 'map (:)' in merge to diags

diag :: [[a]] - [a]
diag = toList . concatFL . foldr diags []
 where
diags [] ys = ys
diags (x:xs) ys = (x:) : merge (map (:) xs) ys

merge [] ys = ys
merge xs@(_:_) [] = xs
merge (x:xs) (y:ys) = (x . y) : merge xs ys

If we now replace toList and concatFL by its definitions it looks very  
similar to the original implementation.


diag :: [[a]] - [a]
diag = foldr (.) id (foldr diags []) []
 where
diags [] ys = ys
diags (x:xs) ys = (x:) : merge (map (:) xs) ys

merge [] ys = ys
merge xs@(_:_) [] = xs
merge (x:xs) (y:ys) = (x . y) : merge xs ys

 diag l = foldr (.) id ((sel l . flip sel) ((:[]).(:))) []
  where
   sel = foldr (\a b c - id : mrg (a c) (b c)) (const []) . map  
(flip id)


   mrg [] ys = ys
   mrg xs [] = xs
   mrg (x:xs) (y:ys) = (x.y) : mrg xs ys

I guess that we can inline diags and get the definition above but I am  
kind of stuck here.


Cheers, Jan

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


Re: [Haskell-cafe] ANN: Elerea, another FRP library

2009-04-15 Thread Peter Verswyvelen
Well, a breakout game does *not* work (yet) in most other FRP
implementations except Yampa, which do have firm theoretical foundations :-)
2009/4/15 Patai Gergely patai_gerg...@fastmail.fm

  I don't think using dirty tricks to implement FRP deserves
  flak, at all, from my POV, it sounds like complaining that the
  IO monad is implemented using C... meaning that if you're that
  close to bare thunks, you have every right to use any means
  necessary to make them behave properly.
 Dirtiness is not the problem, but the fact that it can leak out at the
 present moment. I want guarantees to exclude the possibility of
 undesired behaviour on the user side. Am I right thinking that the
 NOINLINE pragma on unsafeDupablePerformIO prevents the problem of
 multiple evaluation discussed yesterday? Or should I add NOINLINE to
 primitives in Elerea.Internal too? If that guaranteed sharing, it would
 certainly solve most of the problems we talked about. Apart from that,
 I'm still not sure that latching works the way intended all the time,
 but the fact that the breakout example works is an indication that at
 least it's not hopelessly broken.

 Gergely

 --
 http://www.fastmail.fm - Access all of your messages and folders
  wherever you are

 ___
 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] Code Golf

2009-04-15 Thread Emil Axelsson

Why not:

  diag = [(x, sum-x) | sum - [2..], x - [1 .. sum-1]]

/ Emil



MigMit skrev:

If I understand the problem correctly...

Prelude let diag = concat . diags where diags ((x:xs):xss) = [x] : 
zipWith (:) xs (diags xss)

Prelude take 10 $ diag [[ (m,n) | n - [1..]] | m - [1..]]
[(1,1),(1,2),(2,1),(1,3),(2,2),(3,1),(1,4),(2,3),(3,2),(4,1)]

Sebastian Fischer wrote on 15.04.2009 14:32:

Fancy some Codegolf?

I wrote the following function for list diagonalization:

  diag l = foldr (.) id ((sel l . flip sel) ((:[]).(:))) []
   where
sel = foldr (\a b c - id : mrg (a c) (b c)) (const []) . map 
(flip id)

 
mrg [] ys = ys
mrg xs [] = xs
mrg (x:xs) (y:ys) = (x.y) : mrg xs ys

Self explanatory, isn't it? Here is a test case:

*Main take 10 $ diag [[ (m,n) | n - [1..]] | m - [1..]]
[(1,1),(1,2),(2,1),(1,3),(2,2),(3,1),(1,4),(2,3),(3,2),(4,1)]

I was trying to golf it down [^1] but my brain explodes. If you 
succeed in reducing keystrokes, I'd be happy to know!


Cheers,
Sebastian

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


Re: [Haskell-cafe] GHC including System.Time but not Data.Time?

2009-04-15 Thread John Goerzen
Lennart Augustsson wrote:
 Removing a package in a minor release is, to quote, an epic fail.
 I don't understand how that could be done.

I agree.  Is there any chance of 6.10.3 reverting the change?

-- John

 
   -- Lennart
 
 On Tue, Apr 14, 2009 at 6:56 PM, Bulat Ziganshin
 bulat.zigans...@gmail.com wrote:
 Hello John,

 Tuesday, April 14, 2009, 8:44:12 PM, you wrote:

 I understand the goal of removing stuff from GHC, but the practical
 implications can be rather annoying.
 i think that Haskell Platform will eventually replace what GHC was for
 a years, i.e. out-of-box solution for practical haskell usage. and ghc
 should be just what its name implies - bare compiler

 but i agree that stripping one package in minor 6.10.2 version, w/o
 Haskell Platform really available was an error

 --
 Best regards,
  Bulatmailto:bulat.zigans...@gmail.com

 ___
 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[2]: [Haskell-cafe] GHC including System.Time but not Data.Time?

2009-04-15 Thread Bulat Ziganshin
Hello John,

Wednesday, April 15, 2009, 5:35:00 PM, you wrote:

 I agree.  Is there any chance of 6.10.3 reverting the change?

both 6.6 and 6.8 had last releases at spring, so i don't expect new
6.10.* at all



-- 
Best regards,
 Bulatmailto:bulat.zigans...@gmail.com

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


[Haskell-cafe] types and braces

2009-04-15 Thread Conor McBride

Hi folks

In search of displacement activity, I'm trying to tweak
Language.Haskell.Exts to support a few more perfidious
Exts I have in mind -- they only need a preprocessor,
but I do need to work on parsed programs, ideally.

I was hoping to add a production to the grammar of types
to admit expressions, delimited by braces:

  { exp }

The idea is that instead of writing, (er, hi Claus),

data True
data False

one just re-uses yer actual Bool (which becomes kind
{Bool}) and writes {True} or {False}.

The trouble is, the production I've added causes a
reduce/reduce conflict in the grammar, but I don't get
any more precise complaint than that.

I guess what I'd like to know is whether I just need to
debug my grammar extension, or whether the notation I'm
proposing actually introduces a serious ambiguity that
I'm too dim to notice. I'm mostly sending this in the
hope that I have one of those d'oh moments you
sometimes get when you articulate a stupid question in
public.

Put me out of my misery, please...

Cheers

Conor

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


[Haskell-cafe] Re: [ANNOUNCE] hgettext 0.1.10 - last major release

2009-04-15 Thread Florent Becker
Vasyl Pasternak vasyl.paster...@gmail.com writes:

 Hello,

 I've uploaded last (and latest) significant version on hgettext
 module. Currently it works fine, and has bindings to all gettext
 functions (from libintl.h). Next versions will be only bug fixes of
 this version.

 I don't see any strong reasons to write any combinators over this
 basic bindings. Haskell needs more powerful internationalization
 library, and I am plan to design it, but it will be completely
 different from gettext principles, so this library will be released
 with another name.

Does this means that the string files (if they exist at all) won't be
in po format, or some approximation thereof? This could be a problem
for translators.

Florent

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


Re: [Haskell-cafe] types and braces

2009-04-15 Thread Lennart Augustsson
I'd suggest using some different kind of brackets to relieve the
misery, like {| |}.

On Wed, Apr 15, 2009 at 4:10 PM, Conor McBride
co...@strictlypositive.org wrote:
 Hi folks

 In search of displacement activity, I'm trying to tweak
 Language.Haskell.Exts to support a few more perfidious
 Exts I have in mind -- they only need a preprocessor,
 but I do need to work on parsed programs, ideally.

 I was hoping to add a production to the grammar of types
 to admit expressions, delimited by braces:

  { exp }

 The idea is that instead of writing, (er, hi Claus),

 data True
 data False

 one just re-uses yer actual Bool (which becomes kind
 {Bool}) and writes {True} or {False}.

 The trouble is, the production I've added causes a
 reduce/reduce conflict in the grammar, but I don't get
 any more precise complaint than that.

 I guess what I'd like to know is whether I just need to
 debug my grammar extension, or whether the notation I'm
 proposing actually introduces a serious ambiguity that
 I'm too dim to notice. I'm mostly sending this in the
 hope that I have one of those d'oh moments you
 sometimes get when you articulate a stupid question in
 public.

 Put me out of my misery, please...

 Cheers

 Conor

 ___
 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] types and braces

2009-04-15 Thread Conor McBride


On 15 Apr 2009, at 16:01, Lennart Augustsson wrote:


I'd suggest using some different kind of brackets to relieve the
misery, like {| |}.


That would speed up my tinkering, certainly.

I did have a d'oh moment: you can write

  data Foo = Moo {goo :: Int}  -- braces where a type goes

and indeed, commenting out field declarations makes happy
happy. However, these { exp } guys never stand as types of
things, only as parameters of types, so it might be possible
to resolve the problem without fat brackets. Whether it's
worth it is another matter...

Cheers

Conor

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


[Haskell-cafe] cabal install vs. profiling

2009-04-15 Thread David F. Place
Hi,

Suppose I have installed a number of libraries and have written a
program using them.  Now, I want to profile my program.  What is the
best way to get the profiling versions of the libraries installed?

Thanks,
David

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


Re: [Haskell-cafe] cabal install vs. profiling

2009-04-15 Thread Gwern Branwen

On Wed, Apr 15, 2009 at 11:21 AM, David F. Place d...@vidplace.com wrote:

Hi,

Suppose I have installed a number of libraries and have written a
program using them.  Now, I want to profile my program.  What is the
best way to get the profiling versions of the libraries installed?

Thanks,
David


I'd chuck 'library-profiling: True' into my .cabal/config, and do 'cabal install 
--reinstall list of libraries' (being careful to exclude the core libraries 
like unix and process).

--
gwern

signature.asc
Description: OpenPGP digital signature
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] ANN: level-monad-0.3

2009-04-15 Thread Sebastian Fischer

I am pleased to announce version 0.3 of the package level-monad.

This package implements breadth-first search directly as an instance  
of MonadPlus (without using an intermediate tree representation). In  
version 0.3 I have added a MonadPlus instance for iterative deepening  
inspired by Michael Spivey's paper on Algebras for combinatorial  
search[1].


The package is on Hackage:
http://hackage.haskell.org/cgi-bin/hackage-scripts/package/level-monad

Sources are on Github:
http://github.com/sebfisch/level-monad

Cheers,
Sebastian

[1]: http://spivey.oriel.ox.ac.uk/mike/search-jfp.pdf
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Looking for the fastest Haskell primes algorithm

2009-04-15 Thread Adrian Neumann

I've just uploaded a package with some functions I had lying around.

 http://hackage.haskell.org/cgi-bin/hackage-scripts/package/Numbers


Am 14.04.2009 um 14:40 schrieb Niemeijer, R.A.:

Today I happened to need a large list of prime numbers. Obviously  
this is a well-known problem, so I figured there would be something  
on Hackage that I could use. Surprisingly, there isn’t, or if there  
is it’s not easy to find. Searching for prime or primes on Hackage  
reveals nothing. Searching for primes on Hayoo gives  
Codec.Encryption.RSA.NumberTheory, but that uses the inefficient  
one-liner implementation. The HaskellWiki article on primes (http:// 
www.haskell.org/haskellwiki/Prime_numbers) has a number of  
implementations, but the faster they get, the longer and uglier  
they become.




Since it’s such a common problem I’d say it would be a good idea to  
add a package to Hackage that exports


primes :: [Integer]

and hides the ugly implementation details. Data.Numbers.Primes  
seems a logical choice for the namespace, but I’m open to suggestions.




The trick then is to find the most efficient implementation of  
primes. The Haskell wiki article mentions ONeillPrimes.hs as one of  
the fastest ones, but maybe there’s a faster version. So my  
question is: does anybody know what the fastest Haskell algorithm  
for generating primes is?


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




PGP.sig
Description: Signierter Teil der Nachricht
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] Fast mutable arrays of ByteString?

2009-04-15 Thread Maxime Henrion
Hello all,


I have been rewriting a small utility program of mine from C to Haskell
for fun.  This tool reads lines from stdin or from files, shuffles them
one or more times using the Fisher-Yates algorithm, and outputs the
result to stdout.

Since this algorithm is based on in-place updates, I've been storing my
strings in a mutable array in the ST monad.  Since it's holding strings
I could not use an unboxed array.  The resulting program works fine and
seems to run at a decent speed, even though it is much slower than the
original C version, slightly more so than I expected.

While trying to optimize it using profiling, and playing with the number
of shuffling passes, I noticed that this operation was responsible for a
significant amount of the runtime, much more so than with the C version.
I also noticed that the %GC time was around 56%.

In order to do more tests, I wrote another version of this program which
keeps the strings in a pure and immutable array, and stores the indices
of this array in an unboxed mutable ST array.  The shuffling is then
done on this indices array instead of the strings array.

This version runs much faster and only spends ~21% of its time in the
garbage collector, at the cost of consuming more memory for the indices
array.

I'm attaching both versions of the code to this e-mail, and I'd be
curious to hear about any possible improvements to it, and whether the
performance of STArray of ByteString I'm observing corresponds to
people's expectations.

Thanks in advance,
Maxime Henrion
{-# LANGUAGE BangPatterns #-}
module Main where

import Control.Monad
import Control.Monad.ST
 
import Data.Array.ST
import Data.ByteString.Char8 (ByteString)
import qualified Data.ByteString.Char8 as S
import Data.Maybe

import System.Console.GetOpt
import System.Environment
import System.IO
import System.Random

data Config = Config
  { separator :: Char
  , numPasses :: Int
  } deriving (Eq, Show)

defaultConfig = Config
  { separator = '\n'
  , numPasses = 1
  }

options :: [OptDescr (Config - Config)]
options =
  [ Option ['0'] [] (NoArg (\cfg - cfg { separator = '\0' }))
  expect ASCII NUL characters as separators
  , Option ['d'] [] (OptArg ((\d cfg - cfg { separator = d }) . maybe '\n' head) delim)
  use provided character as separator
  , Option ['n'] [] (OptArg ((\n cfg - cfg { numPasses = n }) . readNumPasses) npass)
  run # passes instead of just 1
  ]
 where readNumPasses = maybe 1 (headMaybe 1 fst . reads)
   headMaybe _ f [x] = f x
   headMaybe d _ _   = d

main :: IO ()
main = do argv - getArgs
  case getOpt RequireOrder options argv of
(opts, args, []) - do g - newStdGen
   input - getInput args
   let Config { separator = sep
  , numPasses = n
  } = foldl (flip id) defaultConfig opts
   forM_ (shuffle g n (slice sep input)) $ \ln -
 S.putStr ln  putChar sep
(_,  _, (err:_)) - do prog - getProgName
   hPutStr stderr (prog ++ :  ++ err)

getInput :: [FilePath] - IO ByteString
getInput [] = S.getContents
getInput ps = S.concat `fmap` mapM S.readFile ps

slice :: Char - ByteString - (Int, [ByteString])
slice d s = slice' d s 1 []
  where
slice' d s !count lns =
  case S.elemIndex d s of
Nothing- (count, s:lns)
Just n
 | n == S.length s - 1 - (count, S.take n s:lns) -- ignore empty trailing lines
 | otherwise   - slice' d (S.drop (n + 1) s) (count + 1) (S.take n s:lns)
{-# INLINE slice #-}

shuffle :: RandomGen g = g - Int - (Int, [ByteString]) - [ByteString]
shuffle g n (count,lns) =
  runST $ do
arr - newListArray (0,count - 1) lns :: ST s (STArray s Int ByteString)
forM_ swaps $ \(i,j) -
  when (i /= j) $ do
tmp - readArray arr i
readArray arr j = writeArray arr i
writeArray arr j tmp 
getElems arr
  where swaps = zipWith (\n k - (n - 1, k `mod` n))
  (concat $ replicate n [count,count-1..2]) (randoms g)
{-# LANGUAGE BangPatterns #-}
module Main where

import Control.Monad
import Control.Monad.ST
 
import Data.Array
import Data.Array.ST
import Data.ByteString.Char8 (ByteString)
import qualified Data.ByteString.Char8 as S
import Data.Maybe

import System.Console.GetOpt
import System.Environment
import System.IO
import System.Random

data Config = Config
  { separator :: Char
  , numPasses :: Int
  } deriving (Eq, Show)

defaultConfig = Config
  { separator = '\n'
  , numPasses = 1
  }

options :: [OptDescr (Config - Config)]
options =
  [ Option ['0'] [] (NoArg (\cfg - cfg { separator = '\0' }))
  expect ASCII NUL characters as separators
  , Option ['d'] [] (OptArg ((\d cfg - cfg { separator = d }) . maybe '\n' head) 

RE: [Haskell-cafe] Strange type error with associated type synonyms

2009-04-15 Thread Simon Peyton-Jones

| But the core part of my suggestion (which this example was meant
| to help explain) remains attractive, at least to me: somewhere during
| type inference, GHC *does* unify the *apparently free* 'd' with an
| internal type variable (lets call it 'd1, as in the type error message)

You are speculating about the *algorithm*.  I rather doubt that exposing more 
of the algorithm to users is going to be helpful; the whole point of a 
declarative description of the type system is that it specifies which programs 
are typeable without giving the nitty gritty of an algorithm.

Even I, who implemented GHC's current algorithm, cannot follow your algorithmic 
explanation.

| that has no explicit counterpart in source code or type signature,
| so the inferred type should not be
|
| f' :: forall d. (Fun d) = Memo d a - Memo d a -- (1)
|
| but rather
|
| f' :: forall d. (Fun d,d~d1) = Memo d a - Memo d a -- (2)

What is this d1?  Where is it bound?

| All I'm suggesting is that the type *printed* by GHCi does not
| really represent the type *inferred* by GHCi (or else there should
| not be any attempt to match the *free* 'd' against some unknown
| 'd1', as the error message says), and that there might be ways to
| make the discrepancy explicit, by printing the inferred type differently.

I believe that it *does* really represent the type inferred by GHC, in fact.

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


Re: [Haskell-cafe] Re: Maybe off-topic -- Writing contracts or software specifications

2009-04-15 Thread Peter Verswyvelen
There's one sentence I remember from some Extreme Programming books I read:
the customer only knows what he wants when he gets it

:-)


On Tue, Apr 14, 2009 at 11:27 AM, Achim Schneider bars...@web.de wrote:

 Richard O'Keefe o...@cs.otago.ac.nz wrote:

  If you have a low level of trust, you'll need a great level of
  detail, and it still won't help.
 
 Heh. Keep your friends close, your enemies closer.

 Freelancing, I was always paid per hour, not per feature. From my
 experience, writing something like The contractor will work closely
 with an employee designated by Foo to ensure formal and informal, known
 or yet to be discovered, specifications are implemented is the best
 thing you can do. If you have it, mention your QA and its guidelines.
 If you don't have it, get both. [1]

 It's more than enough to boot a bad teamplayer out of his contract,
 doesn't induce frowns in top coders (SNAFU, as those are the ones you
 want to hire), does not risk mis-specifying requirements (which, with
 legal backing, is also SNAFU) and doesn't take longer and/or cost more
 to work out than the program itself (SNAFU, again). Be sure that not
 only bugs are fixed, but the reasons they appeared in the first place,
 too: That's the secret people writing space shuttle control software and
 similar use.


 [1] Even if it's just one guy working out things like Every function
must be documented and me getting a bug report saying Help text
does not mention how to display help text.
 --
 (c) this sig last receiving data processing entity. Inspect headers
 for copyright history. All rights reserved. Copying, hiring, renting,
 performance and/or quoting of this signature prohibited.


 ___
 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] ANN: Elerea, another FRP library

2009-04-15 Thread Claus Reinke

but the fact that the breakout example works is an indication that at
least it's not hopelessly broken.

Well, a breakout game does *not* work (yet) in most other FRP
implementations except Yampa, which do have firm theoretical foundations :-)


While certainly more entertaining, the problem looks similar enough
to the NLift example (a lift serving requests on n floors[0]) in FunWorlds 
(the 2002 OpenGL version[1], not the 2001 VRML version[2]), chosen

to test some expressiveness aspects of the language:

- a dynamically updated collection (requests in NLift, bricks in breakout)
- an object moving in response to user input (lift/paddle+ball)
- collection and object reacting to each other's relative positions 
   (lift at floor levels/paddle ball brick collisions)


In NLift, user input (keyboard) adds to the requests collection, and the
lift reacts to the request collection and its own status, while in breakout, 
user input (mouse) directly controls the paddle, to which the ball reacts. 
The lift stopping at a floor directly removes a request there, while breakout 
bricks disappear when hit by the additional ball. In NLift, collisions and 
movement are one-dimensional, while breakout is two-dimensional.


On the other hand, I hadn't got round to cleaning up the interface, 
let alone firming the theoretical foundations, so perhaps this isn't an 
exception to your rule?-) But I thought I'd mention it on the topic of

other FRP libraries, with variations of approach/concepts.

Claus

[0] http://community.haskell.org/~claus/FunWorlds/NLift.hs
[1] http://community.haskell.org/~claus/FunWorlds/
[2] http://community.haskell.org/~claus/FunWorlds/VRML/

FunWorlds/OpenGL in brief:

- a behaviour is a description of an experiment

- a behaviour can be sampled (performing the experiment), yielding a current
value and a residual behaviour (the latter replaces the original behaviour)

- the results of measurements can be broadcast and observed via behavioural
channels (a channel observer simply behaves as the channel source behaviour,
with a slight delay)

That's it! The is no special role for time at all. One can establish local
clocks, one can even broadcast their ticking behaviours. But one cannot take an
arbitrary absolute time and ask for the value of a behaviour at that time
(other than actually running that behaviour forward or backward from now).

Also, there is a natural distinction between describing and running a
behaviour, with the ability to refer to either the description or to sample
outcomes. And having the same behaviour description on both sides of an event
in a stepper/until does not mean that nothing changes at the step: the second
copy doesn't continue where the first left off, but starts from its own
beginning (with no special tricks to achieve this). There are no separate
events, and delays enter via behavioural channels.

Well, there were lots of negatives as well (eg FunWorlds was an
engine-exposed workbench rather than a user-directed library), but I 
thought I'd try to get you interested first!-) I'd love to have funding to

work out the details and clean up/modernize the interface, but without
funding, it'll just have to wait until I get round to it (or one of the newer
FRP libraries renders it superfluous..).

If you try the examples, you'll notice that some of them run too fast on
modern machines (because they weren't tied to an external clock), so
you'd have to slow them down (eg, Surface and Torus, in addition to 
the standard rotate/scale controls, also react to 't'/'T' for scaling time) 
but they are are still fun to watch in their naivete (try Boids for simplicity, 
Flock2 for chaos - you'll need to scale it 's'/'S').



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


Re: [Haskell-cafe] types and braces

2009-04-15 Thread Niklas Broberg
Hi Conor,

Conor McBride:
 The trouble is, the production I've added causes a
 reduce/reduce conflict in the grammar, but I don't get
 any more precise complaint than that.

To get more precise complaints, you should give the -i flag to happy,
that will cause happy to print the whole parser table into a file
named Parser.info. It also tells you in which states the conflicts
occur, allowing you to track 'em down.

 I guess what I'd like to know is whether I just need to
 debug my grammar extension, or whether the notation I'm
 proposing actually introduces a serious ambiguity that
 I'm too dim to notice. I'm mostly sending this in the
 hope that I have one of those d'oh moments you
 sometimes get when you articulate a stupid question in
 public.

I don't immediately see what the clash in that context would be - I
*think* what you propose should be doable. I'd be interested to know
what you come up with, or I might have a look at it myself when I find
a few minutes to spare.

Cheers,

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


Re: [Haskell-cafe] types and braces

2009-04-15 Thread Conor McBride

Hi Niklas

Good to hear from you, and thanks for providing such a
useful starting point for my experiments.

On 15 Apr 2009, at 19:27, Niklas Broberg wrote:


Hi Conor,

Conor McBride:

The trouble is, the production I've added causes a
reduce/reduce conflict in the grammar, but I don't get
any more precise complaint than that.


To get more precise complaints, you should give the -i flag to happy,
that will cause happy to print the whole parser table into a file
named Parser.info. It also tells you in which states the conflicts
occur, allowing you to track 'em down.


So that's how you do it! I was expecting that some such thing
would exist.





I guess what I'd like to know is whether I just need to
debug my grammar extension, or whether the notation I'm
proposing actually introduces a serious ambiguity that
I'm too dim to notice. I'm mostly sending this in the
hope that I have one of those d'oh moments you
sometimes get when you articulate a stupid question in
public.


I don't immediately see what the clash in that context would be - I
*think* what you propose should be doable. I'd be interested to know
what you come up with, or I might have a look at it myself when I find
a few minutes to spare.


I've found that I can add a production

atype :: { Type }
  ...
  | '{' trueexp '}'

if I remove the productions for record declarations

constr1 :: { ConDecl }
  | con '{' '}'   { RecDecl $1 [] }
  | con '{' fielddecls '}'{ RecDecl $1 (reverse $3) }

which suggests that it is indeed the syntax

  data Moo = Foo {goo :: Boo Hoo}

which is in apparent conflict with my proposed extension.
The current parser uses the type parser btype to parse the
initial segment of constructor declarations, so my change
causes trouble.

Further trouble is in store from infix constructors

  data Noo = Foo {True} :*: Foo {False}

should make sense, but you have to look quite far to
distinguish that from a record.

So I don't see that my proposed extension introduces a
genuine ambiguity, but it does make the parser a bit
knottier.

I can use (|...|) as the brackets I need in the meantime,
without even disturbing the lexer, but I'd much rather
use {...} if I can learn a bit more happy hacking. My
efforts so far have been clumsy and frustrating, but -i
might help me see what I'm doing wrong.

Subtle stuff

Conor

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


[Haskell-cafe] Enum to String, and back?

2009-04-15 Thread michael rice
Hi,

Using Show it is possible to establish a relationship between an enum type

data Color
    = Red
    | Blue
    | Green
    | Yellow
    | Orange
    | Brown
    | White
    | Black
    deriving (Show, Eq, Enum, Bounded)

and a String type to display it.

*Main Red
Red
*Main [Red,Green,Blue]
[Red,Green,Blue]
*Main

which is

Red :: Color - Red :: [Char] 

Can one as easily establish a reverse relationship, i.e., convert a String type 
like Red back to its corresponding Color type?

So that

Red :: [Char] - Red :: Color


Michael  




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


Re: [Haskell-cafe] Enum to String, and back?

2009-04-15 Thread Martijn van Steenbergen

Hi Michael,

michael rice wrote:
Can one as easily establish a reverse relationship, i.e., convert a 
String type like Red back to its corresponding Color type?


So that

Red :: [Char] - Red :: Color


Yes, simply add Read to your list of to be derived type classes. Then 
you can say:


 read Red :: Color

HTH,

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


Re: [Haskell-cafe] Enum to String, and back?

2009-04-15 Thread Rahul Kapoor
On Wed, Apr 15, 2009 at 3:13 PM, michael rice nowg...@yahoo.com wrote:
 Using Show it is possible to establish a relationship between an enum type
 and a String type to display it.
 Can one as easily establish a reverse relationship, i.e., convert a String
 type like Red back to its corresponding Color type?

Make it an instance of the Read type class.
http://haskell.org/ghc/docs/latest/html/libraries/base/Prelude.html#t%3ARead

That will allow you to write -

read Red :: Color
= Red

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


Re: [Haskell-cafe] ANN: Elerea, another FRP library

2009-04-15 Thread Peter Verswyvelen
I think it would be nice if we could make a reactive benchmark or
something: some tiny examples that capture the essence of reactive systems,
and a way to compare each solution's pros and cons.
For example the plugging a space leak with an arrow papers reduces the
recursive signal problem to

e = integral 1 e

Maybe the Nlift problem is a good example for dynamic collections, but I
guess we'll need more examples.

The reason why I'm talking about examples and not semantics is because the
latter seems to be pretty hard to get right for FRP?

On Wed, Apr 15, 2009 at 6:39 PM, Claus Reinke claus.rei...@talk21.comwrote:

 but the fact that the breakout example works is an indication that at
 least it's not hopelessly broken.

 Well, a breakout game does *not* work (yet) in most other FRP
 implementations except Yampa, which do have firm theoretical foundations
 :-)


 While certainly more entertaining, the problem looks similar enough
 to the NLift example (a lift serving requests on n floors[0]) in FunWorlds
 (the 2002 OpenGL version[1], not the 2001 VRML version[2]), chosen
 to test some expressiveness aspects of the language:

 - a dynamically updated collection (requests in NLift, bricks in breakout)
 - an object moving in response to user input (lift/paddle+ball)
 - collection and object reacting to each other's relative positions   (lift
 at floor levels/paddle ball brick collisions)

 In NLift, user input (keyboard) adds to the requests collection, and the
 lift reacts to the request collection and its own status, while in
 breakout, user input (mouse) directly controls the paddle, to which the ball
 reacts. The lift stopping at a floor directly removes a request there, while
 breakout bricks disappear when hit by the additional ball. In NLift,
 collisions and movement are one-dimensional, while breakout is
 two-dimensional.

 On the other hand, I hadn't got round to cleaning up the interface, let
 alone firming the theoretical foundations, so perhaps this isn't an
 exception to your rule?-) But I thought I'd mention it on the topic of
 other FRP libraries, with variations of approach/concepts.

 Claus

 [0] http://community.haskell.org/~claus/FunWorlds/NLift.hs
 [1] http://community.haskell.org/~claus/FunWorlds/
 [2] http://community.haskell.org/~claus/FunWorlds/VRML/

 FunWorlds/OpenGL in brief:

 - a behaviour is a description of an experiment

 - a behaviour can be sampled (performing the experiment), yielding a
 current
 value and a residual behaviour (the latter replaces the original behaviour)

 - the results of measurements can be broadcast and observed via behavioural
 channels (a channel observer simply behaves as the channel source
 behaviour,
 with a slight delay)

 That's it! The is no special role for time at all. One can establish local
 clocks, one can even broadcast their ticking behaviours. But one cannot
 take an
 arbitrary absolute time and ask for the value of a behaviour at that time
 (other than actually running that behaviour forward or backward from
 now).

 Also, there is a natural distinction between describing and running a
 behaviour, with the ability to refer to either the description or to sample
 outcomes. And having the same behaviour description on both sides of an
 event
 in a stepper/until does not mean that nothing changes at the step: the
 second
 copy doesn't continue where the first left off, but starts from its own
 beginning (with no special tricks to achieve this). There are no separate
 events, and delays enter via behavioural channels.

 Well, there were lots of negatives as well (eg FunWorlds was an
 engine-exposed workbench rather than a user-directed library), but I
 thought I'd try to get you interested first!-) I'd love to have funding to
 work out the details and clean up/modernize the interface, but without
 funding, it'll just have to wait until I get round to it (or one of the
 newer
 FRP libraries renders it superfluous..).

 If you try the examples, you'll notice that some of them run too fast on
 modern machines (because they weren't tied to an external clock), so
 you'd have to slow them down (eg, Surface and Torus, in addition to the
 standard rotate/scale controls, also react to 't'/'T' for scaling time) but
 they are are still fun to watch in their naivete (try Boids for simplicity,
 Flock2 for chaos - you'll need to scale it 's'/'S').



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


[Haskell-cafe] Mondrian and Haskell

2009-04-15 Thread Vasili I. Galchin
Hello,

  Several days ago I posted a question about retargeting GHC to generate
CIL so that Haskell could be a .NET language. One objection was Haskell
lazy nature didn't fit well with .NET's CLR. I found a couple publications


http://www.ddj.com/windows/184404967;jsessionid=0AVCEATVAEGKMQSNDLOSKH0CJUNN2JVN?_requestid=33708
... more popular presentation

http://docs.msdnaa.net/ark_new/Webfiles/WhitePapers/ECOOP.pdf... this
paper seems to be saying that Mondrian's lazy nature fits in quite well

Any opinions from Mondrian people listening in? What lessons were learned
from the Mondrian experience that could speak to Haskell in particular GHC?

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


[Haskell-cafe] Brackets and Asynchronous Exceptions

2009-04-15 Thread Andrew Gallagher

Hi,

In a program I am writing, I have many locations where I acquire a 
resource, perform an operation with it, then release it.  I have been 
using 
the 'bracket' function so that the release operation would be performed 
even if the operation threw an exception.  This seems to work nicely.


In the event of an asynchronous exception, however, is there a possible 
scenario where a release is not performed after an acquire?


Looking at the example given in bracket documentation:

bracket
   (openFile filename ReadMode)
   (hClose)
   (\fileHandle - do { ... })

Is it possbile that an asynchronous exception could be raised in this 
thread after openFile executes but *before* the appropriate handlers are 
installed and the operation is run, preventing hClose from executing?


If 'bracket' does not handle this case, should I be using the 
block/unblock functions to disable asynchronous exceptions:


block
   (bracket
  (openFile filename ReadMode)
  (hClose)
  (\fileHandle - do
 unblock
 ({ ... })))

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


Re: [Haskell-cafe] Brackets and Asynchronous Exceptions

2009-04-15 Thread Jason Dagit
On Wed, Apr 15, 2009 at 4:06 PM, Andrew Gallagher a...@cs.ucla.edu wrote:
 Hi,

 In a program I am writing, I have many locations where I acquire a resource,
 perform an operation with it, then release it.  I have been using the
 'bracket' function so that the release operation would be performed even
 if the operation threw an exception.  This seems to work nicely.

 In the event of an asynchronous exception, however, is there a possible
 scenario where a release is not performed after an acquire?

 Looking at the example given in bracket documentation:

 bracket
   (openFile filename ReadMode)
   (hClose)
   (\fileHandle - do { ... })

 Is it possbile that an asynchronous exception could be raised in this thread
 after openFile executes but *before* the appropriate handlers are installed
 and the operation is run, preventing hClose from executing?

 If 'bracket' does not handle this case, should I be using the block/unblock
 functions to disable asynchronous exceptions:

 block
   (bracket
      (openFile filename ReadMode)
      (hClose)
      (\fileHandle - do
         unblock
         ({ ... })))

Does this answer your question?
http://haskell.org/ghc/docs/latest/html/libraries/base/src/Control-Exception-Base.html#bracket

If so, I found it by going to haskell.org/hoogle searching for bracket
and then following the haddock Source to the definition.

I hope that helps!
Jason
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] Re: ANN: Elerea, another FRP library

2009-04-15 Thread Achim Schneider
Peter Verswyvelen bugf...@gmail.com wrote:

 The reason why I'm talking about examples and not semantics is
 because the latter seems to be pretty hard to get right for FRP?

There's a difference between those two? I've heard much, but never
anyone complaining about specifications overlapping in a compatible
way.

-- 
(c) this sig last receiving data processing entity. Inspect headers
for copyright history. All rights reserved. Copying, hiring, renting,
performance and/or quoting of this signature prohibited.


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


Re: [Haskell-cafe] Brackets and Asynchronous Exceptions

2009-04-15 Thread Andrew Gallagher
Great. Thanks!  This is exactly what I was looking for.  Apparently this 
issue is also described in the paper Asynchronous Exception in Haskell.


Thanks,
Andrew

On Wed, 15 Apr 2009, Jason Dagit wrote:


On Wed, Apr 15, 2009 at 4:06 PM, Andrew Gallagher a...@cs.ucla.edu wrote:

Hi,

In a program I am writing, I have many locations where I acquire a resource,
perform an operation with it, then release it.  I have been using the
'bracket' function so that the release operation would be performed even
if the operation threw an exception.  This seems to work nicely.

In the event of an asynchronous exception, however, is there a possible
scenario where a release is not performed after an acquire?

Looking at the example given in bracket documentation:

bracket
  (openFile filename ReadMode)
  (hClose)
  (\fileHandle - do { ... })

Is it possbile that an asynchronous exception could be raised in this thread
after openFile executes but *before* the appropriate handlers are installed
and the operation is run, preventing hClose from executing?

If 'bracket' does not handle this case, should I be using the block/unblock
functions to disable asynchronous exceptions:

block
  (bracket
     (openFile filename ReadMode)
     (hClose)
     (\fileHandle - do
        unblock
        ({ ... })))


Does this answer your question?
http://haskell.org/ghc/docs/latest/html/libraries/base/src/Control-Exception-Base.html#bracket

If so, I found it by going to haskell.org/hoogle searching for bracket
and then following the haddock Source to the definition.

I hope that helps!
Jason
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Data.ByteString woes

2009-04-15 Thread Jason Dusek
  Could you pastebin something that demoes the error?

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


Re: [Haskell-cafe] Enum to String, and back?

2009-04-15 Thread michael rice
Thanks guys. It works like a charm.

Michael

--- On Wed, 4/15/09, Rahul Kapoor r...@trie.org wrote:

From: Rahul Kapoor r...@trie.org
Subject: Re: [Haskell-cafe] Enum to String, and back?
To: 
Cc: haskell-cafe@haskell.org
Date: Wednesday, April 15, 2009, 3:20 PM

On Wed, Apr 15, 2009 at 3:13 PM, michael rice nowg...@yahoo.com wrote:
 Using Show it is possible to establish a relationship between an enum type
 and a String type to display it.
 Can one as easily establish a reverse relationship, i.e., convert a String
 type like Red back to its corresponding Color type?

Make it an instance of the Read type class.
http://haskell.org/ghc/docs/latest/html/libraries/base/Prelude.html#t%3ARead

That will allow you to write -

read Red :: Color
= Red

HTH
Rahul
___
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] Code Golf

2009-04-15 Thread Matt Morrow
I think this has the semantics you're looking for. (it would probably be
somewhat prettier if mappend wasn't such an ugly identifier (compared to,
say, (++)), but this is just me trying to sneak a shot in against the Monoid
method's names ;)

ghci let diag = foldr (curry (prod mappend fst snd . uncurry (coprod
mappend (splitAt 2) (splitAt 1 []

ghci diag [[1,2,3],[4,5,6],[7,8,9]]
[1,2,4,3,5,7,6,8,9]
ghci diag [[1,2,3],[4],[5,6,7]]
[1,2,4,3,5,6,7]


On Wed, Apr 15, 2009 at 5:32 AM, Sebastian Fischer 
s...@informatik.uni-kiel.de wrote:

 Fancy some Codegolf?

 I wrote the following function for list diagonalization:

  diag l = foldr (.) id ((sel l . flip sel) ((:[]).(:))) []
   where
sel = foldr (\a b c - id : mrg (a c) (b c)) (const []) . map (flip id)
 
mrg [] ys = ys
mrg xs [] = xs
mrg (x:xs) (y:ys) = (x.y) : mrg xs ys

 Self explanatory, isn't it? Here is a test case:

*Main take 10 $ diag [[ (m,n) | n - [1..]] | m - [1..]]
[(1,1),(1,2),(2,1),(1,3),(2,2),(3,1),(1,4),(2,3),(3,2),(4,1)]

 I was trying to golf it down [^1] but my brain explodes. If you succeed in
 reducing keystrokes, I'd be happy to know!

 Cheers,
 Sebastian

 [^1]: http://codegolf.com/
 ___
 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] Code Golf

2009-04-15 Thread Matt Morrow
*..against Monoid's method names.

On Wed, Apr 15, 2009 at 9:59 PM, Matt Morrow moonpa...@gmail.com wrote:

 ... against the Monoid method's names.

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


Re: [Haskell-cafe] Code Golf

2009-04-15 Thread Matt Morrow
And i forgot to include the defs of (co)prod:

coprod () i1 i2 = (\a b - i1 a  i2 b)
prod   () p1 p2 = (\a   - p1 a  p2 a)

diag = foldr (curry (prod mappend
fst
snd
. uncurry (coprod mappend
(splitAt 2)
(splitAt 1 []

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


[Haskell-cafe] Issues with running Ghci from emacs

2009-04-15 Thread Daryoush Mehrtash
I am having problem running GHCI with Haskell files that include imports.
I am running emacs22 on Ubuntu,  with haskell-mode-2.4 extensions.

I load my file (Fal.lhs in this case) in emacs.  Then try to run the Ghci by
doing C-c C-l. The result is shown below.   Ghci fails to find the
Draw.lhs which is also on the same directory as the Fal.lhs.   Note:  If I
go to the directory where Fal.lhs is and run Ghci directly it all works
fine.   Any idea how I can get the interepreter to work form emacs?

GHCi, version 6.10.1: http://www.haskell.org/ghc/  :? for help
Loading package ghc-prim ... linking ... done.
Loading package integer ... linking ... done.
Loading package base ... linking ... done.
*Prelude :cd ~/.cabal/
Prelude :load ../Documents/haskell/SOE/src/Fal.lhs
*
../Documents/haskell/SOE/src/Fal.lhs:76:9:
Could not find module `Draw':
  Use -v to see a list of the files searched for.
Failed, modules loaded: none.
Prelude

Thanks,

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