Re: [Haskell-cafe] (no subject)

2013-06-10 Thread Tobias Dammers
On Mon, Jun 10, 2013 at 05:41:05PM +0530, Zed Becker wrote:
 
  Haskell, is arguably the best example of a design-by-committee language.

You do realize that design-by-committee is generally understood to
refer to the antipattern where a committee discusses a design to death
and delivers an inconsistent, mediocre spec, as opposed to a situation
where a leader figure takes the loose ends, runs with them, and turns
them into a coherent, inspiring whole?

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


Re: [Haskell-cafe] (no subject)

2013-06-10 Thread Tom Ellis
On Mon, Jun 10, 2013 at 05:41:05PM +0530, Zed Becker wrote:
  Haskell, is arguably the best example of a design-by-committee language.
 The syntax is clean and most importantly, consistent. The essence of a
 purely functional programming is maintained, without disturbing its real
 world capacity.
 
  To all the people who revise the Haskell standard, and implement the
 language,
 
1.  Promise to me, and the rest of the community, that you will keep
up the good effort :)
2.  Promise to me, and the rest of the community, that Haskell will
always spiritually remain the same clean, consistent programming
language as it is now!

Hear hear!  Hopefully we, the Haskell community, will be able to support
this endevour with our time and efforts.

Tom

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


Re: [Haskell-cafe] (no subject)

2013-06-10 Thread Flavio Villanustre
Zed,

while I don't disagree regarding the clean and consistent syntax of
Haskell, do you realize that some people would argue that camels are horses
designed by committee too? :)

While designing by committee guarantees agreement across a large number of
people, it does not always ensure efficiency, as committees may lead to
poor compromises, sometimes.

However, Haskell may be an example of a good case of design-by-committee
computer language.

Flavio

Flavio Villanustre


On Mon, Jun 10, 2013 at 8:11 AM, Zed Becker zed.bec...@gmail.com wrote:

  Hi all,


  Haskell, is arguably the best example of a design-by-committee language.
 The syntax is clean and most importantly, consistent. The essence of a
 purely functional programming is maintained, without disturbing its real
 world capacity.


  To all the people who revise the Haskell standard, and implement the
 language,


1.

  Promise to me, and the rest of the community, that you will keep
  up the good effort :)
  2.

  Promise to me, and the rest of the community, that Haskell will
  always spiritually remain the same clean, consistent programming 
 language
  as it is now!


  Regards,

 Zed Becker

 ___
 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] (no subject)

2013-06-10 Thread Jerzy Karczmarczuk

Hm...

Haskell was /developed/ by teams, but we had BEFORE: hope, miranda, ML 
... The heritage is quite important.
And individuals (say, Mark Jones) contributed to Haskell constructs. So, 
the /design/ is not entirely committe based



1.

Promise to me, and the rest of the community, that
Haskell will always spiritually remain the same clean,
consistent programming language as it is now!


Yes.
Dear Mom, dear Dad! Promise me that you will never die...

I wish that for all of you.
Jerzy Karczmarczuk

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


Re: [Haskell-cafe] (no subject)

2013-06-10 Thread MigMit
It really sounds rude, to demand promises from somebody who just gave you a big 
present.

Отправлено с iPhone

10.06.2013, в 16:11, Zed Becker zed.bec...@gmail.com написал(а):

 Hi all,
 
 Haskell, is arguably the best example of a design-by-committee language. The 
 syntax is clean and most importantly, consistent. The essence of a purely 
 functional programming is maintained, without disturbing its real world 
 capacity.
 
 To all the people who revise the Haskell standard, and implement the language,
 Promise to me, and the rest of the community, that you will keep up the good 
 effort :)
 Promise to me, and the rest of the community, that Haskell will always 
 spiritually remain the same clean, consistent programming language as it is 
 now!
 
 Regards,
 Zed Becker
 ___
 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] (no subject)

2013-06-10 Thread Tom Ellis
On Mon, Jun 10, 2013 at 05:44:26PM +0400, MigMit wrote:
 It really sounds rude, to demand promises from somebody who just gave you a 
 big present.

Without wishing to preempt Zed Becker, I interpreted his email as an
expression of delight at how well Haskell has been designed and of hope that
it may endure, rather than literally as a demand for the Haskell committee
to grant him promises.  I hope I haven't misunderstood.

Tom

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


Re: [Haskell-cafe] (no subject)

2013-06-10 Thread Alberto G. Corona
I have ever wondered how a committee could have made Haskell.

My conclusion is the following:

For one side there were many mathematicians involved, the authors of the
most terse language(s) existent: the math notation.

For the other, the lemma avoid success at all costs which  kept the
committee away of pressures for doing it quick and dirty and also freed it
from deleterious individualities


2013/6/10 Tobias Dammers tdamm...@gmail.com

 On Mon, Jun 10, 2013 at 05:41:05PM +0530, Zed Becker wrote:
 
   Haskell, is arguably the best example of a design-by-committee language.

 You do realize that design-by-committee is generally understood to
 refer to the antipattern where a committee discusses a design to death
 and delivers an inconsistent, mediocre spec, as opposed to a situation
 where a leader figure takes the loose ends, runs with them, and turns
 them into a coherent, inspiring whole?

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




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


Re: [Haskell-cafe] (no subject)

2013-06-10 Thread Richard A. O'Keefe

On 11/06/2013, at 1:58 AM, Alberto G. Corona wrote:

 I have ever wondered how a committee could have made Haskell.

A committee made Algol 60, described as an improvement on most
of its successors.  A committee maintains Scheme.

On the other hand, an individual gave us Perl.
And an individual gave us JavaScript.
And let's face it, an individual gave C++ its big start.


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


Re: [Haskell-cafe] (no subject)

2012-01-05 Thread Antoine Latter
On Thu, Jan 5, 2012 at 10:54 AM, Christoph Breitkopf
chbreitk...@googlemail.com wrote:
 Hello,

 I'm trying to figure out how to handle versioning of my IntervalMap
 package. I've just read the package versioning
 policy: http://www.haskell.org/haskellwiki/Package_versioning_policy

 I don't quite understand all the recommendations in the above document,
 though:

 a) You are not allowed to remove or change the types of existing stuff. Ok.

 b) You are allowed to add new functions. But that can break compilation
 because of name conflicts. Seems to be allowed on the grounds that this is
 easy to fix in the client code.

This will never break clients who are using qualified imports, or only
importing the symbols they use, which is strongly recommended
behavior.


 c) You are not allowed to add new instances. I don't get this - how is this
 any worse than b)?

Unlike adding functions, there is no way for a client of your library
to control which instances they import.

Antoine


 I do understand that it is not generally possible to prevent breaking code
 - for example if the client code depends on buggy behavior that gets fixed
 in a minor version update. That seems unavoidable - after all, bugfixes are
 _the_ reason for minor updates.

 Regards,

 Chris

 ___
 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] (no subject)

2011-11-28 Thread Antoine Latter
On Mon, Nov 28, 2011 at 4:12 PM, Willem Obbens dub...@hotmail.com wrote:
 Hello,
 I get this error when I try to derive an instance of the Show typeclass:
 Abc.hs:21:60:
     Couldn't match expected type `Vector' with actual type `[Point]'
     In the first argument of `show'', namely `xs'
     In the second argument of `(++)', namely `show' xs'
     In the second argument of `(++)', namely `,  ++ show' xs'
 Failed, modules loaded: none.
 Here's the faulty code:
 newtype Point = Point Int
 instance Show Point where
    show (Point a) = [chr $ a + 48]

 data Vector = Vector [Point]
 instance Show Vector where
    show (Vector ys) =
       let show' (Vector [z])     = show z
           show' (Vector (x:xs))  = show x ++ ,  ++ show' xs
           show' (Vector [])      = []
       in  ( ++ show' ys ++ )

Here you're treating the value 'ys' as if its type was 'Vector', but
its type is '[Point]'.

Does that help?

Antoine

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


Re: [Haskell-cafe] (no subject)

2011-11-28 Thread Brent Yorgey
On Mon, Nov 28, 2011 at 04:20:54PM -0600, Antoine Latter wrote:
 On Mon, Nov 28, 2011 at 4:12 PM, Willem Obbens dub...@hotmail.com wrote:
  Hello,
  I get this error when I try to derive an instance of the Show typeclass:
  Abc.hs:21:60:
      Couldn't match expected type `Vector' with actual type `[Point]'
      In the first argument of `show'', namely `xs'
      In the second argument of `(++)', namely `show' xs'
      In the second argument of `(++)', namely `,  ++ show' xs'
  Failed, modules loaded: none.
  Here's the faulty code:
  newtype Point = Point Int
  instance Show Point where
     show (Point a) = [chr $ a + 48]
 
  data Vector = Vector [Point]
  instance Show Vector where
     show (Vector ys) =
        let show' (Vector [z])     = show z
            show' (Vector (x:xs))  = show x ++ ,  ++ show' xs
            show' (Vector [])      = []
        in  ( ++ show' ys ++ )

You've made  show' :: Vector - String, but I'm guessing you actually
want to make it  show' :: [Point] - String; i.e. get rid of the
Vector constructors in the show' patterns.

-Brent

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


Re: [Haskell-cafe] (no subject)

2011-11-28 Thread Willem O





Yes, thank you. Here's my simple fix:
newtype Point = Point Int
instance Show Point where   show (Point a) = [chr $ a + 48]
data Vector = Vector [Point]
instance Show Vector where
   show (Vector ys) =
  let show' [z] = show z
   show' (x:xs)  = show x ++ ,  ++ show' xs
   show' []  = []
  in  ( ++ show' ys ++ )
And I added this function: 
createPoint :: Int - PointcreatePoint x = Point x
When I loaded the file containing all this into ghci and executed 'Vector $ map 
createPoint [1..5]' the result was '(1, 2, 3, 4, 5)' (without the quotes).This 
was actually more or less a test question as I'm new to haskell-cafe, but I 
hope people who will read this message will learn from my mistake.
Thank you.
 From: aslat...@gmail.com
 Date: Mon, 28 Nov 2011 16:20:54 -0600
 Subject: Re: [Haskell-cafe] (no subject)
 To: dub...@hotmail.com
 CC: haskell-cafe@haskell.org
 
 On Mon, Nov 28, 2011 at 4:12 PM, Willem Obbens dub...@hotmail.com wrote:
  Hello,
  I get this error when I try to derive an instance of the Show typeclass:
  Abc.hs:21:60:
  Couldn't match expected type `Vector' with actual type `[Point]'
  In the first argument of `show'', namely `xs'
  In the second argument of `(++)', namely `show' xs'
  In the second argument of `(++)', namely `,  ++ show' xs'
  Failed, modules loaded: none.
  Here's the faulty code:
  newtype Point = Point Int
  instance Show Point where
 show (Point a) = [chr $ a + 48]
 
  data Vector = Vector [Point]
  instance Show Vector where
 show (Vector ys) =
let show' (Vector [z]) = show z
show' (Vector (x:xs))  = show x ++ ,  ++ show' xs
show' (Vector [])  = []
in  ( ++ show' ys ++ )
 
 Here you're treating the value 'ys' as if its type was 'Vector', but
 its type is '[Point]'.
 
 Does that help?
 
 Antoine

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


Re: [Haskell-cafe] (no subject)

2011-11-28 Thread Erik Hesselink
On Mon, Nov 28, 2011 at 23:55, Willem O dub...@hotmail.com wrote:
 And I added this function:
 createPoint :: Int - Point
 createPoint x = Point x
 When I loaded the file containing all this into ghci and executed 'Vector $
 map createPoint [1..5]' the result was '(1, 2, 3, 4, 5)' (without the
 quotes).

Note that you do not need this function. You can just use the 'Point'
constructor:

map Point [1..5]

Erik

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


Re: [Haskell-cafe] (no subject)

2011-07-30 Thread Chris Smith
On Sat, 2011-07-30 at 15:07 -0700, KC wrote:
 A language that runs on the JVM or .NET has the advantage of Oracle 
 Microsoft making those layers more parallelizable.

On top of the answers you've got regarding whether this exists, let me
warn you against making assumptions like the above.  There are certainly
good reasons for wanting Haskell to run on the JVM or CLR, but
parallelism doesn't look like one of them.

The problem is that the cost models of things on the JVM or CLR are so
different that if you directly expose the threading and concurrency
stuff from the JVM or CLR, you're going to kill all the Haskell bits of
parallelism.  A huge contribution of Haskell is to have very
light-weight threads, which can be spawned cheaply and can number in the
tens of thousands, if not hundreds of thousands.  If you decide that
forkIO will just spawn a new Java or CLR thread, performance of some
applications will change by orders of magnitude, or they will just plain
crash and refuse to run.  Differences of that scope are game-changing.
So you risk, not augmenting Haskell concurrency support by that of the
JVM or CLR, but rather replacing it.  And that certainly would be a
losing proposition.

Maybe there's a creative way to combine advantages from both, but it
will require something besides the obvious one-to-one mapping of
execution contexts.

-- 
Chris


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


Re: [Haskell-cafe] (no subject)

2011-07-06 Thread Thomas DuBuisson
Ian,
This requires dynamic typing using Data.Dynamic (for application) and
Data.Typeable (to do the typing).   Namely, you are asking for the
dynApply function:

 START CODE
import Data.Dynamic
import Data.Typeable
import Control.Monad

maybeApp :: (Typeable a, Typeable b, Typeable c) = a - b - Maybe c
maybeApp a = join . fmap fromDynamic . dynApply (toDyn a) . toDyn
 END CODE

In the above we obtain representations of your types in the form of
Dynamic data types using toDyn.  Then, using dynApply, we get a
value of type Maybe Dynamic, which we convert back into a c type
with fromDynamic.  The join is just there to collapse the type from
a Maybe (Maybe c) into the desired type of Maybe c.

Cheers,
Thomas

P.S.
If I totally misunderstood, and you want static typing then you just
need to realize you _don't_ want types a and b (fully polymorphic)
but rather types (b - c) and b:

apply :: (b - c) - b - c
apply a b = a b

But this seems rather silly, so I hope you were looking for my first answer.


On Wed, Jul 6, 2011 at 2:12 AM, Ian Childs ian.chi...@hertford.ox.ac.uk wrote:
 Suppose I have two terms s and t of type a and b respectively, and I
 want to write a function that returns s applied to t if a is an arrow type
 of form b - c, and nothing otherwise. How do i convince the compiler to
 accept the functional application only in the correct instance?

 Thanks,
 Ian

 ___
 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] (no subject)

2011-06-13 Thread Fernando Henrique Sanches
I'm sorry, somehow my e-mail account got kidnapped. The link is a virus and
should NOT be opened. I apologise for any inconvenience.

Fernando Henrique Sanches


2011/6/13 Fernando Henrique Sanches fernandohsanc...@gmail.com


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

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


Re: [Haskell-cafe] (no subject)

2010-05-19 Thread Brent Yorgey
On Wed, May 19, 2010 at 01:37:49PM +, R J wrote:
 
 This is another proof-layout question, this time from Bird 1.4.7.
 We're asked to define the functions curry2 and uncurry2 for currying and 
 uncurrying functions with two arguments.  Simple enough:
 curry2 :: ((a, b) - c) - (a - (b - c))curry2 f x y   =  f 
 (x, y)
 uncurry2   :: (a - (b - c)) - ((a, b) - c)uncurry2 f (x, y)  =  f 
 x y
 The following two assertions are obviously true theorems, but how are the 
 formal proofs laid out?

There are lots of variations, I wouldn't say there's one right way
to organize/lay out the proofs.  But here's how I might do it:

  curry2 (uncurry2 f) x y 
=  { def. of curry2 }
  uncurry2 f (x,y)
=  { def. of uncurry2 }
  f x y

I'll let you do the other one.

By the way, are you working through these problems just for
self-study, or is it homework for a class?

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


Re: [Haskell-cafe] (no subject)

2009-10-15 Thread wren ng thornton

Jake McArthur wrote:

staafmeister wrote:

Yes I know but there are a lot of problems requiring O(1) array updates
so then you are stuck with IO again


Or use ST. Or use IntMap (which is O(log n), but n is going to max out 
on the integer size for your architecture, so it's really just O(32) or 
O(64), which is really just constant time).


Actually, IntMap is O(min(n,W)) where W is the number of bits in an Int. 
Yes, IntMaps are linear time in the worst case (until they become 
constant-time). In practice this is competitive with all those O(log n) 
structures though.


Whereas Data.Map is O(log n) for the usual balanced tree approach.

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


Re: [Haskell-cafe] (no subject)

2009-10-15 Thread Eugene Kirpichov
There are also the judy arrays
http://hackage.haskell.org/package/HsJudy
http://hackage.haskell.org/package/judy

dons recently advertised the latter as being 2x faster than IntMap,
but I don't know in what respect these two packages differ and why Don
decided to create 'judy' despite the existence of HsJudy.

2009/10/15 wren ng thornton w...@freegeek.org:
 Jake McArthur wrote:

 staafmeister wrote:

 Yes I know but there are a lot of problems requiring O(1) array updates
 so then you are stuck with IO again

 Or use ST. Or use IntMap (which is O(log n), but n is going to max out on
 the integer size for your architecture, so it's really just O(32) or O(64),
 which is really just constant time).

 Actually, IntMap is O(min(n,W)) where W is the number of bits in an Int.
 Yes, IntMaps are linear time in the worst case (until they become
 constant-time). In practice this is competitive with all those O(log n)
 structures though.

 Whereas Data.Map is O(log n) for the usual balanced tree approach.

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




-- 
Eugene Kirpichov
Web IR developer, market.yandex.ru
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] (no subject)

2009-10-15 Thread Robin Green
At Thu, 15 Oct 2009 10:15:46 +0400,
Eugene Kirpichov wrote:
 but I don't know in what respect these two packages differ and why Don
 decided to create 'judy' despite the existence of HsJudy.

HsJudy doesn't compile against the latest judy library (as Don knew) -
presumably he had a good reason to start a new package instead of
patching the old one.

There should be a way to mark packages as deprecated on hackage, and
at the same time direct people to a more suitable alternative. Aside
from uploading a dummy new version (ugh!), I don't see a way to do
that currently.
-- 
Robin
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] (no subject)

2009-08-22 Thread Luke Palmer
On Fri, Aug 21, 2009 at 7:03 PM, Sebastian
Sylvansebastian.syl...@gmail.com wrote:
 I think that there must be standard function that can do this. What do
 experienced Haskellers use?

 I usually just whip up a quick parser using Text.ParserCombinators.Parsec

I usually prefer ReadP for quick stuff, for an unknown reason.  I
guess it feels like there is less infrastructure to penetrate, it
gives me the primitives and I structure the parser according to my
needs.

But yeah, I think parser combinators are the way to go.  It's really
not much work at all once you get the hang of it.
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] (no subject)

2009-08-22 Thread staafmeister


Thank you for the reply.


Thomas ten Cate wrote:
 
 Although you most certainly can use a State monad, in most problems
 this isn't necessary. Most algorithms that you need to solve
 programming contest problems can be written in a purely functional
 style, so you can limit monadic code to just a few helper functions.
 

Yes I know but there are a lot of problems requiring O(1) array updates
so then you are stuck with IO again


Thomas ten Cate wrote:
 
 For example, this reads input in the style you mention (assuming the
 strings don't contain whitespace):
 
 import Control.Monad

 answer = id

 parse [] = []
 parse (s:p:r) = (s, (read p) :: Int) : parse r

 run = getLine  getLine = putStrLn . show . answer . parse . words

 main = flip replicateM_ run = readLn
 
 The answer function would be a pure function that computes the answer
 for a particular run. This main function is reusable for all problems
 with many runs.
 
 Observe that the number of edges (e), provided as a convenience for
 memory allocation in many other languages, is not even necessary in
 Haskell :)
 

Yes you're main is short. But how would you do it elegantly if 
instead of line breaks and spaces one would have only spaces.
Every thing on one big line. My C code would not mind one bit.


Thomas ten Cate wrote:
 
 (If anyone knows a better way than explicit recursion to map over a
 list, two elements at a time, or zip its even elements with its odd
 elements, I'd love to hear! I can imagine a convoluted fold with a
 boolean in its state, but it's ugly.)
 

Yes I missed such a function in a couple of problems I wanted to solve.
I would expect a generic function
groupN::Int - [a] - [[a]]
that groups a list into groups of N

Best,
Gerben
-- 
View this message in context: 
http://www.nabble.com/%28no-subject%29-tp25088427p25094244.html
Sent from the Haskell - Haskell-Cafe mailing list archive at Nabble.com.

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


Re: [Haskell-cafe] (no subject)

2009-08-22 Thread Sebastian Sylvan
On Sat, Aug 22, 2009 at 3:20 PM, staafmeister g.c.stave...@uu.nl wrote:



 Thank you for the reply.


 Thomas ten Cate wrote:
 
  Although you most certainly can use a State monad, in most problems
  this isn't necessary. Most algorithms that you need to solve
  programming contest problems can be written in a purely functional
  style, so you can limit monadic code to just a few helper functions.
 

 Yes I know but there are a lot of problems requiring O(1) array updates
 so then you are stuck with IO again


Not necessarily. The ST monad will usually do just as well.


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


Re: [Haskell-cafe] (no subject)

2009-08-22 Thread Jake McArthur

staafmeister wrote:

Yes I know but there are a lot of problems requiring O(1) array updates
so then you are stuck with IO again


Or use ST. Or use IntMap (which is O(log n), but n is going to max out 
on the integer size for your architecture, so it's really just O(32) or 
O(64), which is really just constant time).


And, realistically, very few problems actually require indexed access on 
a large scale like this.



[parsing stuff]


As far as parsing is concerned, maybe you should look at Parsec. I know 
it sounds like overkill, but it's easy enough to use that it's quite 
lightweight in practice. Your example scenario:


inputData :: Parser InputData
inputData = many1 digit * newline * many (testCase * newline)
where testCase = many1 digit * newline * sepBy edge (char ' ')
  edge = liftA2 (,) (many nonspace * char ' ')
(read $ digits)

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


Re: [Haskell-cafe] (no subject)

2009-08-21 Thread Don Stewart
G.C.Stavenga:
 
 
 Hi, I'm just started to learn Haskell. Coming from a programming contest
 background (where it is important to be able to solve problems in a small
 amount of code) I'm wondering what the best way is for simple IO.
 
 A typical input file (in a programming contest) is just a bunch of numbers
 which you want to read one by one (sometimes interspersed with strings). In
 C/C++ this is easily done with either scanf or cin which reads data
 separated by spaces. In Haskell I have not found an equally satisfactionary
 method. The methods I know of
 
 1) Stay in the IO monad and write your own readInt readString functions. A lot
 of code for something easy.
 
 2) Use interact together with words and put the list of lexemes in a State
 monad and define getInt where at least you can use read.
 
 3) Use ByteString.Char8 which has readInt (but I couldn't find a
 readString). But one has to put it also in a State monad.
 
 I think that there must be standard function that can do this. What do
 experienced Haskellers use?


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


Re: [Haskell-cafe] (no subject)

2009-08-21 Thread staafmeister



Don Stewart-2 wrote:
 
 G.C.Stavenga:
 
 
 Hi, I'm just started to learn Haskell. Coming from a programming contest
 background (where it is important to be able to solve problems in a small
 amount of code) I'm wondering what the best way is for simple IO.
 
 A typical input file (in a programming contest) is just a bunch of
 numbers
 which you want to read one by one (sometimes interspersed with strings).
 In
 C/C++ this is easily done with either scanf or cin which reads data
 separated by spaces. In Haskell I have not found an equally
 satisfactionary
 method. The methods I know of
 
 1) Stay in the IO monad and write your own readInt readString functions.
 A lot
 of code for something easy.
 
 2) Use interact together with words and put the list of lexemes in a
 State
 monad and define getInt where at least you can use read.
 
 3) Use ByteString.Char8 which has readInt (but I couldn't find a
 readString). But one has to put it also in a State monad.
 
 I think that there must be standard function that can do this. What do
 experienced Haskellers use?
 
 
 map read . lines
 
 Thank you for the reply. But this only works for if you read only integers
 all on different lines.
 But in general you have a structure like
 
 first line -- integer specifying the number of testcases (n)
 Then for each testcase 
 a line with an integer specifying the number of edges (e)
 a line with e pairs of string s and int p where p is the number asociated
 with string s, etc.
 
 Such a structure cannot be parsed by map read.lines
 What I used is words to tokenize and put the list in a State monad with
 readInt, readString, etc. functions, to mimic
 C code. This seems to be a lot of overkill, so there must be an simpler
 way
 ___
 Haskell-Cafe mailing list
 Haskell-Cafe@haskell.org
 http://www.haskell.org/mailman/listinfo/haskell-cafe
 
 

-- 
View this message in context: 
http://www.nabble.com/%28no-subject%29-tp25088427p25088830.html
Sent from the Haskell - Haskell-Cafe mailing list archive at Nabble.com.

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


Re: [Haskell-cafe] (no subject)

2009-08-21 Thread Sebastian Sylvan
On Fri, Aug 21, 2009 at 11:42 PM, Stavenga, G.C. g.c.stave...@uu.nl wrote:



 Hi, I'm just started to learn Haskell. Coming from a programming contest
 background (where it is important to be able to solve problems in a small
 amount of code) I'm wondering what the best way is for simple IO.

 A typical input file (in a programming contest) is just a bunch of numbers
 which you want to read one by one (sometimes interspersed with strings). In
 C/C++ this is easily done with either scanf or cin which reads data
 separated by spaces. In Haskell I have not found an equally satisfactionary
 method. The methods I know of

 1) Stay in the IO monad and write your own readInt readString functions. A
 lot
 of code for something easy.

 2) Use interact together with words and put the list of lexemes in a State
 monad and define getInt where at least you can use read.

 3) Use ByteString.Char8 which has readInt (but I couldn't find a
 readString). But one has to put it also in a State monad.

 I think that there must be standard function that can do this. What do
 experienced Haskellers use?


I usually just whip up a quick parser using
Text.ParserCombinators.Parsechttp://www.haskell.org/ghc/docs/latest/html/libraries/parsec/Text-ParserCombinators-Parsec.html

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


Re: [Haskell-cafe] (no subject)

2009-05-31 Thread Claus Reinke

--
type F a = Int

class A a where
 foo :: A b = a (F b)
--

GHC - OK
Hugs - Illegal type F b in constructor application


This time, I'd say Hugs is wrong (though eliminating that initial
complaint leads back to an ambiguous and unusable method 'foo').

4.2.2 Type Synonym Declarations, lists only class instances as
exceptions for type synonyms, and 'Int' isn't illegal there.


--
type F a = Int

class A a where
 foo :: F a

instance A Bool where
 foo = 1

instance A Char where
 foo = 2

xs = [foo :: F Bool, foo :: F Char]
--

GHC:

M.hs:14:6:
   Ambiguous type variable `a' in the constraint:
 `A a' arising from a use of `foo' at M.hs:14:6-8
   Probable fix: add a type signature that fixes these type variable(s)

M.hs:14:21:
   Ambiguous type variable `a1' in the constraint:
 `A a1' arising from a use of `foo' at M.hs:14:21-23
   Probable fix: add a type signature that fixes these type variable(s)

Hugs: [1,2]


Neither seems correct? 4.3.1 Class Declarations, says:

   The type of the top-level class method vi is: 
   vi :: forall u,w. (C u, cxi) =ti 
   The ti must mention u; ..


'foo's type, after synonym expansion, does not mention 'a'.

Claus


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


Re: [Haskell-cafe] (no subject)

2009-05-31 Thread Claus Reinke

--
type F a = Int

class A a where
 foo :: A b = a (F b)
--

GHC - OK
Hugs - Illegal type F b in constructor application


This time, I'd say Hugs is wrong (though eliminating that initial
complaint leads back to an ambiguous and unusable method 'foo').


I only just recognized the horrible error message from the first
example.. what Hugs is trying to tell us about is a kind error!

The kind of 'a' in 'F' defaults to '*', but in 'A', 'F' is applied to
'b', which, via 'A b' is constrained to '*-*'. So Hugs is quite
right (I should have known!-).

The error message can be improved drastically, btw:

   :set +k
   ERROR file:.\hugs-vs-ghc.hs:19 - Kind error in constructor application
   *** expression : F b
   *** constructor : b
   *** kind : a - b
   *** does not match : *

See http://cvs.haskell.org/Hugs/pages/hugsman/started.html and
search for '+k' - highly recommended if you're investigating kinds.

Claus


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


Re: [Haskell-cafe] (no subject)

2009-03-04 Thread Richard O'Keefe


On 5 Mar 2009, at 4:02 am, R J wrote:


Could someone provide an elegant solution to Bird problem 4.2.13?


This is the classic Lisp SAMEFRINGE problem in disguise.

You say that the method of converting CatLists to lists and then
comparing those is a hack, but I take leave to doubt that.
It's easy to get right, and it works.

== and  are, in general, O(n) operations on lists,
so the O(n) cost of converting trees to lists isn't
unreasonable.  In fact given ((Wrap 1) ++ ..) ++ ..) )
it can take O(n) time to reach the very first element.
Best of all, the fact that Haskell is lazy means that
converting trees to lists and comparing the lists are
interleaved; if comparison stops early the rest of the
trees won't be converted.

One way to proceed in a strict language is to work with a
(pure) state involving
- the current focus of list 1
- the current focus of list 2
- the rest of list 1 (as a list of parts)
- the rest of list 2 (as a list of parts).

I thought I had demonstrated this when one last check showed
a serious bug in my code.  In any case, this relies on lists
to implement the stacks we use for the rest of the tree.
Your unwrap approach is much easier to get right.


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


Re: [Haskell-cafe] (no subject)

2008-11-25 Thread Dougal Stanton
2008/11/25 apostolos flessas [EMAIL PROTECTED]:
 hi,

 i am looking for someone to help me with an assignment!
 can anyone help me?

Hi Tolis!

Have a look at the homework help policy, so you know what people will
and will not answer.

http://www.haskell.org/haskellwiki/Homework_help


Then let us know what you're trying to do, and what your difficulty has been.


Cheers,


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


Re: [Haskell-cafe] (no subject)

2008-05-08 Thread Daniel Fischer
Am Donnerstag, 8. Mai 2008 15:36 schrieb [EMAIL PROTECTED]:
 Hi I have a bit of a dilemma.I have a list of lists, eg,
 [[1,2,3],[4,5,6],[7,8,9]]. Imagine they represent a grid with 0-2 on the x
 axis and 0-2 on the y axis, eg, (0,0) is 1, (1,0) is 2, (2,1) is 6, etc and
 (2,3) is 9. I want to be able to put in the list of lists, and the (x,y)
 coordinate, and return the value. 

 Also, I need to be able to replace a value in the list. Eg, if I wanted to
 replace (2,3) with 100, then the output of the expression would be
 [[1,2,3],[4,5,6],[7,8,100]].

 Any help would be great!

To get the value at a position, look up (!!)
To replace a value, you could use zipWith

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


Re: [Haskell-cafe] (no subject)

2007-05-24 Thread Donald Bruce Stewart
leaveye.guo:
 Hi MailList Haskell-Cafe:
 
 Till now, which module / package / lib can i use to access binary
 file ? And is this easy to use in GHC ?

Data.Binary? Or perhaps just Data.ByteString, available on hackage,

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

or in base.

-- Don


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


Re: [Haskell-cafe] (no subject)

2007-05-24 Thread L.Guo
Thanks for your suggestion, and sorry for the subject.

I have read the introduction of Data.ByteString, it is helpful.

And also, there is one problem left. When i read a binary file, data is 
truncated at the charactor EOF.

Which function could do this work correctly ?

--   
L.Guo
2007-05-24

-
发件人:Donald Bruce Stewart
发送日期:2007-05-24 14:03:27
收件人:L.Guo
抄送:MailList Haskell-Cafe
主题:Re: [Haskell-cafe] (no subject)

leaveye.guo:
 Hi MailList Haskell-Cafe:
 
 Till now, which module / package / lib can i use to access binary
 file ? And is this easy to use in GHC ?

Data.Binary? Or perhaps just Data.ByteString, available on hackage,

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

or in base.

-- Don


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


Re: [Haskell-cafe] (no subject)

2007-05-24 Thread Donald Bruce Stewart
leaveye.guo:
 Thanks for your suggestion, and sorry for the subject.
 
 I have read the introduction of Data.ByteString, it is helpful.
 
 And also, there is one problem left. When i read a binary file, data
 is truncated at the charactor EOF.
 
 Which function could do this work correctly ?

Hmm. Do you have an example?

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


Re: [Haskell-cafe] (no subject)

2007-05-24 Thread Ketil Malde

 And also, there is one problem left. When i read a binary file, data is 
 truncated at the charactor EOF.

Which character is this: ^D or ^Z?  Which operating system - Windows,
perhaps?  And you are reading from a file, not from stdin?

-k

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


Re: [Haskell-cafe] (no subject)

2007-05-24 Thread L.Guo
Sorry for not familiar to the email client.

My system is WinXP, and using GHC 6.6.
And is read from file.
Data is truncated at the ^Z char.

I just wrote one simple test code.

 import IO
 
 writeTest fn = do
   h - openFile fn WriteMode
   mapM_ (\p - hPutChar h (toEnum p::Char)) $ [0..255] ++ [0..255]
   hClose h
 
 accessTest fn = do
   h - openFile fn ReadMode
   s - hGetContents h
   putStrLn . show . map fromEnum $ s
   hClose h
 
 main = do
   writeTest ttt
   accessTest ttt


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


Re: [Haskell-cafe] (no subject)

2007-05-24 Thread Marc Weber
On Thu, May 24, 2007 at 02:38:05PM +0800, L.Guo wrote:
 Thanks for your suggestion, and sorry for the subject.
 
 I have read the introduction of Data.ByteString, it is helpful.
 
 And also, there is one problem left. When i read a binary file, data is 
 truncated at the charactor EOF.

You have to use readBinaryFile instead of readFile.
I had the same trouble as well.

I finally implemented accessing single characters in C and did use ffi
because I didn't know haw to do this i haskell properly. ( using
peek/poke functions 4 bytes got written (wihch is annotateted somewhere
) If you are interested I can sent you the modified ByteString package.

If someone can tell me which haskell function to use to set a random
char in a memory buffer I would be pleased ..

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


Re: [Haskell-cafe] (no subject)

2007-05-24 Thread Donald Bruce Stewart
marco-oweber:
 On Thu, May 24, 2007 at 02:38:05PM +0800, L.Guo wrote:
  Thanks for your suggestion, and sorry for the subject.
  
  I have read the introduction of Data.ByteString, it is helpful.
  
  And also, there is one problem left. When i read a binary file, data is 
  truncated at the charactor EOF.
 
 You have to use readBinaryFile instead of readFile.
 I had the same trouble as well.
 
 I finally implemented accessing single characters in C and did use ffi
 because I didn't know haw to do this i haskell properly. ( using
 peek/poke functions 4 bytes got written (wihch is annotateted somewhere
 ) If you are interested I can sent you the modified ByteString package.
 
 If someone can tell me which haskell function to use to set a random
 char in a memory buffer I would be pleased ..

'poke'

or else use unboxed Word8 arrays

Check the src for Data.ByteString for examples.
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: Re: [Haskell-cafe] (no subject)

2007-05-24 Thread L.Guo
to Ketil :

Tring openBinaryFile, I notice that I cannot make one usable buffer,
just because I can not find one function to malloc a memory or just
get one change-able buffer.

:-$


to Marc:

I can not locate which module including readBinaryFile.
And I use hoogle search engine.



Could you give me some more hints ?

--   
L.Guo
2007-05-24

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


Re: Re: [Haskell-cafe] (no subject)

2007-05-24 Thread Donald Bruce Stewart
leaveye.guo:
 to Ketil :
 
 Tring openBinaryFile, I notice that I cannot make one usable buffer,
 just because I can not find one function to malloc a memory or just
 get one change-able buffer.
 
 :-$

No 'malloc' here in Haskell land: that's done automatically.  Recall
that 'getContents' will read your opened file into a [Char]. (or use
Data.ByteString to get a stream of Word8).

What are you trying to do?

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


Re: Re: [Haskell-cafe] (no subject)

2007-05-24 Thread L.Guo
To read the handle openBinaryFile returns, both the hGetBuf and
hGetBufNonBlocking needs one parameter _buf_ of type Ptr a.
I can not get one data of that type.

In the doc, there is only nullPtr, and also some type cast functions.
I failed to find some other buffer-maker function.

What should I do ?

--   
L.Guo
2007-05-24

-
From: Donald Bruce Stewart
At: 2007-05-24 17:03:55
Subject: Re: Re: [Haskell-cafe] (no subject)

What are you trying to do?

-- Don

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


Re: Re: [Haskell-cafe] (no subject)

2007-05-24 Thread Donald Bruce Stewart
leaveye.guo:
 To read the handle openBinaryFile returns, both the hGetBuf and
 hGetBufNonBlocking needs one parameter _buf_ of type Ptr a.
 I can not get one data of that type.
 
 In the doc, there is only nullPtr, and also some type cast functions.
 I failed to find some other buffer-maker function.
 
 What should I do ?

I mean, what problem are you trying to solve? Ptrs aren't the usual way
to manipulate files in Haskell.

Here, for example, is a small program to print the first byte of a
binary file:

import System.IO
import qualified Data.ByteString as B

main = do
h - openBinaryFile a.out ReadMode
s - B.hGetContents h
print (B.head s)

When run:

$ ./a.out 
127

Note there's no mallocs or pointers involved.

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


Re: Re: [Haskell-cafe] (no subject)

2007-05-24 Thread Ketil Malde
On Thu, 2007-05-24 at 17:01 +0800, L.Guo wrote:

 Tring openBinaryFile, 

Well, did you get it to work?

 I can not locate which module including readBinaryFile.

This is what I find in System.IO (ghci :b System.IO):

  openBinaryFile :: FilePath - IOMode - IO Handle
  openBinaryTempFile :: FilePath - String - IO (FilePath, Handle)
  hSetBinaryMode :: Handle - Bool - IO ()

so you have the option of either using openBinaryFile or openFile and
using hSetBinaryMode to true. I guess - I've never had to use them.  

I can't find a readBinaryFile either, but writing one might be a good
excercise?

Makes me wonder whether one should have binary be the default?  I'm a
stranger in Windows-land, but are there cases where you want reading of
a file to be terminated on ^Z?  Seems pretty awful to me.

Concerning mutable buffers, it is of course possible, but hardly
idiomatic Haskell.  Why do you need mutability?

-k



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


Re: Re: [Haskell-cafe] (no subject)

2007-05-24 Thread L.Guo
Very thanks for your example, I have not notice that there is a group of
hGetxxx functions in ByteString. In other words, I was using hGetxxx which
implemented in IO module. So it always failed.



--   
L.Guo
2007-05-24

-
From: Donald Bruce Stewart
At: 2007-05-24 17:31:02
Subject: Re: Re: [Haskell-cafe] (no subject)

I mean, what problem are you trying to solve? Ptrs aren't the usual way
to manipulate files in Haskell.

...

-- Don

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


Re: [Haskell-cafe] (no subject)

2007-05-24 Thread Tillmann Rendel

Hello,

Ketil Malde wrote:

Makes me wonder whether one should have binary be the default?  I'm a
stranger in Windows-land, but are there cases where you want reading
of a file to be terminated on ^Z?  Seems pretty awful to me.


The ghc docs state about openBinaryFile:


Like openFile, but open the file in binary mode. On Windows, reading
a file in text mode (which is the default) will translate CRLF to LF,
and writing will translate LF to CRLF. [...] text mode treats control-Z as EOF


The CRLF-to-LF translation is the more important part. It allows '\n' to 
stand for the end of a line on windows, too, even if lines are 
terminated by two characters in windows text files.


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


Re: [Haskell-cafe] (no subject)

2006-03-15 Thread Bulat Ziganshin
Hello José,

Wednesday, March 15, 2006, 5:54:49 PM, you wrote:

JMV #ifdef __WIN32__

i use the following:

#if defined(mingw32_HOST_OS) || defined(__MINGW32__) || defined(_MSC_VER)


-- 
Best regards,
 Bulatmailto:[EMAIL PROTECTED]

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


Re: [Haskell-cafe] (no subject)

2004-09-10 Thread Paul Hudak
To add briefly to what John wrote, there is a webpage for Yampa:
www.haskell.org/yampa
which includes all of our publications on FRP/Yampa as well as a decent 
release of our latest implementation of Yampa (based on arrows).  The 
release has ample examples of how to use Yampa for graphics, animation, 
and basic control systems such as used in robotics.

Also, although most of the developers have dispersed, I believe that 
most of them are still interested in the ideas, and the 
[EMAIL PROTECTED] mailing list would probably be responsive if 
anyone bothered to use it.

  -Paul Hudak
John C. Peterson wrote:
From: John Peterson [EMAIL PROTECTED]
To: [EMAIL PROTECTED]
Subject: Re: [Haskell-cafe] Functional Reactive Programming
Functional Reactive Programming is alive but in need of some new
students to push the effort a bit.  A lot of us have taken teaching
or industrial positions so the old FRP team is a bit depleted.
I don't think anyone is working on Yampa directly at the moment.
Although it's stable and working well it lacks a critical mass of nice
libraries to make it attractive.
I'm still plugging on a wxHaskell port to Yampa (the wxFruit stuff).
I've made some semantic changes to Yampa so I probably shouldn't say
it's real Yampa but pretty close.  I should have something to release
later this fall. 

Aside from that, we have a student working in the hybrid modeling
area.  That's good stuff but not likely to produce software of
interest to Joe Haskell.  Another student is keeping the robotics side
of things alive but it's in the context of a very specialized robotic
hardware environment.
So there you go!
   John
___
Haskell-Cafe mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell-cafe
--
Professor Paul Hudak
Chair, Dept of Computer Science   Office: (203) 432-1235
Yale University   FAX:(203) 432-0593
P.O. Box 208285   email:  [EMAIL PROTECTED]
New Haven, CT 06520-8285  WWW:www.cs.yale.edu/~hudak
___
Haskell-Cafe mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell-cafe