[Haskell-cafe] Cabal, lib and exe in one

2007-05-01 Thread Magnus Therning
I'm trying to create a single cabal file containing specs for both a
library and an executable using that library.  I'm not having much luck
though :(

This is what I have so far:

  name: foo
  version: 0.1
  exposed-modules: Foo.Bar
  other-modules: Foo.Qux Foo.C2HS
  hs-source-dirs: src
  include-dirs: csrc
  c-sources: csrc/qux.c
  extensions: ForeignFunctionInterface
  build-depends: base, haskell98
  
  executable: foo
  hs-source-dirs: test-src
  main-is: foo.hs
  other-modules: Foo.Bar

When built this is the message I get:
  test-src/foo.hs:5:7:
  Could not find module `Foo.Bar':
Use -v to see a list of the files searched for.

How do I specify that Foo.Bar is found where cabal puts it
(./dist/build/)?

/M

-- 
Magnus Therning (OpenPGP: 0xAB4DFBA4)
[EMAIL PROTECTED] Jabber: [EMAIL PROTECTED]
http://therning.org/magnus

Software is not manufactured, it is something you write and publish.
Keep Europe free from software patents, we do not want censorship
by patent law on written works.

Finagle's Fifth Law:
Always draw your curves, then plot your readings.


pgpIR3R1wXkeF.pgp
Description: PGP signature
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


RE: [Haskell-cafe] FIT for Haskell

2007-05-01 Thread Bayley, Alistair
 From: [EMAIL PROTECTED] 
 [mailto:[EMAIL PROTECTED] On Behalf Of Philipp Volgger
 
 Who wrote FIT for Haskell on http://darcs.haskell.org/FIT/? 
 Does anybody know if the version is stable?

Hello Philipp,

That would be me. It's not finished or stable, and I don't think it'll
work with GHC-6.6 on Windows because it uses hs-plugins. I figured I'd
better save the code somewhere, because I lost some work when my laptop
died last year.

It's not finished in the sense that I haven't implemented all of the
test suite; I got as far as the Music Example in the standard tests
(http://fit.c2.com/wiki.cgi?MusicExample) but I have not implemented
RowFixture, which the Music Example requires. Also, the
Algol-derivative-language implementations of FIT (Java, C#, etc) use
static class variables (i.e. global mutable state) in the Music Example,
so there's some redesign work to get it to run in Haskell.

I'd be happy to explain how it works if you're interested in
contributing.

Alistair
*
Confidentiality Note: The information contained in this message,
and any attachments, may contain confidential and/or privileged
material. It is intended solely for the person(s) or entity to
which it is addressed. Any review, retransmission, dissemination,
or taking of any action in reliance upon this information by
persons or entities other than the intended recipient(s) is
prohibited. If you received this in error, please contact the
sender and delete the material from any computer.
*
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] Re: 'Proper' use of the State monad

2007-05-01 Thread DavidA
 1) Using State GameState r and then call execState for each game event
 (i.e. user input) so I can do IO
 2) Using StateT GameState IO () and have the entire game live in one
 big execStateT call. (I note XMonad does something similar.)

I'm also interested in the answer to this question. One concern I would have 
about option 2 is that it looks like it breaks encapsulation, to use a phrase 
from OOP.

What I mean is, it seems like good design would mean that you could write and 
test the game logic totally independently of any IO. Game functions such 
as makeMove ought to have type signatures that don't involve any IO. Can this 
be achieved in option 2?


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


[Haskell-cafe] what exactly does deriving (Functor, Monad, MonadIO) do?

2007-05-01 Thread Thomas Hartman

I was trying to follow the reasoning in Don's article on using haskell
for shell scripting

 http://cgi.cse.unsw.edu.au/~dons/blog/2007/03/10

In the source listing at the end we is

 newtype Shell a = Shell { runShell :: ErrorT String IO a }
   deriving (Functor, Monad, MonadIO)

and I don't understand it what deriving is doing here, nor have I
been able to find documentation on it.

 http://en.wikibooks.org/wiki/Haskell/Class_declarations

claims:

You can only use deriving with a limited set of built-in classes. They are:

Eq  Ord Enum Bounded  Show  Read 

But, here we are deriving classes not in that list. So, is this a
recently added feature? Or something that came in from

 {-# OPTIONS -fglasgow-exts #-} ?

I would just like to understand this, and I can't figure out how to begin.

Thanks for any help!

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


Re: [Haskell-cafe] what exactly does deriving (Functor, Monad, MonadIO) do?

2007-05-01 Thread Donald Bruce Stewart
tphyahoo:
 I was trying to follow the reasoning in Don's article on using haskell
 for shell scripting
 
  http://cgi.cse.unsw.edu.au/~dons/blog/2007/03/10
 
 In the source listing at the end we is
 
  newtype Shell a = Shell { runShell :: ErrorT String IO a }
deriving (Functor, Monad, MonadIO)
 
 and I don't understand it what deriving is doing here, nor have I
 been able to find documentation on it.

That's 'cunning newtype deriving, my new favourite ghc language
extension.


http://www.haskell.org/ghc/docs/latest/html/users_guide/type-extensions.html#newtype-deriving

We also use it in xmonad,

newtype X a = X (ReaderT XConf (StateT XState IO) a)
deriving (Functor, Monad, MonadIO, MonadState XState, MonadReader XConf)

:-)

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


[Haskell-cafe] Re: Poor first impression

2007-05-01 Thread Simon Marlow

brad clawsie wrote:

On Mon, Apr 30, 2007 at 09:53:06PM +0100, Andrew Coppin wrote:

 brad clawsie wrote:

installing a modern linux on this box is a thirty minute exercise.

 Ah - a volunteer! :-)


absolutely! for the low cost of one round-trip business-class seat from
san jose to wherever this box is, and i will happily insert a recent 
ubuntu cd and click the install icon.


Well, no way is it a 30 minute job to upgrade the OS on a production multi-user 
Linux system.  Surely I don't need to go into details here.


A better solution would be to use someone else's box via BuildBot.  I think 
someone offered to donate a couple of FC boxes for the builds recently.


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


Re: [Haskell-cafe] what exactly does deriving (Functor, Monad, MonadIO) do?

2007-05-01 Thread Thomas Hartman

Thanks Dons.

There's also a short and sweet explanation here.

http://hackage.haskell.org/trac/haskell-prime/wiki/NewtypeDeriving

I am going to try and wrap my head around this, as I am very
interested in solutions for haskell / shell interaction.

Are there are any good examples of code written without this
extension, alongside code condensed by using this extension. That
would be helpful for understanding what's going on.

Thomas.



2007/5/1, Donald Bruce Stewart [EMAIL PROTECTED]:

tphyahoo:
 I was trying to follow the reasoning in Don's article on using haskell
 for shell scripting

  http://cgi.cse.unsw.edu.au/~dons/blog/2007/03/10

 In the source listing at the end we is

  newtype Shell a = Shell { runShell :: ErrorT String IO a }
deriving (Functor, Monad, MonadIO)

 and I don't understand it what deriving is doing here, nor have I
 been able to find documentation on it.

That's 'cunning newtype deriving, my new favourite ghc language
extension.


http://www.haskell.org/ghc/docs/latest/html/users_guide/type-extensions.html#newtype-deriving

We also use it in xmonad,

newtype X a = X (ReaderT XConf (StateT XState IO) a)
deriving (Functor, Monad, MonadIO, MonadState XState, MonadReader XConf)

:-)

-- Don


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


Re: [Haskell-cafe] Bloom Filter

2007-05-01 Thread Josef Svenningsson

Hi,

Just a small comment on one of the comments.

On 5/1/07, [EMAIL PROTECTED] [EMAIL PROTECTED] wrote:

Also, rather than this:

add :: Bloom a - a - Bloom a

a better argument order is this:

insert :: a - Bloom a - Bloom a

That way, you can use it with foldr.


Hmmm. If you want to create a Bloom using a fold wouldn't it make more
sense to use foldl'? I think the argument order is fine.

Cheers,

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


Re: [Haskell-cafe] Cabal, lib and exe in one

2007-05-01 Thread Duncan Coutts
On Tue, 2007-05-01 at 09:34 +0100, Magnus Therning wrote:
 I'm trying to create a single cabal file containing specs for both a
 library and an executable using that library.  I'm not having much luck
 though :(
 
 This is what I have so far:
 
   name: foo
   version: 0.1
   exposed-modules: Foo.Bar
   other-modules: Foo.Qux Foo.C2HS
   hs-source-dirs: src
   include-dirs: csrc
   c-sources: csrc/qux.c
   extensions: ForeignFunctionInterface
   build-depends: base, haskell98
   
   executable: foo
   hs-source-dirs: test-src
   main-is: foo.hs
   other-modules: Foo.Bar
 
 When built this is the message I get:
   test-src/foo.hs:5:7:
   Could not find module `Foo.Bar':
 Use -v to see a list of the files searched for.
 
 How do I specify that Foo.Bar is found where cabal puts it
 (./dist/build/)?

But surely Foo.Bar is in src, it is afterall exactly the same module as
the one you're using in the library, no?

So if foo.hs is in test-src and Foo/Bar.hs is in src then I think you
just need:

hs-source-dirs: test-src, src

You cannot specify that things are found in dist/build since that dir
can placed anywhere by the user. But I don't see that you'd want to, I
can't see how it makes any sense.

Duncan

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


Re: [Haskell-cafe] Re: 'Proper' use of the State monad

2007-05-01 Thread Sebastian Sylvan

On 5/1/07, DavidA [EMAIL PROTECTED] wrote:


 1) Using State GameState r and then call execState for each game event
 (i.e. user input) so I can do IO
 2) Using StateT GameState IO () and have the entire game live in one
 big execStateT call. (I note XMonad does something similar.)

I'm also interested in the answer to this question. One concern I would
have
about option 2 is that it looks like it breaks encapsulation, to use a
phrase
from OOP.

What I mean is, it seems like good design would mean that you could write
and
test the game logic totally independently of any IO. Game functions such
as makeMove ought to have type signatures that don't involve any IO. Can
this
be achieved in option 2?



You could, of course, do both.

I do think it's a good idea to write your own game monad which
encapsulates all of the unsafe functions that you might want to do in an
application specific approprate way, rather than just having your unsafe
skin be the IO monad. So for example, if you want to spawn an actor in the
game world and attach an AI thread to govern its behaviour you'd need a
function which interanlly uses forkIO, sets up a bunch of TVars for
messaging etc., but from the Game monad's pespective that can be
encapsulated. There *are* things which are just inherently imperative in
nature, and are easier to do like that (threads with message passing, for
example, is not necessarily bad, sometimes they are the Right Abstraction --
actor AI is probably a good example), but you can make it a lot nicer and
less unsafe by writing your own unsafe skin which supplies slightly safer
encapsulations tailored for your specific application.

But of course, you could have another monad which ONLY deals with pure
changes to the game state that you then evaluate from the underlying monad.
So the GameEngine monad is the unsafe skin, and then you have the Game
monad which just does a pure computation on the game state. Then you'd have
a function like:

game :: Game a - GameEngine a
game g = do
 state - get
 gstate - gameState state
 let ( res, gstate' ) = runState g
 put ( state{ gameState = gstate' } )
 return res

Which simply runs a game action on the game part of the GameEngine state.

--
Sebastian Sylvan
+44(0)7857-300802
UIN: 44640862
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] what exactly does deriving (Functor, Monad, MonadIO) do?

2007-05-01 Thread Brandon S. Allbery KF8NH


On May 1, 2007, at 6:05 , Thomas Hartman wrote:


Are there are any good examples of code written without this
extension, alongside code condensed by using this extension. That
would be helpful for understanding what's going on.


I think all this does is save you from having to write a bunch of  
wrappers that unwrap the contained value, do something to it, and  
rewrap the result.


--
brandon s. allbery  [solaris,freebsd,perl,pugs,haskell]   
[EMAIL PROTECTED]
system administrator  [openafs,heimdal,too many hats]   
[EMAIL PROTECTED]
electrical and computer engineering, carnegie mellon university   
KF8NH



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


Re: [Haskell-cafe] what exactly does deriving (Functor, Monad, MonadIO) do?

2007-05-01 Thread David House

On 01/05/07, Brandon S. Allbery KF8NH [EMAIL PROTECTED] wrote:

I think all this does is save you from having to write a bunch of
wrappers that unwrap the contained value, do something to it, and
rewrap the result.


Exactly. Basically what newtype deriving does is if you have a
declaration like the following:

 newtype T = TConstructor M

And M instantiates some class (like Monad, Functor etc), you can
derive that class for T. For example, here's how the Functor instance
would look for the following newtype:

 newtype MyMaybe a = MM (Maybe a) deriving (Functor)

 -- The instance looks like this:
 instance Functor MyMaybe where
   fmap f (MM a) = MM (fmap f a)

The instance just unwraps and rewraps the newtype constructor.

--
-David House, [EMAIL PROTECTED]
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


RE: [Haskell-cafe] Displaying infered type signature of 'offside' functions

2007-05-01 Thread Simon Peyton-Jones
| I like the strong static type system of Haskell for various
| reasons. One reason is, that it makes easier to understand new
| code. I.e. when I read code I type ':t foo' in ghci/hugs from
| time to time, to check my own idea of the type signature, if it
| is not included in the source code.

The principal difficulties here are to do with what do we want rather the 
implementation challenges.

1.  Should the compiler print the type of every declaration? Should GHCi allow 
you to ask the type of a local decl?

2.  How should the variables be identified?  There may be many local bindings 
for 'f', so you can't say just :t f.  Ditto if dumping all local bindings.

3.  Do you want all locally-bound variables (including those bound by lambda or 
case), or just letrec/where bound ones?   I think 'all', myself, but there are 
a lot of them.

4.  (This is the trickiest one.)  The type of a function may mention type 
variables bound further out.  Consider
f :: [a] - Int
f xs = let v = head xs in ...

The type of 'v' is simply 'a'.  Not 'forall a. a', but rather 'if xs:[a] then 
*that* a!'  In general there may also be existential type variables bound by an 
enclosing pattern match too.

So it's not easy to see how to report v's type.  In general there is no type 
signature for f, which only makes matters worse, since there is no name to use 
for the in-scope type variable.


These are all user-interface issues.  If some people would like to thrash out a 
design, and put it on the Wiki, I think there is a good chance that someone 
(possibly even me) would implement it.

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


[Haskell-cafe] Re: Type-level programming problem

2007-05-01 Thread Thomas Schilling


On 1 maj 2007, at 06.12, [EMAIL PROTECTED] wrote:


We see it is a value polymorphic over four type variables: ns, a, b,
and c. The type variable 'a' is also the type of the value, so we have
a way to instantiate it. There is no direct way to instantiate the
remaining three. If there were a functional dependency a - ns, a-b,
a-c, we could have instantiated the remaining variables. But there
are no such dependencies. So, there is really no way we can
ever instantiate the type variables ns, b and c -- and so the  
typechecker

will complain.

So, we need either a functional dependency a - ns in the definition
of Foo, or defaultA should have a signature defaultA :: ns - a
(and ditto for other defaults).


In fact I had this signature for a while, but then I had already  
changed the definition of Foo to a different signature.  Good to know  
that I wasn't too far off..



As I understand, the function
'defaultA' can be present in different components, identified by
ns. When we write 'defaultA' however, how can we say that we mean
defaultA of component X rather than of component Y? There isn't any
way to name the desired component...

Incidentally, if we represent components by records
data XRec = XRec { defaultA :: XA }
then the type of defaultA is Xref - XA. It is the function from the
type of the `namespace'. This seems to suggest the
signature of defaultA should be ns - a ...

BTW, there are other ways to add the name of the namespace to the
signature of defaultA. For example:
newtype TaggedT ns a = TaggedT a
class Foo ns a b c | ...
 defaultA :: TaggedT ns a
or
class Foo ns a b c | ...
 defaultA :: ns a

etc.


Thank you for your quick and helpful response.  I'll look into what  
works best for my purposes.


Thanks,

/ Thomas

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


[Haskell-cafe] Hugs/nhc getting progressively slower

2007-05-01 Thread Neil Mitchell

Hi,

I like to develop on Hugs, because its a nice platform to work with,
and provides WinHugs, auto-reloading, sub-second compilation etc.
Unfortunately some of the newer libraries (ByteString/Binary in
particular) have been optimised to within an inch of their lives on
GHC, at the cost of being really really slow on Hugs.

Taking the example of Yhc Core files, which are stored in binary.
Using a very basic hPutChar sequence is miles faster (10x at least)
than all the fancy ByteString/Binary trickery.

Taking the example of nobench, Malcolm told me he reimplemented
ByteString in terms of [Char] and gained a massive performance
increase (6000x springs to mind, but that seems way too high to be
true) using nhc.

Could we have a collective thought, and decide whether we wish to
either kill off all compilers that don't start with a G, or could
people at least do minimal benchmarking on Hugs? I'm not quite sure
what the solution is, but it probably needs some discussion.

Thanks

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


[Haskell-cafe] Is Hs-Plugins dead?

2007-05-01 Thread Philipp Volgger
Is Hs-Plugins still under develeopment; is there still somebody who is 
updating it?



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


[Haskell-cafe] Bloom Filter

2007-05-01 Thread Dom
 
 Reminds me of this code from Data.Binary:
 
 unroll :: Integer - [Word8]
 unroll = unfoldr step
   where
 step 0 = Nothing
 step i = Just (fromIntegral i, i `shiftR` 8)
 
 roll :: [Word8] - Integer
 roll   = foldr unstep 0
   where
 unstep b a = a `shiftL` 8 .|. fromIntegral b
 
 Which is a bit stream-fusion inspired, I must admit.
 

But better than what is in Codec.Utils:

 toBase x =
map fromIntegral .
reverse .
map (flip mod x) .
takeWhile (/=0) .
iterate (flip div x)
 
 -- | Take a number a convert it to base n as a list of octets.
 
 toOctets :: (Integral a, Integral b) = a - b - [Octet]
 toOctets n x = (toBase n . fromIntegral) x

 powersOf n = 1 : (map (*n) (powersOf n))

 -- | Take a list of octets (a number expressed in base n) and convert it
 --   to a number.
 
 fromOctets :: (Integral a, Integral b) = a - [Octet] - b
 fromOctets n x =
fromIntegral $
sum $
zipWith (*) (powersOf n) (reverse (map fromIntegral x))

It seems a shame that everyone has to roll their own.

Dominic.

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


Re: [Haskell-cafe] Hugs/nhc getting progressively slower

2007-05-01 Thread Duncan Coutts
On Tue, 2007-05-01 at 20:37 +0100, Neil Mitchell wrote:
 Hi,
 
 I like to develop on Hugs, because its a nice platform to work with,
 and provides WinHugs, auto-reloading, sub-second compilation etc.
 Unfortunately some of the newer libraries (ByteString/Binary in
 particular) have been optimised to within an inch of their lives on
 GHC, at the cost of being really really slow on Hugs.
 
 Taking the example of Yhc Core files, which are stored in binary.
 Using a very basic hPutChar sequence is miles faster (10x at least)
 than all the fancy ByteString/Binary trickery.
 
 Taking the example of nobench, Malcolm told me he reimplemented
 ByteString in terms of [Char] and gained a massive performance
 increase (6000x springs to mind, but that seems way too high to be
 true) using nhc.

That does not surprise me.

 Could we have a collective thought, and decide whether we wish to
 either kill off all compilers that don't start with a G, or could
 people at least do minimal benchmarking on Hugs? I'm not quite sure
 what the solution is, but it probably needs some discussion.

I don't think doing minimal benchmarking on hugs will help at all unless
we are prepared to act on it and I'm pretty sure anything we do to
improve hugs performance will be detrimental to the GHC performance.

We're optimising for totally different sets of primitives. With GHC
we're optimising for machine code and thinking about branch prediction
and cache misses. We're also writing high level combinators that are
quite inefficient to execute directly but we rely on inlining and
rewrite rules to combine then expand them to efficient low level code.

With hugs/yhc/nhc I assume the optimisation technique is simply to
minimise the number of primitive reduction steps. This is really totally
different. I don't see any obvious way of reconciling the two in a
single implementation of an interface. Having totally different
implementations of an interface for different Haskell systems is an
option though it has obvious disadvantages.

So I don't know what to do. We're not stopping out quest for high
performance idiomatic code because it doesn't play nicely with
interpreters.

Duncan

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


Re: [Haskell-cafe] Cabal, lib and exe in one

2007-05-01 Thread Magnus Therning
On Tue, May 01, 2007 at 12:02:18 +0100, Duncan Coutts wrote:
On Tue, 2007-05-01 at 09:34 +0100, Magnus Therning wrote:
 I'm trying to create a single cabal file containing specs for both a
 library and an executable using that library.  I'm not having much luck
 though :(
 
 This is what I have so far:
 
   name: foo
   version: 0.1
   exposed-modules: Foo.Bar
   other-modules: Foo.Qux Foo.C2HS
   hs-source-dirs: src
   include-dirs: csrc
   c-sources: csrc/qux.c
   extensions: ForeignFunctionInterface
   build-depends: base, haskell98
   
   executable: foo
   hs-source-dirs: test-src
   main-is: foo.hs
   other-modules: Foo.Bar
 
 When built this is the message I get:
   test-src/foo.hs:5:7:
   Could not find module `Foo.Bar':
 Use -v to see a list of the files searched for.
 
 How do I specify that Foo.Bar is found where cabal puts it
 (./dist/build/)?

But surely Foo.Bar is in src, it is afterall exactly the same module as
the one you're using in the library, no?

Yes.

So if foo.hs is in test-src and Foo/Bar.hs is in src then I think you
just need:

hs-source-dirs: test-src, src

No, that's not enough, I also have to add the following lines to make
the executable compile and link:

  extensions: ForeignFunctionInterface
  c-sources: csrc/ptrace.c

That is, I end up compiling the library a second time!  Can't I get the
executable to link against the library that was just created?

You cannot specify that things are found in dist/build since that dir
can placed anywhere by the user. But I don't see that you'd want to, I
can't see how it makes any sense.

I was just expecting to not have to repeat myself in the cabal file.
Not such a strange thing to expect from a build system, I think :-)

Also, I don't really see what you mean by that dir can be placed
anywhere by the user.  That dir is created as part of the build
process and it's location is, AFAICS, always going to be ./dist/build.
Finding the library after installation is another matter, but that
problem should be taken care of during the `./Setup.hs configure` stage.

/M

-- 
Magnus Therning (OpenPGP: 0xAB4DFBA4)
[EMAIL PROTECTED] Jabber: [EMAIL PROTECTED]
http://therning.org/magnus


pgpTakY9VUp1p.pgp
Description: PGP signature
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Re: 'Proper' use of the State monad

2007-05-01 Thread Yitzchak Gale

DavidA wrote:

What I mean is, it seems like good design would mean that you could write and
test the game logic totally independently of any IO. Game functions such
as makeMove ought to have type signatures that don't involve any IO. Can this
be achieved in option 2?


Here is one way:

For functions that do not need IO, use types that look like:

MonadState GameState m = ... - m a

For functions that only do IO without refering to the
game state, use:

MonadIO m = ... - m a

For functions that do both, use:

(MonadIO m, MonadState GameState m) = ... - m a

Testing of the pure game functions can use
State GameState, testing of pure IO functions can
use IO, and production can use StateT GameState IO.

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


Re: [Haskell-cafe] Is Hs-Plugins dead?

2007-05-01 Thread Stefan O'Rear
On Tue, May 01, 2007 at 09:51:37PM +0200, Philipp Volgger wrote:
 Is Hs-Plugins still under develeopment; is there still somebody who is 
 updating it?

Not really.  It works perfectly and fills its niche.  Mature software
is not under development! 

It is still maintained by Don Stewart.

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


Re: [Haskell-cafe] Cabal, lib and exe in one

2007-05-01 Thread Duncan Coutts
On Tue, 2007-05-01 at 22:29 +0100, Magnus Therning wrote:

 So if foo.hs is in test-src and Foo/Bar.hs is in src then I think you
 just need:
 
 hs-source-dirs: test-src, src
 
 No, that's not enough, I also have to add the following lines to make
 the executable compile and link:
 
   extensions: ForeignFunctionInterface
   c-sources: csrc/ptrace.c
 
 That is, I end up compiling the library a second time!  Can't I get the
 executable to link against the library that was just created?

 I was just expecting to not have to repeat myself in the cabal file.
 Not such a strange thing to expect from a build system, I think :-)

Yes this is an interesting question about what it means to have programs
in the same cabal package as an executable.

Currently having a executable and a library inside a cabal package is
not the same thing as having a library package and separate package that
contains only that executable. The difference is that when the
executable is in the same cabal package it merely has access to the same
modules, it doesn't 'depend' on that library package exactly. So for
example it can access modules which are not exposed by the library and
indeed it can compile those same modules with completely different build
flags. So currently those modules will be built twice.

It's not clear to me that this is the right meaning, or indeed that we
should allow multiple entries in a single .cabal file. I think it might
be better to just have multiple .cabal files (possibly in the same
directory). Then we could be explicit and state that an executable
depends on the library or if we want to use different build flags, or
use modules that are not exposed by the lib then we can do that and only
in that case do we build those modules twice.

 Also, I don't really see what you mean by that dir can be placed
 anywhere by the user.  That dir is created as part of the build
 process and it's location is, AFAICS, always going to be ./dist/build.

Actually it's location can be set at configure time with --scratchdir=
so that for example you could put it in a temp dir or something. 


Duncan

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


Re: [Haskell-cafe] Bloom Filter

2007-05-01 Thread ajb
G'day all.

Quoting Dom [EMAIL PROTECTED]:

 But better than what is in Codec.Utils:
[deletia]
 It seems a shame that everyone has to roll their own.

That and integer log base 2.

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


Re: [Haskell-cafe] Bloom Filter

2007-05-01 Thread ajb
G'day all.

I wrote:

  insert :: a - Bloom a - Bloom a
 
  That way, you can use it with foldr.

Quoting Josef Svenningsson [EMAIL PROTECTED]:

 Hmmm. If you want to create a Bloom using a fold wouldn't it make more
 sense to use foldl'? I think the argument order is fine.

You're right that foldl' makes more sense than foldr in this case.
Nevertheless, the usual Haskell convention is that insert-like functions
have the same argument order as the cons operator (:).

Haskell libraries have a real problem with the proliferation of
conventions for various things.  This order is the usual convention,
so follow it.  If you don't like it, there's always flip.

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


Re: [Haskell-cafe] Is Hs-Plugins dead?

2007-05-01 Thread Donald Bruce Stewart
pvolgger:
 Is Hs-Plugins still under develeopment; is there still somebody who is 
 updating it?

It's in stasis. It will likely get a little bit more updating when I
finish my phd.  It's needed for lambdabot in #haskell, so that's enough
pressure to keep it working :-)

For the longer term, a more maintainable approach is to provide an
hs-plugins api over the ghc-api, in my opinion. Then the bits of
hs-plugins that break when compiler versions change (.hi file parsing
and package file parsing), won't break.

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