[Haskell-cafe] Re: The Opposite of $

2007-12-04 Thread Alan Hawkins


| is not defined in the prelude but can be defined as 

let (|) = flip ($)

to make it the opposite of $ which means the syntax looks more like the
 Unix pipe '|' command

eg. 
filter  (\x- x 3  x  7) $ [1..10] ++ [5]
[1..10] ++ [5] | filter  (\x- x 3  x  7)

res: [4,5,6]

note that with the | the function applications are read as naturally
 left to right as apposed to the 
$ which reads left to right. a style more in line with the syntax f (x)





  

Never miss a thing.  Make Yahoo your home page. 
http://www.yahoo.com/r/hs
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] regexen no go with 6.8.1?

2007-12-04 Thread Jason Dusek
Is it just me, or are all the regex implementations broken with
new change in lib layout for 6.8.1?

Are fixes available in darcs?

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


Re: [Haskell-cafe] Advice for clean code.

2007-12-04 Thread Felipe Lessa
On Dec 4, 2007 1:28 AM, Don Stewart [EMAIL PROTECTED] wrote:
 -- How to display results
 instance Show Action where
 show MoveOutOfBounds= Sorry you can't move in that direction.
 show (MoveBadTerrain a) = case a of
   Wall  - You walk into a wall.
   Tree  - There is a tree in the way.
   otherwise - You can't move there.
 show MoveOk = Good move.

I always thought show was meant for returning a String that could be
used to recreate the original data if you copy-pasted it in your code
or if you used read (i.e. read . show == id). Reading the
documentation more carefully, I see that [1] says that this property
holds for *derived* instances, and says nothing about it in the
general case.

So, what's the deal here? May I use Show for anything without breaking
conventions? And how about Read?

Thanks!

[1] 
http://haskell.org/ghc/docs/latest/html/libraries/base-3.0.0.0/Prelude.html#t%3AShow

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


Re: [Haskell-cafe] Advice for clean code.

2007-12-04 Thread Dougal Stanton
On 04/12/2007, Felipe Lessa [EMAIL PROTECTED] wrote:

 I always thought show was meant for returning a String that could be
 used to recreate the original data if you copy-pasted it in your code
 or if you used read (i.e. read . show == id). Reading the
 documentation more carefully, I see that [1] says that this property
 holds for *derived* instances, and says nothing about it in the
 general case.

 So, what's the deal here? May I use Show for anything without breaking
 conventions? And how about Read?


That seems to be convention though I don't think it's required for the
correct operation of anything. Anyone?

-- 
Dougal Stanton
[EMAIL PROTECTED] // http://www.dougalstanton.net
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] Re: Nofib modifications

2007-12-04 Thread Simon Marlow

I'd do something like

#if defined(__nhc98__) || defined(YHC)
#define NO_MONOMORPHISM_RESTRICTION
#endif

#ifdef NO_MONOMORPHISM_RESTRICTION
powers :: [[Integer]]
#endif

just to make it quite clear what's going on.  (good comments would do just 
as well).


Cheers,
Simon

Simon Peyton-Jones wrote:

By all means apply a patch, I think.

Simon

| -Original Message-
| From: [EMAIL PROTECTED] [mailto:[EMAIL PROTECTED] On Behalf Of Neil Mitchell
| Sent: 03 December 2007 17:34
| To: Haskell Cafe
| Cc: Simon Marlow; Malcolm Wallace; Duncan Coutts
| Subject: [Haskell-cafe] Nofib modifications
|
| Hi,
|
| Some of the nofib suite are messed up by Yhc/nhc because of the
| monomorphism restriction. Take imaginary/bernouilli as an example:
|
| powers = [2..] : map (zipWith (*) (head powers)) powers
|
| Hugs and GHC both see powers :: [[Integer]] and a CAF.
|
| Yhc (and nhc) both see powers :: (Enum a, Num a) = [[a]] and no CAF.
|
| This completely destroys the performance in Yhc/nhc. Since this is not
| so much a performance aspect but a compiler bug, based on a feature
| whose future in Haskell' is as yet unclear, perhaps it would be wise
| to patch nofib to include an explicit type signature where this
| matters. I am happy to send in a patch (or just apply it) - but I have
| no idea who maintains the suite. I've CC'd those people who make
| substantial use of the nofib suite.
|
| Thanks
|
| Neil
| ___
| Haskell-Cafe mailing list
| Haskell-Cafe@haskell.org
| http://www.haskell.org/mailman/listinfo/haskell-cafe


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


[Haskell-cafe] Re: Leopard: ghc 6.8.1 and the case of the missing _environ

2007-12-04 Thread Simon Marlow

Joel Reymont wrote:

Symptoms:

You build 6.8.1 from source on Leopard (x86 in my case) and then

junior:ghc-6.8.1 joelr$ ghci
GHCi, version 6.8.1: http://www.haskell.org/ghc/  :? for help
ghc-6.8.1:
/usr/local/lib/ghc-6.8.1/lib/base-3.0.0.0/HSbase-3.0.0.0.o: unknown 
symbol `_environ'
Loading package base ... linking ... ghc-6.8.1: unable to load package 
`base'



Problem:

ghc binaries are being stripped upon installation which eliminates 
_environ, e.g.


junior:tmp joelr$ nm x|grep environ
2ff0 T ___hscore_environ
0004d004 D _environ

junior:tmp joelr$ strip x
junior:tmp joelr$ nm x|grep environ

Solution:

Need to make sure install-sh does _not_ use the -s option. Haven't found 
out where this needs to be done yet. A temporary workaround is to ask 
Manuel for the pre-built binaries.


MacOS folks: is this still an issue?  If so, could someone create a ticket?

Cheers,
Simon

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


Re: [Haskell-cafe] Re: do

2007-12-04 Thread Luke Palmer
On Dec 4, 2007 11:39 AM, Jules Bean [EMAIL PROTECTED] wrote:
 Ben Franksen wrote:
  I don't buy this. As has been noted by others before, IO is a very special
  case, in that it can't be defined in Haskell itself, and there is no
  evaluation function runIO :: IO a - a.

 This is a straw man. Most monads will not have such a function:

When I first learned monads, I heard that once you get into IO, you
can never get out.
The point here was that that doesn't generalize, so a student might
start thinking that
a monad is like a taint flag or something.  Not to say that statement
that it's a complete
falsity when generalized to other monads -- it's reflective of the
algebra of monads --
you just have to define never a little differently. :-)

In any case, I don't think that's a big issue.  While it is important
to eliminate things
that monads aren't from students' possible models, it's better just to
build a good model
in the first place.

FWIW, the list monad was how I made the leap from monads do IO to
monads do nifty stuff.

Luke

 There is no function (State s a) - a.

 There is no function (r - a) - a.

 There is no function (Random a) - a. [assuming some random monad, often
 discussed]

 There is no function (Supply s a) - a. [Another useful monad although
 not one of the standard ones]

 There are no (total) functions Maybe a - a, [a] - a, Either e a - a.



 As to the topic of the thread: I agree IO is an unusual monad. I'm not
 sure if I agree that it shouldn't be used as a teaching basis. I think
 there are all kinds of ways to teach haskell; I'd be inclined to want to
 start with some IO, without explaining the plumbing in detail, and then
 come back to it later with better perspective when discussing general
 monads.

 Jules

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

2007-12-04 Thread Jules Bean

Ben Franksen wrote:

I don't buy this. As has been noted by others before, IO is a very special
case, in that it can't be defined in Haskell itself, and there is no
evaluation function runIO :: IO a - a.


This is a straw man. Most monads will not have such a function:

There is no function (State s a) - a.

There is no function (r - a) - a.

There is no function (Random a) - a. [assuming some random monad, often 
discussed]


There is no function (Supply s a) - a. [Another useful monad although 
not one of the standard ones]


There are no (total) functions Maybe a - a, [a] - a, Either e a - a.



As to the topic of the thread: I agree IO is an unusual monad. I'm not 
sure if I agree that it shouldn't be used as a teaching basis. I think 
there are all kinds of ways to teach haskell; I'd be inclined to want to 
start with some IO, without explaining the plumbing in detail, and then 
come back to it later with better perspective when discussing general 
monads.


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


Re: [Haskell-cafe] ANN: Shu-thing 1.0 and Monadius 0.9

2007-12-04 Thread Neil Bartlett

Hi Gwern,

Shu-thing is great fun!

I think Monadius isn't compiling because most of the source files are  
missing; you only have Main.hs in there.


Regards
Neil

On 4 Dec 2007, at 01:53, [EMAIL PROTECTED] wrote:

Hi everyone. With the permission of the authors, I'd like to  
announce the release  upload to Hackage of two games written in  
Haskell (you may've seen them mentioned here once or twice before):


*Monadius
*Shu-thing

They are both scrolling 2 dimensional arcade shooting games which  
use 3D vector graphics. Shu-thing is a fairly simpler upwards  
scrolling shooter with one level and geometric objects; Monadius is  
a sort of clone/homage to the classic arcade game Gradius, and I  
find it quite fun (although I have yet to beat it).


You can find screenshots and original here:
*http://www.geocities.jp/takascience/index_en.html#haskell

The Hackage pages:
*http://hackage.haskell.org/cgi-bin/hackage-scripts/package/Monadius-0.9.20071203 

*http://hackage.haskell.org/cgi-bin/hackage-scripts/package/Shu-thing-1.0.20071203 



--

They both have dependencies on GLUT, and it's definitely advisable  
to have 3D acceleration enabled on your system. I've only tested  
them with GHC 6.8.1 and up (where they work fine) on my Gentoo Linux  
box.


You should be able to 'cabal install' Shu-thing, but Monadius  
doesn't compile successfully for reasons I don't understand.


--

My changes to the programs in question are not terribly major -  
largely Cabalizing them, formatting and making stylistic changes,  
stomping most -Wall messages, and occasionally changing algorithms  
or attempting to optimize them. In the case of Monadius, I removed  
all the Windows-specific material (the audio files were apparently  
copyright violations, so no big loss) and improved storage of replay  
files.


I'd like to thank Takayuki Muranushi for answering my questions  
about the code and giving permission to update them. I hereby  
release all my changes into the public domain.


--
gwern
___
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] foild function for expressions

2007-12-04 Thread Kalman Noel
Ryan Ingram wrote:
 On 12/3/07, Kalman Noel [EMAIL PROTECTED] wrote:
  You're confusing sum and product types.
 I'm not so sure; it looks like they already have that type (Exp) and wants
 to use AlgExp to hold the folding functions used.

Ah, I didn't catch that on the first read.  I suppose Carlo should then
tell us what Exp exactly looks like; and it would be nice, too, to
explain to me what the function in question is supposed to achieve then.
He doesn't seem to want to reduce the expression, after all.

Kalman

--
Free pop3 email with a spam filter.
http://www.bluebottle.com/tag/5

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


Re: [Haskell-cafe] Advice for clean code.

2007-12-04 Thread Henning Thielemann

On Tue, 4 Dec 2007, Dougal Stanton wrote:

 On 04/12/2007, Felipe Lessa [EMAIL PROTECTED] wrote:
 
  I always thought show was meant for returning a String that could be
  used to recreate the original data if you copy-pasted it in your code
  or if you used read (i.e. read . show == id). Reading the
  documentation more carefully, I see that [1] says that this property
  holds for *derived* instances, and says nothing about it in the
  general case.
 
  So, what's the deal here? May I use Show for anything without breaking
  conventions? And how about Read?

 That seems to be convention though I don't think it's required for the
 correct operation of anything. Anyone?

You will find that convention comfortable if you work in GHCi - may it be
just for debugging. In turn I think it is even good to leak results of
'show' to the outside world, but due to lack of alternatives I'm doing it
myself regularly. Since 'show' is intended to show internals of a data
structure (and this is what 'deriving Show' implements) this will leak
internal information to the user. But the user does not know the internals
of your program, does not know your function and constructor names, so
they are not of much help for him. And if the function names tell
something to the user, he might still want to get them presented in his
mother's tongue.
 I encountered e.g. the following problem: I printed numbers for
processing by a different program. GHC's 'show' returned '1.0e-2', Hugs'
'show' returned '0.01' - both are correct Haskell literals, but the
postprocessing program didn't understand '1.0e-2'. That is 'show' does not
give you much control on the output format that you need for reliable
post-processing.
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] Re: [Haskell] IVars

2007-12-04 Thread Bertram Felgenhauer
[redirecting to haskell-cafe]

Simon Peyton-Jones wrote:
 But since the read may block, it matters *when* you perform it.  For
 example if you print Hello and then read the IVar, you'll block
 after printing; but if you read the IVar and then print, the print
 won't come out.  If the operation was pure (no IO) then you'd have
 a lot less control over when it happened.

Well, the same can happen with any pure computation that does not
terminate. It's the compiler's job to avoid that, and as far as I know
ghc is pretty careful not to reorder pure computations and IO
operations too much.

I'd argue for adding both an IO and a pure version of readIVar to an
IVar implementation. Both have their uses; the firts gives you a little
extra control, while the second one can easily be evaluated on demand,
at the risk of creating a mine field of potential deadlocks.

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


Re: [Haskell-cafe] regexen no go with 6.8.1?

2007-12-04 Thread Duncan Coutts
On Tue, 2007-12-04 at 02:02 -0800, Jason Dusek wrote:
 Is it just me, or are all the regex implementations broken with
 new change in lib layout for 6.8.1?
 
 Are fixes available in darcs?

Use these ones:

http://hackage.haskell.org/cgi-bin/hackage-scripts/package/regex-base-0.72.0.1
http://hackage.haskell.org/cgi-bin/hackage-scripts/package/regex-posix-0.72.0.2
http://hackage.haskell.org/cgi-bin/hackage-scripts/package/regex-compat-0.71.0.1


Duncan

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


Re: [Haskell-cafe] Advice for clean code.

2007-12-04 Thread Jules Bean

Felipe Lessa wrote:

On Dec 4, 2007 1:28 AM, Don Stewart [EMAIL PROTECTED] wrote:

-- How to display results
instance Show Action where
show MoveOutOfBounds= Sorry you can't move in that direction.
show (MoveBadTerrain a) = case a of
  Wall  - You walk into a wall.
  Tree  - There is a tree in the way.
  otherwise - You can't move there.
show MoveOk = Good move.


I always thought show was meant for returning a String that could be
used to recreate the original data if you copy-pasted it in your code
or if you used read (i.e. read . show == id). Reading the
documentation more carefully, I see that [1] says that this property
holds for *derived* instances, and says nothing about it in the
general case.


I would not write what dons wrote.

I would have a custom function here rather than misusing Show in this 
way; call it showMoveError or similar. For mostly the reasons Felipe gave.


I don't think it's hugely important though.

Jules

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


Re: [Haskell-cafe] An interesting monad: Prompt

2007-12-04 Thread Ryan Ingram
Ask and ye shall receive.  A simple guess-a-number game in MonadPrompt
follows.

But before I get to that, I have some comments:

 Serializing the state at arbitrary places is hard; the Prompt contains a
continuation function so unless you have a way to serialize closures it
seems like you lose.  But if you have safe points during the execution at
which you know all relevant state is inside your game state, you can save
there by serializing the state and providing a way to restart the
computation at those safe points.

I haven't looked at MACID at all; what's that?

 {-# LANGUAGE GADTs, RankNTypes #-}
 module Main where
 import Prompt
 import Control.Monad.State
 import System.Random (randomRIO)
 import System.IO
 import Control.Exception (assert)

Minimalist functional references implementation.
In particular, for this example, we skip the really interesting thing:
composability.

See http://luqui.org/blog/archives/2007/08/05/ for a real implementation.

 data FRef s a = FRef
   { frGet :: s - a
   , frSet :: a - s - s
   }

 fetch :: MonadState s m = FRef s a - m a
 fetch ref = get = return . frGet ref

 infix 1 =:
 infix 1 =:
 (=:) :: MonadState s m = FRef s a - a - m ()
 ref =: val = modify $ frSet ref val
 (=:) :: MonadState s m = FRef s a - m a - m ()
 ref =: act = act = modify . frSet ref
 update :: MonadState s m = FRef s a - (a - a) - m ()
 update ref f = fetch ref = \a - ref =: f a

Interactions that a user can have with the game:

 data GuessP a where
GetNumber :: GuessP Int
Guess :: GuessP Int
Print :: String - GuessP ()

Game state.

We could do this with a lot less state, but I'm trying to show what's
possible here.  In fact, for this example it's probably easier to just
thread the state through the program directly, but bigger games want real
state, so I'm showing how to do that.

 data GuessS = GuessS
   { gsNumGuesses_ :: Int
   , gsTargetNumber_ :: Int
   }

 -- a real implementation wouldn't do it this way :)
 initialGameState :: GuessS
 initialGameState = GuessS undefined undefined

 gsNumGuesses, gsTargetNumber :: FRef GuessS Int
 gsNumGuesses   = FRef gsNumGuesses_   $ \a s - s { gsNumGuesses_   = a }
 gsTargetNumber = FRef gsTargetNumber_ $ \a s - s { gsTargetNumber_ = a }

Game monad with some useful helper functions

 type Game = StateT GuessS (Prompt GuessP)

 gPrint :: String - Game ()
 gPrint = prompt . Print

 gPrintLn :: String - Game ()
 gPrintLn s = gPrint (s ++ \n)

Implementation of the game:

 gameLoop :: Game Int
 gameLoop = do
update gsNumGuesses (+1)
guessNum - fetch gsNumGuesses
gPrint (Guess # ++ show guessNum ++ :)
guess - prompt Guess
answer - fetch gsTargetNumber

if guess == answer
  then do
gPrintLn Right!
return guessNum
  else do
gPrintLn $ concat
[ You guessed too 
, if guess  answer then low else high
, ! Try again.
]
gameLoop

 game :: Game ()
 game = do
gsNumGuesses =: 0
gsTargetNumber =: prompt GetNumber
gPrintLn I'm thinking of a number.  Try to guess it!
numGuesses - gameLoop
gPrintLn (It took you  ++ show numGuesses ++  guesses!)

Simple unwrapper for StateT that launches the game.

 runGame :: Monad m = (forall a. GuessP a - m a) - m ()
 runGame f = runPromptM f (evalStateT game initialGameState)

Here is the magic function for interacting with the player in IO.  Exercise
for the reader: make this more robust.

 gameIOPrompt :: GuessP a - IO a
 gameIOPrompt GetNumber = randomRIO (1, 100)
 gameIOPrompt (Print s) = putStr s
 gameIOPrompt Guess = fmap read getLine

If you wanted to add undo, all you have to do is save off the current Prompt
in the middle of runPromptM; you can return to the old state at any time.

 gameIO :: IO ()
 gameIO = do
 hSetBuffering stdout NoBuffering
 runGame gameIOPrompt

Here's a scripted version.

 type GameScript = State [Int]

 scriptPrompt :: Int - GuessP a - GameScript a
 scriptPrompt n GetNumber = return n
 scriptPrompt _ (Print _) = return ()
 scriptPrompt _ Guess = do
 (x:xs) - get -- fails if script runs out of answers
 put xs
 return x

 scriptTarget :: Int
 scriptTarget = 23
 scriptGuesses :: [Int]
 scriptGuesses = [50, 25, 12, 19, 22, 24, 23]

gameScript is True if the game ran to completion successfully, and False or
bottom otherwise.
Try adding or removing numbers from scriptGuesses above and re-running the
program.

 gameScript :: Bool
 gameScript = null $ execState (runGame (scriptPrompt scriptTarget))
scriptGuesses

 main = do
assert gameScript $ return ()
gameIO
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] unification would give infinite type

2007-12-04 Thread Rafael
Hi... I give this error using hugs for the code:

---
f = foldl (\x y - add x y) 0 [1,2,3]
add x y = return (x + y)
---
I try:

f = foldl (\x y - counter x y) (return 0) [1,2,3]

but it dont solve,  and with ghci:


Occurs check: cannot construct the infinite type: b = m b
  Expected type: b
  Inferred type: m b
In the expression: add x y
In a lambda abstraction: \ x y - add x y


thnks.

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


Re: [Haskell-cafe] unification would give infinite type

2007-12-04 Thread Emil Axelsson

Hi,

Depending on what you want, you should either remove 'return' or change to 
'foldM' (from Control.Monad). If you choose the latter, you also need to add a 
type signature to f (because of the monomorphism restriction).


/ Emil



On 2007-12-04 14:43, Rafael wrote:

Hi... I give this error using hugs for the code:

---
f = foldl (\x y - add x y) 0 [1,2,3]
add x y = return (x + y)
---
I try:

f = foldl (\x y - counter x y) (return 0) [1,2,3]

but it dont solve,  and with ghci:


Occurs check: cannot construct the infinite type: b = m b
  Expected type: b
  Inferred type: m b
In the expression: add x y
In a lambda abstraction: \ x y - add x y


thnks.

att
Rafael
___
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] unification would give infinite type

2007-12-04 Thread Mattias Bengtsson

Rafael skrev:

Hi... I give this error using hugs for the code:

---
f = foldl (\x y - add x y) 0 [1,2,3]
add x y = return (x + y)
---
I try:

f = foldl (\x y - counter x y) (return 0) [1,2,3]

but it dont solve,  and with ghci:


Occurs check: cannot construct the infinite type: b = m b
  Expected type: b
  Inferred type: m b
In the expression: add x y
In a lambda abstraction: \ x y - add x y
  
return isn't what you would expect it is if you come from an imperative 
programming background.
It might be a bit early in your haskell journey for this but return is 
one of the two most important functions in the Monad typeclass and not a 
language construct as in C and Java.

Anyhow, try this definition of add instead:
 add x y = x + y
or for short:
 add = (+)

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


Re: [Haskell-cafe] Array copying

2007-12-04 Thread Jules Bean

Andrew Coppin wrote:

Andrew Coppin wrote:
copy :: Word32 - IOUArray Word32 Bool - Word32 - IO (IOUArray 
Word32 Bool)

copy p grid size = do
 let size' = size * p
 grid' - newArray (1,size') False

 mapM_
   (\n - do
 b - readArray grid n
 if b
   then mapM_ (\x - writeArray grid' (n + size*x) True) [0..p-1]
   else return ()
   )
   [1..size]

 return grid'


Actually, thinking about this... for most kinds of arrays (whether boxed 
or unboxed, mutable or immutable) there's probably a more efficient way 
to copy the data then this. Maybe we should add something to the various 
array APIs to allow efficient copying of arrays / large chunks of arrays?


Ideally we'd have the compiler generate optimal code anyway, then you 
wouldn't need such things.


So, let's hope those compiler/optimiser guys keep working hard!

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


[Haskell-cafe] ghc overlapping instances

2007-12-04 Thread Steffen Mazanek
Hello,

I want to quickcheck a property on a datatype representing
programs (=[Stmt]) and need to define a specific instance

instance Arbitrary [Stmt]

(mainly to restrict the size of the list).

In quickcheck an instance Arbitrary of lists is already defined.
Which parameters do I have to give ghc such that it accepts
such an instance? In hugs -98 +o is enough. I have
tried -XOverlappingInstances, -XFlexibleInstances and also
-XIncoherentInstances, however I still got an overlapping
instances error for this declaration.

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


Re: [Haskell-cafe] unification would give infinite type

2007-12-04 Thread Rafael
Hi Emil,  I'm beginning in monad area...

I don't know about monomorphis restriction, but foldM works, a lot of thanks...
Matias tnks too, i'm conscious about return in the monadic chain.

thnks.

On Dec 4, 2007 12:00 PM, Emil Axelsson [EMAIL PROTECTED] wrote:
 Hi,

 Depending on what you want, you should either remove 'return' or change to
 'foldM' (from Control.Monad). If you choose the latter, you also need to add a
 type signature to f (because of the monomorphism restriction).

 / Emil




 On 2007-12-04 14:43, Rafael wrote:
  Hi... I give this error using hugs for the code:
 
  ---
  f = foldl (\x y - add x y) 0 [1,2,3]
  add x y = return (x + y)
  ---
  I try:
 
  f = foldl (\x y - counter x y) (return 0) [1,2,3]
 
  but it dont solve,  and with ghci:
 
  
  Occurs check: cannot construct the infinite type: b = m b
Expected type: b
Inferred type: m b
  In the expression: add x y
  In a lambda abstraction: \ x y - add x y
  
 
  thnks.
 
  att
  Rafael
  ___
  Haskell-Cafe mailing list
  Haskell-Cafe@haskell.org
  http://www.haskell.org/mailman/listinfo/haskell-cafe
 ___
 Haskell-Cafe mailing list
 Haskell-Cafe@haskell.org
 http://www.haskell.org/mailman/listinfo/haskell-cafe

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


[Haskell-cafe] Re: Haskell interface file (.hi) format?

2007-12-04 Thread Simon Marlow

Stefan O'Rear wrote:

On Sun, Dec 02, 2007 at 05:45:48AM +0100, Tomasz Zielonka wrote:

On Fri, Nov 30, 2007 at 08:55:51AM +, Neil Mitchell wrote:

Hi


  Prelude :b Control.Concurrent.MVar
  module 'Control.Concurrent.MVar' is not interpreted

:b now defaults to :breakpoint, you want :browse

That's a questionable decision, IMO:
- it changes behavior
- I expect :browse to be used more often, so it deserves the sort
  :b version (:bro is not that short)

On the other hand, this change can have an (unintended?) feature
advertising effect ;-)


It's not a decision at all.  :b is the first command starting with b,
which was browse yesterday, is breakpoint today, and tomorrow will be
something you've never heard of.  


Well, it wasn't quite that accidental.  I noticed that :b had changed, made 
a unilateral decision that :breakpoint was likely to be typed more often 
than :browse, and decided to leave it that way.



It's inherently fragile, and shouldn't
be relied on in scripts - and if :b does anything funny, spell out the
command!


FWIW, I wish we'd never implemented the first prefix match behaviour, 
unextensible as it is.  We could change it for 6.10...


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


Re: [Haskell-cafe] ghc overlapping instances

2007-12-04 Thread Isaac Dupree

Steffen Mazanek wrote:

Hello,

I want to quickcheck a property on a datatype representing
programs (=[Stmt]) and need to define a specific instance

instance Arbitrary [Stmt]

(mainly to restrict the size of the list).


you don't always need to use instances. for example, I have (where 
Predicate is a type I defined which I gave a separate normal Arbitrary 
instance)


arbpredicate :: Gen Predicate
arbpredicate = do ...

prop_assocUnify :: Property
prop_assocUnify =
 forAll arbpredicate $ \a -
 forAll arbpredicate $ \b -
 forAll arbpredicate $ \c - ...boolean result


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


Re: [Haskell-cafe] Advice for clean code.

2007-12-04 Thread Don Stewart
jules:
 Felipe Lessa wrote:
 On Dec 4, 2007 1:28 AM, Don Stewart [EMAIL PROTECTED] wrote:
 -- How to display results
 instance Show Action where
 show MoveOutOfBounds= Sorry you can't move in that 
 direction.
 show (MoveBadTerrain a) = case a of
   Wall  - You walk into a wall.
   Tree  - There is a tree in the 
   way.
   otherwise - You can't move there.
 show MoveOk = Good move.
 
 I always thought show was meant for returning a String that could be
 used to recreate the original data if you copy-pasted it in your code
 or if you used read (i.e. read . show == id). Reading the
 documentation more carefully, I see that [1] says that this property
 holds for *derived* instances, and says nothing about it in the
 general case.
 
 I would not write what dons wrote.
 
 I would have a custom function here rather than misusing Show in this 
 way; call it showMoveError or similar. For mostly the reasons Felipe gave.

Yes, this is considered bad practice in larger project (not so much in
little hacks), since read . show should hold, as should the 'paste'
property.

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


Re: [Haskell-cafe] An interesting monad: Prompt

2007-12-04 Thread Thomas Hartman
Thank you!

I really appreciate your explanation, and I hope this will enable me
to do some interesting and usefull stuff, in addition to firming up my
understanding of some of the more advanced haskell type system
features.

MACID is a sort of RDBMS replacement used as a backend by the HAppS
web framework.

To quote from http://www.haskell.org/communities/05-2007/html/report.html

Apps as Simple State Transformers

HAppS keeps your application development very simple. You represent
state with the Haskell data structure you find most natural for that
purpose. Your app then is just a set of state transformer functions
(in the MACID Monad) that take an event and state as input and that
evaluate to a new state, a response, and a (possibly null) set of
sideeffects.

It sounds great, but in practice it is not that simple to use, largely
because HAppS is in such a state of flux right now that even
installing the current codebase is pretty daunting.

However, I think a simple example of using MACID to guess a number
would be a great piece of documentation, and it might even be a step
towards using HAppS/MACID to easily do things other than serve web
apps. (HAppS is meant to be a general application serving framework,
but all the docu is oriented towards serving web pages, and even that
documentation is pretty shaky.)

What I ultimately would like to do is adapt this guess a number stuff
to HAppS/MACID so it is an example server for a multi-user console app
with this cool undo/replay/logging functionality which can then be
plugged into more sophisticated uses. Porting the console app to a web
app would be a further step. Hopefully, since all the state stuff has
been so meticulously compartmentalized it's easy and obvious how to do
this, just a matter of changing the IO to be outputting html rather
than console text. That is the HAppS tutorial I would like to see.

thomas.

2007/12/4, Ryan Ingram [EMAIL PROTECTED]:
 Ask and ye shall receive.  A simple guess-a-number game in MonadPrompt
 follows.

 But before I get to that, I have some comments:


 Serializing the state at arbitrary places is hard; the Prompt contains a
 continuation function so unless you have a way to serialize closures it
 seems like you lose.  But if you have safe points during the execution at
 which you know all relevant state is inside your game state, you can save
 there by serializing the state and providing a way to restart the
 computation at those safe points.

 I haven't looked at MACID at all; what's that?

  {-# LANGUAGE GADTs, RankNTypes #-}
  module Main where
  import Prompt
  import Control.Monad.State
  import System.Random (randomRIO)
  import System.IO
  import Control.Exception (assert)

 Minimalist functional references implementation.
 In particular, for this example, we skip the really interesting thing:
 composability.

 See http://luqui.org/blog/archives/2007/08/05/ for a real
 implementation.

  data FRef s a = FRef
{ frGet :: s - a
, frSet :: a - s - s
}

  fetch :: MonadState s m = FRef s a - m a
  fetch ref = get = return . frGet ref

  infix 1 =:
  infix 1 =:
  (=:) :: MonadState s m = FRef s a - a - m ()
  ref =: val = modify $ frSet ref val
  (=:) :: MonadState s m = FRef s a - m a - m ()
  ref =: act = act = modify . frSet ref
  update :: MonadState s m = FRef s a - (a - a) - m ()
  update ref f = fetch ref = \a - ref =: f a

 Interactions that a user can have with the game:

  data GuessP a where
 GetNumber :: GuessP Int
 Guess :: GuessP Int
 Print :: String - GuessP ()

 Game state.

 We could do this with a lot less state, but I'm trying to show what's
 possible here.  In fact, for this example it's probably easier to just
 thread the state through the program directly, but bigger games want real
 state, so I'm showing how to do that.

  data GuessS = GuessS
{ gsNumGuesses_ :: Int
, gsTargetNumber_ :: Int
}

  -- a real implementation wouldn't do it this way :)
  initialGameState :: GuessS
  initialGameState = GuessS undefined undefined

  gsNumGuesses, gsTargetNumber :: FRef GuessS Int
  gsNumGuesses   = FRef gsNumGuesses_   $ \a s - s { gsNumGuesses_   = a }
  gsTargetNumber = FRef gsTargetNumber_ $ \a s - s { gsTargetNumber_ = a }

 Game monad with some useful helper functions

  type Game = StateT GuessS (Prompt GuessP)

  gPrint :: String - Game ()
  gPrint = prompt . Print

  gPrintLn :: String - Game ()
  gPrintLn s = gPrint (s ++ \n)

 Implementation of the game:

  gameLoop :: Game Int
  gameLoop = do
 update gsNumGuesses (+1)
 guessNum - fetch gsNumGuesses
 gPrint (Guess # ++ show guessNum ++ :)
 guess - prompt Guess
 answer - fetch gsTargetNumber
 
 if guess == answer
   then do
 gPrintLn Right!
 return guessNum
   else do
 gPrintLn $ concat
 [ You guessed too 
 , if guess  answer then low else high
 , ! Try again.
 ]
 gameLoop

  game :: Game ()
  game 

[Haskell-cafe] isSpace

2007-12-04 Thread Ryan Bloor
hi
 
I am having trouble with a function that is supposed to eliminate spaces from 
the start of a String and return the resulting string. I reckon a dropWhile 
could be used but the isSpace bit is causing me problems...
 
words :: String - String
words a = case dropWhile isSpace a of
  - 
 s:ss - (s:word) : words rest
   where (word,rest) = break isSpace ss
 
 
Thanks
 
Ryan
_
The next generation of MSN Hotmail has arrived - Windows Live Hotmail
http://www.newhotmail.co.uk___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] foild function for expressions

2007-12-04 Thread Carlo Vivari



Brent Yorgey wrote:
 
 
 One comment: it looks like (add exp1 exp2), (and exp1 exp2) and so on
 above
 are not correct.  The second argument of foldExp is a value of type Exp,
 so
 you are pattern-matching on the constructors of Exp, and constructors are
 always uppercase.  Perhaps Exp has constructors named Add, And, and so on?
 Then you would want to do something like
 
 

Yepp, it's my fault I wasn't too precise in my explanation.
There's a declaration of the data type EXP,  which is not difficult to gess
with the things I've said:

data Exp = LitI Int
   |LitB Bool
   |Add Exp Exp
   |And Exp Exp
   |If Exp Exp Exp

I'm going to read carefully all of your answer now (thanks to all!!!), and
then I'll tell you. ;)


-- 
View this message in context: 
http://www.nabble.com/foild-function-for-expressions-tf4932877.html#a14155122
Sent from the Haskell - Haskell-Cafe mailing list archive at Nabble.com.

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


Re: [Haskell-cafe] Looking for smallest power of 2 = Integer

2007-12-04 Thread Steven Fodstad
Dan Piponi wrote:
 Is there anything in any of the interfaces to Integer that will allow
 me to quickly find the highest bit set in an Integer? If not, does
 anyone have any recommendations for how to do it efficiently. There
 are some obvious things that come to mind but which might involve
 quite a bit of useless copying of data internally by the
 implementation of Integer.
 --
 Dan
The subject line and your description disagree by 1 bit.  Take the
number 7: its binary representation would be 0111, with 0100 being the
highest bit, whereas the smallest power of 2 = 7 is 8, or 1000 in
binary.  And how do you want the results?  The place value of that
highest bit?  Or its index?

For the index, how about this:

truncate  . (/(log 2)) . log . fromIntegral

for the place value, just add an exponent function and another cast:

(2**) . fromIntegral . truncate  . (/(log 2)) . log . fromIntegral

If you want the smallest power of 2 = the integer, just change truncate
to ceiling.
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] isSpace

2007-12-04 Thread Brent Yorgey
On Dec 4, 2007 12:13 PM, Ryan Bloor [EMAIL PROTECTED] wrote:

 hi

 I am having trouble with a function that is supposed to eliminate spaces
 from the start of a String and return the resulting string. I reckon a
 dropWhile could be used but the isSpace bit is causing me problems...


You need to be more specific.  What trouble are you having?  What problems
is the isSpace bit causing?

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


Re: [Haskell-cafe] Looking for smallest power of 2 = Integer

2007-12-04 Thread David Benbennick
On Dec 4, 2007 9:21 AM, Steven Fodstad [EMAIL PROTECTED] wrote:
 For the index, how about this:

 truncate  . (/(log 2)) . log . fromIntegral

That will not work.  It will convert the Integer to Double, which will
overflow if the Integer is very large.
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] isSpace

2007-12-04 Thread Ryan Bloor
HI
 
I will try and explain it better. 
I am meaning to write a function that takes a string,  apple and 
eliminates the spaces at the start ONLY. called removeSpace :: String 
- String
 
I decided to use the function 'dropWhile' and another one 'isSpace' in the 
'removeSpace' function.
 
 removeSpace:: String - String removeSpace a = case dropWhile isSpace a of 
 - 
 
I get stuck here... I am not sure how to go about this function. 
 
Any ideas.
 
Ryan
 
_
The next generation of MSN Hotmail has arrived - Windows Live Hotmail
http://www.newhotmail.co.uk___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] isSpace

2007-12-04 Thread Brent Yorgey
On Dec 4, 2007 1:29 PM, Ryan Bloor [EMAIL PROTECTED] wrote:

 HI

 I will try and explain it better.
 I am meaning to write a function that takes a string,  apple and
 eliminates the spaces at the start ONLY. called removeSpace ::
 String - String

 I decided to use the function 'dropWhile' and another one 'isSpace' in the
 'removeSpace' function.

  removeSpace:: String - String
  removeSpace a = case dropWhile isSpace a of
   -



I am not sure why you think you need to do a case analysis here.  Think
about what 'dropWhile isSpace' does.

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


Re: [Haskell-cafe] ANN: Shu-thing 1.0 and Monadius 0.9

2007-12-04 Thread gwern0
On 2007.12.04 12:12:04 +, Neil Bartlett [EMAIL PROTECTED] scribbled 2.2K 
characters:
 Hi Gwern,

 Shu-thing is great fun!

 I think Monadius isn't compiling because most of the source files are
 missing; you only have Main.hs in there.

 Regards
 Neil

Oh - you're absolutely right. For some reason, cabal's sdist didn't include all 
the files. Weird.

But I think I've fixed it:
*http://hackage.haskell.org/cgi-bin/hackage-scripts/package/Monadius-0.9.20071204

Looking at the contents of the tar ball, it now seems to have everything, and 
Monadius does indeed successfully 'cabal install Monadius'.

Sorry everyone!

--
gwern


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


Re: [Haskell-cafe] isSpace

2007-12-04 Thread Thomas Hartman
look at the examples of dropWhile usage you got from the first result
when you get when you google on dropWhile.

t.

2007/12/4, Ryan Bloor [EMAIL PROTECTED]:

 HI

  I will try and explain it better.
  I am meaning to write a function that takes a string,  apple and
 eliminates the spaces at the start ONLY. called removeSpace ::
 String - String

  I decided to use the function 'dropWhile' and another one 'isSpace' in the
 'removeSpace' function.

   removeSpace:: String - String
  removeSpace a = case dropWhile isSpace a of
   -

  I get stuck here... I am not sure how to go about this function.

  Any ideas.

  Ryan


 
 Can you guess the film? Search Charades!
 ___
 Haskell-Cafe mailing list
 Haskell-Cafe@haskell.org
 http://www.haskell.org/mailman/listinfo/haskell-cafe


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


[Haskell-cafe] Re: Nofib modifications

2007-12-04 Thread Neil Mitchell
Hi

 I'd do something like

 #if defined(__nhc98__) || defined(YHC)
 #define NO_MONOMORPHISM_RESTRICTION
 #endif

 #ifdef NO_MONOMORPHISM_RESTRICTION
 powers :: [[Integer]]
 #endif

 just to make it quite clear what's going on.  (good comments would do just
 as well).

I'd rather avoid CPP, as Hugs doesn't have CPP by default (certainly
on Windows), so it would make it a little harder to run with Hugs.

I am happy to write comments such as:

-- only required for compilers that fail to correctly implement the
monomorphism restriction

Thanks

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


Re: [Haskell-cafe] Looking for largest power of 2 = Integer

2007-12-04 Thread Dan Piponi
On Dec 3, 2007 10:05 PM, David Benbennick [EMAIL PROTECTED] wrote:

 Could you please post your code here when you're done?  I'd be
 interested to see the final result.

This is just experimental code I'm playing with in order to implement
exact real arithmetic, so there'll never be a final result :-) But
this is what I'm currently playing with. It's hard-coded for a
platform with 64 bit Ints and 64 bit limbs of Integers. This is my
first ever foray into the binary underbelly of Haskell, using
information from
http://www.haskell.org/ghc/docs/4.06/users_guide/ghc-libs-ghc.html,
and I've probably written this code really stupidly.

import GHC.Exts
import Data.Bits

fastTestBit :: Integer - Int - Bool
fastTestBit n i = case n of
S# m - testBit (I# m) i
J# l d - let I# w = shiftR i 6
  b = i .. 63
   in testBit (I# (indexIntArray# d w)) b

-- Assumes n/=0
topBit :: Integer - Int
topBit n = case n of
S# m - topBit' n 63
J# l _ - topBit' n (64*I# l-1)
where
topBit' n i = if fastTestBit n i then i else topBit' n (i-1)

I don't need something super-fast (ie. clever bit twiddling tricks),
just something not stupidly slow. Despite what dons says, testBit is
stupidly slow :-) fastTestbit takes microseconds instead of seconds on
2^1000. Maybe a portable tidied up version of fastTestBit ought to
go into Data.Bits. These kinds of operations are ubiquitous in
numerical algorithms.

And note the fixed title :-)
--
Dan
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] foild function for expressions

2007-12-04 Thread David Menendez
On Dec 3, 2007 12:18 PM, Carlo Vivari [EMAIL PROTECTED] wrote:


 Hi! I'm a begginer in haskell and I have a problem with an exercise, I
 expect
 someone could help me:

 In one hand I have a declaration of an algebra data, like this:

 data AlgExp a = AlgExp
 { litI  :: Int - a,
   litB :: Bool - a,
   add :: a - a - a,
   and :: a - a - a,
   ifte :: a - a - a - a}

 (being ifte an 'ifthenelse' expresion...)

 What I want to do is to write a fold function for expressions, something
 like this:

 foldExp :: AlgExp a - Exp - a
 foldExp alg (LitI i) = litI alg i
 foldExp alg (LitB i) = litB alg i
 foldExp alg (add exp1 exp2) = ¿¿¿???
 foldExp alg (and exp1 exp2) = ¿¿¿???
 foldExp alg (ifte exp1 exp2 exp3) = ¿¿¿???


You'll want something like this:

foldExp alg (Add e1 e2) = add alg (foldExp alg e1) (foldExp alg e2)


-- 
Dave Menendez [EMAIL PROTECTED]
http://www.eyrie.org/~zednenem/
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] foild function for expressions

2007-12-04 Thread Carlo Vivari

Yes,as  I said before to other of you
the exp data type was also declared in the exercise (my fault not to say
it), and look as this:

data Exp = LitI Int 
   |LitB Bool 
   |Add Exp Exp 
   |And Exp Exp 
   |If Exp Exp Exp 

-- 
View this message in context: 
http://www.nabble.com/foild-function-for-expressions-tf4932877.html#a14158061
Sent from the Haskell - Haskell-Cafe mailing list archive at Nabble.com.

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


Re: [Haskell-cafe] Looking for largest power of 2 = Integer

2007-12-04 Thread Don Stewart
dpiponi:
 On Dec 3, 2007 10:05 PM, David Benbennick [EMAIL PROTECTED] wrote:
 
  Could you please post your code here when you're done?  I'd be
  interested to see the final result.
 
 This is just experimental code I'm playing with in order to implement
 exact real arithmetic, so there'll never be a final result :-) But
 this is what I'm currently playing with. It's hard-coded for a
 platform with 64 bit Ints and 64 bit limbs of Integers. This is my
 first ever foray into the binary underbelly of Haskell, using
 information from
 http://www.haskell.org/ghc/docs/4.06/users_guide/ghc-libs-ghc.html,
 and I've probably written this code really stupidly.
 
 import GHC.Exts
 import Data.Bits
 
 fastTestBit :: Integer - Int - Bool
 fastTestBit n i = case n of
 S# m - testBit (I# m) i
 J# l d - let I# w = shiftR i 6
   b = i .. 63
in testBit (I# (indexIntArray# d w)) b
 
 -- Assumes n/=0
 topBit :: Integer - Int
 topBit n = case n of
 S# m - topBit' n 63
 J# l _ - topBit' n (64*I# l-1)
 where
 topBit' n i = if fastTestBit n i then i else topBit' n (i-1)
 
 I don't need something super-fast (ie. clever bit twiddling tricks),
 just something not stupidly slow. Despite what dons says, testBit is
 stupidly slow :-) fastTestbit takes microseconds instead of seconds on
 2^1000. Maybe a portable tidied up version of fastTestBit ought to
 go into Data.Bits. These kinds of operations are ubiquitous in
 numerical algorithms.

Awesome. We can use this in Data.Bits, if you've got some QuickChecks
for it. 

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


[Haskell-cafe] Re: [Haskell] IVar

2007-12-04 Thread Isaac Dupree


A pure readIVar would be just like lazy I/O, with similar drawbacks.  
With readIVar, the effect that lets you observe the evaluation order 
is writeIVar; with hGetContents it is hClose.  Conclusion: it's 
probably no worse than lazy I/O.


Actually, it's considerably better.


+: implementation may not evaluate something that may terminate/block, 
anyway


IVar may change from blocking to non-blocking, unlike most pure 
expressions.  This is only meaningful if trying to evaluate it would 
prevent it from gaining a value.  It can only have such an effect 
(helping the IVar gain a value) if the same thread would do any IO (if 
it wasn't for the unnecessary evaluation).  IO is generally observable, 
so getting stuck on a normal non-terminating expression wouldn't be any 
more acceptable than getting stuck on an IVar in that case.


... all assuming unsafeInterleaveIO doesn't exist, because it's unsafe, 
so the semantics are undefined of when it gets evaluated relative to 
later normally-sequenced IO actions, if it will be eventually evaluated 
for sure -- right?  Nevertheless its intended use generally assumes that 
it will be evaluated as if its evaluation might not terminate, i.e. as 
late as possible.  If it is in fact (a finite amount of) non-blocking 
IO, then evaluating it early will only have consequences on when the IO 
happens (and therefore its effect/result), not directly on the program's 
non-termination or actions.


It gets more confusing the more I think about it!


to modify Simon's example, it looks to me like treating readIVar as 
potentially non-terminating, and writeIVar as potentially having 
side-effects, is enough:


main = do
--irrelevant  x - newIVar
let y = last [1..]
print test  --was irrelevant  writeIVar x 3
print y

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


[Haskell-cafe] NY Functional Programmers Network: F# Talk by Don Syme, Monday De cember 10th at 7pm

2007-12-04 Thread Mansell, Howard
Credit Suisse will be hosting a talk by Don Syme from Microsoft Research on 
Monday December 10th.  He will talk about F# and Microsoft's plans for it.

This talk is arranged by the New York Functional Programmers Network, a group 
of individuals in the New York area who are interested in functional 
programming.  Many of us also use functional programming in our work life.  
Despite the URL below, we are typically interested in statically typed 
functional languages.

If you are interested in coming, please RSVP at the meetup site below:
http://lisp.meetup.com/59/ http://lisp.meetup.com/59/  

Regards
Howard Mansell
Global Modelling  Analytics Group
Credit Suisse

==
Please access the attached hyperlink for an important electronic communications 
disclaimer: 

http://www.credit-suisse.com/legal/en/disclaimer_email_ib.html
==
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] RFI: Link errors with random pkg on 6.8.1

2007-12-04 Thread Jim Stuttard

Hi,
Getting same error in 2 diff. apps
* built with ghc-6.8.1.
* random-1.0.0.0 also built with 6.8.1
* random-1.0.0.0 is registered

# HAppS
-6.8.1/lib/random-1.0.0.0/HSrandom-1.0.0.0.o: unknown symbol 
`oldzmtimezm1zi0zi0zi0_SystemziTime_a99_info'

ghc-6.8.1: unable to load package `random-1.0.0.0'
# Haskell$ ghci DonsGame-0.1.hs
GHCi, version 6.8.1: http://www.haskell.org/ghc/  :? for help
Loading package base ... linking ... done.
[1 of 1] Compiling Game ( DonsGame-0.1.hs, interpreted )
Ok, modules loaded: Game.
*Game main
Loading package old-locale-1.0.0.0 ... linking ... done.
Loading package old-time-1.0.0.0 ... linking ... done.
Loading package filepath-1.1.0.0 ... linking ... done.
Loading package directory-1.0.0.0 ... linking ... done.
Loading package unix-2.2.0.0 ... linking ... done.
Loading package process-1.0.0.0 ... linking ... done.
Loading package random-1.0.0.0 ... linking ... interactive: 
/usr/local/lib/ghc-6.8.1/lib/random-1.0.0.0/HSrandom-1.0.0.0.o: unknown 
symbol `oldzmtimezm1zi0zi0zi0_SystemziTime_a99_info'

ghc-6.8.1: unable to load package `random-1.0.0.0'

# ubuntu gutsy  2.6.22-14-server #1 SMP Sun Oct 14 23:34:23 GMT 2007 
i686 GNU/Linux



Jim

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


Re: [Haskell-cafe] Looking for smallest power of 2 = Integer

2007-12-04 Thread Conal Elliott
Whatever the answer is, I expect it's relevant to Data.IntSet, which uses
big-endian patricia trees.  - Conal

On Dec 3, 2007 8:36 PM, Dan Piponi [EMAIL PROTECTED]  wrote:

 Is there anything in any of the interfaces to Integer that will allow
 me to quickly find the highest bit set in an Integer? If not, does
 anyone have any recommendations for how to do it efficiently. There
 are some obvious things that come to mind but which might involve
 quite a bit of useless copying of data internally by the
 implementation of Integer.
 --
 Dan
 ___
 Haskell-Cafe mailing list
 Haskell-Cafe@haskell.org
 http://www.haskell.org/mailman/listinfo/haskell-cafe

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


[Haskell-cafe] Re: [Haskell] Nested guards?

2007-12-04 Thread Neil Mitchell
Hi

 server text
| Just xs - parse text = let
  x | field1 `elem` xs   = error ... do one thing ...
| field2 `elem` xs   = error ... do something else ...
  in x
 server  _ = error ... invalid request ...

This now has the wrong semantics - before if parse text returned Just
[] the error invalid request branch was invoked, now its a pattern
match failure.

I haven't used pattern guards that much (but will once Haskell'
standardises them, or they get implemented in Hugs!), but their syntax
seems quite natural. This extension seems to make it harder to
understand them, and gives some nasty , | parsing issues for a human
at least - quite possibly for a compiler too. Perhaps if you gave a
little grammar for extended pattern guards (compared to the original)
it would be easier to see how naturally they fit in.

Thanks

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


Re: [Haskell-cafe] Re: [Haskell] IVar

2007-12-04 Thread Conal Elliott
 main = do
 --irrelevant  x - newIVar
 let y = last [1..]
 print test  --was irrelevant  writeIVar x 3
 print y

Exactly.  The termination concern doesn't seem to have to do with readIVar.

On Dec 4, 2007 11:56 AM, Isaac Dupree [EMAIL PROTECTED] wrote:


  A pure readIVar would be just like lazy I/O, with similar drawbacks.
  With readIVar, the effect that lets you observe the evaluation order
  is writeIVar; with hGetContents it is hClose.  Conclusion: it's
  probably no worse than lazy I/O.
 
  Actually, it's considerably better.

 +: implementation may not evaluate something that may terminate/block,
 anyway

 IVar may change from blocking to non-blocking, unlike most pure
 expressions.  This is only meaningful if trying to evaluate it would
 prevent it from gaining a value.  It can only have such an effect
 (helping the IVar gain a value) if the same thread would do any IO (if
 it wasn't for the unnecessary evaluation).  IO is generally observable,
 so getting stuck on a normal non-terminating expression wouldn't be any
 more acceptable than getting stuck on an IVar in that case.

 ... all assuming unsafeInterleaveIO doesn't exist, because it's unsafe,
 so the semantics are undefined of when it gets evaluated relative to
 later normally-sequenced IO actions, if it will be eventually evaluated
 for sure -- right?  Nevertheless its intended use generally assumes that
 it will be evaluated as if its evaluation might not terminate, i.e. as
 late as possible.  If it is in fact (a finite amount of) non-blocking
 IO, then evaluating it early will only have consequences on when the IO
 happens (and therefore its effect/result), not directly on the program's
 non-termination or actions.

 It gets more confusing the more I think about it!


 to modify Simon's example, it looks to me like treating readIVar as
 potentially non-terminating, and writeIVar as potentially having
 side-effects, is enough:

 main = do
 --irrelevant  x - newIVar
 let y = last [1..]
 print test  --was irrelevant  writeIVar x 3
 print y

 Isaac
 ___
 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] Why is this strict in its arguments?

2007-12-04 Thread Paulo J. Matos
Hello all,

As you might have possibly read in some previous blog posts:
http://users.ecs.soton.ac.uk/pocm06r/fpsig/?p=10
http://users.ecs.soton.ac.uk/pocm06r/fpsig/?p=11

we (the FPSIG group) defined:
data BTree a = Leaf a
   | Branch (BTree a) a (BTree a)

and a function that returns a list of all the paths (which are lists
of node values) where each path element makes the predicate true.
findAllPath :: (a - Bool) - (BTree a) - Maybe [[a]]
findAllPath pred (Leaf l) | pred l = Just [[l]]
  | otherwise = Nothing
findAllPath pred (Branch lf r rt) | pred r = let lfpaths = findAllPath pred lf
 rtpaths = findAllPath pred rt
 in
   if isNothing lfpaths 
isNothing rtpaths
   then Nothing
   else
   if isNothing lfpaths
   then Just (map (r:)
$ fromJust rtpaths)
   else
   if isNothing rtpaths
   then Just (map
(r:) $ fromJust lfpaths)
   else Just (map
(r:) $ fromJust rtpaths ++ fromJust lfpaths)
  | otherwise = Nothing

Later on we noticed that this could be simply written as:
findAllPath :: (a - Bool) - (BTree a) - [[a]]
  findAllPath pred = g where
  g (Leaf l) | pred l = [[l]]
  g (Branch lf r rt) | pred r = map (r:) $ (findAllPath pred
lf) ++ (findAllPath pred rt)
  g _  = []

without even using maybe. However, 2 questions remained:
1 - why is the first version strict in its arguments?
2 - if it really is strict in its arguments, is there any automated
way to know when a function is strict in its arguments?

Cheers,

-- 
Paulo Jorge Matos - pocm at soton.ac.uk
http://www.personal.soton.ac.uk/pocm
PhD Student @ ECS
University of Southampton, UK
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Looking for largest power of 2 = Integer

2007-12-04 Thread David Benbennick
On Dec 4, 2007 11:51 AM, Don Stewart [EMAIL PROTECTED] wrote:
 Awesome. We can use this in Data.Bits, if you've got some QuickChecks
 for it.

Hear hear.  But is there any way to just make the compiler use
fastTestBit in place of testBit :: (Bits a) = a - Int - Bool when a
= Integer?  (That is, without having to introduce a new function to
the public interface of Data.Bits.)  Some kind of SPECIALIZE pragma,
perhaps?

I've attached a program with two QuickCheck properties.  Unfortunately
they fail on negative Integers.  I can't figure out why.
{-# OPTIONS_GHC -fglasgow-exts #-}

module Main where

import Test.QuickCheck
import Data.Bits
import GHC.Exts

fastTestBit :: Integer - Int - Bool
fastTestBit n i = case n of
   S# m - testBit (I# m) i
   J# l d - let I# w = shiftR i 6
 b = i .. 63
 in testBit (I# (indexIntArray# d w)) b

prop_testBit1 :: Integer - Int - Bool
prop_testBit1 i n = testBit i n == fastTestBit i n

-- Test fastTestBit on large Integers
prop_testBit2 :: Integer - Int - Int - Bool
prop_testBit2 i j n = testBit k n == fastTestBit k n where k = i ^ (abs j)

main = do
  putStrLn Testing prop_testBit1:
  quickCheck prop_testBit1
  putStrLn Testing prop_testBit2:
  quickCheck prop_testBit2
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Looking for largest power of 2 = Integer

2007-12-04 Thread Don Stewart
dbenbenn:
 On Dec 4, 2007 11:51 AM, Don Stewart [EMAIL PROTECTED] wrote:
  Awesome. We can use this in Data.Bits, if you've got some QuickChecks
  for it.
 
 Hear hear.  But is there any way to just make the compiler use
 fastTestBit in place of testBit :: (Bits a) = a - Int - Bool when a
 = Integer?  (That is, without having to introduce a new function to
 the public interface of Data.Bits.)  Some kind of SPECIALIZE pragma,
 perhaps?

{-# RULES
Integer fastTestBit forall x n.
testBit x n = fastTestBit :: Integer - Int - Bool
 #-}

I think should work. If testBit is in the Bits class though, we can just
add it for instance Bits Integer

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


Re: [Haskell-cafe] ghc overlapping instances

2007-12-04 Thread Stefan O'Rear
On Tue, Dec 04, 2007 at 03:36:20PM +0100, Steffen Mazanek wrote:
 Hello,
 
 I want to quickcheck a property on a datatype representing
 programs (=[Stmt]) and need to define a specific instance
 
 instance Arbitrary [Stmt]
 
 (mainly to restrict the size of the list).
 
 In quickcheck an instance Arbitrary of lists is already defined.
 Which parameters do I have to give ghc such that it accepts
 such an instance? In hugs -98 +o is enough. I have
 tried -XOverlappingInstances, -XFlexibleInstances and also
 -XIncoherentInstances, however I still got an overlapping
 instances error for this declaration.

You shouldn't use lists if you need to have special instance behavior -
lists are for perfectly ordinary sequences of things.  If a program is
just a bunch of unrelated statements, then use [], otherwise use a
custom (new)type.

Stefan


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


[Haskell-cafe] Re: [Haskell] Nested guards?

2007-12-04 Thread Roberto Zunino
Neil Mitchell wrote:
 server text
| Just xs - parse text = let
  x | field1 `elem` xs   = error ... do one thing ...
| field2 `elem` xs   = error ... do something else ...
  in x
 server  _ = error ... invalid request ...
 
 This now has the wrong semantics - before if parse text returned Just
 [] the error invalid request branch was invoked, now its a pattern
 match failure.

I missed that, thanks.

The MonadPlus way is not as elegant, but not too ugly I think:

server text =
  do   Just xs - return $ parse text
   do   guard $ field1 `elem` xs
return ... do one thing ...
 `mplus` do
guard $ field2 `elem` xs
return ... do something else ...
`mplus`
   return ... invalid request ...

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


Re: [Haskell-cafe] isSpace

2007-12-04 Thread Stefan O'Rear
On Tue, Dec 04, 2007 at 05:13:19PM +, Ryan Bloor wrote:
 hi
  
 I am having trouble with a function that is supposed to eliminate spaces from 
 the start of a String and return the resulting string. I reckon a dropWhile 
 could be used but the isSpace bit is causing me problems...
  
 words :: String - String
 words a = case dropWhile isSpace a of
   - 
  s:ss - (s:word) : words rest
where (word,rest) = break isSpace ss

You might want to write the code for the first case; an expression is
mandatory after -.

Stefan


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


Re: [Haskell-cafe] Why is this strict in its arguments?

2007-12-04 Thread Neil Mitchell
Hi

 findAllPath :: (a - Bool) - (BTree a) - [[a]]
   findAllPath pred = g where
   g (Leaf l) | pred l = [[l]]
   g (Branch lf r rt) | pred r = map (r:) $ (findAllPath pred
 lf) ++ (findAllPath pred rt)
   g _  = []

 without even using maybe. However, 2 questions remained:
 1 - why is the first version strict in its arguments?

Because in all call paths findAllPath will call g with its second
argument. g will always evaluate (by pattern matching on) its value
argument.

 2 - if it really is strict in its arguments, is there any automated
 way to know when a function is strict in its arguments?

Yes, strictness analysis is a very well studied subject -
http://haskell.org/haskellwiki/Research_papers/Compilation#Strictness
. Essentially, an argument is strict if passing _|_ for that value
results in _|_. So to take your example, evaluating:

findAllPath a _|_
g _|_
_|_

Since g tests what value _|_ has, we get bottom.

Thanks

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


Re: [Haskell-cafe] Why is this strict in its arguments?

2007-12-04 Thread Roberto Zunino
Neil Mitchell wrote:
 is there any automated
 way to know when a function is strict in its arguments?
 
 Yes, strictness analysis is a very well studied subject -

...and is undecidable, in general. ;-)

Zun.


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


Re: [Haskell-cafe] Why is this strict in its arguments?

2007-12-04 Thread Stefan O'Rear
On Tue, Dec 04, 2007 at 09:41:36PM +, Paulo J. Matos wrote:
 Hello all,
 
 As you might have possibly read in some previous blog posts:
 http://users.ecs.soton.ac.uk/pocm06r/fpsig/?p=10
 http://users.ecs.soton.ac.uk/pocm06r/fpsig/?p=11
 
 we (the FPSIG group) defined:
 data BTree a = Leaf a
| Branch (BTree a) a (BTree a)
 
 and a function that returns a list of all the paths (which are lists
 of node values) where each path element makes the predicate true.
 findAllPath :: (a - Bool) - (BTree a) - Maybe [[a]]
 findAllPath pred (Leaf l) | pred l = Just [[l]]
   | otherwise = Nothing
 findAllPath pred (Branch lf r rt) | pred r = let lfpaths = findAllPath pred lf
  rtpaths = findAllPath pred rt
  in
if isNothing lfpaths 
 isNothing rtpaths
then Nothing
else
if isNothing lfpaths
then Just (map (r:)
 $ fromJust rtpaths)
else
if isNothing rtpaths
then Just (map
 (r:) $ fromJust lfpaths)
else Just (map
 (r:) $ fromJust rtpaths ++ fromJust lfpaths)
   | otherwise = Nothing
 
 Later on we noticed that this could be simply written as:
 findAllPath :: (a - Bool) - (BTree a) - [[a]]
   findAllPath pred = g where
   g (Leaf l) | pred l = [[l]]
   g (Branch lf r rt) | pred r = map (r:) $ (findAllPath pred
 lf) ++ (findAllPath pred rt)
   g _  = []
 
 without even using maybe. However, 2 questions remained:
 1 - why is the first version strict in its arguments?

Because of the definition of strictness.  A function is strict iff f
undefined = undefined.

findAllPath pred undefined - undefined because of the case analysis
findAllPath undefined (Leaf _) - undefined because pred is applied in
  the guard
findAllPath undefined Branch{} - undefined because pred is applied in
  the guard

 2 - if it really is strict in its arguments, is there any automated
 way to know when a function is strict in its arguments?

No, because this is in general equivalent to the halting problem:

f _ = head [ i | i - [1,3.], i == sum [ k | k - [1..i-1], i `mod` k == 0 ] ]

f is strict iff there do not exist odd perfect numbers.

However, fairly good conservative approximations exist, for instance in
the GHC optimizer - compile your code with -ddump-simpl to see (among
other things) a dump of the strictness properties determined.  (use -O,
of course)

Stefan


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


[Haskell-cafe] when I am rebuilding a package that has package dependencies

2007-12-04 Thread Galchin Vasili
Hello,

Which document discusses how to first build all dependencies and then
finally the target package? I prefer to read relevant documentation so I get
fully up to speed  rather than take up bandwidth on this newsgroup asking
one question at a time.

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


Re: [Haskell-cafe] Looking for largest power of 2 = Integer

2007-12-04 Thread Dan Piponi
There's a bit of work required to make this code good enough for
general consumption, and I don't know much about Haskell internals.

(1) What is the official way to find the size of a word? A quick
look at 6.8.1's base/GHC/Num.lhs reveals that it uses a #defined
symbol.

(2) Is it safe to assume an underlying implementation based on GMP?
(In Num.lhs there is an alternative definition for .NET. Is that ever
used?) Is it safe to assume the size of a GMP limb is the same as
the word size? (I'm assuming it is for now.)

David said:

 I've attached a program with two QuickCheck properties.  Unfortunately
 they fail on negative Integers.  I can't figure out why.

Judging by Num.lhs, the sign of the Integer is stored as the sign of
the length of the Integer in limbs. The code needs to deal with that
explicitly, as well as doing some bounds checking on the index.

Anyway, if someone can help with those questions I can try to write a
bulletproof version of the code.
--
Dan
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] Re: Looking for smallest power of 2 = Integer

2007-12-04 Thread ChrisK
Sterling Clover wrote:
 Actually, I suspect GHC's strictness analyzer will give you reasonable
 performance with even the naive version, but fancier ideas are at
 http://graphics.stanford.edu/~seander/bithacks.html#IntegerLog
 

If given an 'n' you are looking for the (2^x) such that 2^x = n  2^(x-1)
then you could use the method at
http://graphics.stanford.edu/~seander/bithacks.html#RoundUpPowerOf2

This does not return 'x', it returns the integer '2^x' instead.

Here is my contribution:

 import Data.Bits
 
 -- Takes input Integer =0 
 -- let p = roundUpPower2 r
 -- in assert ( ((r==0)  (p==1))
 --  || (r0)  (p=r)  (p2*r)
 --  || (r0)  (p=r)  (2*pr)
 -- This function is good for p == 2^x where x :: Int
 -- and will fail when abs(r) is greater than about 2^(maxBound::Int)
 --
 -- Other policies for r0 are possible.
 roundUpPower2 :: Integer - Integer
 roundUpPower2 r =
   case compare r 0 of
 LT - let p' = negate (roundUpPower2 (negate r))
   in if p' == r then p' else p' `div` 2
 EQ - 1
 GT - shifting (pred r) 1
  where
   shifting !v !k | sv == 0 = succ v
  | otherwise = shifting (v .|. sv) (shiftL k 1)
 where sv = shiftR v k
 
 test = map (\r - (r,roundUpPower2 r)) [-17..17]
 
 check (r,p) = ((r==0)  (p==1)) 
   || (r0)  (p=r)  (p2*r)
   || (r0)  (p=r)  (2*pr)
 
 main = do mapM_ print test
   print (all check test)
 

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


[Haskell-cafe] Clean Dynamics and serializing code to disk

2007-12-04 Thread gwern0
Hey everyone; recently I've been toying around with various methods of writing 
a shell and reading the academic literature on such things. The best prior art 
on the subject seems to be the ESTHER shell (see 
http://citeseer.ist.psu.edu/689593.html, 
http://citeseer.ist.psu.edu/744494.html, 
ftp://ftp.cs.kun.nl/pub/Clean/papers/2003/vWeA2003-Esther.pdf).

Now, ESTHER is a really cool looking shell, but it has two main problems for me:
1) Source doesn't seem to be available anywhere online
2) It's written in Clean and not Haskell

No problem. All the hard stuff is done, and there's like a good 50 pages of 
documentation, so how hard could it be? Clean is practically Haskell anyway.

But immediately I ran into a road-block:

 The shell is built on top of Clean's hybrid static/dynamic type system and 
its dynamic I/O run-time support. It allows programmers to save any Clean 
expression, i.e a graph that can contain data, references to functions, and 
closures to disk. Clean expressions can be written to disk as a _dynamic_, 
which contains a representation of their (polymorphic) static type, while 
preserving sharing. Clean programs can load dynamics from disk and use run-time 
type pattern matching to reintegrate it into the statically-typed program.

The Data.Dynamic library seems to do everything as far as dynamic types and 
run-time pattern matching goes, but I haven't figured out how one could write 
Haskell expressions to disk, like Clean's system 
http://www.st.cs.ru.nl/papers/2002/verm2002-LazyDynamicIO.ps.gz apparently 
allows.

Does anyone know if there are any neat or tricky ways this could be done? 
Projects, extensions, whatever?

On #haskell, quicksilver did tell me of one neat way to serialize various stuff 
through Data.Binary by using ADTs along the lines of the following simple 
example:

--

module Main (main)
where
import Data.Binary
data Math = Add | Subtract | Multiply
deriving Show

eval :: (Num a) = Math - a - a - a
eval f = case f of
   Add - (+)
   Subtract - (-)
   Multiply - (*)

instance Binary Math where
  put Add = putWord8 0
  put Subtract = putWord8 1
  put Multiply = putWord8 2
  get = do tag_ - getWord8
   case tag_ of
 0 - return Add
 1 - return Subtract
 2 - return Multiply


main = do encodeFile tmp.s [Add, Subtract, Multiply]
  a - decodeFile tmp.s
  putStr $ show (a :: [Math])

--

Since from my Lisp days I know that code is data, it strikes me that one could 
probably somehow smuggle Haskell expressions via this route although I am not 
sure this is a good way to go or even how one would do it (to turn, say, a list 
of the chosen ADT back into real functions, you need the 'eval' function, but 
apparently eval can only produce functions of the same type - so you'd need to 
either create as many adts and instances as there are varieties of type 
signatures in Haskell '98 and the libraries, I guess, or somehow encode in a 
lambda calculus). Is that a route worth pursuing?

--
gwern


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


Re: [Haskell-cafe] Why is this strict in its arguments?

2007-12-04 Thread Ryan Ingram
Is there a reason why strictness is defined as
 f _|_ = _|_

instead of, for example,
 forall x :: Exception. f (throw x) = throw x
where an exception thrown from pure code is observable in IO.

In the second case we need to prove that the argument is evaluated at some
point, which is also equivalent to the halting problem but more captures the
notion of f evaluates its argument rather than either f evaluates its
argument, or f _ is _|_

I suppose the first case allows us to do more eager evaluation; but are
there a lot of cases where that matters?

  -- ryan

On 12/4/07, Stefan O'Rear [EMAIL PROTECTED] wrote:

 On Tue, Dec 04, 2007 at 09:41:36PM +, Paulo J. Matos wrote:
  Hello all,
 
  As you might have possibly read in some previous blog posts:
  http://users.ecs.soton.ac.uk/pocm06r/fpsig/?p=10
  http://users.ecs.soton.ac.uk/pocm06r/fpsig/?p=11
 
  we (the FPSIG group) defined:
  data BTree a = Leaf a
 | Branch (BTree a) a (BTree a)
 
  and a function that returns a list of all the paths (which are lists
  of node values) where each path element makes the predicate true.
  findAllPath :: (a - Bool) - (BTree a) - Maybe [[a]]
  findAllPath pred (Leaf l) | pred l = Just [[l]]
| otherwise = Nothing
  findAllPath pred (Branch lf r rt) | pred r = let lfpaths = findAllPath
 pred lf
   rtpaths = findAllPath
 pred rt
   in
 if isNothing lfpaths 
  isNothing rtpaths
 then Nothing
 else
 if isNothing lfpaths
 then Just (map (r:)
  $ fromJust rtpaths)
 else
 if isNothing
 rtpaths
 then Just (map
  (r:) $ fromJust lfpaths)
 else Just (map
  (r:) $ fromJust rtpaths ++ fromJust lfpaths)
| otherwise = Nothing
 
  Later on we noticed that this could be simply written as:
  findAllPath :: (a - Bool) - (BTree a) - [[a]]
findAllPath pred = g where
g (Leaf l) | pred l = [[l]]
g (Branch lf r rt) | pred r = map (r:) $ (findAllPath pred
  lf) ++ (findAllPath pred rt)
g _  = []
 
  without even using maybe. However, 2 questions remained:
  1 - why is the first version strict in its arguments?

 Because of the definition of strictness.  A function is strict iff f
 undefined = undefined.

 findAllPath pred undefined - undefined because of the case analysis
 findAllPath undefined (Leaf _) - undefined because pred is applied in
  the guard
 findAllPath undefined Branch{} - undefined because pred is applied in
  the guard

  2 - if it really is strict in its arguments, is there any automated
  way to know when a function is strict in its arguments?

 No, because this is in general equivalent to the halting problem:

 f _ = head [ i | i - [1,3.], i == sum [ k | k - [1..i-1], i `mod` k == 0
 ] ]

 f is strict iff there do not exist odd perfect numbers.

 However, fairly good conservative approximations exist, for instance in
 the GHC optimizer - compile your code with -ddump-simpl to see (among
 other things) a dump of the strictness properties determined.  (use -O,
 of course)

 Stefan

 -BEGIN PGP SIGNATURE-
 Version: GnuPG v1.4.6 (GNU/Linux)

 iD8DBQFHVc/eFBz7OZ2P+dIRAmJKAKCDPQl1P5nYNPBOoR6isw9rAg5XowCgwI1s
 02/+pzXto1YRiXSSslZsmjk=
 =7dDj
 -END PGP SIGNATURE-

 ___
 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] Why is this strict in its arguments?

2007-12-04 Thread Stefan O'Rear
On Tue, Dec 04, 2007 at 03:07:01PM -0800, Ryan Ingram wrote:
 Is there a reason why strictness is defined as
  f _|_ = _|_
 
 instead of, for example,
  forall x :: Exception. f (throw x) = throw x
 where an exception thrown from pure code is observable in IO.
 
 In the second case we need to prove that the argument is evaluated at some
 point, which is also equivalent to the halting problem but more captures the
 notion of f evaluates its argument rather than either f evaluates its
 argument, or f _ is _|_
 
 I suppose the first case allows us to do more eager evaluation; but are
 there a lot of cases where that matters?

Is there a reason why 2 + 2 is defined as 4 instead of, for example,
5?

Strictness is more useful in practice, simpler to define, and easier to
approximate.

What benefit does your notion offer?

Stefan


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


Re: [Haskell-cafe] Why is this strict in its arguments?

2007-12-04 Thread Ryan Ingram
On 12/4/07, Stefan O'Rear [EMAIL PROTECTED] wrote:

 Is there a reason why 2 + 2 is defined as 4 instead of, for example,
 5?


Wow.  That wasn't really necessary.  4 has a clear meaning (the number after
the number after the number after the number after zero) which is equivalent
to 2 + 2.  I'm not talking about naming issues; you could say that 5 was
that number but then nobody would know what you are talking about.  I am
asking about the history  motivation behind the original definition of
strictness, not arguing for a redefinition.

Strictness is more useful in practice, simpler to define, and easier to
 approximate.


Please elaborate; this is exactly why I asked.  In particular, more useful
in practice is the thing I am most curious about.


 What benefit does your notion offer?


Well, one usually says something like f is strict in its 2nd argument
which on casual reading tends to make me think that it has something to do
with the argument.  By the actual definition, however, f _ _ = undefined is
strict in all of its arguments; but it's clear from the definition that the
arguments are irrelevant.

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


Re: [Haskell-cafe] Why is this strict in its arguments?

2007-12-04 Thread Lennart Augustsson
I don't even understand what your notation means.

But apart from that, there are good reasons to define strictness
denotationally instead of operationally.  Remember that _|_ is not only
exceptions, but also non-termination.

For instance, the following function is strict without using its argument:
f x = f x
because
f _|_ = _|_

  -- Lennart

On Dec 4, 2007 11:07 PM, Ryan Ingram [EMAIL PROTECTED] wrote:

 Is there a reason why strictness is defined as
  f _|_ = _|_

 instead of, for example,
  forall x :: Exception. f (throw x) = throw x
 where an exception thrown from pure code is observable in IO.

 In the second case we need to prove that the argument is evaluated at some
 point, which is also equivalent to the halting problem but more captures the
 notion of f evaluates its argument rather than either f evaluates its
 argument, or f _ is _|_

 I suppose the first case allows us to do more eager evaluation; but are
 there a lot of cases where that matters?

   -- ryan

 On 12/4/07, Stefan O'Rear [EMAIL PROTECTED] wrote:

  On Tue, Dec 04, 2007 at 09:41:36PM +, Paulo J. Matos wrote:
   Hello all,
  
   As you might have possibly read in some previous blog posts:
   http://users.ecs.soton.ac.uk/pocm06r/fpsig/?p=10
   http://users.ecs.soton.ac.uk/pocm06r/fpsig/?p=11
  
   we (the FPSIG group) defined:
   data BTree a = Leaf a
  | Branch (BTree a) a (BTree a)
  
   and a function that returns a list of all the paths (which are lists
   of node values) where each path element makes the predicate true.
   findAllPath :: (a - Bool) - (BTree a) - Maybe [[a]]
   findAllPath pred (Leaf l) | pred l = Just [[l]]
 | otherwise = Nothing
   findAllPath pred (Branch lf r rt) | pred r = let lfpaths = findAllPath
  pred lf
rtpaths = findAllPath
  pred rt
in
  if isNothing lfpaths 
   isNothing rtpaths
  then Nothing
  else
  if isNothing
  lfpaths
  then Just (map (r:)
   $ fromJust rtpaths)
  else
  if isNothing
  rtpaths
  then Just (map
   (r:) $ fromJust lfpaths)
  else Just (map
   (r:) $ fromJust rtpaths ++ fromJust lfpaths)
 | otherwise = Nothing
  
   Later on we noticed that this could be simply written as:
   findAllPath :: (a - Bool) - (BTree a) - [[a]]
 findAllPath pred = g where
 g (Leaf l) | pred l = [[l]]
 g (Branch lf r rt) | pred r = map (r:) $ (findAllPath pred
   lf) ++ (findAllPath pred rt)
 g _  = []
  
   without even using maybe. However, 2 questions remained:
   1 - why is the first version strict in its arguments?
 
  Because of the definition of strictness.  A function is strict iff f
  undefined = undefined.
 
  findAllPath pred undefined - undefined because of the case analysis
  findAllPath undefined (Leaf _) - undefined because pred is applied in
   the guard
  findAllPath undefined Branch{} - undefined because pred is applied in
   the guard
 
   2 - if it really is strict in its arguments, is there any automated
   way to know when a function is strict in its arguments?
 
  No, because this is in general equivalent to the halting problem:
 
  f _ = head [ i | i - [1,3.], i == sum [ k | k - [1..i-1], i `mod` k ==
  0 ] ]
 
  f is strict iff there do not exist odd perfect numbers.
 
  However, fairly good conservative approximations exist, for instance in
  the GHC optimizer - compile your code with -ddump-simpl to see (among
  other things) a dump of the strictness properties determined.  (use -O,
  of course)
 
  Stefan
 
  -BEGIN PGP SIGNATURE-
  Version: GnuPG v1.4.6 (GNU/Linux)
 
  iD8DBQFHVc/eFBz7OZ2P+dIRAmJKAKCDPQl1P5nYNPBOoR6isw9rAg5XowCgwI1s
  02/+pzXto1YRiXSSslZsmjk=
  =7dDj
  -END PGP SIGNATURE-
 
  ___
  Haskell-Cafe mailing list
  Haskell-Cafe@haskell.org
  http://www.haskell.org/mailman/listinfo/haskell-cafe
 
 

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


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


Re: [Haskell-cafe] Why is this strict in its arguments?

2007-12-04 Thread Stefan O'Rear
On Tue, Dec 04, 2007 at 03:35:28PM -0800, Ryan Ingram wrote:
 On 12/4/07, Stefan O'Rear [EMAIL PROTECTED] wrote:
 
  Is there a reason why 2 + 2 is defined as 4 instead of, for example,
  5?
 
 Wow.  That wasn't really necessary.  4 has a clear meaning (the number after
 the number after the number after the number after zero) which is equivalent
 to 2 + 2.  I'm not talking about naming issues; you could say that 5 was
 that number but then nobody would know what you are talking about.  I am
 asking about the history  motivation behind the original definition of
 strictness, not arguing for a redefinition.

Oh.  Sorry.

  Strictness is more useful in practice, simpler to define, and easier to
  approximate.
 
 Please elaborate; this is exactly why I asked.  In particular, more useful
 in practice is the thing I am most curious about.

When you see an expression of the form:

f a

you generally want to evaluate a before applying; but if a is _|_, this
will only give the correct result if f a = _|_.  Merely 'guaranteed to
evaluate' misses out on some common cases, for instance ifac:

ifac 0 a = a
ifac n a = ifac (n - 1) (a * n)

ifac is guaranteed to either evaluate a, or go into an infinite loop -
so it can be found strict, and unboxed.  Whereas 'ifac -1 (error moo)'
is an infinite loop, so using a definition based on evaluation misses
this case.

  What benefit does your notion offer?
 
 Well, one usually says something like f is strict in its 2nd argument
 which on casual reading tends to make me think that it has something to do
 with the argument.  By the actual definition, however, f _ _ = undefined is
 strict in all of its arguments; but it's clear from the definition that the
 arguments are irrelevant.

Stefan


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


Re: [Haskell-cafe] Why is this strict in its arguments?

2007-12-04 Thread John Meacham
On Tue, Dec 04, 2007 at 03:35:28PM -0800, Ryan Ingram wrote:
 On 12/4/07, Stefan O'Rear [EMAIL PROTECTED] wrote:
 Well, one usually says something like f is strict in its 2nd argument
 which on casual reading tends to make me think that it has something to do
 with the argument.  By the actual definition, however, f _ _ = undefined is
 strict in all of its arguments; but it's clear from the definition that the
 arguments are irrelevant.

this becomes more clear if you translate strictness into a logical
representation.

f x y = z

saying f is strict in y is equivalent to

y diverges implies z diverges.

note that this is a one way implication.

so, if z diverges, then the implication is trivially satisfied, as it is
if y doesn't diverge, however if y diverges then z must diverge and that
is what strictness means. 

or equivalantly

z diverges \/  ! y diverges 


for an example of why this is useful think of the following

imagine we know we are applying a function f to _|_, and we know f is
strict in its first argument. Knowing it is strict, we can elide the
call to f altogether and return bottom immediately. this is true whether
f examines it's argument or not, since f _|_ = _|_ and we know we are
passing _|_ then we can just return _|_. This is one of many
optimizations that 'strictness analysis' allows.

John

* note, I am using 'x diverges' and 'x is bottom' to mean the same
  thing. Not all agree this is correct usage, even sometimes I don't.
  but for the purposes of this it is fine IMHO.



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


[Haskell-cafe] Re: Why is this strict in its arguments?

2007-12-04 Thread Aaron Denney
On 2007-12-04, Paulo J. Matos [EMAIL PROTECTED] wrote:
 Hello all,

 As you might have possibly read in some previous blog posts:
 http://users.ecs.soton.ac.uk/pocm06r/fpsig/?p=10
 http://users.ecs.soton.ac.uk/pocm06r/fpsig/?p=11

 we (the FPSIG group) defined:
 data BTree a = Leaf a
| Branch (BTree a) a (BTree a)

Totally avoiding your question, but I'm curious as to why you
deliberately exclude empty trees.

Come to think of it, how can you represent a tree with two elements?

Wouldn't 

 data BTree a = Empty
  | Branch (BTree a) a (BTree a)

be better?

-- 
Aaron Denney
--

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


Re: [Haskell-cafe] Re: [Haskell] Nested guards?

2007-12-04 Thread Nicolas Frisby
It seems there is previous background here that I am unaware of. I'll
chime in anyway.

What you describe as the wrong semantics seems to me to be the more
appropriate. I am inferring that your expected behavior is explained
such that the first server match ought to fail (and fall through to
the second server match) because the pattern in the let fails. This
seems odd to me. If the parse test expression yields a Just
constructor, then hasn't the first server match succeeded and we ought
now commit to the let expression?

I apologize if this should be obvious to anyone familiar with the extension.

On Dec 4, 2007 2:46 PM, Neil Mitchell [EMAIL PROTECTED] wrote:
 Hi

  server text
 | Just xs - parse text = let
   x | field1 `elem` xs   = error ... do one thing ...
 | field2 `elem` xs   = error ... do something else ...
   in x
  server  _ = error ... invalid request ...

 This now has the wrong semantics - before if parse text returned Just
 [] the error invalid request branch was invoked, now its a pattern
 match failure.

 I haven't used pattern guards that much (but will once Haskell'
 standardises them, or they get implemented in Hugs!), but their syntax
 seems quite natural. This extension seems to make it harder to
 understand them, and gives some nasty , | parsing issues for a human
 at least - quite possibly for a compiler too. Perhaps if you gave a
 little grammar for extended pattern guards (compared to the original)
 it would be easier to see how naturally they fit in.

 Thanks

 Neil
 ___
 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] Why is this strict in its arguments?

2007-12-04 Thread Ryan Ingram
On 12/4/07, Stefan O'Rear [EMAIL PROTECTED] wrote:

 When you see an expression of the form:

 f a

 you generally want to evaluate a before applying; but if a is _|_, this
 will only give the correct result if f a = _|_.  Merely 'guaranteed to
 evaluate' misses out on some common cases, for instance ifac:

 ifac 0 a = a
 ifac n a = ifac (n - 1) (a * n)

 ifac is guaranteed to either evaluate a, or go into an infinite loop -
 so it can be found strict, and unboxed.  Whereas 'ifac -1 (error moo)'
 is an infinite loop, so using a definition based on evaluation misses
 this case.


By this line:
you generally want to evaluate a before applying; but if a is _|_, this
will only give the correct result if f a = _|_

I assume you mean that it's generally more efficient to do things that way,
because the calling function may have more information about a or how it
is calculated, so you may be able to optimize better by doing eager
evaluation whenever it is correct.

Your ifac example makes perfect sense, thanks.

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


Re: [Haskell-cafe] Re: [Haskell] Nested guards?

2007-12-04 Thread Iavor Diatchki
Hello everyone,
Just to clarify, the intended semantics of my example was that it
should behave as if we were to duplicate the common prefix:

server text
  | Just xs - parse text, field1 `elem` xs   = ... do one thing ...
  | Just xs - parse text, field2 `elem` xs   = ... do something else ...

server  _ = ... invalid request ...

The difference is that the nested version is shorter, and probably way
easier for the compiler to produce reasonable code.As I said in my
first post, I am not sure what would be a nice notation for nesting
the guards:  the notation that I used in the example was just the
first thing that came to mind, we might be able to do better.

-Iavor


On Dec 4, 2007 7:26 PM, Nicolas Frisby [EMAIL PROTECTED] wrote:
 It seems there is previous background here that I am unaware of. I'll
 chime in anyway.

 What you describe as the wrong semantics seems to me to be the more
 appropriate. I am inferring that your expected behavior is explained
 such that the first server match ought to fail (and fall through to
 the second server match) because the pattern in the let fails. This
 seems odd to me. If the parse test expression yields a Just
 constructor, then hasn't the first server match succeeded and we ought
 now commit to the let expression?

 I apologize if this should be obvious to anyone familiar with the extension.


 On Dec 4, 2007 2:46 PM, Neil Mitchell [EMAIL PROTECTED] wrote:
  Hi
 
   server text
  | Just xs - parse text = let
x | field1 `elem` xs   = error ... do one thing ...
  | field2 `elem` xs   = error ... do something else ...
in x
   server  _ = error ... invalid request ...
 
  This now has the wrong semantics - before if parse text returned Just
  [] the error invalid request branch was invoked, now its a pattern
  match failure.
 
  I haven't used pattern guards that much (but will once Haskell'
  standardises them, or they get implemented in Hugs!), but their syntax
  seems quite natural. This extension seems to make it harder to
  understand them, and gives some nasty , | parsing issues for a human
  at least - quite possibly for a compiler too. Perhaps if you gave a
  little grammar for extended pattern guards (compared to the original)
  it would be easier to see how naturally they fit in.
 
  Thanks
 
  Neil
  ___
  Haskell-Cafe mailing list
  Haskell-Cafe@haskell.org
  http://www.haskell.org/mailman/listinfo/haskell-cafe
 
 ___
 Haskell-Cafe mailing list
 Haskell-Cafe@haskell.org
 http://www.haskell.org/mailman/listinfo/haskell-cafe

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


Re: [Haskell-cafe] Why is this strict in its arguments?

2007-12-04 Thread Stefan O'Rear
On Tue, Dec 04, 2007 at 07:43:36PM -0800, Ryan Ingram wrote:
 On 12/4/07, Stefan O'Rear [EMAIL PROTECTED] wrote:
 
  When you see an expression of the form:
 
  f a
 
  you generally want to evaluate a before applying; but if a is _|_, this
  will only give the correct result if f a = _|_.  Merely 'guaranteed to
  evaluate' misses out on some common cases, for instance ifac:
 
  ifac 0 a = a
  ifac n a = ifac (n - 1) (a * n)
 
  ifac is guaranteed to either evaluate a, or go into an infinite loop -
  so it can be found strict, and unboxed.  Whereas 'ifac -1 (error moo)'
  is an infinite loop, so using a definition based on evaluation misses
  this case.
 
 
 By this line:
 you generally want to evaluate a before applying; but if a is _|_, this
 will only give the correct result if f a = _|_
 
 I assume you mean that it's generally more efficient to do things that way,
 because the calling function may have more information about a or how it
 is calculated, so you may be able to optimize better by doing eager
 evaluation whenever it is correct.

Yes - if we know that a value is needed, eager evaluation is more
efficient, because no time need be spent constructing and
deconstructing expressions in memory.

More significantly, strictness facilitates certain unboxing
transformations.  Since ifac is strict, (optimized) code will never call
it with anything except a concrete number, so we can gainfully
specialize it to the case of a pre-evaluated argument; so instead of
passing pointer-to-Int-node, we can just pass a raw machine integer.
With a few passes of standard compilation technology (inlining +, etc)
we wind up with the moral equivalent of while (n--) { i *= n; }.

 Your ifac example makes perfect sense, thanks.

Stefan


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


[Haskell-cafe] a positive challenge for the Haskell effort .....

2007-12-04 Thread Galchin Vasili
http://code.enthought.com/enthon/ .. how do Haskell libraries/packages stack
up against this challenge?

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


[Haskell-cafe] building HUnit and other packages on Windows cygwin ...

2007-12-04 Thread Galchin Vasili
Hello,

I believe that HUnit has absolutely not other package dependencies. When
I do a runhaskell Setup.hs build, I get the following error message: gcc:
installation problem, cannot
exec `cc1': No such file or directory. I am not sure what cc1 is? A
pass/phase of the gnu gcc compiler?

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


[Haskell-cafe] Expert systems

2007-12-04 Thread Joel Reymont

Is there an expert system implemented in Haskell, or a library perhaps?

A CLIPS/RETE implementation?

The main stumbling point, from my perspective, is how to implement a  
knowledge base and check whether patterns with a certain shape have  
been asserted. It's much easier to do this in a dynamically-typed  
language.


Am I mistaken?

Thanks, Joel

--
http://wagerlabs.com





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