[Haskell-cafe] Haskell for categorists

2007-07-16 Thread Miguel Mitrofanov
Just being curious.

There are a lot of tutorials ensuring the reader that, although
Haskell is based on category theory, you don't have to know CT to use
Haskell. So, is there ANY Haskell tutorial for those who do know CT?

I don't need it, personally, but still...

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


Re[2]: [Haskell-cafe] Haskell monads for newbies

2007-07-16 Thread Bulat Ziganshin
Hello Andrew,

Monday, July 16, 2007, 1:06:42 AM, you wrote:

 I have a vague recollection of somebody muttering something about
 ByteStrings and memory-mapped files...?

http://www.haskell.org/library/StreamsBeta.tar.gz

you can either open m/m file with openBinaryMMFile and use it to
read/write any data including ByteStrings or use the following code
that maps file into memory and allow to use it as ByteString

-- -
-- Mapping file contents into ByteString / memory buffer

#if defined(__GLASGOW_HASKELL__)

#if defined(USE_BYTE_STRING)
-- | Like mmapBinaryFilePtr, but returns ByteString representing
-- the entire file contents.
mmapBinaryFileBS :: FilePath - IO ByteString
mmapBinaryFileBS f = do
(fp,l) - mmapBinaryFilePtr f
return $ fromForeignPtr fp 0 l
#endif

-- | Like 'readFile', this reads an entire file directly into a
-- 'ByteString', but it is even more efficient.  It involves directly
-- mapping the file to memory.  This has the advantage that the contents
-- of the file never need to be copied.  Also, under memory pressure the
-- page may simply be discarded, while in the case of readFile it would
-- need to be written to swap. You can run into bus
-- errors if the file is modified.
mmapBinaryFilePtr :: FilePath - IO (ForeignPtr a, Int)
mmapBinaryFilePtr f = do
fd - openBinaryFD f ReadMode
len - fdFileSize fd
l - checkedFromIntegral len $ do   -- some files are 4GB at those days ;)
fail $ mmapBinaryFilePtr: file '++f++' is too big (++show len++ 
bytes) !
-- Don't bother mmaping small files because each mmapped file takes up
-- at least one full VM block.
if l  mmap_limit
   then do fp - mallocForeignPtrBytes l
   withForeignPtr fp $ \p- fdGetBuf fd p l
   fdClose fd
   return (fp, l)
   else do
   mmfd - myOpenMMap fd ReadMode
   p - myMMap mmfd ReadMode 0 l
   let unmap = do myUnMMap p l
  myCloseMMap mmfd
  fdClose fd
  return ()
   fp - FC.newForeignPtr p unmap
   return (fp, l)

where mmap_limit = 16*1024
#endif



-- 
Best regards,
 Bulatmailto:[EMAIL PROTECTED]

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


Re: [Haskell-cafe] Haskell for categorists

2007-07-16 Thread Donald Bruce Stewart
miguelimo38:
 Just being curious.
 
 There are a lot of tutorials ensuring the reader that, although
 Haskell is based on category theory, you don't have to know CT to use
 Haskell. So, is there ANY Haskell tutorial for those who do know CT?
 
 I don't need it, personally, but still...
 

I'd probably start here:

http://haskell.org/haskellwiki/Blog_articles/Mathematics#Category_theoretic

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


[Haskell-cafe] Re: no-coding functional data structures via lazyness

2007-07-16 Thread Dave Bayer
apfelmus apfelmus at quantentunnel.de writes:

 While your observation that merge may create an implicit heap is true,
 it doesn't happen in your code :) When unfolding the foldr1, we get
 something like
 
   2:.. `merge'` (3:.. `merge'` (5:.. `merge1` (...)))
 
 i.e. just a linear chain of merges. Retrieving the least element is
 linear time in the worst case. This shape will not change with
 subsequent reductions of  merge. In other words, it's the responsibility
 of  fold  to build a heap. Mergesort shows how a fold can build a heap:
 
   http://thread.gmane.org/gmane.comp.lang.haskell.general/15007
 
 For  primes , the heap shape has to be chosen carefully in order to
 ensure termination. It's the same problem that forces you to use  foldr1
 merge'  instead of  foldr1 merge .
 
 There's also a long thread about prime sieves
 
   http://thread.gmane.org/gmane.comp.lang.haskell.cafe/19699

Indeed. Your answer sent my head spinning, giving me something to think about
on a flight AMS to SFO. Thanks!

Here is a prime sieve that can hang within a factor of two of the fastest
code in that thread, until it blows up on garbage collection:

-

diff  :: Ord a = [a] - [a] - [a]
diff xs@(x:xt) ys@(y:yt) = case compare x y of
LT - x : (diff  xt ys)
EQ - (diff  xt yt)
GT - (diff  xs yt)
diff _ _ = undefined

union :: Ord a = [a] - [a] - [a]
union xs@(x:xt) ys@(y:yt) = case compare x y of
LT - x : (union xt ys)
EQ - x : (union xt yt)
GT - y : (union xs yt)
union _ _ = undefined

twig :: Ord a = [a] - [a] - [a]
twig (x:xt) ys = x : (union xt ys)
twig _ _ = undefined

pair :: Ord a = [[a]] - [[a]]
pair (x:y:xs) = twig x y : (pair xs)
pair _ = undefined

tree :: Ord a = [[a]] - [a]
tree xs  = 
let g (x:xt) = x : (g $ pair xt)
g _ = undefined
in  foldr1 twig $ g xs

seed :: Integral a = [a]
seed = [2,3,5,7,11,13]

wheel :: Integral a = [a]
wheel  = drop 1 [ 30*j+k | j - [0..], k - [1,7,11,13,17,19,23,29] ]

multiples :: Integral a = [a]
multiples = tree ps
where f p n = mod n p /= 0
  g (_,ns) p = ([ n*p | n - ns ], filter (f p) ns)
  ps = map fst $ tail $ scanl g ([], wheel) $ drop 3 primes

primes :: Integral a = [a]
primes = seed ++ (diff (drop 3 wheel) multiples)

-

Here are some timings:

[Integer] -O   10^410^510^610^7
-
ONeillPrimes  |  0m0.023s |  0m0.278s |  0m3.682s | 0m53.920s
  primes  |  0m0.022s |  0m0.341s |  0m5.664s | 8m12.239s

This differs from your code in that it works with infinite lists, so
it can't build a balanced tree; the best it can do is to build a vine
of subtrees that double in size.

My conclusion so far from this and other experiments is that pushing
data structures into the lazy evaluation model does make them run faster,
but at the expense of space, which eventually leads to the code's untimely
demise.

I can imagine a lazy functional language that would support reification
of suspended closures, so one could incrementally balance the suspended
computation above. As far as I can tell, Haskell is not such a language.
I'd love it, however, if someone could surprise me by showing me the
idiom I'm missing here.

I will post a version of this code (I have faster but less readable
versions) to the prime sieve thread. First, I'm waiting for
the other shoe to drop, I still feel like I'm missing something.

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


Re: [Haskell-cafe] Clearly, Haskell is ill-founded

2007-07-16 Thread Conor McBride

Hi Derek

On 16 Jul 2007, at 02:48, Derek Elkins wrote:


On Mon, 2007-07-16 at 02:29 +0100, Conor McBride wrote:

Hi


data{-codata-} Punter = Speak String (String - Punter)




[..]




data{-codata-} Stream x = x : (Stream x)



cafe :: Punter - (String - Punter) - Stream (String, String)
cafe (Speak question learn) guru =
  let  Speak answer guru' = guru question
  in   (question, answer) : (cafe (learn answer) guru')


If the Punter asks the appropriate question, perhaps the guru will  
spend

the rest of time thinking about an answer.


It's true that answers can take a while, but not forever if the guru is
also a productive coprogram. In more realistic examples, mere  
productivity

might not be enough: you might want to be sure that questions will
eventually be answered, after some initial segment of busy responses.

To that end, an exercise. Implement a codata type

data{-codata-} Mux x y = ...

which intersperses x's and y's in such a way that

  (1) an initial segment of a Mux does not determine whether the next
element is an x or a y (ie, no forced *pattern* of alternation)

  (2) there are productive coprograms

demuxL :: Mux x y - Stream x
demuxR :: Mux x y - Stream y

(ie, alternation is none the less forced)

You may need to introduce some (inductive) data to achieve this. If you
always think always, then you need codata, but if you eventually think
eventually, you need data.

All the best

Conor

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


[Haskell-cafe] Re: Haskell shootout game

2007-07-16 Thread apfelmus
Hugh Perkins wrote:
 Had an idea: a real shootout game for Haskell.

 scripts fight in an arena for a second or so, and the results are
 published to the website

Sounds great :)

There are lots of robot battle games out there, like

  http://realtimebattle.sourceforge.net/
  http://robocode.sourceforge.net

but none in Haskell, of course. I think there's a classic predecessor to
those but I don't know exactly.

 Each turn is represented by a function something like:
 
 doturn :: String - [[GridValue]] - (Action,String)

The explicit state can be dispensed with by introducing a stream type

  data Robot = Robot (BattleField - (Action, Robot)

  type BattleField = [[GridValue]]

This way, the program is entirely free in how to choose its state
representation. You can turn any  doturn - based program into a
stream-based one

  toRobot :: String - (BattleField - String - (Action,String))
- Robot
  toRobot s doturn = Robot $ \arena -
 let (action, s') = doturn bf s in (action, toRobot s' doturn)

The drawback is that it's no longer possible to save a snapshot of each
program's state to disk and resume the fight later.

Regards,
apfelmus

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


Re: [Haskell-cafe] Re: Haskell shootout game

2007-07-16 Thread Jules Bean

apfelmus wrote:

Hugh Perkins wrote:

Had an idea: a real shootout game for Haskell.

scripts fight in an arena for a second or so, and the results are
published to the website


Sounds great :)

There are lots of robot battle games out there, like

  http://realtimebattle.sourceforge.net/
  http://robocode.sourceforge.net

but none in Haskell, of course. I think there's a classic predecessor to
those but I don't know exactly.


I suspect they are probably viewed as 'descendants' in a weak sense from 
Core War, which in turn was inspired by Darwin. However these two, since 
the act more 'directly' in the memory space of a virtual CPU are quite 
different in character.


I can't substantiate that suspicion with any evidence, though.

Either way it would be a fun thing for someone to write for haskell.

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


Re: [Haskell-cafe] Haskell shootout game

2007-07-16 Thread Bas van Dijk

This would be a lot of fun! Make sure to take the lessons from
http://haskell.org/haskellwiki/Safely_running_untrusted_Haskell_code
into account.

regards,

Bas van Dijk

On 7/15/07, Hugh Perkins [EMAIL PROTECTED] wrote:

Had an idea: a real shootout game for Haskell.

The way it would work is:
- you email a haskell program to a specific address
- it shows up on a web-page

The webpage shows the last submitted solution for each person
- anyone can select two solutions and click Fight
- the scripts fight in an arena for a second or so, and the results are
published to the website

The arena itself comprises:
- a 2d grid, of a certain size (or maybe variable size)
- each grid cell can be a wall, or one of the opponents
- the boundaries of the grid are walls
- random blocks of wall are placed around the grid

The opponents only perceive what is in a section of space to their front, in
a 45 degree arc from either side of the direction they are facing
- each player can face along one of the four grid axes

Each player takes it in turns to move
- at each move the player can:
   - move one square
   - turn 90 degrees, in either direction
   - fire

Firing will score one point if the opponent is in the line of fire at that
time, and there are no intervening walls.

Opponents can see the direction the other opponent is facing, as long as the
other opponent is in their view arc, and there are no intervening walls.

Each turn is represented by a function something like:

doturn :: String - [[GridValue]] - (Action,String)

-- [[GridValue]] is a map of what Me sees this turn, or has seen previously
-- the Strings are a way for the function to pass state to itself between
moves

data GridValue = Opponent | Me | Wall | Empty
data Action = Fire | MoveNorth | MoveSouth |MoveEast | MoveWest | TurnLeft |
TurnRight | Wait-- (players can move backwards and sideways)

The turn would be run as a separate thread, which either terminates
successfully, or is aborted after a fixed time x milliseconds (maybe 10
milliseconds?)

The String that doturn produces at the end of a turn is passed back in at
the beginning of the next turn (so one could use gread/gshow to
serialize/deserialize arbitrary data types, and there is no limitation on
what data can be stored in the state).

After say 1000 turns, the results are the points of each script. (or we
could give each script a number of lives and if its loses them all the
other script wins outright)


This can run on a hosted webserver probably, because each match is part of a
webpage request, and lasts a maximum of about a second, so shouldnt be
terminated prematurely by cpu-monitoring scripts.


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



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


Re[2]: [Haskell-cafe] In-place modification

2007-07-16 Thread Bulat Ziganshin
Hello Jon,

Sunday, July 15, 2007, 9:46:42 PM, you wrote:

 This should tell you that your C++ is not very good. This is several times
 faster, for example:

 For some reason you were using C-style allocation rather than the C++ STL to
 implement a bit vector. The STL implementation is optimized.

i bet that this version allocates exactly one bit per element, like
Haskell version. so *this* comparison is fair, while old was unfair

-- 
Best regards,
 Bulatmailto:[EMAIL PROTECTED]

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


Re: [Haskell-cafe] Re: Re[4]: In-place modification

2007-07-16 Thread Bulat Ziganshin
Hello Chris,

Monday, July 16, 2007, 8:46:37 AM, you wrote:

 Topcoder certainly isn't about benchmarking.  Undoubtedly, it would be
 absolutely awesome to be able to use Haskell in topcoder... but it 
 wouldn't say anything about speed.  My guess is that practically no 
 topcoder submissions fail by exceeding the allowable time limit.  The 
 competition (the alg one, which is the only one anyone really cares 
 about) is about solving problems quickly (in programmer time) and 
 accurately.

that's ideal for haskell. like ICFP, if they will allow haskell code,
then all winer solutions will be written using it



-- 
Best regards,
 Bulatmailto:[EMAIL PROTECTED]

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


Re[2]: [Haskell-cafe] Ray tracer

2007-07-16 Thread Bulat Ziganshin
Hello ajb,

Monday, July 16, 2007, 5:00:54 AM, you wrote:
 But I don't think that means there is no role for Haskell in
 rendering. Examples of places I think Haskell could play a role are:
 the shader language, [...]

 For the record, I've written 2.5 production shader compilers.  The
 0.5 was in Haskell. :-)

and why you stopped at 0.5? was it due to haskell limitations or
something else? how haskell looks in this area compared to other
languages (and what other languages you used)?


-- 
Best regards,
 Bulatmailto:[EMAIL PROTECTED]

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


Re: [Haskell-cafe] Haskell shootout game

2007-07-16 Thread PR Stanley

Is this some sort of a war game?
At 11:14 16/07/2007, you wrote:

This would be a lot of fun! Make sure to take the lessons from
http://haskell.org/haskellwiki/Safely_running_untrusted_Haskell_code
into account.

regards,

Bas van Dijk

On 7/15/07, Hugh Perkins [EMAIL PROTECTED] wrote:

Had an idea: a real shootout game for Haskell.

The way it would work is:
- you email a haskell program to a specific address
- it shows up on a web-page

The webpage shows the last submitted solution for each person
- anyone can select two solutions and click Fight
- the scripts fight in an arena for a second or so, and the results are
published to the website

The arena itself comprises:
- a 2d grid, of a certain size (or maybe variable size)
- each grid cell can be a wall, or one of the opponents
- the boundaries of the grid are walls
- random blocks of wall are placed around the grid

The opponents only perceive what is in a section of space to their front, in
a 45 degree arc from either side of the direction they are facing
- each player can face along one of the four grid axes

Each player takes it in turns to move
- at each move the player can:
   - move one square
   - turn 90 degrees, in either direction
   - fire

Firing will score one point if the opponent is in the line of fire at that
time, and there are no intervening walls.

Opponents can see the direction the other opponent is facing, as long as the
other opponent is in their view arc, and there are no intervening walls.

Each turn is represented by a function something like:

doturn :: String - [[GridValue]] - (Action,String)

-- [[GridValue]] is a map of what Me sees this turn, or has seen previously
-- the Strings are a way for the function to pass state to itself between
moves

data GridValue = Opponent | Me | Wall | Empty
data Action = Fire | MoveNorth | MoveSouth |MoveEast | MoveWest | TurnLeft |
TurnRight | Wait-- (players can move backwards and sideways)

The turn would be run as a separate thread, which either terminates
successfully, or is aborted after a fixed time x milliseconds (maybe 10
milliseconds?)

The String that doturn produces at the end of a turn is passed back in at
the beginning of the next turn (so one could use gread/gshow to
serialize/deserialize arbitrary data types, and there is no limitation on
what data can be stored in the state).

After say 1000 turns, the results are the points of each script. (or we
could give each script a number of lives and if its loses them all the
other script wins outright)


This can run on a hosted webserver probably, because each match is part of a
webpage request, and lasts a maximum of about a second, so shouldnt be
terminated prematurely by cpu-monitoring scripts.


___
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] Indentation Creep

2007-07-16 Thread Claus Reinke


as Thomas pointed out off-list, the transformation sequence as given 
is not type-preserving. i even documented that problem in my email, 
because i thought the type was dodgy, but forgot to track it down 
before posting. so here are the changes. a good demonstration that

does it still compile? is not a sufficient test for refactoring!-)

claus


 to prepare for our next step, we apply lift to all barebones STM
 operations, readTVar, write, empty, nullT. at this stage, our types
 (asking ghci, with :t dmin') are slightly redundant:

   dmin' :: (MonadTrans t1, Monad (t1 STM)) 
 = TVar (Trie t) - t1 STM (Maybe (t, Bool))


 since our particular MonadTrans, MaybeT, already wraps results in
 Maybe, this is one level of Maybe too much. so, when we remove our
 local definitions of mplus and  (replacing  with =), we remove
 that extra layer of Maybe, by removing the redundant (Just _) in
 returns, and by replacing 'return Nothing' with 'mzero'. 


we also need to take into account that the second readTVar already 
returns a Maybe, so we only need to wrap it in MaybeT, without 
applying the full lift.



we could now declare the type as

   dmin' :: TVar (Trie t) - MaybeT STM (Maybe t, Bool)


there's that dodgy type. it should just be:

   dmin' :: TVar (Trie t) - MaybeT STM (t, Bool)
 

 after all that refactoring, the code should look something like this:

   dmin p = maybe (error dmin: no values) (return . fst) 
   = runMaybeT (dmin' p)


   dmin' p = do
   t - lift $ readTVar p
   case t of
   Empty - mzero
   Trie l m r - 
   (dmin' l =

   (\ (v,e) - do
 case e of
 True - do
 me - lift $ empty m
 re - lift $ nullT r
 lift $ write m p (v,me  re)
 False - return (v,e)))
   `mplus` (((lift $ readTVar m) =


it was the return-wrapping of lift that introduced the extra Maybe 
here. this TVar already holds Maybes, so this should just be:


   `mplus` (((MaybeT $ readTVar m) =


 next, we can make use of the fact that pattern match failure in
 do-notation invokes fail in the monad, by defining 'fail msg = mzero'
 in our wrapped monad, and by pattern matching directly on the result
 of the first readTVar' (we only need the Trie-case, the other case
 will fail to match, leading to mzero, which is what we wanted anyway).


we can also use this feature to replace the half-lifted second
readTVar with a fully lifted readTVar' followed by a pattern match
on 'Just v'.


   - final version
   dmin p = maybe (error dmin: no values) (return . fst) 
  = runMaybeT (dmin' p)


   dmin' p = do
   Trie l m r - readTVar' p
   (do (v,e) - dmin' l
   (do guard e
   me - empty m
   re - nullT r
   write m p (v,me  re))
`mplus` return ((v,e)))
`mplus` (do v - readTVar' m


by employing pattern-match failure handling, this can become:

   `mplus` (do Just v - readTVar' m


re - nullT r
write m p (v,re))
`mplus` (do (v,e) - dmin' r
when e $ writeTVar' p Empty
return ((v,e)))
`mplus` error emit nasal daemons
   where
   readTVar'  var = lift $ readTVar var
   writeTVar' var val = lift $ writeTVar var val

   write m p (v,False) = lift $ writeTVar m Nothing  return ((v,False))
   write m p (v,True ) = lift $ writeTVar p Emptyreturn ((v,True))

   nullT :: Monad m = TriePtr t - m Bool
   nullT t = undefined

   empty m = lift $ liftM isNothing $ readTVar m

   data MaybeT m a = MaybeT { runMaybeT :: m (Maybe a) }

   instance Monad m = Monad (MaybeT m) where
 return  = MaybeT . return . Just
 a = b = MaybeT $ runMaybeT a = maybe (return Nothing) (runMaybeT . b)
 fail msg= mzero

   instance Monad m = MonadPlus (MaybeT m) where
 mzero   = MaybeT $ return Nothing
 a `mplus` b = MaybeT $ runMaybeT a = maybe (runMaybeT b) (return . Just)

   instance MonadTrans MaybeT where
 lift m = MaybeT $ m = return . Just

   - final version


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


Re: [Haskell-cafe] Re: Haskell shootout game

2007-07-16 Thread Claus Reinke

There are lots of robot battle games out there, like
but none in Haskell, of course. 


do the icfp contests count? not even limited to haskell, and
there were several tasks that look related, including:

http://alliance.seas.upenn.edu/~plclub/cgi-bin/contest/ants.html

http://icfpc.plt-scheme.org/spec.html

http://web.cecs.pdx.edu/%7Esheard/2002IcfpContest/task.html

claus

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


Re: [Haskell-cafe] Re: Maintaining the community

2007-07-16 Thread Andrew Coppin

Chris Smith wrote:
Well, it doesn't have to go over anywhere.  I'm reading and posting 
just fine with NNTP right now.  It works great.
  


How'd you manage that?

I found out I could do so by reading this thread.  Until then, I'd 
avoided haskell-cafe, hanging out mostly on IRC for the last few months 
because I didn't want the high volume of email.
  


I've been avoiding it for over a year for the same reason. (And because 
I didn't want people to have my real email address, but never mind...)


Actually, since this is the first time I've tried to seriously use 
Thundrebird for email, I'm surprised at how buggy it is...


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


Re: [Haskell-cafe] Maintaining the community

2007-07-16 Thread Andrew Coppin

Donald Bruce Stewart wrote:

zednenem:
  

On 7/15/07, Derek Elkins [EMAIL PROTECTED] wrote:


There is no version of bytestrings without stream fusion and there never
was.  Bytestrings have no compiler support, it is just a library.
  

I'm not sure that's correct. Stream fusion is a particular fusion
technique that wasn't introduced until fairly recently.

From what I can tell, none of the versions available from
http://www.cse.unsw.edu.au/~dons/fps.html include it. You have to go
to http://www.cse.unsw.edu.au/~dons/papers/CSL06.html and get the
code from the fps-unstable branch.



That's right. Both stream fusion for lists and bytestrings are currently
only in darcs,

http://www.cse.unsw.edu.au/~dons/code/fps-unstable/
http://www.cse.unsw.edu.au/~dons/code/streams/list/

Bytestrings will be streamed by the next release.
  


...which brings me back to my original how do I know if it's there? 
question. ;-)


My copy of GHC sitting here certainly *has* support for lists and byte 
strings in it - but I have no clue what version...


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


Re: Re[6]: [Haskell-cafe] In-place modification

2007-07-16 Thread Sebastian Sylvan

On 16/07/07, Bulat Ziganshin [EMAIL PROTECTED] wrote:

Hello Sebastian,

Sunday, July 15, 2007, 9:05:14 PM, you wrote:

 As we've demonstrated there's nothing stopping you from writing
 imperative C-like algorithms in Haskell (just like C#), and there
 certainly wasn't any major performance difference

as Donald mentioned, this test is just limited by cache speed, not by
speed of code generated.


But wouldn't you say that in general, if you spend the effort you can
write low-level imperative algorithms in Haskell that perform
reasonably well? Especially compared to e.g. C#? I think your own
libraries demonstrate this!

I'm not saying it's as convenient (see the recent thread about monad
splices) to write low-level imperative code in Haskell, but using
laziness in C# was hardly a walk on the beach either!
So my point is that Haskell isn't geared towards low-level
optimizations and performance, but in the few places where you do need
it, you *can* get it (IMO for only moderately more inconvenience than
you pay for *everything* in a low-level imperative language). Whereas
C# is a bit the other way around (easy to modify state, inconvenient
to write high-level/lazy/concurrent/etc. code), though something like
C is even more the other way around.

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


Re[6]: [Haskell-cafe] In-place modification

2007-07-16 Thread Bulat Ziganshin
Hello Sebastian,

Sunday, July 15, 2007, 9:05:14 PM, you wrote:

 As we've demonstrated there's nothing stopping you from writing
 imperative C-like algorithms in Haskell (just like C#), and there
 certainly wasn't any major performance difference

as Donald mentioned, this test is just limited by cache speed, not by
speed of code generated.


-- 
Best regards,
 Bulatmailto:[EMAIL PROTECTED]

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


benchmarks Re: [Haskell-cafe] Re: SHA1 again

2007-07-16 Thread Bulat Ziganshin
Hello Dominic,

Sunday, July 15, 2007, 11:44:10 PM, you wrote:

 forget it if you're interested in performance near a C implementation
 such as GNU sha1sum.
 

 I don't think it's unreasonable to think we could get near to C performance 
 and
 we've been getting closer.

btw, if someone interested in fair comparison of quality of code,
generated by various compilers, then sha1 or something like it will be
good idea. it's clearly algorithm limited by raw processing power
rather than cache speed, libraries or something else

-- 
Best regards,
 Bulatmailto:[EMAIL PROTECTED]

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


Re: [Haskell-cafe] Haskell for categorists

2007-07-16 Thread Bulat Ziganshin
Hello Miguel,

Monday, July 16, 2007, 10:00:21 AM, you wrote:
 There are a lot of tutorials ensuring the reader that, although
 Haskell is based on category theory, you don't have to know CT to use
 Haskell. So, is there ANY Haskell tutorial for those who do know CT?

it's like driving courses for Chemistry Professors :)

-- 
Best regards,
 Bulatmailto:[EMAIL PROTECTED]

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


Re: [Haskell-cafe] Re: Haskell shootout game

2007-07-16 Thread Oliver Batchelor

Hi,

I've had a go at making a robot battle game in Haskell (a robocode clone), I
was using Yampa for both the robots and the game logic - however using Yampa
for the game logic presented a number of problems, mostly in ensuring every
single piece of data emitted from the game logic portion was evaluated.

I had a fair amount of work done, and it was shaping up nicely, but it
needed simplification, trying to add in too many extras such as physical
simulation of collisions etc. turned it into a bit of a monster when the
core design needed some work!

http://saulzar.orcon.net.nz/robots2.jpg

I'd definitely like to give it another go, this time without Yampa for game
logic - though it seems fantastic for the user robot code, perhaps it
needn't be compulsory - interested users could always use Yampa if they
desired.



Oliver Batchelor


On 7/16/07, apfelmus [EMAIL PROTECTED] wrote:


Hugh Perkins wrote:
 Had an idea: a real shootout game for Haskell.

 scripts fight in an arena for a second or so, and the results are
 published to the website

Sounds great :)

There are lots of robot battle games out there, like

  http://realtimebattle.sourceforge.net/
  http://robocode.sourceforge.net

but none in Haskell, of course. I think there's a classic predecessor to
those but I don't know exactly.

 Each turn is represented by a function something like:

 doturn :: String - [[GridValue]] - (Action,String)

The explicit state can be dispensed with by introducing a stream type

  data Robot = Robot (BattleField - (Action, Robot)

  type BattleField = [[GridValue]]

This way, the program is entirely free in how to choose its state
representation. You can turn any  doturn - based program into a
stream-based one

  toRobot :: String - (BattleField - String - (Action,String))
- Robot
  toRobot s doturn = Robot $ \arena -
 let (action, s') = doturn bf s in (action, toRobot s' doturn)

The drawback is that it's no longer possible to save a snapshot of each
program's state to disk and resume the fight later.

Regards,
apfelmus

___
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] Help with IO and randomR

2007-07-16 Thread Niko Korhonen
I'm writing some code to generate a dither (=noise) signal. I'm trying
to generate an infinite series of noise with triangular distribution but
my code hangs into an infinite loop. The problem is that I'm not very
good with Haskell IO yet and I can't figure out how to write this piece
of IO code without it looping infinitely.

So, in short, how do I do this without getting into an infinite loop:

tpdfs :: (Int, Int) - IO [Int]
tpdfs (low, high) = do
  first - getStdRandom (randomR (low, high))
  second - getStdRandom (randomR (low, high))
  let r = (first + second) `div` 2
  rest - tpdfs (low, high)
  return (r : rest)

Caller site:

do
  nums - tpdfs (2, 12)
  let ns = take 7 nums

Niko

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


Re[8]: [Haskell-cafe] In-place modification

2007-07-16 Thread Bulat Ziganshin
Hello Sebastian,

Monday, July 16, 2007, 2:53:36 PM, you wrote:
 But wouldn't you say that in general, if you spend the effort you can
 write low-level imperative algorithms in Haskell that perform
 reasonably well? Especially compared to e.g. C#? I think your own
 libraries demonstrate this!

i've said that
1) low-level programming in Haskell is possible, although not as
convenient as in C
2) low-level code will be much faster than high-level one, but not as
fast as C code

once i summed up my experience - you may either write
1) high-level code, which is written 10x faster than in C but works
100x slower
2) low-level code that is written 3x slower than in C and works 3x
slower too

if you think that Haskell code may be as fast as C one - try to
rewrite sha1 in any haskell style and compare it to highly optimized C
versions

it's all about small self-contained number-crunching algorithms -
for larger ones and especially for whole applications i got very
different results - code is, say, 3x slower while written 3x faster.
it's probably because OS calls, C libraries and highly-optimized
libraries written by other people are taken into account; also ghc
imho has better global-level optimization than C++ compilers, for
example it has better inlining policy

 I'm not saying it's as convenient (see the recent thread about monad
 splices) to write low-level imperative code in Haskell, but using
 laziness in C# was hardly a walk on the beach either!
 So my point is that Haskell isn't geared towards low-level
 optimizations and performance, but in the few places where you do need
 it, you *can* get it (IMO for only moderately more inconvenience than
 you pay for *everything* in a low-level imperative language).

are you really wrote such code or just believe to Haskell advertizing
company? :D

-- 
Best regards,
 Bulatmailto:[EMAIL PROTECTED]

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


Re: [Haskell-cafe] Help with IO and randomR

2007-07-16 Thread Bryan Burgers

On 7/16/07, Niko Korhonen [EMAIL PROTECTED] wrote:

I'm writing some code to generate a dither (=noise) signal. I'm trying
to generate an infinite series of noise with triangular distribution but
my code hangs into an infinite loop. The problem is that I'm not very
good with Haskell IO yet and I can't figure out how to write this piece
of IO code without it looping infinitely.

So, in short, how do I do this without getting into an infinite loop:

tpdfs :: (Int, Int) - IO [Int]
tpdfs (low, high) = do
  first - getStdRandom (randomR (low, high))
  second - getStdRandom (randomR (low, high))
  let r = (first + second) `div` 2
  rest - tpdfs (low, high)
  return (r : rest)

Caller site:

do
  nums - tpdfs (2, 12)
  let ns = take 7 nums

Niko


I did not look at it long enough to tell you why there is an infinite
loop. However, think about it on a high level with me.

You want a stream of these random numbers (I'm not sure what a
triangular distribution is, but that's okay). To get one of these, you
take two random numbers and perform a combination function (\x y - (x
+ y) `div` 2 ) on them.

So you can lift this from one random numbers to a stream of random
numbers if you have have two streams of random numbers instead of just
two random numbers. zipWith is the function that brings us from one
number to a stream of numbers.

tpdfs range = do
  g - newStdGen   -- get a random generator
  (g1, g2) - return $ split g   -- make two random generators out of it
  return $ zipWith combine (randomRs range g1) (randomRs range g2)
-- get two streams of random numbers, and combine them elementwise.

combine x y = (x + y) `div` 2

Uh, I know that's a very poor explanation, but hopefully it gives you
an alternate way to look at the problem.
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Re: Haskell shootout game

2007-07-16 Thread David LaPalomento

On 7/16/07, Claus Reinke [EMAIL PROTECTED] wrote:


 There are lots of robot battle games out there, like
 but none in Haskell, of course.

do the icfp contests count? not even limited to haskell, and
there were several tasks that look related, including:

http://alliance.seas.upenn.edu/~plclub/cgi-bin/contest/ants.html

http://icfpc.plt-scheme.org/spec.html

http://web.cecs.pdx.edu/%7Esheard/2002IcfpContest/task.html


claus



Perhaps it would be interesting to generalize the notion of a 'game' so that
programmers could design their own simple games to compete in as well as
designing game-playing agents?  I'm not sure if this presents problems as
far as running untrusted code but it would add a lot of appeal to the site
in my mind.  If designed right, the agents could be run against multiple
games; seeing a hierarchy of agent performance across a number of different
challenges would be very cool.

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


Re: [Haskell-cafe] Maintaining the community

2007-07-16 Thread Malcolm Wallace
Alex Queiroz [EMAIL PROTECTED] wrote:

  This is so much true. It has the effect of disguising Haskell as
 a PhD-only language.

And what would be wrong with Haskell being a PhD-only language, if it
were true?

OK, so I'm not genuinely suggesting that you must possess or be studying
for a PhD, to grok Haskell.  But I find nothing alarming about the
suggestion that one needs a fairly high level of intelligence, and some
training, in order to be able to use Haskell effectively.

After all, we would expect the same attributes (intelligence and
training) from a neurosurgeon, a nuclear scientist, or someone who
calculates how to land a person on the moon.  Programming computers may
not seem very skilled to most people, but maybe that is simply because
we are so familiar with it being done so badly.  I'm all for improving
the quality of software, and the corollary is that that means improving
the quality of programmers (by stretching our brains!).

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


Re: [Haskell-cafe] Maintaining the community

2007-07-16 Thread Alex Queiroz

Hallo,

On 7/16/07, Malcolm Wallace [EMAIL PROTECTED] wrote:


OK, so I'm not genuinely suggesting that you must possess or be studying
for a PhD, to grok Haskell.  But I find nothing alarming about the
suggestion that one needs a fairly high level of intelligence, and some
training, in order to be able to use Haskell effectively.



If I say I'm not stupid, would you believe me? I'm not saying
that Visual Basic-level programmers should be able to understand
haskell without a lot more studying and practice. What I'm saying is
that almost every topic in Haskell Café evolves into a very high level
discussion that may frighten some beginners, as it seems that without
a PhD in programming languages and category theory, the language is
not for you.

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


Re: [Haskell-cafe] Haskell monads for newbies

2007-07-16 Thread Andrew Coppin

Donald Bruce Stewart wrote:

andrewcoppin:
  

I saw a quote somewhere round here that went like this:

 Haskell isn't really suited to heavily I/O-oriented programs.
 What, you mean like darcs?
 ...oh yeah.




Great quote! :)
  


TY. :-)

Be even greater if I could remember who the heck said it... (It's 
probably a #haskell quote from the Humour section on the Wiki, as a guess.)


Actually, thinking about it, if you wanted to demonstrate just how badly 
Haskell sucks at I/O, we have:


- Darcs
- XMonad
- Lambdabot
- Frag
- Wasn't there a stand-alone HTTP server somewhere?
- GHC (provides make-like functionallity, and also invokes half a dozen 
external programs to do its work)

- Any others?

Yep, I'd say that's pretty conclusive. ;-)

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


Re: [Haskell-cafe] can't build hIDE

2007-07-16 Thread Salvatore Insalaco


src/Hide/Plugin/LoaderMidLevel.hs:126:26: Not in scope: `moduleFS'




hIDE uses low-level GHC APIs to do some of its tricks. Unfortunately, GHC
APIs change faster than hIDE, so the last version of hIDE is not compatible
with GHC 6.6.

As far as I know, in GHC 6.6 moduleFS has been renamed moduleNameFS. You can
try to replace moduleFS with moduleNameFS on line 126 in
src/Hide/Plugin/LoaderMidLevel.hs, and try to recompile.

Tell me if you manage to compile it with this fix, hIDE authors could be
interested.

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


Re: [Haskell-cafe] When is extra-libraries config in .cabal

2007-07-16 Thread Edward Ing

Before solving the problem, GHC builds would proceed fine. The link
problem occurred during runtime.

What libraries on the Windows operating would the build have succeeded
on? Win32 Api -- do those have the standard C functions.

If these libraries are available, I wonder why the link failed during runtime.

(There is a libmsvcrt.a under  c:\ghc\ghc-6.6.1\gcc-lib, should this
have played a role? )

Edward Ing




On unix the C compiler generally links to the standard C library without
you having to ask for it explicitly.

I'm not sure that if we automatically linked to msvcrt that everyone
would be happy. Many people seem to think msvcrt is to be avoided in
preference of 'native' win32 calls.

 Information for understanding this problem would be great.

This is a slightly tricky problem because the names of the libraries to
link to are different on different operating systems.

We don't have a proper solution to this at the moment. I'm posting this
to the cabal-devel list in case anyone has any good practical realistic
suggestions.

Duncan



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


[Haskell-cafe] Re: Help with IO and randomR

2007-07-16 Thread Niko Korhonen
Bryan Burgers wrote:
 Uh, I know that's a very poor explanation, but hopefully it gives you
 an alternate way to look at the problem.

Yes, this was extremely helpful, thank you very much. The moments where
one realizes that a large piece of clumsy code can be replaced with a
simple high-level function application seem to be an integral part of
learning Haskell. This time it was zipWith. Previously (for me) it has
been the folds :)

I know that in Haskell there almost always is a high-level solution to a
recursive problem (the legendary here's a one-line fold that replaces
your entire program), but sometimes it can be very difficult to see,
especially if IO is involved.

Niko

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


[Haskell-cafe] Re: Haskell for categorists

2007-07-16 Thread Dave Bayer
Miguel Mitrofanov miguelimo38 at yandex.ru writes:

 There are a lot of tutorials ensuring the reader that, although
 Haskell is based on category theory, you don't have to know CT to use
 Haskell. So, is there ANY Haskell tutorial for those who do know CT?

If you know category theory, it's a good bet that you're used to learning new
subjects by reading research papers. You may even subscribe to the old acorn
that it's best to read original sources.

One can't learn Haskell _just_ by reading papers, but it sure helps give
perspective on how Haskell came to be, which in turn helps Haskell make more
sense. Go read the original papers suggesting that category theory might be
helpful in functional programming. Then try to find monads in the classic
category theory textbooks, and stare at the surrounding pages.

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


[Haskell-cafe] Re: Maintaining the community

2007-07-16 Thread apfelmus
Alex Queiroz wrote:
 On 7/16/07, Malcolm Wallace [EMAIL PROTECTED] wrote:

 OK, so I'm not genuinely suggesting that you must possess or be studying
 for a PhD, to grok Haskell.  But I find nothing alarming about the
 suggestion that one needs a fairly high level of intelligence, and some
 training, in order to be able to use Haskell effectively.
 
 What I'm saying is that almost every topic in Haskell Café evolves
 into a very high level discussion that may frighten some beginners,
 as it seems that without a PhD in programming languages and category
 theory, the language is not for you.

  read . takeWhile (not . frightening)

;)

Personally, I perceive Haskell as being easier than every other
programming language. In other words, if Haskell requires a PhD, Visual
Basic requires a Nobel Prize. How the heck do imperative programmers
produce working code and how are they able to read the resulting mess
afterwards? I just don't get it :)

To be serious, those frightening things are often very simple concepts
but will remain frightening if not explained well. My experience is that
wikis, blog posts and online tutorials can't replace a textbook-quality,
well, textbook. Unless the online materials are textbook-quality as
well, of course. Really, the best way to learn Haskell (and most other
things) is to read/buy/borrow a textbook.

This also applies to the mailing list and the cache of answers for
optimization volume. One example is the hGetContents - hClose
question. I think that most people encountering this problem won't
realize on the first try that hGetContents is the culprit. But how to
formulate a good search query then? In the end, I think that the best
way to avoid trouble with hGetContents is to be introduced to it in a
textbook chapter IO and Files.

Regards,
apfelmus

PS: hGetContents-hClose is particularly strange since you need
operational semantics of lazy evaluation to understand it.

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


RE: [Haskell-cafe] Haskell shootout game

2007-07-16 Thread Re, Joseph (IT)
Interestingly enough, we're doing something very similar for [EMAIL PROTECTED]'s
2007 MechMania XIII contest (http://en.wikipedia.org/wiki/Mechmania), an
AI competition hosted during our annual Reflections Projections
conference.
 
  I can't release too many details until the day of the contest (Oct
13), but it's tactical, grid based combat game where you get one day to
write an AI (while testing in a pre-arena of sorts that is rendered to a
video wall in the middle of the conference building's atrium) and then
the next morning we run a (usually double elimination) tournament and
display all the simulations on a giant projector.  You can look at
screenshots / client API docs from 2006 as an example until we post the
details the night of the contest.
 
  After the contest we post results, (hopefully) clean up the code, and
release it for people to play with.  We're not professionals, nor do we
mainly write games, but it should be clean enough for someone to modify
and play around with.
 
   I guess it goes without saying that you can actually enter the
contest proper by coming to the conference if you happen to live in the
middle of nowhere (Champaign-Urbana, IL USA).  Registration will be up
(www.acm.uiuc.edu/conference/) towards the end of summer.



From: [EMAIL PROTECTED]
[mailto:[EMAIL PROTECTED] On Behalf Of Hugh Perkins
Sent: Sunday, July 15, 2007 2:47 PM
To: haskell-cafe
Subject: [Haskell-cafe] Haskell shootout game


Had an idea: a real shootout game for Haskell.

The arena itself comprises:
- a 2d grid, of a certain size (or maybe variable size) 
- each grid cell can be a wall, or one of the opponents
- the boundaries of the grid are walls
- random blocks of wall are placed around the grid

This can run on a hosted webserver probably, because each match is part
of a webpage request, and lasts a maximum of about a second, so shouldnt
be terminated prematurely by cpu-monitoring scripts.


NOTICE: If received in error, please destroy and notify sender. Sender does not 
intend to waive confidentiality or privilege. Use of this email is prohibited 
when received in error.
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


RE: [Haskell-cafe] Haskell shootout game

2007-07-16 Thread Joachim Breitner
Hi,

a similar variation of the idea can be found on 
http://infon.dividuum.de
A nice feature o this game is that you can upload the (lua) code while
the game is running, so the rounds tend to be quite long (~1h maybe) and
the people can adjust their AI constantly.

It was very popular at the last two GPN conferences in Karlsruhe.

Greetings,
Joachim


Am Montag, den 16.07.2007, 11:31 -0400 schrieb Re, Joseph (IT):
 Interestingly enough, we're doing something very similar for [EMAIL 
 PROTECTED]'s
 2007 MechMania XIII contest (http://en.wikipedia.org/wiki/Mechmania), an
 AI competition hosted during our annual Reflections Projections
 conference.
  
   I can't release too many details until the day of the contest (Oct
 13), but it's tactical, grid based combat game where you get one day to
 write an AI (while testing in a pre-arena of sorts that is rendered to a
 video wall in the middle of the conference building's atrium) and then
 the next morning we run a (usually double elimination) tournament and
 display all the simulations on a giant projector.  You can look at
 screenshots / client API docs from 2006 as an example until we post the
 details the night of the contest.
  
   After the contest we post results, (hopefully) clean up the code, and
 release it for people to play with.  We're not professionals, nor do we
 mainly write games, but it should be clean enough for someone to modify
 and play around with.
  
I guess it goes without saying that you can actually enter the
 contest proper by coming to the conference if you happen to live in the
 middle of nowhere (Champaign-Urbana, IL USA).  Registration will be up
 (www.acm.uiuc.edu/conference/) towards the end of summer.
 
 
 
 From: [EMAIL PROTECTED]
 [mailto:[EMAIL PROTECTED] On Behalf Of Hugh Perkins
 Sent: Sunday, July 15, 2007 2:47 PM
 To: haskell-cafe
 Subject: [Haskell-cafe] Haskell shootout game
 
 
 Had an idea: a real shootout game for Haskell.
 
 The arena itself comprises:
 - a 2d grid, of a certain size (or maybe variable size) 
 - each grid cell can be a wall, or one of the opponents
 - the boundaries of the grid are walls
 - random blocks of wall are placed around the grid
 
 This can run on a hosted webserver probably, because each match is part
 of a webpage request, and lasts a maximum of about a second, so shouldnt
 be terminated prematurely by cpu-monitoring scripts.
 
 
 NOTICE: If received in error, please destroy and notify sender. Sender does 
 not intend to waive confidentiality or privilege. Use of this email is 
 prohibited when received in error.
 ___
 Haskell-Cafe mailing list
 Haskell-Cafe@haskell.org
 http://www.haskell.org/mailman/listinfo/haskell-cafe

-- 
Joachim nomeata Breitner
  mail: [EMAIL PROTECTED] | ICQ# 74513189 | GPG-Key: 4743206C
  JID: [EMAIL PROTECTED] | http://www.joachim-breitner.de/
  Debian Developer: [EMAIL PROTECTED]
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] Re: Re[8]: In-place modification

2007-07-16 Thread Aaron Denney
On 2007-07-16, Bulat Ziganshin [EMAIL PROTECTED] wrote:
 once i summed up my experience - you may either write
 1) high-level code, which is written 10x faster than in C but works
 100x slower
 2) low-level code that is written 3x slower than in C and works 3x
 slower too

Well, replace you may with Bulat may, and I'll agree.

I'd call the low-level code about equal writing time.  People's milage
will vary enormously.

-- 
Aaron Denney
--

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


[Haskell-cafe] Re: Clearly, Haskell is ill-founded

2007-07-16 Thread apfelmus
Conor McBride wrote:
 To that end, an exercise. Implement a codata type
 
 data{-codata-} Mux x y = ...
 
 which intersperses x's and y's in such a way that
 
   (1) an initial segment of a Mux does not determine whether the next
 element is an x or a y (ie, no forced *pattern* of alternation)
 
   (2) there are productive coprograms
 
 demuxL :: Mux x y - Stream x
 demuxR :: Mux x y - Stream y
 
 (ie, alternation is none the less forced)
 
 You may need to introduce some (inductive) data to achieve this. If you
 always think always, then you need codata, but if you eventually think
 eventually, you need data.

- Spoiler warning: significant λs follow -

A very interesting exercise! Here's a solution:

 -- lists with at least one element
  data List1 x = One x | Cons x (List1 x)

  append :: List1 x - Stream x - Stream x
  append (One x) ys = x : ys
  append (Cons x xs) ys = x : prepend xs ys


 -- stream of alternating runs of xs and ys
  codata Mix x y = Stream (List1 x, List1 y)

  demixL ((xs,ys) : xys) = xs `append` demixL xys
  demixR ((xs,ys) : xys) = ys `append` demixR xys

 -- remove x-bias
  codata Mux x y = Either (Mix x y) (Mix y x)

  demuxL (Left  xys) = demixL xys
  demuxL (Right yxs) = demixR yxs

  demuxR (Left  xys) = demixR xys
  demuxR (Right yxs) = demixL yxs


A non-solution would simply be the pair (Stream x, Stream y), but this
doesn't capture the order in which xs and ys interleave. I think this
can be formalized with the obvious operations

  consL :: x - Mux x y - Mux x y
  consR :: y - Mux x y - Mux x y

by requiring that they don't commute

  consL x . consR y ≠ consR y . consL x

Or rather, one should require that the observation

  observe :: Mux x y - Stream (Either x y)

respects consL and consR:

  observe . consL x = (Left  x :)
  observe . consR y = (Right y :)


Regards,
apfelmus

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


Re[2]: [Haskell-cafe] Maintaining the community

2007-07-16 Thread Bulat Ziganshin
Hello Malcolm,

Monday, July 16, 2007, 4:52:01 PM, you wrote:

 After all, we would expect the same attributes (intelligence and
 training) from a neurosurgeon, a nuclear scientist, or someone who
 calculates how to land a person on the moon.  Programming computers may
 not seem very skilled to most people, but maybe that is simply because
 we are so familiar with it being done so badly.

are you ever tried, for example, programming GUI applications using
WinAPI directly? it required serious skills but i don't think that we
lose too much with all the modern RAD tools

otoh, i don't think that Haskell by itself is too complex. i seen the
same complaints in the early GUI era, early OOP era. Haskell and
functional programming in whole just need to have larger teaching
base: courses, books and so on. and PhDs will always find some tricky
ideas just to prove that they are smarter than other people ;)

-- 
Best regards,
 Bulatmailto:[EMAIL PROTECTED]

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


Re: Re[6]: [Haskell-cafe] In-place modification

2007-07-16 Thread Derek Elkins
On Mon, 2007-07-16 at 11:53 +0100, Sebastian Sylvan wrote:
 On 16/07/07, Bulat Ziganshin [EMAIL PROTECTED] wrote:
  Hello Sebastian,
 
  Sunday, July 15, 2007, 9:05:14 PM, you wrote:
 
   As we've demonstrated there's nothing stopping you from writing
   imperative C-like algorithms in Haskell (just like C#), and there
   certainly wasn't any major performance difference
 
  as Donald mentioned, this test is just limited by cache speed, not by
  speed of code generated.
 
 But wouldn't you say that in general, if you spend the effort you can
 write low-level imperative algorithms in Haskell that perform
 reasonably well? Especially compared to e.g. C#? I think your own
 libraries demonstrate this!
 
 I'm not saying it's as convenient (see the recent thread about monad
 splices) to write low-level imperative code in Haskell, but using
 laziness in C# was hardly a walk on the beach either!
 So my point is that Haskell isn't geared towards low-level
 optimizations and performance, but in the few places where you do need
 it, you *can* get it (IMO for only moderately more inconvenience than
 you pay for *everything* in a low-level imperative language). Whereas
 C# is a bit the other way around (easy to modify state, inconvenient
 to write high-level/lazy/concurrent/etc. code), though something like
 C is even more the other way around.
 

Ah, the secret of Haskell is to make low-level-looking code run slower
than high level code so that people write high-level code.

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


Re: Re[6]: [Haskell-cafe] In-place modification

2007-07-16 Thread Martin Coxall


Ah, the secret of Haskell is to make low-level-looking code run slower
than high level code so that people write high-level code.



The secret of programming is to know which tools to use for which job.
If you're writing device drivers in Visual Basic, you've made a
strategic misstep and need to re-evaluate.

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


Re: [Haskell-cafe] Re: Haskell for categorists

2007-07-16 Thread Derek Elkins
On Mon, 2007-07-16 at 14:23 +, Dave Bayer wrote:
 Miguel Mitrofanov miguelimo38 at yandex.ru writes:
 
  There are a lot of tutorials ensuring the reader that, although
  Haskell is based on category theory, you don't have to know CT to use
  Haskell. So, is there ANY Haskell tutorial for those who do know CT?
 
 If you know category theory, it's a good bet that you're used to learning new
 subjects by reading research papers. You may even subscribe to the old acorn
 that it's best to read original sources.
 
 One can't learn Haskell _just_ by reading papers, but it sure helps give
 perspective on how Haskell came to be, which in turn helps Haskell make more
 sense. Go read the original papers suggesting that category theory might be
 helpful in functional programming. 


 Then try to find monads in the classic
 category theory textbooks, and stare at the surrounding pages.

This is likely to be useless (in that particular connection).

But by all means, Moggi's Notions of Computation is good and anything by
Wadler can safely be assumed to be good in both quality in presentation.
In fact, bringing in aspects from another thread, I wonder how many
newbies never touch the research papers simply because they are
research papers and they assume them to be scary (a good dose of Wadler
or Peyton-Jones will dispel that).

As to the original question: there is nothing that's explicitly a
tutorial for categorists (why would there be?), but many papers do use
that perspective such as Jeremy Gibbons Calculating Functional
Programs.

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


Re: Re[6]: [Haskell-cafe] In-place modification

2007-07-16 Thread Derek Elkins
On Mon, 2007-07-16 at 17:41 +0100, Martin Coxall wrote:
 
  Ah, the secret of Haskell is to make low-level-looking code run slower
  than high level code so that people write high-level code.
 
 
 The secret of programming is to know which tools to use for which job.
 If you're writing device drivers in Visual Basic, you've made a
 strategic misstep and need to re-evaluate.

That  sounds like a challenge.

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


Re: [Haskell-cafe] Re: Clearly, Haskell is ill-founded

2007-07-16 Thread Stefan Holdermans

Conor's exercise:


To that end, an exercise. Implement a codata type

data{-codata-} Mux x y = ...

which intersperses x's and y's in such a way that

  (1) an initial segment of a Mux does not determine whether the next
element is an x or a y (ie, no forced *pattern* of alternation)

  (2) there are productive coprograms

demuxL :: Mux x y - Stream x
demuxR :: Mux x y - Stream y

(ie, alternation is none the less forced)

You may need to introduce some (inductive) data to achieve this. If  
you
always think always, then you need codata, but if you eventually  
think

eventually, you need data.


I came up with:

  data Stream a = ConsS a (Stream a) -- CODATA
  data Mux a b  = Mux (L a b) (R a b) (Mux a b)  -- CODATA

  data L a b = LL a | LR b (L a b)
  data R a b = RL a (R a b) | RR b

  lastL  :: L a b - a
  lastL (LL x)   =  x
  lastL (LR y l) =  lastL l

  initL  :: L a b - Stream b - Stream b
  initL (LL x)   =  id
  initL (LR y l) =  ConsS y . initL l

  lastR  :: R a b - b
  lastR (RL x r) =  lastR r
  lastR (RR y)   =  y

  initR  :: R a b - Stream a - Stream a
  initR (RL x r) =  ConsS x . initR r
  initR (RR y)   =  id

  demuxL :: Mux a b - Stream a
  demuxL (Mux l r m) =  ConsS (lastL l) (initR r (demuxL m))

  demuxR :: Mux a b - Stream b
  demuxR (Mux l r m) =  initL l (ConsS (lastR r) (demuxR m))

Cheers,

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


[Haskell-cafe] -O2 compile option can give speed increase over -O. Fasta shootout program test runs.

2007-07-16 Thread Richard Kelsall

I have been playing with the Fasta program in the shootout to see if
I can make it umm faster. Starting from dons program on this page and
adding some timing calculations as suggested on this wiki page

http://shootout.alioth.debian.org/gp4/benchmark.php?test=fastalang=ghcid=2
http://www.haskell.org/haskellwiki/Timing_computations

I added different OPTIONS into the top line of the program did a
ghc --make fasta.hs   and ran it each time with  fasta 250
(This is one tenth of the shootout figure.) These runs all keep the
existing OPTIONS of  -fbang-patterns -fexcess-precision

  Seconds   OPTIONS Added
  ---   -
   40.5
   40.5-funbox-strict-fields
   40.4  {-# INLINE rand #-}
   17.2-O
   17.0-O  -fvia-C
   14.4-O  -optc-march=pentium4
   11.5-O2
   11.2-O3
   11.5-O3   {-# INLINE rand #-}
   11.3-O2 -optc-march=pentium4

There was a bit of variation, I've averaged over two runs. This is on
an Intel Pentium D 2.66GHz running W2K and GHC 6.6.1.

It seems the -O2 option can give a significant speed increase relative
to just the -O option. This is contrary to the documentation which says

http://www.haskell.org/ghc/docs/latest/html/users_guide/options-optimise.html
http://www.haskell.org/ghc/docs/latest/html/users_guide/faster.html

it won't make any difference. I guess it's program, architecture and
operating system specific, but according to these figures the -O2 option
seems well worth a try for programs that need speed. It may be that
we sacrifice bounds checking or something important with -O2, I don't
know.


Richard.

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


Re: [Haskell-cafe] Re: Clearly, Haskell is ill-founded

2007-07-16 Thread Stefan Holdermans

I wrote:


I came up with [...]


apfelmus' solution is of course more elegant, but I guess it boils  
down to the same basic idea.


Cheers,

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


Re: [Haskell-cafe] problem with IO, strictness, and let

2007-07-16 Thread Tim Newsham

The problem is that you're closing the file twice.  When you call any
function of the getContents family, you assign to that function the
responsibility to close the file, no sooner than it is no longer needed.
Don't call hClose yourself, Bad Things will happen.


If you close the file, the stream will suddenly end.  I believe silent
data corruption is worse than a crash :)  (currently, hGetContents also
truncates on I/O error, but that's much less common and syslog will tell
you about it anyway)


Why can't hClose be more... um... lazy?


Stefan


Tim Newsham
http://www.thenewsh.com/~newsham/
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] can't build hIDE

2007-07-16 Thread Vadim
Salvatore Insalaco wrote:


 src/Hide/Plugin/LoaderMidLevel.hs:126:26: Not in scope: `moduleFS'




 hIDE uses low-level GHC APIs to do some of its tricks. Unfortunately, GHC
 APIs change faster than hIDE, so the last version of hIDE is not
 compatible
 with GHC 6.6.

 As far as I know, in GHC 6.6 moduleFS has been renamed moduleNameFS.
 You can
 try to replace moduleFS with moduleNameFS on line 126 in
 src/Hide/Plugin/LoaderMidLevel.hs, and try to recompile.


thanks for the help.

I still get errors, though:

[5 of 6] Compiling Hide.Plugin.LoaderMidLevel (
src/Hide/Plugin/LoaderMidLevel.hs, dist/build/Hide/Plugin/LoaderMidLevel.o )

src/Hide/Plugin/LoaderMidLevel.hs:98:35:
Couldn't match expected type `SrcSpan'
   against inferred type `UnlinkedBCO'
In the second argument of `linkExpr', namely `unlinked'
In a 'do' expression: hvalue - linkExpr hscEnv unlinked
In the expression:
do name - fmap expectOneName (parseName session symbol)
   Just tything - lookupName session name
   let globalId = getGlobalId tything
   hscEnv - sessionHscEnv session
   unlinked - coreExprToBCOs (hsc_dflags hscEnv) (Var globalId)
   hvalue - linkExpr hscEnv unlinked
   return (hvalue, idType globalId)

src/Hide/Plugin/LoaderMidLevel.hs:126:40:
Couldn't match expected type `ModuleName'
   against inferred type `Module'
In the first argument of `moduleNameFS', namely `(nameModule n)'
In the first argument of `zEncodeFS', namely
`(moduleNameFS (nameModule n))'
In the first argument of `unpackFS', namely
`(zEncodeFS (moduleNameFS (nameModule n)))'

setup build failed for packages/hidePlugin


Thanks once again!

Vadim.

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


Re: Re[6]: [Haskell-cafe] In-place modification

2007-07-16 Thread Sebastian Sylvan

On 16/07/07, Derek Elkins [EMAIL PROTECTED] wrote:

On Mon, 2007-07-16 at 17:41 +0100, Martin Coxall wrote:
 
  Ah, the secret of Haskell is to make low-level-looking code run slower
  than high level code so that people write high-level code.
 

 The secret of programming is to know which tools to use for which job.
 If you're writing device drivers in Visual Basic, you've made a
 strategic misstep and need to re-evaluate.

That  sounds like a challenge.


Well they've been written in both Haskell[1], and C#[2], so VB might
not be out of the realm of possibility (in fact, I think any language
that compiles to CIL is fine for [2])!


[1] http://programatica.cs.pdx.edu/House/
[2] http://programatica.cs.pdx.edu/House/

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


Re: Re[6]: [Haskell-cafe] In-place modification

2007-07-16 Thread Sebastian Sylvan

On 16/07/07, Sebastian Sylvan [EMAIL PROTECTED] wrote:

On 16/07/07, Derek Elkins [EMAIL PROTECTED] wrote:
 On Mon, 2007-07-16 at 17:41 +0100, Martin Coxall wrote:
  
   Ah, the secret of Haskell is to make low-level-looking code run slower
   than high level code so that people write high-level code.
  
 
  The secret of programming is to know which tools to use for which job.
  If you're writing device drivers in Visual Basic, you've made a
  strategic misstep and need to re-evaluate.

 That  sounds like a challenge.

Well they've been written in both Haskell[1], and C#[2], so VB might
not be out of the realm of possibility (in fact, I think any language
that compiles to CIL is fine for [2])!


[1] http://programatica.cs.pdx.edu/House/
[2] http://programatica.cs.pdx.edu/House/



[2] http://research.microsoft.com/os/singularity/

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


Re: Re[6]: [Haskell-cafe] In-place modification

2007-07-16 Thread Martin Coxall

 Well they've been written in both Haskell[1], and C#[2], so VB might
 not be out of the realm of possibility (in fact, I think any language
 that compiles to CIL is fine for [2])!


Ah, but that's really VB.Net rather than proper Old School VB. VB.Net
is just C# in a flowery frock.

My point stands though, although you can write any program in any
Turing-complete language, doesn't mean you *should*.

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


Re: [Haskell-cafe] Re: Re[4]: In-place modification

2007-07-16 Thread Hugh Perkins

On 7/16/07, Bulat Ziganshin [EMAIL PROTECTED] wrote:


 Topcoder certainly isn't about benchmarking.  Undoubtedly, it would be
 absolutely awesome to be able to use Haskell in topcoder... but it
 wouldn't say anything about speed.  My guess is that practically no
 topcoder submissions fail by exceeding the allowable time limit.  The
 competition (the alg one, which is the only one anyone really cares
 about) is about solving problems quickly (in programmer time) and
 accurately.

that's ideal for haskell. like ICFP, if they will allow haskell code,
then all winer solutions will be written using it



Careful. Although writer's solution (the reference solution) must run in
under 1 second in Java, many problems run really close to the 2-second limit
in practice.  That means if your language is inherently 30% slower, you may
fail the harder problems.
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] xkcd #287 NP-Complete

2007-07-16 Thread Hugh Perkins

On 7/16/07, Tom Pledger [EMAIL PROTECTED] wrote:


I'll be a nuisance and bring up this case:

 solve 150005 [2, 4, 150001]



Argh, that makes my solution hang! :-/
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Re: xkcd #287 NP-Complete

2007-07-16 Thread Hugh Perkins

On 7/16/07, Chung-chieh Shan [EMAIL PROTECTED] wrote:


Here's my solution to the xkcd problem (yay infinite lists):



dynamic programming?

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


Re: [Haskell-cafe] Re: xkcd #287 NP-Complete

2007-07-16 Thread Hugh Perkins

Your solution looks really elegant, and runs insanely fast.  Can you explain
how it works?
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] maybe OT: open standards: ooxml, are haskellers interested ?

2007-07-16 Thread Marc Weber
At the moment I only know of questions about interfacing the API of
Microsoft office eg using COM technology.

This shows that at least some haskellers are interested in office
documents.

That's why I want to mention
www.noooxml.org

Summary:
Microsoft wants to create a new ISO standard for its OOXML format which
you will never be able to implement completely. 
It's also about 6000 pages compared to 600 pages (ODT, OpenOffice is
using this)

Most haskell libraries are kind of open source. If tey weren't haskell
wouldn't be that appealing.

More information about topics like this can be found on www.ffii.org

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


[Haskell-cafe] Re: xkcd #287 NP-Complete

2007-07-16 Thread apfelmus
Tom Pledger wrote:
 We've seen some nice concise solutions that can deal with the original
 problem:
 
 solve 1505 [215, 275, 335, 355, 420, 580]
 
 I'll be a nuisance and bring up this case:
 
 solve 150005 [2, 4, 150001]
 
 A more scalable solution is to use an explicit heap that brings together
 all the ways to get to each partial sum.  I coded one using Data.Map,
 but it's a bit long-winded and ugly.

How about

  import Data.Map as Map

  xkcd purse xs = foldl' (flip add) (Map.fromList [(0,[])]) xs ! purse
where
add price = Map.unionsWith (++)
  . take (purse `div` price + 1) . iterate (additem price)

additem price = Map.map (map (price:))
  . Map.mapMaybeWithKey clip
  . Map.mapKeysMonotonic (price +)
clip cost x = if cost = purse then Just x else Nothing

Regards,
apfelmus

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


Re: [Haskell-cafe] Maintaining the community

2007-07-16 Thread Hugh Perkins

On 7/16/07, Malcolm Wallace [EMAIL PROTECTED] wrote:


After all, we would expect the same attributes (intelligence and
training) from a neurosurgeon, a nuclear scientist, or someone who
calculates how to land a person on the moon.  Programming computers may
not seem very skilled to most people, but maybe that is simply because
we are so familiar with it being done so badly.  I'm all for improving
the quality of software, and the corollary is that that means improving
the quality of programmers (by stretching our brains!).



You want people doing difficult expensive high-risk tasks to be intelligent
and well trained, but you want their task to be as easy as possible.

Would you rather a nuclear reactor needs to be controlled by feeding in
punch cards, or by having a big round dial labelled power, that you can
move from 0 to 200 MegaWatts?  Of course, you'd like the guy moving that
dial to be well trained and intelligent.  Welcome to why flying airlines is
well-paid and boring.
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Maintaining the community

2007-07-16 Thread Jonathan Cast
On Monday 16 July 2007, Hugh Perkins wrote:
 On 7/16/07, Malcolm Wallace [EMAIL PROTECTED] wrote:
  After all, we would expect the same attributes (intelligence and
  training) from a neurosurgeon, a nuclear scientist, or someone who
  calculates how to land a person on the moon.  Programming computers may
  not seem very skilled to most people, but maybe that is simply because
  we are so familiar with it being done so badly.  I'm all for improving
  the quality of software, and the corollary is that that means improving
  the quality of programmers (by stretching our brains!).

 You want people doing difficult expensive high-risk tasks to be intelligent
 and well trained, but you want their task to be as easy as possible.

 Would you rather a nuclear reactor needs to be controlled by feeding in
 punch cards, or by having a big round dial labelled power, that you can
 move from 0 to 200 MegaWatts?  Of course, you'd like the guy moving that
 dial to be well trained and intelligent.  Welcome to why flying airlines is
 well-paid and boring.

*For airline pilots.*  For most people, flying airliners is poorly-paid and 
quite exciting (at least up until the inevitable crash).  Haskell may be a 
PhD language, but (that is, it isn't, but even if it were) it's quite easy to 
work in for PhDs.  Which isn't at all the same thing as being easy to work in 
for VB programmers.

Jonathan Cast
http://sourceforge.net/projects/fid-core
http://sourceforge.net/projects/fid-emacs
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] problem with IO, strictness, and let

2007-07-16 Thread Matthew Brecknell
Tim Newsham:
 Why can't hClose be more... um... lazy?

Lazy in what way? hGetContents already closes the OS handle when it
reaches the end of file.

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


Re: [Haskell-cafe] Maintaining the community

2007-07-16 Thread Thomas Conway

On 7/16/07, Malcolm Wallace [EMAIL PROTECTED] wrote:


OK, so I'm not genuinely suggesting that you must possess or be studying
for a PhD, to grok Haskell.  But I find nothing alarming about the
suggestion that one needs a fairly high level of intelligence, and some
training, in order to be able to use Haskell effectively.


When I was a teenager I thought people with PhDs were minor deities.
Having done one, and knowing lots of people with them, I can tell you,
the vast majority of people with a PhD (including me)  have merely
above average intelligence. A PhD is not a mark of intelligence. It's
a mark of persistence. (Shall we say obsession?)

I think Malcolm's analogy to other professions is quite apt. If we
expect to be taken seriously as professionals, it would be
unsurprising to find that we need to engage in some strenuous [mental]
effort to acquire the skills.

And this is where I think Haskell has it all over C++, Java, and the
rest. Haskell is easy to learn at a simple level, and hard to learn at
the expert level, but once learned is very powerful and has excellent
payoffs in terms of productivity. With C++ or Java, the expertise is
somewhat easier to acquire, but you never get the payoff. And before
you all flame, yes, I do know C++ at an expert level, and that is
exactly why, after 7 years of writing server software in C++, I now
want to do it in Haskell.

cheers,
T
--
Dr Thomas Conway
[EMAIL PROTECTED]

Silence is the perfectest herald of joy:
I were but little happy, if I could say how much.
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] -O2 compile option can give speed increase over -O. Fasta shootout program test runs.

2007-07-16 Thread Donald Bruce Stewart
r.kelsall:
 I have been playing with the Fasta program in the shootout to see if
 I can make it umm faster. Starting from dons program on this page and
 adding some timing calculations as suggested on this wiki page
 
 http://shootout.alioth.debian.org/gp4/benchmark.php?test=fastalang=ghcid=2
 http://www.haskell.org/haskellwiki/Timing_computations
 
 I added different OPTIONS into the top line of the program did a
 ghc --make fasta.hs   and ran it each time with  fasta 250
 (This is one tenth of the shootout figure.) These runs all keep the
 existing OPTIONS of  -fbang-patterns -fexcess-precision
 
   Seconds   OPTIONS Added
   ---   -
40.5
40.5-funbox-strict-fields
40.4  {-# INLINE rand #-}
17.2-O
17.0-O  -fvia-C
14.4-O  -optc-march=pentium4
11.5-O2
11.2-O3
11.5-O3   {-# INLINE rand #-}
11.3-O2 -optc-march=pentium4
 
 There was a bit of variation, I've averaged over two runs. This is on
 an Intel Pentium D 2.66GHz running W2K and GHC 6.6.1.
 
 It seems the -O2 option can give a significant speed increase relative
 to just the -O option. This is contrary to the documentation which says
 
 http://www.haskell.org/ghc/docs/latest/html/users_guide/options-optimise.html
 http://www.haskell.org/ghc/docs/latest/html/users_guide/faster.html
 
 it won't make any difference. I guess it's program, architecture and
 operating system specific, but according to these figures the -O2 option
 seems well worth a try for programs that need speed. It may be that
 we sacrifice bounds checking or something important with -O2, I don't
 know.

Yes, -O2 is getting better, as new optimisations like SpecConstr are
enabled by it. For shootout problems, I'd selectively test with -O2, and
if it is better, use that.

Good work! And yes, I see that it is currently compiled with:

-O fbang-patterns -fexcess-precision  -fglasgow-exts  -optc-march=pentium4

if -O2 is consistently better here, then we could happily switch.

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


[Haskell-cafe] Re: ANNOUNCE: CC-delcont-0.1; Delimited continuations for Haskell

2007-07-16 Thread Dan Doel
Hello again,

I apologize for replying to myself, but since no one else is talking to me, I 
suppose I have no choice. :)

Anyhow, in case some people were intrigued, but simply didn't speak up (and 
because I was interested in seeing how easily it could be done), I took the 
liberty of implementing a version of the parser inverter that mimics the 
OCaml semantics pretty closely (I think). As I mentioned, this involves 
making a list data type that incorporates monads, so that it can be lazy in 
the side effects used to produce it. In short it looks like this:

data MList' m a = MNil | MCons a (MList m a)
type MList m a = m (MList' m a)

So, each list tail (including the entire list) is associated with a side 
effect, which has the ultimate effect that you can build lists in ways such 
as:

toMList :: Monad m = m (Maybe t) - MList m t
toMList gen = gen = maybe nil (`cons` toMList gen)

This is the MList analogue of the toList function from the previous list 
(slightly modified here to demonstrate the similarity):

toList :: Monad m = m (Maybe a) - m [a]
toList gen = gen = maybe (return []) (\c - liftM (c:) $ toList gen)

However, toList uses liftM, which will strictly sequence the effects (the 
recursive toList call has to complete before the whole list is returned), 
whereas toMList simply adds the *monadic action* to produce the rest of the 
list as the tail, and so the side effects it entails don't actually occur 
until a consumer asks to see that part of the list.

So, the proof is in the output. The sample program (source included as an 
attachment) demonstrates normal lexing (where the underlying monad is just 
IO) and inverted lexing (which uses delimited continuations layered over IO). 
The 'lexing' is just the 'words' function adapted to MLists (I thought about 
doing a full-on parser, but I think that'd require making the parser a monad 
transformer (essentially) over the base monad, which would be complex, to say 
the least). The relevant parts look like so:

normalLex :: IO ()
normalLex = printTokens
   (wordsML
  (liftList
 The quick brown fox jumps over the lazy dog))

reqLex :: CCT ans IO ()
reqLex = do p1 - begin
p2 - provideSome The quick brown  p1
pStrLn Break 1
p3 - provideSome fox jumps over  p2
pStrLn Break 2
p4 - provideSome the laz p3
pStrLn Break 3
provideSome y dog p4 = finish
pStrLn Rollback
provideSome iest dog p4 = finish
return ()

Which main invokes appropriately. Output looks like so:

Normal Lexing
-
The
quick
brown
fox
jumps
over
the
lazy
dog
-


Inverted Lexing
---
The
quick
brown
Break 1
fox
jumps
over
Break 2
the
Break 3
lazy
dog
Rollback
laziest
dog
---

So, success! Tokens are printed out as soon as the lexer is able to recognize 
them, properly interleaved with other IO side effects, and resuming from an 
intermediate parse does not cause duplication of output.

So, that wasn't really that hard to hack up. However, I should mention that it 
wasn't trivial, either. When converting list functions to MList functions, 
you have to be very careful not to perform side effects twice. For instance, 
my first pass gave output like:

...
he
uick
rown
Break 1
ox
...

Although it worked fine with the normal lexer. The culprit? I had written 
nullML like so:

nullML :: Monad m = MList m a - m Bool
nullML m = isNothing `liftM` uncons m

But in that version, testing for null, and then using the list performs side 
effects twice, and due to the way the delimited continuations produce MLists, 
characters were getting dropped! The correct version is:

nullML :: Monad m = MList m a - m (Bool, MList m a)
nullML m = uncons m = maybe (return (True, nil))
  (\(a,m') - return (False, a `cons` m'))

Which returns both whether the list is null, and a new list that won't perform 
a duplicate side effect. So, I guess what I'm saying is that reasoning about 
code with lots of embedded side effects can be difficult. :)

As a final aside, it should be noted that to get the desired effect (that is, 
laziness with interleaved side effects), it's important to make use of the 
monadic data structures as much as possible. For instance, wordsML produces 
not an (m [MList m a]) or MList m [a] or anything like that (although the 
latter may work), but an MList m (MList m a), which is important for the 
effects to be able to get a hold over printTokens. However, if you want to 
produce something that's not a list, say, a tree, you'll have to write an 
MTree, or, in general, one lazy-effectful data structure for 

[Haskell-cafe] Why does Data.Map exist when...

2007-07-16 Thread Tony Morris
-BEGIN PGP SIGNED MESSAGE-
Hash: SHA1

...it seems to be a special case of Set? Does Data.Map add anything more
useful than Map' below?

import Data.Set as Set

newtype MyPair a b = MP (a, b)
  deriving Show

instance (Eq a) = Eq (MyPair a b) where
  MP (a, _) == MP (a', _) = a == a'

instance (Ord a) = Ord (MyPair a b) where
  MP (a, _) `compare` MP(a', _) = a `compare` a'

type Map' k a = Set (MyPair k a)

- --
Tony Morris
http://tmorris.net/

-BEGIN PGP SIGNATURE-
Version: GnuPG v1.4.6 (GNU/Linux)
Comment: Using GnuPG with Mozilla - http://enigmail.mozdev.org

iD8DBQFGnDgEmnpgrYe6r60RAu4FAJ93Fwcx7ZX08+qO4ZlzRVV52TXpNQCeNr7u
ioq0XrWt/Wymfh52W1spiFk=
=FC5h
-END PGP SIGNATURE-
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Why does Data.Map exist when...

2007-07-16 Thread Dan Doel
On Monday 16 July 2007, Tony Morris wrote:
 ...it seems to be a special case of Set? Does Data.Map add anything more
 useful than Map' below?

Why does Data.Set exist when it's just a special case of Data.Map?

import Data.Map

type Set a = Map a ()

And, in fact, I think going this way doesn't lose any functionality, whereas 
implementing Map in terms of Set loses you stuff like unionWith (at least, 
barring your taking time to re-implement it specifically), which may or may 
not be a big deal to you (I think I've used it before, though).

The answer is, I suppose, that the interface is subtly different (and the 
semantics may be, too; are you sure that your insert using Set behaves the 
same way as insert on Map?), and when you're doing Set stuff, you don't want 
to be bugged by the fact that you're using a Map of ()s, and vice versa 
(although you could probably finesse things to the point where it wouldn't be 
noticeable).

The real question is why there's Data.Map and Data.IntMap, when the compiler 
should really be able to detect that we're using a certain key type, and 
automatically use the optimized Map for that key type without our having to 
do anything. And the answer to that is that maybe, in the future, that will 
be the case, once associated types/data families are widely available. :)

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


Re: [Haskell-cafe] Why does Data.Map exist when...

2007-07-16 Thread Matthew Brecknell
Tony Morris:
 ...it seems to be a special case of Set? Does Data.Map add anything more
 useful than Map' below?
 
 [... Map-like structure based on Data.Set ...]

Note that you could also attempt to go in the other direction (but see
the comments about strictness below):

 type Set' a = Data.Map.Map a ()

Certainly, Data.Map and Data.Set are very similar in their
implementations, but rather than seeing one as a specialisation of the
other, it's more helpful to see them both as specialisations of a basic
underlying binary tree structure. The specialisation occurs both in the
interfaces (for the convenience of the user), and in the implementations
(for efficiency).

For example, at the interface, consider how you would perform the
equivalent of Data.Map.lookup using your Map' type. You'll need a clever
combination of intersection, singleton and toList, with appropriate
lifting into an arbitrary monad.

If you look at the implementations, you'll note that, among other
things, the Data.Map.Map type is strict in the key, but not in the
associated value. Data.Set is not strict in the value, so your Map' type
will not be strict in its key. As well as improving the performance of
Data.Map, strictness in the key also helps avoid problems with memory
leaks.

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


Re: [Haskell-cafe] Why does Data.Map exist when...

2007-07-16 Thread Dan Weston

Your Map' (==) is lying! :)

Your definition purports to establish an equivalence class for all MP 
(key,value) with the same key, but MP(key,1) and MP(key,2) are not 
equivalent in any meaningful way outside the internals of Map' (else 
you could dispense with the payload entirely!)


Set is now not a representation of Map', but a co-representation. 
Details are exposed to outsiders to hide them from Map'. Everyone else 
pays so that Map' 's life is a little easier.


Contrast that with, say, a set represented by a list, with compare 
defined to sort before comparing. This is a meaningful (to outsiders) 
equivalence relation because it hides the internal representation 
artifact that lists have a (spurious) ordering.


IMHO the interface should represent the external properties, not some 
internal invariant. In short, Map' doesn't say what it mean and mean 
what it says. If you told me for a, b :: MyPair k v that a == b, I would 
(foolishly) expect that a = b. I suspect that I wouldn't be the only one 
to make that mistake.


Dan Weston

Tony Morris wrote:

-BEGIN PGP SIGNED MESSAGE-
Hash: SHA1

...it seems to be a special case of Set? Does Data.Map add anything more
useful than Map' below?

import Data.Set as Set

newtype MyPair a b = MP (a, b)
  deriving Show

instance (Eq a) = Eq (MyPair a b) where
  MP (a, _) == MP (a', _) = a == a'

instance (Ord a) = Ord (MyPair a b) where
  MP (a, _) `compare` MP(a', _) = a `compare` a'

type Map' k a = Set (MyPair k a)

- --
Tony Morris
http://tmorris.net/

-BEGIN PGP SIGNATURE-
Version: GnuPG v1.4.6 (GNU/Linux)
Comment: Using GnuPG with Mozilla - http://enigmail.mozdev.org

iD8DBQFGnDgEmnpgrYe6r60RAu4FAJ93Fwcx7ZX08+qO4ZlzRVV52TXpNQCeNr7u
ioq0XrWt/Wymfh52W1spiFk=
=FC5h
-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] -O2 compile option can give speed increase over -O. Fasta shootout program test runs.

2007-07-16 Thread Derek Elkins
On Tue, 2007-07-17 at 11:24 +1000, Donald Bruce Stewart wrote:
 r.kelsall:
  I have been playing with the Fasta program in the shootout to see if
  I can make it umm faster. Starting from dons program on this page and
  adding some timing calculations as suggested on this wiki page
  
  http://shootout.alioth.debian.org/gp4/benchmark.php?test=fasta〈=ghcid=2
  http://www.haskell.org/haskellwiki/Timing_computations
  
  I added different OPTIONS into the top line of the program did a
  ghc --make fasta.hs   and ran it each time with  fasta 250
  (This is one tenth of the shootout figure.) These runs all keep the
  existing OPTIONS of  -fbang-patterns -fexcess-precision
  
Seconds   OPTIONS Added
---   -
 40.5
 40.5-funbox-strict-fields
 40.4  {-# INLINE rand #-}
 17.2-O
 17.0-O  -fvia-C
 14.4-O  -optc-march=pentium4
 11.5-O2
 11.2-O3
 11.5-O3   {-# INLINE rand #-}
 11.3-O2 -optc-march=pentium4
  
  There was a bit of variation, I've averaged over two runs. This is on
  an Intel Pentium D 2.66GHz running W2K and GHC 6.6.1.
  
  It seems the -O2 option can give a significant speed increase relative
  to just the -O option. This is contrary to the documentation which says
  
  http://www.haskell.org/ghc/docs/latest/html/users_guide/options-optimise.html
  http://www.haskell.org/ghc/docs/latest/html/users_guide/faster.html
  
  it won't make any difference. I guess it's program, architecture and
  operating system specific, but according to these figures the -O2 option
  seems well worth a try for programs that need speed. It may be that
  we sacrifice bounds checking or something important with -O2, I don't
  know.
 
 Yes, -O2 is getting better, as new optimisations like SpecConstr are
 enabled by it. For shootout problems, I'd selectively test with -O2, and
 if it is better, use that.
 
 Good work! And yes, I see that it is currently compiled with:
 
 -O fbang-patterns -fexcess-precision  -fglasgow-exts  -optc-march=pentium4
 
 if -O2 is consistently better here, then we could happily switch.

Just to add as this was not addressed. -O2 -does not- turn off bounds
checking or any other obvious safety mechanism.

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