Re: [Haskell-cafe] Re: instance Eq (a - b)

2010-04-15 Thread roconnor

On Thu, 15 Apr 2010, Maciej Piechotka wrote:


Are

f 0 = 1
f n = f (n - 1) + f (n - 2)

and

g 0 = 1
g n | n  0 = g (n - 1) + g (n - 2)
| n  0 = g (n + 2) - g (n + 1)

The same (morally) function?

Are:

f x = 2*x

and

f x = undefined

The same function


Try using the (x == y) == (f x = g y) test yourself.

--
Russell O'Connor  http://r6.ca/
``All talk about `theft,''' the general counsel of the American Graphophone
Company wrote, ``is the merest claptrap, for there exists no property in
ideas musical, literary or artistic, except as defined by statute.''
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] cabal: other-modules

2010-04-15 Thread Johannes Waldmann
What is the purpose of the Other-Modules section in a cabal file?
(I.e., can we drop it?)

If it's just the set of dependencies of the Exported-Modules,
then a reasonable build system should be able to figure this out on its own.

The current situation is that I have to manage this list manually
(or is there some tool?) and if I forget to name some other-module,
then cabal install happily builds and installs (!) the package anyway, 
but I'm getting linker errors when using it. 
This is a nuisance, to say the least.

J.W.


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


[Haskell-cafe] Re: instance Eq (a - b)

2010-04-15 Thread roconnor

On Wed, 14 Apr 2010, Ashley Yakeley wrote:


On 2010-04-14 14:58, Ashley Yakeley wrote:

On 2010-04-14 13:59, rocon...@theorem.ca wrote:


There is some notion of value, let's call it proper value, such that
bottom is not one.

In other words bottom is not a proper value.

Define a proper value to be a value x such that x == x.

So neither undefined nor (0.0/0.0) are proper values

In fact proper values are not just subsets of values but are also
quotients.

thus (-0.0) and 0.0 denote the same proper value even though they are
represented by different Haskell values.


The trouble is, there are functions that can distinguish -0.0 and 0.0.
Do we call them bad functions, or are the Eq instances for Float and
Double broken?


I'd call them disrespectful functions, or maybe nowadays I might call them
improper functions.  The good functions are respectful functions or
proper functions.

Proper functions are functions that are proper values i.e. f == f  which
is defined to mean that (x == y) == f x == f y (even if this isn't a 
decidable relation).



Worse, this rules out values of types that are not Eq.


Hmm, I guess I'm carrying all this over from the world of dependently 
typed programming where we have setoids and the like that admit equality 
relations that are not necessarily decidable.  In Haskell only the 
decidable instances of equality manage to have a Eq instance.  The other 
data types one has an (partial) equivalence relation in mind but it goes 
unwritten.


But in my dependently typed world we don't have partial values so there 
are no bottoms to worry about; maybe these ideas don't carry over 
perfectly.


--
Russell O'Connor  http://r6.ca/
``All talk about `theft,''' the general counsel of the American Graphophone
Company wrote, ``is the merest claptrap, for there exists no property in
ideas musical, literary or artistic, except as defined by statute.''
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] Re: Fwd: Re: Simple game: a monad for each player

2010-04-15 Thread Heinrich Apfelmus
Limestraël wrote:
 Okay, I start to understand better...
 
 Just, Heinrich, how would implement the mapMonad function in terms of the
 operational package?
 You just shown the signature.

Ah, that has to be implemented by the library, the user cannot implement
this. Internally, the code would be as Bertram suggests:

mapMonad :: (Monad m1, Monad m2)
 = (forall a . m1 a - m2 a)
 - ProgramT instr m1 a - ProgramT instr m2 a
mapMonad f (Lift m1)  = Lift (f m1)
mapMonad f (Bind m k) = Bind (mapMonad f m) (mapMonad f . k)
mapMonad f (Instr i)  = Instr i

I was musing that every instance of  MonadTrans  should implement this
function.

Also note that there's a precondition on  f  , namely it has to respect
the monad laws:

f (m = k) = f m = f . k
f return= return

For instance,

f :: Identity a - IO a
f x = launchMissiles  return (runIdentity x)

violates this condition.


Regards,
Heinrich Apfelmus

--
http://apfelmus.nfshost.com

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


[Haskell-cafe] Re: instance Eq (a - b)

2010-04-15 Thread Ashley Yakeley
On Thu, 2010-04-15 at 03:53 -0400, rocon...@theorem.ca wrote:
 Hmm, I guess I'm carrying all this over from the world of dependently 
 typed programming where we have setoids and the like that admit equality 
 relations that are not necessarily decidable.  In Haskell only the 
 decidable instances of equality manage to have a Eq instance.  The other 
 data types one has an (partial) equivalence relation in mind but it goes 
 unwritten.
 
 But in my dependently typed world we don't have partial values so there 
 are no bottoms to worry about; maybe these ideas don't carry over 
 perfectly.

It's an interesting approach, though, since decided equality seems to
capture the idea of full value fairly well.

I'm currently thinking along the lines of a set V of Platonic values,
while Haskell names are bound to expressions that attempt to calculate
these values. At any given time during the calculation, an expression
can be modelled as a subset of V. Initially, it's V, as calculation
progresses it may become progressively smaller subsets of V.

Saying a calculation is bottom is to make a prediction that cannot in
general be decided. It's to say that the calculation will always be V.
If it ever becomes not V, it's a partial value. If it ever becomes a
singleton, it's a complete value.

On the other hand, this approach may not help with strict vs. non-strict
functions.

-- 
Ashley Yakeley

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


Re: [Haskell-cafe] GHC, odd concurrency space leak

2010-04-15 Thread Neil Brown

Jason Dagit wrote:
On Wed, Apr 14, 2010 at 3:13 PM, Daniel Fischer 
daniel.is.fisc...@web.de mailto:daniel.is.fisc...@web.de wrote:


Am Mittwoch 14 April 2010 23:49:43 schrieb Jason Dagit:
  It will be interesting to hear what fixes this!
 
 
  forever' m = do _ - m
  forever' m

 When I define that version of forever, the space leak goes away.

Not with optimisations.


Thanks for pointing that out.  I forgot to say so in my email.

Here are two reduced versions of the original program:


snip

I find non-termination with a much simpler program than yours (GHC 6.12.1):

\begin{code}{-# OPTIONS -O1 #-}

import Control.Concurrent
import Control.Monad (forever)

main = do
  putStrLn Main thread starting
  forkIO $ do putStrLn Started thread
  forever $ return ()
  putStrLn Delaying
  threadDelay (1 * 100)
  putStrLn Delayed
\end{code}

If I compile that with ghc --make -threaded and run it, with -O1 or 
-O2, it burns CPU and never terminates.  With -O0 it terminates.  So 
looks like some optimisation is causing the problem.


I might guess it's something to do with the RTS and threadDelay that's 
causing the problem.  Delayed is never printed on my system, so it 
seems like (even when run with +RTS -N2) the original thread is not ever 
being rescheduled; perhaps the timeout queue isn't checked properly when 
a thread is burning up the CPU like that, and optimisations are on?


Thanks,

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


Re: [Haskell-cafe] ANN: haskell-src-exts 1.9.0

2010-04-15 Thread Sean Leather
Hi Niklas,


 I'm pleased to announce the release of haskell-src-exts-1.9.0!

 * On hackage: http://hackage.haskell.org/package/haskell-src-exts


Any idea why the Haddock docs have not been generated for this version?
There's also no built on available. Is it an issue with the server?

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


Re[2]: [Haskell-cafe] GHC, odd concurrency space leak

2010-04-15 Thread Bulat Ziganshin
Hello Neil,

Thursday, April 15, 2010, 12:37:35 PM, you wrote:

 I find non-termination with a much simpler program than yours (GHC 6.12.1):
forkIO $ do putStrLn Started thread
forever $ return ()

ghc multithreading is actually cooperative: it switches only on memory
allocation. since almost any haskell code allocates, there is no
problem - it works like preemptive one. but sometimes this assumption
fails - with optimization enabled, your code doesn't allocate so there
are no chances for thread switching. replacing return () with
threadDelay call solves the problem


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

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


Re: [Haskell-cafe] Nomic game in Haskell

2010-04-15 Thread Dupont Corentin
Yes indeed, Nomic couldn't be fully coded, only a subset of it could be.
Rules that are outside of the box cannot be expressed, the goal is, to
have the largest box possible!

Your rule:
* Players must stand when proposing new rules.
couldn't be coded directly, of course, since the computer has no
sensor to detect the position of player ;)

But it could be indirectly. Your rule could be coded like that:
Full rule tiltle: Players must stand when proposing new rules
Code when filtering a proposed rule: A question is asked to all
players except the author of the rule: Does Player X stood when he
proposed this rule? A vast majority of Yes must be acknowlegded to
accept the rule.


On the other hand, if we choose not to interpret the rules, the
program could just be a configuration management system for rules.
It could be a web site that maintain active rules, allow player voting etc.

Corentin.



On 4/15/10, Brent Yorgey byor...@seas.upenn.edu wrote:
 On Wed, Apr 14, 2010 at 09:14:18PM +0200, Dupont Corentin wrote:
 Hello Café,
 do you know Nomic?

 It's a fabulous and strange game where you have the right to change the
 rules in the middle of the game!
 In fact, changing the rules is the goal of the game. Changing a rule is
 considered as a move.
 Of course even that could be changed!

 www.nomic.net

 I'm wondering if it could be possible to implement a Nomic (or an helper
 for
 the game) in Haskell.
 Haskell seems appropriate for that, since functions are first order
 objects,
 and Haskell is good at DSLs.

 I don't think you could actually implement Nomic in the way you
 describe, because any system you come up with will necessarily place
 restrictions on what sorts of rules you are able to represent.  Much
 of the fun of Nomic lies in coming up with new rules that are
 completely outside the box.  For example, how would you encode a rule
 like

   * Players must stand when proposing new rules.

 or

   * Rules which do not mention other rules shall remain in effect
 until such time as the mobile telephone of the Grand Counselor
 rings.

 You get the idea.

 However, implementing some sort of system for encoding certain types
 of rules, and checking that they are valid/consistent/etc. sounds like
 it could be a fun project from which you would probably learn a lot!
 Essentially, you would be designing a syntax for rules, and a type
 system for ensuring that rules are valid or used in valid ways.  It
 wouldn't be Nomic, but it could be something fun.

 -Brent
 ___
 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] Re: Fwd: Re: Simple game: a monad for each player

2010-04-15 Thread Limestraël
Ok, but there is no function such as mapMonad in the operational package?

By the way, I noticed that ProgramT is not automatically made instance of
MonadIO when possible. It could be:
instance (MonadIO m) = MonadIO (ProgramT r m) where
liftIO = lift . liftIO

Is that intentional?
( In fact, I think it's a slip in the mtl package itself, since every
instance of MonadTrans can be declared instance of MonadIO:
instance (MonadTrans t, MonadIO m) = MonadIO (t m) where
liftIO = lift . liftIO
)

By the way, I finally managed to use operational to modify my TicTacToe
game.
(One shot, by the way, I had no bugs ^^. Very nice when it happens...)
Human player and AI are working. I'm currently fixing the Network player.
If you are interested, I could upload my code (it can be another example of
how to use the operational package).

In the end, I used a mix of your solution and my former one.
I have a Request datatype:
data Request a where
  GetGrid   :: Request Grid
  TurnDone  :: (Grid, Maybe GridResult) - Request ()
  GetResult :: Request (Maybe GridResult)

(Grid is what you called Board, GridResult is a type which indicates if
someone wins or if there is a draw)

The game monad is PlayerMonadT, and is a newtype:

newtype PlayerMonadT m a = PMT (ProgramT Request m a)
  deriving (Functor, Monad, MonadTrans)

I still have a datatype Player, which contains functions: (I tried to use
classes, but it was more complicated)

data Player m m' = Player {
  -- | Gets the mark (Cross or Circle) of the player
  plMark  :: Mark,
  -- | Called when the player must play
  plTurn  :: Grid - m Pos,
  -- | Called when player tries to play at a forbidden position
  plForbidden :: Pos - m (),
  -- | Called when game has ended.
  plGameOver  :: GridResult - m (),
  -- | Used to reach PlayerMonad in the monad stack
  plLift  :: forall a. PlayerMonadT m' a - m a,
  -- | Used to run the monad stack the player runs in
  plRun   :: forall a. m a - PlayerMonadT m' a
}

*m* is the monad stack the player runs in. It must be able to run it, by
providing a plRun function.
*m'* is the top monad, which can't be run (IO for human, any monad for AI,
etc.)
The alteration done to this type is the addition of the plLift and plRun
functions. Those are the functions you, Heinrich, and Bertram told me about.

Then, *all* the players play according to this logic:

playerLogic :: (Monad m) = Player m m' - m ()
playerLogic pl = do
  let toProg = plLift pl . PMT . singleton
  grid - toProg GetGrid
  pos - plTurn pl grid
  case checkCell grid (plMark pl) pos of
Nothing - do-- The cell was already filled in
  plForbidden pl pos -- We signal the error
  playerLogic pl -- We start the turn again
Just newGridAndResult - do
 -- The cell has been successfully marked, so we got
a new grid
  toProg $ TurnDone newGridAndResult
 -- At this point, the interpreter will switch to
the other player
  mbResult - toProg $ GetResult
 -- This player is back, and wants to know what's
new
  case mbResult of
Nothing  - playerLogic pl
Just res - plGameOver pl res

We can then run this function with the player custom stack thanks to the
runPlayer function:
runPlayer :: (Monad m) = Player m m' - PlayerMonadT m' ()
runPlayer pl = plRun pl $ playerLogic pl

And finally, the interpreter:
doGame :: (Monad m) = Grid - [PlayerMonadT m ()] - m Grid
doGame initGrid players =
  mapM unwrap players = flip evalStateT (initGrid, Nothing) . eval
  where
unwrap (PMT pl) = viewT pl

eval :: (Monad m) = [PromptT Request m ()] - StateT (Grid, Maybe
GridResult) m Grid

eval [] = liftM fst get

eval ((Return _) : pls) = eval pls

eval ((GetGrid := pl) : pls) = do
  (grid, _) - get
  p - lift . viewT $ pl grid
  eval $ p : pls

eval ((TurnDone (newGrid, mbResult) := pl) : pls) = do
  put (newGrid, mbResult)
  p - lift . viewT $ pl ()
  eval $ pls ++ [p]

eval ((GetResult := pl) : pls) = do
  (_, mbResult) - get
  p - lift . viewT $ pl mbResult
  eval $ p : pls

The game can be launched by doing for example:
let pl1 = humanPlayer Cross
let pl2 = artificialPlayer Circle levelOfDifficulty
doGame blankGrid [runPlayer pl1, runPlayer pl2]

I did it!

2010/4/15 Heinrich Apfelmus apfel...@quantentunnel.de

 Limestraël wrote:
  Okay, I start to understand better...
 
  Just, Heinrich, how would implement the mapMonad function in terms of the
  operational package?
  You just shown the signature.

 Ah, that has to be implemented by the library, the user cannot implement
 this. Internally, the code would be as Bertram suggests:

mapMonad :: (Monad m1, Monad m2)
 = (forall a . m1 a - m2 a)
 - ProgramT instr m1 a - ProgramT instr m2 a
mapMonad f (Lift m1)  = Lift (f m1)
mapMonad f (Bind m k) = Bind (mapMonad f m) (mapMonad f . k)
mapMonad f (Instr i)  = Instr i

 I 

Re: [Haskell-cafe] Can't install Criterion package on ghc ..

2010-04-15 Thread stefan kersten
On 13.04.10 14:46, Mozhgan kabiri wrote:
 I am trying to install Criterion package, but I keep getting an error
 and I can't figure it out why it is like this !!
[...]
 [8 of 9] Compiling Data.Vector.Algorithms.Intro (
 Data/Vector/Algorithms/Intro.hs, dist/build/Data/Vector/Algorithms/Intro.o )
 ghc: panic! (the 'impossible' happened)
   (GHC version 6.10.4 for i386-unknown-linux):
 idInfo co{v a9WB} [tv]

 Please report this as a GHC bug:  http://www.haskell.org/ghc/reportabug

fwiw, the latest version of vector-algorithms (0.3.1) seems to build with ghc
6.10.4.

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


Re: [Haskell-cafe] ANN: haskell-src-exts 1.9.0

2010-04-15 Thread Ivan Lazar Miljenovic
Sean Leather leat...@cs.uu.nl writes:
 I'm pleased to announce the release of haskell-src-exts-1.9.0!

 * On hackage: http://hackage.haskell.org/package/haskell-src-exts


 Any idea why the Haddock docs have not been generated for this version?
 There's also no built on available. Is it an issue with the server?

Looks built to me...

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


Re: [Haskell-cafe] cabal: other-modules

2010-04-15 Thread Ivan Lazar Miljenovic
Johannes Waldmann waldm...@imn.htwk-leipzig.de writes:

 What is the purpose of the Other-Modules section in a cabal file?
 (I.e., can we drop it?)

Non-exported modules.

 If it's just the set of dependencies of the Exported-Modules,
 then a reasonable build system should be able to figure this out on
 its own.

Explicit is better than implicit; this lets you have hidden modules that
don't get shipped, auto-generated modules, etc.

 The current situation is that I have to manage this list manually
 (or is there some tool?) and if I forget to name some other-module,
 then cabal install happily builds and installs (!) the package anyway, 
 but I'm getting linker errors when using it. 

Interesting; it normally complains when this occurs (for me at least);
care to share the .cabal file to see which files it didn't complain
about?

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


Re: [Haskell-cafe] Re: True Random Numbers

2010-04-15 Thread Yitzchak Gale
Since they weren't mentioned in this thread, I'll point
out that there are better sources of entropy than
/dev/random, /dev/urandom, and the Windows API.

For example, the two sites

https://random.org/integers
https://www.fourmilab.ch/hotbits/secure_generate.html

both offer free random bits via a secure REST interface.

Random.org is run by Mads Haahr of the School of
Computer Science and Statistics at Trinity College, Dublin.
They use background atmospheric radio noise to
generate the entropy.

Fourmilab is run by John Walker. He uses a source of
radioactive decay (Ce 137) and a geiger counter to
generate the entropy.

Both sites have gone to some trouble in design and
testing to ensure that their entropy is truly random.

There are quotas on the number of bits you can retrieve
per day for free at each of the sites. At random.org, you
can purchase additional entropy at low cost.

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


Re: [Haskell-cafe] ANN: haskell-src-exts 1.9.0

2010-04-15 Thread Sean Leather
On Thu, Apr 15, 2010 at 12:00, Ivan Lazar Miljenovic 
ivan.miljeno...@gmail.com wrote:

 Sean Leather leat...@cs.uu.nl writes:
  I'm pleased to announce the release of haskell-src-exts-1.9.0!
 
  * On hackage: http://hackage.haskell.org/package/haskell-src-exts
 
 
  Any idea why the Haddock docs have not been generated for this version?
  There's also no built on available. Is it an issue with the server?

 Looks built to me...


Hmm, now it does. Apparently, the server saw my email and responded nicely.


http://hackage.haskell.org/packages/archive/haskell-src-exts/1.9.0/logs/success/

Thanks, Hackage!

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


Re: [Haskell-cafe] cabal: other-modules

2010-04-15 Thread Malcolm Wallace


On 15 Apr 2010, at 08:24, Johannes Waldmann wrote:


What is the purpose of the Other-Modules section in a cabal file?
(I.e., can we drop it?)

If it's just the set of dependencies of the Exported-Modules,
then a reasonable build system should be able to figure this out on  
its own.


It is not used by the build system.  It is used by 'cabal sdist' to  
build a distribution package that contains everything needed.  If a  
file is not listed in the .cabal file, it will not end up in the  
tarball.  Cabal has no dependency analysis to help discover un-listed  
modules.


Regards,
Malcolm

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


Re: [Haskell-cafe] ANN: haskell-src-exts 1.9.0

2010-04-15 Thread Ivan Lazar Miljenovic
Sean Leather leat...@cs.uu.nl writes:
 Hmm, now it does. Apparently, the server saw my email and responded
 nicely.

Well, it takes half an hour or so...

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


Re: [Haskell-cafe] Can't login to GHC trac

2010-04-15 Thread Daniel Fischer
Am Donnerstag 15 April 2010 05:38:23 schrieb Jason Dagit:
 On Tue, Apr 13, 2010 at 3:47 AM, Erik de Castro Lopo
 mle...@mega-nerd.commle%2...@mega-nerd.com

  wrote:
 
  Daniel Fischer wrote:
   Am Dienstag 13 April 2010 09:29:18 schrieb Erik de Castro Lopo:
Anyone else have the same problem?
  
   I have that problem with my hackage (Cabal/cabal-install) trac
   account (Firefox, SeaMonkey, Konqueror).
   It started when I forgot the password and had it mail a new one to
   me.
 
  Yep, thats when my problems started.

 Same here (with the GHC trac).  I had to create a new account to get
 around it.

 Jason

You might try again now, if you prefer your old username. Ian fixed 
something yesterday (I don't know whether it was a global fix or only the 
accounts with known problems) and it works again for me.
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] ANN: haskell-src-exts 1.9.0

2010-04-15 Thread Sean Leather

  Hmm, now it does. Apparently, the server saw my email and responded
  nicely.

 Well, it takes half an hour or so...


Yes, version 1.9.0 of haskell-src-exts was uploaded on Sun Apr 11 10:43:03
UTC 2010, but the ghc build is dated as modified on 15-Apr-2010 02:42 (in
some unknown timezone) according the log 
http://hackage.haskell.org/packages/archive/haskell-src-exts/1.9.0/logs/success/.
I believe that's longer than 30 minutes.

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


Re: [Haskell-cafe] What is the consensus about -fwarn-unused-do-bind ?

2010-04-15 Thread Henning Thielemann
John Meacham schrieb:
 On Fri, Apr 09, 2010 at 09:07:29AM -0700, Bryan O'Sullivan wrote:
 On Fri, Apr 9, 2010 at 6:44 AM, Ivan Lazar Miljenovic 
 ivan.miljeno...@gmail.com wrote:
 As of 6.12.1, the new -fwarn-unused-do-bind warning is activated with
 -Wall.  This is based off a bug report by Neil Mitchell:
 http://hackage.haskell.org/trac/ghc/ticket/3263 .

 However, does it make sense for this to be turned on with -Wall?

 Personally, I find it to be tremendously noisy and unhelpful, and I always
 edit my .cabal files to turn it off. I think of it as a usability
 regression.
 
 I strongly agree.
 
 I do not even think it is bad style to ignore the result of a monad,
 depending on the particular monad used, it could be extremely common. If
 anything there should be a pragma one can attach to ceratin functions to
 warn if the result is unused, like 'mapM'. This would be similar to what
 gcc does, where you can specify an attribute saying a functions result
 should be used or the compiler should complain.

The question is: Would people design libraries in a different way, if it
is encouraged to respect monadic results?
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] ANN: haskell-src-exts 1.9.0

2010-04-15 Thread Ivan Lazar Miljenovic
Sean Leather leat...@cs.uu.nl writes:
 Yes, version 1.9.0 of haskell-src-exts was uploaded on Sun Apr 11 10:43:03
 UTC 2010, but the ghc build is dated as modified on 15-Apr-2010 02:42 (in
 some unknown timezone) according the log 
 http://hackage.haskell.org/packages/archive/haskell-src-exts/1.9.0/logs/success/.
 I believe that's longer than 30 minutes.

Interesting maybe there was some error on Hackage that stopped the
builder from working...

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


[Haskell-cafe] Re: cabal: other-modules

2010-04-15 Thread Johannes Waldmann
What happened was this:

1. add some modules to a library (but forget to mention them in the cabal file),
   then (in the lib source dir, without cleaning/reconfiguring) 
   cabal install --global (runs without complaint)

2. re-compile an application that uses the library 
   (cabal configure  cabal build): this gave undefined symbol errors
   (for things from the added modules)

(with ghc-6.12.1 on i386 debian)

I still don't see why this other-modules is needed.
Ok, I understand the technical reason that cabal 
does not do dependency analysis but morally, it should?

Best regards - J.W.


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


Re: [Haskell-cafe] Re: cabal: other-modules

2010-04-15 Thread José Pedro Magalhães
Hi,

On Thu, Apr 15, 2010 at 14:40, Johannes Waldmann 
waldm...@imn.htwk-leipzig.de wrote:

 What happened was this:

 1. add some modules to a library (but forget to mention them in the cabal
 file),
   then (in the lib source dir, without cleaning/reconfiguring)
   cabal install --global (runs without complaint)

 2. re-compile an application that uses the library
   (cabal configure  cabal build): this gave undefined symbol errors
   (for things from the added modules)


Just to say that this has happened to me very often as well, on Windows. The
first time it took me quite some time to realize what was going wrong...


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


Re: [Haskell-cafe] Re: cabal: other-modules

2010-04-15 Thread Ivan Lazar Miljenovic
Johannes Waldmann waldm...@imn.htwk-leipzig.de writes:
 What happened was this:
 I still don't see why this other-modules is needed.
 Ok, I understand the technical reason that cabal 
 does not do dependency analysis but morally, it should?

Why are people suddenly using the term morally when they mean why
doesn't this do what I think it should?  None of its definitions seem
to match what you mean:
http://wordnetweb.princeton.edu/perl/webwn?s=moral

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


Re: [Haskell-cafe] ANN: haskell-src-exts 1.9.0

2010-04-15 Thread Ross Paterson
On Thu, Apr 15, 2010 at 10:52:51AM +0200, Sean Leather wrote:
 Any idea why the Haddock docs have not been generated for this
 version? There's also no built on available. Is it an issue with
 the server?

A glitch when I was switching the builds to use cabal install --dry-run.
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] True Random Numbers

2010-04-15 Thread Yitzchak Gale
Christopher Done wrote:
 betterStdGen :: IO StdGen

Here's what I have been using. It's a bit more complete.
Of course, you can always use mkStdGen with
it to get one of those if you want. (Yes, I often
do that. StdGen is much maligned, but it's pretty good
at what it's designed for.)

Regards,
Yitz

module DevRandom where

import System.IO
import System.IO.Error
import Foreign.Marshal.Alloc
import Foreign.Storable
import Foreign.Ptr

data BlockingMode = Blocking | NonBlocking
  deriving (Eq, Show)

-- Read data from the system random device.
-- Return Nothing if there is currently not
-- enough entropy in the system random device.
devRandom :: Storable a = IO (Maybe a)
devRandom = readDev /dev/random NonBlocking

-- Read data from the system random device.
-- If necessary, wait until there is
-- enough entropy in the system random device.
devRandomWait :: Storable a = IO a
devRandomWait = readDev dev Blocking = maybe (devRandomError dev) return
  where
dev = /dev/random

-- Read data from the system random device.
-- If there is currently not enough entropy
-- in the system random device, use a lower
-- quality source of randomness instead.
devURandom :: Storable a = IO a
devURandom = readDev dev NonBlocking = maybe (devRandomError dev) return
  where
dev = /dev/urandom

readDev :: Storable a = FilePath - BlockingMode - IO (Maybe a)
readDev dev mode = do
h - openFile dev ReadMode
hSetBuffering h NoBuffering
alloca $ getMaybe h undefined
  where
getMaybe :: Storable a = Handle - a - Ptr a - IO (Maybe a)
getMaybe h undef ptr = do
  let size = sizeOf undef
  n - case mode of
 Blocking- hGetBufh ptr size
 NonBlocking - hGetBufNonBlocking h ptr size
  if n  size
then return Nothing
else fmap Just $ peek ptr

devRandomError :: FilePath - IO a
devRandomError p = ioError $ mkIOError illegalOperationErrorType
  Unable to read from the system random device Nothing (Just p)
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Re: instance Eq (a - b)

2010-04-15 Thread Nick Bowler
On 03:53 Thu 15 Apr , rocon...@theorem.ca wrote:
 On Wed, 14 Apr 2010, Ashley Yakeley wrote:
 
  On 2010-04-14 14:58, Ashley Yakeley wrote:
  On 2010-04-14 13:59, rocon...@theorem.ca wrote:
  
  There is some notion of value, let's call it proper value, such that
  bottom is not one.
  
  In other words bottom is not a proper value.
  
  Define a proper value to be a value x such that x == x.
  
  So neither undefined nor (0.0/0.0) are proper values
  
  In fact proper values are not just subsets of values but are also
  quotients.
  
  thus (-0.0) and 0.0 denote the same proper value even though they are
  represented by different Haskell values.
  
  The trouble is, there are functions that can distinguish -0.0 and 0.0.
  Do we call them bad functions, or are the Eq instances for Float and
  Double broken?
 
 I'd call them disrespectful functions, or maybe nowadays I might call them
 improper functions.  The good functions are respectful functions or
 proper functions.

snip from other post
 Try using the (x == y) == (f x = g y) test yourself.

Your definitions seem very strange, because according to this, the
functions

  f :: Double - Double
  f x = 1/x

and 

  g :: Double - Double
  g x = 1/x

are not equal, since (-0.0 == 0.0) yet f (-0.0) /= g (0.0).

-- 
Nick Bowler, Elliptic Technologies (http://www.elliptictech.com/)
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Re: cabal: other-modules

2010-04-15 Thread Dougal Stanton
On Thu, Apr 15, 2010 at 1:49 PM, Ivan Lazar Miljenovic
ivan.miljeno...@gmail.com wrote:
 Johannes Waldmann waldm...@imn.htwk-leipzig.de writes:
 What happened was this:
 I still don't see why this other-modules is needed.
 Ok, I understand the technical reason that cabal
 does not do dependency analysis but morally, it should?

 Why are people suddenly using the term morally when they mean why
 doesn't this do what I think it should?  None of its definitions seem
 to match what you mean:
 http://wordnetweb.princeton.edu/perl/webwn?s=moral

The proper use of words isn't dictated by what is found in small
dictionaries but by the speakers of the language. Also I would caution
against the judgement 'sudden' if you haven't done a corpus check: the
recency illusion can be a real pain.

'Morally' seems just the perfect word for this occasion --- concerned
with right or proper conduct. In this case, potential discrepancies
between the files that cabal 'knows' about when issuing different
commands; or the sense of deceit when it 'appears' to work only for
faults to appear further down the line.

I would guess this is just something we have to live with if cabal
can't be expected to include its own parser  dependency chaser.

Documentation is always a good first step though :-)

Cheers,

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


Re: [Haskell-cafe] Re: cabal: other-modules

2010-04-15 Thread Casey McCann
On Thu, Apr 15, 2010 at 10:45 AM, Dougal Stanton
dou...@dougalstanton.net wrote:
 'Morally' seems just the perfect word for this occasion --- concerned
 with right or proper conduct. In this case, potential discrepancies
 between the files that cabal 'knows' about when issuing different
 commands; or the sense of deceit when it 'appears' to work only for
 faults to appear further down the line.

Beyond that, there are long established traditions in some parts of
programming and mathematics for using ethical/moral terms to describe
qualities that go beyond just technical requirements or correctness;
this program should do the Right Thing, that bit of code is evil,
and so on. Actually defining this moral sense is difficult, though,
and it varies somewhat from one person to another, but there seems to
be at least some common, shared understanding. It's about should and
proper instead of is or must. Personally, I know I've written
code that I'd feel guilty about even if it worked perfectly and no one
else ever saw it--what else would you call that feeling?

From another angle, here's an example of explicit moral terminology
applied to mathematics: http://www.cheng.staff.shef.ac.uk/morality/
The mathematical sense there is slightly different from the
programming sense, I think, but there seems to be some crossover. For
instance, I've gotten the impression that something like a
mathematical moral sense underlies much of the interest in
programming language semantics, FRP, and dependently-typed languages,
though I don't know if the people involved would necessarily call it
that.

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


Re: [Haskell-cafe] Re: instance Eq (a - b)

2010-04-15 Thread Alexander Solla


On Apr 15, 2010, at 12:53 AM, rocon...@theorem.ca wrote:

I'd call them disrespectful functions, or maybe nowadays I might  
call them

improper functions.  The good functions are respectful functions or
proper functions.


There's no need to put these into a different class.  The IEEE defined  
this behavior in 1985, in order to help with rounding error.  Floats  
and doubles are NOT a field, let alone an ordered field.  0.0 =/= -0.0  
by design, for floats and doubles.  0.0 == -0.0 for integers, exact  
computable reals, etc.  The problem isn't the functions, or the Eq  
instance.  It's the semantics of the underlying data type -- or  
equivalently, expecting that floats and doubles form an ordered field.

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


Re: [Haskell-cafe] Re: Fwd: Re: Simple game: a monad for each player

2010-04-15 Thread Limestraël
There is the project.

I changed some little things with the player datatype. For flexibility sake,
it's stack has no longer to contain PlayerMonadT (I needed it for the net
player client)

The most interesting part (the one that deals with operational) is in
TicTacToe/Game.hs

This is not very, very clean (incomplete doc, for instance), but it'll do
the work.
By the way, the game.hs and client.hs are to be modified (it's the only way
to change the type of the players in the game)

2010/4/15 Limestraël limestr...@gmail.com

 Ok, but there is no function such as mapMonad in the operational package?

 By the way, I noticed that ProgramT is not automatically made instance of
 MonadIO when possible. It could be:
 instance (MonadIO m) = MonadIO (ProgramT r m) where
 liftIO = lift . liftIO

 Is that intentional?
 ( In fact, I think it's a slip in the mtl package itself, since every
 instance of MonadTrans can be declared instance of MonadIO:
 instance (MonadTrans t, MonadIO m) = MonadIO (t m) where
 liftIO = lift . liftIO
 )

 By the way, I finally managed to use operational to modify my TicTacToe
 game.
 (One shot, by the way, I had no bugs ^^. Very nice when it happens...)
 Human player and AI are working. I'm currently fixing the Network player.
 If you are interested, I could upload my code (it can be another example of
 how to use the operational package).

 In the end, I used a mix of your solution and my former one.
 I have a Request datatype:
 data Request a where
   GetGrid   :: Request Grid
   TurnDone  :: (Grid, Maybe GridResult) - Request ()
   GetResult :: Request (Maybe GridResult)

 (Grid is what you called Board, GridResult is a type which indicates if
 someone wins or if there is a draw)

 The game monad is PlayerMonadT, and is a newtype:

 newtype PlayerMonadT m a = PMT (ProgramT Request m a)
   deriving (Functor, Monad, MonadTrans)

 I still have a datatype Player, which contains functions: (I tried to use
 classes, but it was more complicated)

 data Player m m' = Player {
   -- | Gets the mark (Cross or Circle) of the player
   plMark  :: Mark,
   -- | Called when the player must play
   plTurn  :: Grid - m Pos,
   -- | Called when player tries to play at a forbidden position
   plForbidden :: Pos - m (),
   -- | Called when game has ended.
   plGameOver  :: GridResult - m (),
   -- | Used to reach PlayerMonad in the monad stack
   plLift  :: forall a. PlayerMonadT m' a - m a,
   -- | Used to run the monad stack the player runs in
   plRun   :: forall a. m a - PlayerMonadT m' a
 }

 *m* is the monad stack the player runs in. It must be able to run it, by
 providing a plRun function.
 *m'* is the top monad, which can't be run (IO for human, any monad for AI,
 etc.)
 The alteration done to this type is the addition of the plLift and plRun
 functions. Those are the functions you, Heinrich, and Bertram told me about.

 Then, *all* the players play according to this logic:

 playerLogic :: (Monad m) = Player m m' - m ()
 playerLogic pl = do
   let toProg = plLift pl . PMT . singleton
   grid - toProg GetGrid
   pos - plTurn pl grid
   case checkCell grid (plMark pl) pos of
 Nothing - do-- The cell was already filled in
   plForbidden pl pos -- We signal the error
   playerLogic pl -- We start the turn again
 Just newGridAndResult - do
  -- The cell has been successfully marked, so we
 got a new grid
   toProg $ TurnDone newGridAndResult
  -- At this point, the interpreter will switch to
 the other player
   mbResult - toProg $ GetResult
  -- This player is back, and wants to know what's
 new
   case mbResult of
 Nothing  - playerLogic pl
 Just res - plGameOver pl res

 We can then run this function with the player custom stack thanks to the
 runPlayer function:
 runPlayer :: (Monad m) = Player m m' - PlayerMonadT m' ()
 runPlayer pl = plRun pl $ playerLogic pl

 And finally, the interpreter:
 doGame :: (Monad m) = Grid - [PlayerMonadT m ()] - m Grid
 doGame initGrid players =
   mapM unwrap players = flip evalStateT (initGrid, Nothing) . eval
   where
 unwrap (PMT pl) = viewT pl

 eval :: (Monad m) = [PromptT Request m ()] - StateT (Grid, Maybe
 GridResult) m Grid

 eval [] = liftM fst get

 eval ((Return _) : pls) = eval pls

 eval ((GetGrid := pl) : pls) = do
   (grid, _) - get
   p - lift . viewT $ pl grid
   eval $ p : pls

 eval ((TurnDone (newGrid, mbResult) := pl) : pls) = do
   put (newGrid, mbResult)
   p - lift . viewT $ pl ()
   eval $ pls ++ [p]

 eval ((GetResult := pl) : pls) = do
   (_, mbResult) - get
   p - lift . viewT $ pl mbResult
   eval $ p : pls

 The game can be launched by doing for example:
 let pl1 = humanPlayer Cross
 let pl2 = artificialPlayer Circle levelOfDifficulty
 doGame blankGrid [runPlayer pl1, runPlayer pl2]

 I did it!

 2010/4/15 Heinrich 

[Haskell-cafe] Re: Fwd: Re: Simple game: a monad for each player

2010-04-15 Thread Heinrich Apfelmus
Limestraël wrote:
 I'd like to make it very accessible, so please don't hesitate to report
 any difficulties with finding and understanding documentation and examples!

 Then I think the name 'Prompt' may be misleading for those who doesn't know
 the MonadPrompt package. Maybe something like 'ProgramView' ?

Very good point. I'll change that in a future version.

 Ok, but there is no function such as mapMonad in the operational package?

No, not yet, but I'll probably add it, or at least its lesser cousin

liftT :: Program instr a - ProgramT instr m a

to a future version of the library. Still pondering.

 By the way, I noticed that ProgramT is not automatically made instance of
 MonadIO when possible. It could be:
 instance (MonadIO m) = MonadIO (ProgramT r m) where
 liftIO = lift . liftIO
 
 Is that intentional?

Yes and no. I refrained from making instances for the  mtl  classes
because I have not clearly thought about the design consequences yet.

I think that monad transformers are not the last word on modular
computational effects yet and I don't want to paint myself into a
corner. For example, as you note, the MonadIO instance could be deduced
automatically from the  MonadTrans  instance.

Of course, if I make  operational  interoperable with the  mtl , then I
better adhere to its style even if I'm not entirely happy with it.

 By the way, I finally managed to use operational to modify my TicTacToe
 game.

Yay! :D

 (One shot, by the way, I had no bugs ^^. Very nice when it happens...)
 Human player and AI are working. I'm currently fixing the Network player.
 If you are interested, I could upload my code (it can be another example of
 how to use the operational package).

Sending me / uploading your TicTacToe code would be great! I probably
won't use it verbatim, but try to simplify it a bit to turn it into
another easy to understand example of how to use  operational .


Regards,
Heinrich Apfelmus

--
http://apfelmus.nfshost.com

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


[Haskell-cafe] Automating injections: adding a type parameter

2010-04-15 Thread Romulus
Hello everyone,

It's my very first post to this mailing list, though i read it for several
months.

I'm very interested in Swiertra's automatic injection technique [1].
http://www.cse.chalmers.se/~wouter//Publications/DataTypesALaCarte.pdfhttp://www.cse.chalmers.se/%7Ewouter//Publications/DataTypesALaCarte.pdf
http://www.cse.chalmers.se/~wouter//Misc/LaCarte.hshttp://www.cse.chalmers.se/%7Ewouter//Misc/LaCarte.hs

As a first exercise, i've tried to write an interpreter/transformer for
propositional logic, in the spirit of [2].
http://www.haskell.org/sitewiki/images/6/6a/TMR-Issue11.pdf

data LProp r = LProp String
instance Functor LProp where
fmap _ (LProp x) =  LProp x
data LAnd r = LAnd r r
instance Functor LAnd where
fmap f (LAnd x y) = LAnd (f x) (f y)


Automatic injections are cool things to write helpers that work with any
type for formulae extending LProp with coproducts:

-- not very expressive, but it's not the point
type ConjLogicF = LProp :+: LAnd
type ConjLogic = Mu ConjLogicF

lprop :: (LProp :: f) = String - Mu f
lprop = \s - inject (LProp s)
land :: (LAnd :: f) = Mu f - Mu f - Mu f
land = \x y - inject (LAnd x y)


However, i'd like to parameterize the type of propositionnal variables for
the logic, that is, not only strings, but a given type parameter p. For
instance (that should make LProp' and LAnd' bifunctors i guess):

data LProp' p r = LProp' p
instance Functor (LProp' p) where
fmap _ (LProp' x) =  LProp' x
data LAnd' p r = LAnd' r r
instance Functor (LAnd' p) where
fmap f (LAnd' x y) = LAnd' (f x) (f y)

type ConjLogicF' p = (LProp' p) :+: (LAnd' p)
type ConjLogic' p = Mu (ConjLogicF' p)

lprop' :: ((LProp' p) :: (f p)) = p - Mu (f p)
lprop' = \x - inject (LProp' x)

I'm stuck with the definition of the helper for LAnd'. I expect :

land' :: ((LAnd' p) :: (f p)) =  Mu (f p) -  Mu (f p) -  Mu (f p)
land' = \x y - inject (LAnd' x y)

... but ghci 6.10.4 does not really like this definition...

Could not deduce (LAnd' p :: f p1)
  from the context (LAnd' p1 :: f p1)
  arising from a use of `inject' at PropSample.hs:128:16-33
Possible fix:
  add (LAnd' p :: f p1) to the context of
the type signature for `land''
  or add an instance declaration for (LAnd' p :: f p1)
In the expression: inject (LAnd' x y)
In the expression: \ x y - inject (LAnd' x y)
In the definition of `land'': land' = \ x y - inject (LAnd' x y)
Failed, modules loaded: none.



Does anybody have a clue for this problem ?
I don't really understand where is the trouble actually.

Cheers,

PS: haskellers rulez ;)


[1]
Swierstra, W.
Data types à la carte
J. Funct. Program.
Cambridge University Press, 2008, 18, 423-436

[2]
Knowles, K.
First-Order Logic à la Carte
The Monad.Reader, 2008, issue 11


-- 
Romuald THION
Docteur level 1.0 - Great master access control, +3 against half-dead
la vie, c'est comme un jeu mal foutu dont on ne connait pas les règles et
où il n'y a pas de sauvegardes
{-# OPTIONS -Wall #-}
{-# OPTIONS -fwarn-simple-patterns #-}
{-# OPTIONS -fwarn-tabs #-}
{-# OPTIONS -fwarn-incomplete-record-updates #-}
{-# OPTIONS -fwarn-monomorphism-restriction #-}

{-# LANGUAGE FlexibleContexts #-}   -- no type variable in context
{-# LANGUAGE FlexibleInstances #-}  -- type vars appears more than once in head
{-# LANGUAGE MultiParamTypeClasses #-}  
{-# LANGUAGE GADTs #-}  -- for Mu
{-# LANGUAGE TypeOperators #-}  -- for :+: and ::
{-# LANGUAGE OverlappingInstances #-}   -- for automatic injections


module Prop where
import Prelude

-- coproduct for (* - *)
data (f :+: g) a where
  Inl :: (f a) - (f :+: g) a
  Inr :: (g a) - (f :+: g) a
infixr 6 :+:

-- the coproduct of two functors is a functor
instance (Functor f, Functor g) = Functor (f :+: g) where
fmap f (Inl x) = Inl (fmap f x)
fmap f (Inr y) = Inr (fmap f y)

-- fixpoint
data Mu f where In {
out :: f (Mu f)
}  :: Mu f

-- catamorphism
type Algebra   f a = f a - a 
cata :: Functor f = (Algebra f a) - (Mu f - a )
cata g = g . fmap (cata g) . out  

-- Evaluation of an algebra
class Functor f = Eval f a where
evalAlgebra :: Algebra f a
-- Evaluation function
eval :: (Eval f a) =  Mu f - a
eval = cata evalAlgebra

-- links between algebra of coproduct
instance (Eval f a, Eval g a) = Eval (f :+: g) a where
evalAlgebra (Inl x) = evalAlgebra x
evalAlgebra (Inr y) = evalAlgebra y

-- automatic injection
class (Functor sub, Functor sup) = sub :: sup where
inj :: sub a - sup a

instance (Functor f) = (::) f f where
inj  = id
instance (Functor f, Functor g) = (::) f (f :+: g) where
inj  = Inl
instance (Functor h, (::) f g) = (::) f (h :+: g) where
inj  = Inr . inj

inject ::  ((::) sub  f) = sub (Mu f) - Mu f
inject = In . inj



data LProp r = LProp String
instance Functor LProp where
fmap _ (LProp x) =  LProp x
instance 

[Haskell-cafe] Building regex-posix for windows

2010-04-15 Thread Станислав Черничкин
I'm having trouble building regex-posix for Windows under MinGW because 
MinGW does not include regex.h. As far as I know Haskell Platform uses 
MinGW and it includes regex-posix. I'd like to build regex-posix by 
myself, like Haskell Platform does. I would appreciate it if someone 
suggests some resources about building regex-posix and other packages 
for windows. I’m also looking for Haskell Platform developer’s blog or 
something similar, where I can read about porting Haskell on Windows. 
Thanks.


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


[Haskell-cafe] Re: instance Eq (a - b)

2010-04-15 Thread Ashley Yakeley

On 2010-04-15 06:18, Nick Bowler wrote:


Your definitions seem very strange, because according to this, the
functions

   f :: Double -  Double
   f x = 1/x

and

   g :: Double -  Double
   g x = 1/x

are not equal, since (-0.0 == 0.0) yet f (-0.0) /= g (0.0).


There's an impedance mismatch between the IEEE notion of equality (under 
which -0.0 == 0.0), and the Haskell notion of equality (where we'd want 
x == y to imply f x == f y).


A Haskellish solution would be to implement Eq so that it compares the 
bits of the representations of Float and Double, thus -0.0 /= 0.0, NaN 
== NaN (if it's the same NaN). But this might surprise people expecting 
IEEE equality, which is probably almost everyone using Float or Double.


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


Re: [Haskell-cafe] Automating injections: adding a type parameter

2010-04-15 Thread Daniel Fischer
Am Donnerstag 15 April 2010 19:19:15 schrieb Romulus:
 Hello everyone,



 I'm stuck with the definition of the helper for LAnd'. I expect :

 land' :: ((LAnd' p) :: (f p)) =  Mu (f p) -  Mu (f p) -  Mu (f p)
 land' = \x y - inject (LAnd' x y)

 ... but ghci 6.10.4 does not really like this definition...

 Could not deduce (LAnd' p :: f p1)
   from the context (LAnd' p1 :: f p1)
   arising from a use of `inject' at PropSample.hs:128:16-33
 Possible fix:
   add (LAnd' p :: f p1) to the context of
 the type signature for `land''
   or add an instance declaration for (LAnd' p :: f p1)
 In the expression: inject (LAnd' x y)
 In the expression: \ x y - inject (LAnd' x y)
 In the definition of `land'': land' = \ x y - inject (LAnd' x y)
 Failed, modules loaded: none.



 Does anybody have a clue for this problem ?
 I don't really understand where is the trouble actually.

The expression (Land' x y) can have the type (Land' q (Mu (f p))) for all 
q. But there's only an instance for the p used in Mu (f p) provided, so

 Could not deduce (LAnd' p :: f p1)
   from the context (LAnd' p1 :: f p1)

The solution is to tell the compiler that this expression should have the 
type LAnd' p (Mu (f p)) for the f and p from the type signature, add

{-# LANGUAGE ScopedTypeVariables #-}

and modify land' to

land' :: forall f p. ((LAnd' p) :: (f p)) =  Mu (f p) -  Mu (f p) -  Mu 
(f p)
land' = \x y - inject (LAnd' x y :: LAnd' p (Mu (f p)))

to be greeted by


[1 of 1] Compiling Prop ( PropSample.hs, interpreted )

PropSample.hs:31:16:
Warning: Declaration of `In' uses deprecated syntax
 Instead, use the form
   In :: {out :: f (Mu f)} - Mu f
Ok, modules loaded: Prop.
*Prop

by 6.12.1 and

$ ghci-6.10.3 PropSample
GHCi, version 6.10.3: http://www.haskell.org/ghc/  :? for help
Loading package ghc-prim ... linking ... done.
Loading package integer ... linking ... done.
Loading package base ... linking ... done.
[1 of 1] Compiling Prop ( PropSample.hs, interpreted )
Ok, modules loaded: Prop.
*Prop

from the older GHC.


 Cheers,

 PS: haskellers rulez ;)

+1



 [1]
 Swierstra, W.
 Data types à la carte
 J. Funct. Program.
 Cambridge University Press, 2008, 18, 423-436

 [2]
 Knowles, K.
 First-Order Logic à la Carte
 The Monad.Reader, 2008, issue 11

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


Re: [Haskell-cafe] Automating injections: adding a type parameter

2010-04-15 Thread Romulus
Clear and concise answer.

Thank you.

On Thu, Apr 15, 2010 at 21:24, Daniel Fischer daniel.is.fisc...@web.dewrote:

 Am Donnerstag 15 April 2010 19:19:15 schrieb Romulus:
  Hello everyone,
 

 
  I'm stuck with the definition of the helper for LAnd'. I expect :
 
  land' :: ((LAnd' p) :: (f p)) =  Mu (f p) -  Mu (f p) -  Mu (f p)
  land' = \x y - inject (LAnd' x y)
 
  ... but ghci 6.10.4 does not really like this definition...
 
  Could not deduce (LAnd' p :: f p1)
from the context (LAnd' p1 :: f p1)
arising from a use of `inject' at PropSample.hs:128:16-33
  Possible fix:
add (LAnd' p :: f p1) to the context of
  the type signature for `land''
or add an instance declaration for (LAnd' p :: f p1)
  In the expression: inject (LAnd' x y)
  In the expression: \ x y - inject (LAnd' x y)
  In the definition of `land'': land' = \ x y - inject (LAnd' x y)
  Failed, modules loaded: none.
 
 
 
  Does anybody have a clue for this problem ?
  I don't really understand where is the trouble actually.

 The expression (Land' x y) can have the type (Land' q (Mu (f p))) for all
 q. But there's only an instance for the p used in Mu (f p) provided, so

 Could not deduce (LAnd' p :: f p1)
   from the context (LAnd' p1 :: f p1)

 The solution is to tell the compiler that this expression should have the
 type LAnd' p (Mu (f p)) for the f and p from the type signature, add

 {-# LANGUAGE ScopedTypeVariables #-}

 and modify land' to

 land' :: forall f p. ((LAnd' p) :: (f p)) =  Mu (f p) -  Mu (f p) -  Mu
 (f p)
 land' = \x y - inject (LAnd' x y :: LAnd' p (Mu (f p)))

 to be greeted by


 [1 of 1] Compiling Prop ( PropSample.hs, interpreted )

 PropSample.hs:31:16:
Warning: Declaration of `In' uses deprecated syntax
 Instead, use the form
   In :: {out :: f (Mu f)} - Mu f
 Ok, modules loaded: Prop.
 *Prop

 by 6.12.1 and

 $ ghci-6.10.3 PropSample
 GHCi, version 6.10.3: http://www.haskell.org/ghc/  :? for help
 Loading package ghc-prim ... linking ... done.
 Loading package integer ... linking ... done.
 Loading package base ... linking ... done.
 [1 of 1] Compiling Prop ( PropSample.hs, interpreted )
 Ok, modules loaded: Prop.
 *Prop

 from the older GHC.

 
  Cheers,
 
  PS: haskellers rulez ;)

 +1

 
 
  [1]
  Swierstra, W.
  Data types à la carte
  J. Funct. Program.
  Cambridge University Press, 2008, 18, 423-436
 
  [2]
  Knowles, K.
  First-Order Logic à la Carte
  The Monad.Reader, 2008, issue 11




-- 
Romuald THION
Docteur level 1.0 - Great master access control, +3 against half-dead
la vie, c'est comme un jeu mal foutu dont on ne connait pas les règles et
où il n'y a pas de sauvegardes
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Nomic game in Haskell

2010-04-15 Thread Dan Piponi
Dupont asked:

 do you know Nomic?

 It's a fabulous and strange game where you have the right to change the rules 
 in the middle of the game!

I know nomic, but as has been pointed out, it's too wide-ranging to be
captured in Haskell. So how about a game played in the Haskell type
system where you get to play whatever type you like?

Let's restrict ourselves to a total fragment of Haskell. Only allow
structural recursion and that sort of thing.

The 'board' is a Haskell type function. It'll look something like this:

type Board a b c ... y z = ...

with type variables a to z (no need to have precisely 26) and so that
the right hand side is a type, not another type function.

(A neutral third party will have to implement Board.)

There are two players. They take turns where a turn consists of
picking a concrete type to bind to precisely one previously unbound
type variable. When there are no more legal moves left, player 1 now
has to exhibit an element of the resulting type. If they succeed, they
win, otherwise player 2 wins. Void is allowed.

For example, consider

type Board a b c d e f g = (Either a b, Either c d, Either e f, g)

Player 1 must start by making g a type they know how to instantiate.
Maybe g=Int. If not, then Player 2 chooses g=Void and they will never
be able to make one of these 4-tuples. From now on, Player 2 has sente
(to use go language) because Player 1 will always have to play in the
same factor of the 4-tuple that Player 2 played in. Ultimately,
however, Player 1 can force a win.
--
Dan
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Building regex-posix for windows

2010-04-15 Thread Stephen Tetley
Hello

You can build GNU's regex C-library with MinGW from source and this
will give you regex.h and libregex.a / libregex.dll.

I think I've only had the Haskell regex-posix package half-working
doing this though; i.e. I could build and install regex-posix after
I'd made and installed GNU regex, but when I tried to use (Haskell)
packages that depended on (Haskell) regex-posix I got linker errors.
As I could live without the dependent packages I never investigated
further.

Best wishes

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


Re: [Haskell-cafe] Building regex-posix for windows

2010-04-15 Thread Jason Dagit
2010/4/15 Станислав Черничкин schernich...@gmail.com

  I'm having trouble building regex-posix for Windows under MinGW because
 MinGW does not include regex.h. As far as I know Haskell Platform uses MinGW
 and it includes regex-posix. I'd like to build regex-posix by myself, like
 Haskell Platform does. I would appreciate it if someone suggests some
 resources about building regex-posix and other packages for windows. I'm
 also looking for Haskell Platform developer's blog or something similar,
 where I can read about porting Haskell on Windows. Thanks.

I don't know the answer to your regex-posix question, but if you're looking
for Haskell friendly blogs, try: http://planet.haskell.org

Is it what you would have expected from a Haskell Platform Developer's
blog?  If not, what were you hoping to find?

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


Re: [Haskell-cafe] Building regex-posix for windows

2010-04-15 Thread Ivan Lazar Miljenovic
Станислав Черничкин schernich...@gmail.com writes:

 I'm having trouble building regex-posix for Windows under MinGW
 because MinGW does not include regex.h.

Which version of regex-posix is this?

I think this might be a bug in regex-posix's .cabal file: the darcs repo
seems to contain a regex.h which should probably be included and used on
Windows.

 As far as I know Haskell Platform uses MinGW and it includes
 regex-posix.

I'm not sure if it uses MinGW or Cygwin.

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


Re: [Haskell-cafe] Building regex-posix for windows

2010-04-15 Thread Stephen Tetley
Hi Ivan

I believe that regex-posix (Haskell) is expecting regex.h to be the
'standard posix' header file. The versions of MinGW / MSys I'm using
from around Christmas last year didn't ship with a Posix regex
implementation, though this might have changed now. I seem to remember
that GNU Posix was available as a package from the MinGW website, but
there was some reason I choose to work from the GNU source tarball
instead (what ever it was, I've now forgotten).

Its certainly possible the original poster doesn't have a Posix regex
implementation under MinGW either - I can't find the darcs repo to
check, but I think MinGW would need more than a header file.

Best wishes

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


[Haskell-cafe] Re: Building regex-posix for windows

2010-04-15 Thread Mikhail Glushenkov
Hi,

Станислав Черничкин schernichkin at gmail.com writes:
 
 
 I'm having
 trouble building regex-posix for Windows [...]

See this thread:

http://thread.gmane.org/gmane.comp.lang.haskell.libraries/12721

Basically, you need to checkout the darcs version which includes
C sources for libregex and hack the .cabal file a bit.

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


[Haskell-cafe] Haskell web dev - ASP .NET analogue?

2010-04-15 Thread Christopher Done
The state of Haskell web development is exciting and messy. We don't
have a de facto way to do it like Rails or Django or ASP .NET, but we
do have many imitations and ideas popping up. You can easily judge
whether the community is happy with the state of web development by
the number of new web frameworks coming out all the time.

I'm wondering if there is a ASP .NET analogue for Haskell. ASP .NET
manages compiled languages like C# well by compiling a given page when
you run it, and also allowing you to build pages into DLLs and then
link them in your project. I have used this development process for a
year in a commercial business and quite like it. It's just really easy
to develop. Often you make little mistakes on a given page, so you
just edit one bit of code -- you don't want to have to run a command
to reload this code yourself. I think that, with Hint, one could write
a Haskell equivalent. The nice thing is you can test your Haskell code
in GHCi and then save the page and load it in the browser and have it
auto-recompile. As to how pages are generated I guess is up to whoever
is using it.

You have a kind of standard separation in ASP .NET:

backend.vb:
Sub submit(sender As Object, e As EventArgs)
lbl1.Text=Your name is   txt1.Text
End Sub

frontend.asp:
form runat=server
Enter your name:
asp:TextBox id=txt1 runat=server /
asp:Button OnClick=submit Text=Submit runat=server /
pasp:Label id=lbl1 runat=server //p
/form

One could blatantly copy this model. And it's not a bad model. To
start with anyway. It has the benefit that it's familiar to many web
programmers, and, importantly, business practice/industry. My
coworkers who only deal with HTML/CSS/JavaScript wouldn't care if
backend.vb became backend.hs.

I wrote an ecommerce site (http://productsforhair.co.uk/) a year ago
in Haskell and used the Text.XHtml.Strict and hated it to be honest.
It looks like a complete mess. Look at these two examples of using
EDSLs to produce content. Messy and unmanageable.

http://paste.lisp.org/display/97840

http://paste.lisp.org/system-server/show/lisppaste/web-server

As much as I love EDSLs like html combinators, as soon as you get a
nontrivial project with big complex elements it soon gets out of hand.
BlazeHtml makes this a little nicer with its `do' syntax but it's
still a problem.
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] Re: Nomic game in Haskell

2010-04-15 Thread Ashley Yakeley

On 2010-04-15 14:00, Dan Piponi wrote:


(A neutral third party will have to implement Board.)


data Three a b c where
{
  MkThree :: Three () () ()
}

type Board a b c d e f g h i =
 Either (Three a b c)
 (Either (Three d e f)
 (Either (Three g h i)
 (Either (Three a d g)
 (Either (Three b e h)
 (Either (Three c f i)
 (Either (Three a e i)
 (Either (Three c e g)
 )))

Player 2 wins, I think.

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


[Haskell-cafe] auto-recompile (Re: Haskell web dev - ASP .NET analogue?)

2010-04-15 Thread Simon Michael
Re the auto-recompiling part, here is one of my favourite tools. I have used it to auto-build happstack, yesod and 
hakyll apps/sites:


# continuous integration - recompile and restart
# whenever a module changes. sp is from searchpath.org, you might
# need the patched version from http://joyful.com/repos/searchpath
ci:
  sp --no-exts --no-default-map ghc --make -o app --make app.hs --run

Also, you didn't ask for this but while I'm pasting.. here's a thorough darcs posthook, for doing something when a 
repo's content changes (add the below to _darcs/prefs/defaults):


apply posthook  make build
apply run-posthook
pull posthook   make build
pull run-posthook
record posthook make build
record run-posthook
obliterate posthook make build
obliterate run-posthook


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


[Haskell-cafe] Re: Nomic game in Haskell

2010-04-15 Thread Dan Piponi
On Thu, Apr 15, 2010 at 4:58 PM, Ashley Yakeley ash...@semantic.org wrote:

 type Board a b c d e f g h i =
  Either (Three a b c)
  (Either (Three d e f)
  (Either (Three g h i)
  (Either (Three a d g)
  (Either (Three b e h)
  (Either (Three c f i)
  (Either (Three a e i)
  (Either (Three c e g)
  )))

In the service of readability we could also define:

data X = X
data O

Though the victory conditions aren't precisely the usual ones.
--
Dan
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] Re: Nomic game in Haskell

2010-04-15 Thread Ashley Yakeley

On 2010-04-15 17:39, Dan Piponi wrote:


In the service of readability we could also define:

data X = X
data O


In that case we'd want

  type Three a b c = (a,b,c)

...which is simpler than my GADT.

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


[Haskell-cafe] Why does the transformers/mtl 'Error' class exist?

2010-04-15 Thread John Millikin
Both the transformers[1] and mtl[2] define a class named 'Error', for
use with MonadError and ErrorT. This class is required for the
instance of Monad (and therefore MonadTrans, MonadIO, etc). However, I
can't figure out why this class exists. Its presence means that
instead of something like:

-
data NameError = ErrorFoo | ErrorBar
validateName :: Monad m = Text - m (Either Error Text)
validateName x = runErrorT $ do
when (some condition) $ throwError ErrorFoo
when (other condition) $ throwError ErrorBar
return x
-

I have to define this, which is more verbose, no more useful, and adds
a fake class to the Haddock docs (with a warning not to use it):
-
data Error = ErrorFoo | ErrorBar

instance Error NameError where
strMsg = error

-- validateName ...
-

Is there any good reason why the 'Error' class can't just be removed?

[1] 
http://hackage.haskell.org/packages/archive/transformers/0.2.0.0/doc/html/Control-Monad-Trans-Error.html
[2] 
http://hackage.haskell.org/packages/archive/mtl/1.1.0.2/doc/html/Control-Monad-Error-Class.html
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Why does the transformers/mtl 'Error' class exist?

2010-04-15 Thread Ryan Ingram
It's used in the implementation of fail for those monads.

class Monad m where
   ...
   fail :: String - m a
   fail = error  -- default implementation

which is then used to desugar do-notation when pattern matching fails:

do
Left x - something
return x
=
 something = \v - case v of { Left x - return x ; _ - fail
Pattern match failure ... }

You can argue about whether fail belongs in Monad (and many people
have), but that's why it is how it is.

  -- ryan

On Thu, Apr 15, 2010 at 7:18 PM, John Millikin jmilli...@gmail.com wrote:
 Both the transformers[1] and mtl[2] define a class named 'Error', for
 use with MonadError and ErrorT. This class is required for the
 instance of Monad (and therefore MonadTrans, MonadIO, etc). However, I
 can't figure out why this class exists. Its presence means that
 instead of something like:

 -
 data NameError = ErrorFoo | ErrorBar
 validateName :: Monad m = Text - m (Either Error Text)
 validateName x = runErrorT $ do
    when (some condition) $ throwError ErrorFoo
    when (other condition) $ throwError ErrorBar
    return x
 -

 I have to define this, which is more verbose, no more useful, and adds
 a fake class to the Haddock docs (with a warning not to use it):
 -
 data Error = ErrorFoo | ErrorBar

 instance Error NameError where
    strMsg = error

 -- validateName ...
 -

 Is there any good reason why the 'Error' class can't just be removed?

 [1] 
 http://hackage.haskell.org/packages/archive/transformers/0.2.0.0/doc/html/Control-Monad-Trans-Error.html
 [2] 
 http://hackage.haskell.org/packages/archive/mtl/1.1.0.2/doc/html/Control-Monad-Error-Class.html
 ___
 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] what does the '~' mean ?

2010-04-15 Thread zaxis

instance (BinaryDefer a, BinaryDefer b) = BinaryDefer (a,b) where
put (a,b) = put2 a b
get = get2 (,)
size x = let ~(a,b) = x in size a + size b
putFixed (a,b) = putFixed2 a b
getFixed = getFixed2 (,)

in `size` function, what does the `~` mean ?

Sincerely!



-
fac n = let {  f = foldr (*) 1 [1..n] } in f 
-- 
View this message in context: 
http://old.nabble.com/what-does-the-%27%7E%27-mean---tp28263383p28263383.html
Sent from the Haskell - Haskell-Cafe mailing list archive at Nabble.com.

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