RE: [Haskell] Dynamic binding

2005-06-22 Thread Ralf Lammel
At the risk of being excluded from this list
(because of an unmoral number of plugs about OOHaskell),
here we go: http://homepages.cwi.nl/~ralf/OOHaskell/

You might start with the appendices of the paper and also read Section 2
which finally implements the Shapes example with ease. The C++ encoding 
is a bit verbose in so far that C++ doesn't quite have type inference,
Haskell does and so OOHaskell does too :-)

Apologies,
Ralf


> -Original Message-
> From: [EMAIL PROTECTED] [mailto:[EMAIL PROTECTED]
On
> Behalf Of Andrew Ward
> Sent: Wednesday, June 22, 2005 6:38 PM
> To: Pal-Kristian Engstad
> Cc: haskell@haskell.org
> Subject: Re: [Haskell] Dynamic binding
> 
> Pal-Kristian Engstad wrote:
> 
> >On Wednesday 22 June 2005 05:38 pm, Andrew Ward wrote:
> >
> >
> >>What would be the normal way for a Haskell programmer to handle the
> >>typical shape example in beginner OO tutorials?
> >>
> >>
> >
> >By not doing OO. You have to ask yourself, what is the purpose and/or
> benefit
> >of using OO? In C++, OO is _useful_ because you restrict the problems
of
> >mutable data (by enclosing it in C++ classes).
> >
> >ML type languages have other methods of doing things, and guess what,
OO
> is
> >not that needed for these languages. Sum-types, pattern-matching and
data
> >constructors make half of the need for OO go away. Higher order
functions
> and
> >make it even less needed. For the rest, there's always work-arounds.
> >
> >PKE.
> >
> >
> To handle the problem of drawing all shapes, in c++, I would have a
list
> of shape pointers:
> 
> struct shape{ virtual void draw(...);};
> struct circle : public shape {...};
> struct square : public shape {...};
> std::list shapes;
> for(std::list::iterator it = shapes.begin();it !=
> shapes.end();++it)
> { (*it)->draw(...); }
> 
> This general pattern of dynamic binding I use over and over again.
Could
> you give me some example code of this type of thing handled in
Haskell's
> way? Assuming that the number of classes deriving from shape might get
> quite large.
> 
> Andrew Ward.
> 
> 
> ___
> Haskell mailing list
> Haskell@haskell.org
> http://www.haskell.org/mailman/listinfo/haskell
___
Haskell mailing list
Haskell@haskell.org
http://www.haskell.org/mailman/listinfo/haskell


Re: [Haskell] Dynamic binding

2005-06-22 Thread Andrew Ward

Pal-Kristian Engstad wrote:


On Wednesday 22 June 2005 05:38 pm, Andrew Ward wrote:
 


What would be the normal way for a Haskell programmer to handle the
typical shape example in beginner OO tutorials?
   



By not doing OO. You have to ask yourself, what is the purpose and/or benefit 
of using OO? In C++, OO is _useful_ because you restrict the problems of 
mutable data (by enclosing it in C++ classes).


ML type languages have other methods of doing things, and guess what, OO is 
not that needed for these languages. Sum-types, pattern-matching and data 
constructors make half of the need for OO go away. Higher order functions and 
make it even less needed. For the rest, there's always work-arounds.


PKE.
 

To handle the problem of drawing all shapes, in c++, I would have a list 
of shape pointers:


struct shape{ virtual void draw(...);};
struct circle : public shape {...};
struct square : public shape {...};
std::list shapes;
for(std::list::iterator it = shapes.begin();it != 
shapes.end();++it)

{ (*it)->draw(...); }

This general pattern of dynamic binding I use over and over again. Could 
you give me some example code of this type of thing handled in Haskell's 
way? Assuming that the number of classes deriving from shape might get 
quite large.


Andrew Ward.


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


[Haskell] Dynamic binding

2005-06-22 Thread Andrew Ward

Hi All,
In Simon Thompson's The Craft of Functional Programming Second Edition, 
page 226, it is mentioned that Laufer (1996) describes a Haskell 
extension to allow dynamic binding. I was wondering if this has been 
implemented as an extension in any of the haskell compilers, or variants?
I am a c++ programmer by trade, only dabbling in Haskell when I was at 
university, so it seems a disadvantage to me to not have dynamic binding 
in Haskell 98.
What would be the normal way for a Haskell programmer to handle the 
typical shape example in beginner OO tutorials?


Andrew Ward.


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


Re: [Haskell] Haskell version of Crystal Space 3D?

2005-06-22 Thread Sebastian Sylvan
On 6/22/05, Benjamin L. Russell <[EMAIL PROTECTED]> wrote:

> Two questions:
> 
> 1) Would a Haskell counterpart to Crystal Space 3D, if
> implemented, potentially be fast enough to run a
> project similar to the 3D real-time Crystal Space
> 3D-based MMORPG "PlaneShift" ( see
> http://www.planeshift.it/main_01.html ) on Mac OS X
> 10.2.8 Jaguar or above?

Most likely yes. For several reasons. First of all the bulk of the
hard work is still being done in C and C++. Crystal Space is in C++ so
all the engine stuff is still done there and the drivers are probably
written in C (perhaps with some asm) and a pretty large amount of time
is spent there.
Second, unless you're doing some _really_ significant processing
(stencil shadows, which invovles lots of geomtry processessing, see
Doom3 which is pretty CPU-bound) on the CPU side you're going to be
GPU bound for pretty much any game.

Basically, no matter what you do (within reason) on the CPU is going
to make much of a difference compared to, say,  optimizing the number
of draw calls you send to the driver.

I see no problem writing 3D games in Haskell speed-wise.

/S

-- 
Sebastian Sylvan
+46(0)736-818655
UIN: 44640862
___
Haskell mailing list
Haskell@haskell.org
http://www.haskell.org/mailman/listinfo/haskell


Re: [Haskell] Haskell version of Crystal Space 3D?

2005-06-22 Thread Benjamin L. Russell
--- robert dockins <[EMAIL PROTECTED]> wrote:

> As it turns out, there is a pretty large conceptual
> gap between the 
> design of most object oriented libraries and
> idiomatic Haskell.  This 
> makes writing useful bindings in Haskell for such
> libraries a tricky 
> business.  If you want it to be easy, I'd say stick
> with an OO language 
> that will more closely match the design (caveat: I
> am not familiar with 
> the design of CS, but I assume it is OO because its
> written in C++).  If 
> you want to learn more about Haskell, then the ease
> question takes a 
> back seat.

Thank you; that's what I was suspecting.  In that
case, I'll see if I can use the existing Java
scripting support for the Crystal Space 3D libraries.

> [comments deleted]
> 
> As to performance, I suspect it would be OK, if you
> were sufficiently 
> good with a profiler.

Thank you; in that case, I should probably learn
Haskell for my next project.  Alternatively, if
Sebastian Sylvan (or anybody else) completes the
Haskell scripting support for Crystal Space 3D before
I start actually using it, then maybe I'll learn
Haskell much sooner.

If only there were Haskell scripting support for
Crystal Space 3D, Haskell would probably be the better
choice overall to write the majority of the project.

Many thanks,

Benjamin L. Russell
___
Haskell mailing list
Haskell@haskell.org
http://www.haskell.org/mailman/listinfo/haskell


Re: [Haskell] Haskell version of Crystal Space 3D?

2005-06-22 Thread Benjamin L. Russell
--- Sebastian Sylvan <[EMAIL PROTECTED]>
wrote:

> I haven't looked at Crystal Space in a while, but
> does it have some
> sort of scripting interface?

According to "About Crystal Space" ( see
http://www.crystalspace3d.org/tikiwiki/tiki-index.php?page=About+Crystal+Space
), Crystal Space 3D reportedly "supports ... scripting
(using Python, Perl, Java, and potentially other
languages)...," so it probably does.


> [comments deleted]
> 
> I'll look into this more this coming fall, if it's
> possible, I will
> write a Haskell scripting interface to Crystal Space
> then (I'm taking
> a course which involves writing plugins to CS).

That would be wonderful.  Please keep me posted if you
do write it.  (Since my mail filter automatically
sorts anything sent to or cc'd to
"haskell@haskell.org" to my "Haskell Mailing List"
folder, please be sure to send me a separate e-mail
message from the one to this mailing list then if
possible.)

Many thanks,

Benjamin L. Russell
___
Haskell mailing list
Haskell@haskell.org
http://www.haskell.org/mailman/listinfo/haskell


Re: [Haskell] Haskell version of Crystal Space 3D?

2005-06-22 Thread robert dockins

Two questions:

1) Would a Haskell counterpart to Crystal Space 3D, if
implemented, potentially be fast enough to run a
project similar to the 3D real-time Crystal Space
3D-based MMORPG "PlaneShift" ( see
http://www.planeshift.it/main_01.html ) on Mac OS X
10.2.8 Jaguar or above?

2) For a hobbyist programmer with a computer science
algorithms background including some coursework in
lambda-calculus, with some programming background in
Scheme and C, and with some knowledge of Java, for the
purpose of writing a project similar to "PlaneShift,"
which of the following options would more likely be
easier to accomplish?

Option A) 
Use the existing Java scripting support already

available in Crystal Space 3D, and deal with debugging
potentially larger programs in Java.

Option B)
Write a Haskell binding for the existing Crystal Space
3D libraries, and then deal with debugging potentially
smaller programs in Haskell.

I have written some programs in Scheme, C, and Java,
but have only audited some lectures, written a few
programs, and studied a few chapters on Haskell so
far.


As it turns out, there is a pretty large conceptual gap between the 
design of most object oriented libraries and idiomatic Haskell.  This 
makes writing useful bindings in Haskell for such libraries a tricky 
business.  If you want it to be easy, I'd say stick with an OO language 
that will more closely match the design (caveat: I am not familiar with 
the design of CS, but I assume it is OO because its written in C++).  If 
you want to learn more about Haskell, then the ease question takes a 
back seat.  To be honest, I don't think there is any easy way to tackle 
a project of this size -- the planeshift people et al have been working 
on this for a long time.


As to performance, I suspect it would be OK, if you were sufficiently 
good with a profiler.




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


Re: [Haskell] Haskell version of Crystal Space 3D?

2005-06-22 Thread Benjamin L. Russell
--- Manuel M T Chakravarty <[EMAIL PROTECTED]>
wrote:

> The "simplest" solution would probably be to write a
> Haskell binding to
> the Crystal Space 3D library.  However, as Crystal
> Space 3D is huge,
> that's a significant effort.  This would be much
> like the existing
> binding to OpenGL
> 
>   http://haskell.org/HOpenGL/
> 
> only that Crystal Space 3D provides higher-level
> functionality.

Thank you for the links.

Two questions:

1) Would a Haskell counterpart to Crystal Space 3D, if
implemented, potentially be fast enough to run a
project similar to the 3D real-time Crystal Space
3D-based MMORPG "PlaneShift" ( see
http://www.planeshift.it/main_01.html ) on Mac OS X
10.2.8 Jaguar or above?

2) For a hobbyist programmer with a computer science
algorithms background including some coursework in
lambda-calculus, with some programming background in
Scheme and C, and with some knowledge of Java, for the
purpose of writing a project similar to "PlaneShift,"
which of the following options would more likely be
easier to accomplish?

Option A) 
Use the existing Java scripting support already
available in Crystal Space 3D, and deal with debugging
potentially larger programs in Java.

Option B)
Write a Haskell binding for the existing Crystal Space
3D libraries, and then deal with debugging potentially
smaller programs in Haskell.

I have written some programs in Scheme, C, and Java,
but have only audited some lectures, written a few
programs, and studied a few chapters on Haskell so
far.

Any advice would be appreciated.

Thanks again,

Benjamin L. Russell
___
Haskell mailing list
Haskell@haskell.org
http://www.haskell.org/mailman/listinfo/haskell


[Haskell] haddock

2005-06-22 Thread Christian Maeder
Hi,

haddock generates html-Files named after the module. Since hierarchical
modules contain dots, such files are seen to have multiple extensions
(regardless of case) by our apache web server.

 http://httpd.apache.org/docs-2.0/mod/mod_mime.html#multipleext

Unfortunately "map" is the extension for our imap handler. Therefore
accessing the file Data.Map.html fails:

http://www.informatik.uni-bremen.de/agbkb/forschung/formal_methods/CoFI/hets/src-distribution/daily/HetCATS/docs/www/ghc/html/libraries/base/Data.Map.html

As far as I can see only Data.Map causes the problem, but a clean
solution would be to avoid multiple extensions for html-files generated
by haddock!

Is there a chance that haddock can be changed that way? (Replacing the
dot by some other character, maybe "-", in html file names only?)

Has only our web server a problem with Data.Map.html?

Cheers Christian
___
Haskell mailing list
Haskell@haskell.org
http://www.haskell.org/mailman/listinfo/haskell


Re: [Haskell] Haskell version of Crystal Space 3D?

2005-06-22 Thread Sebastian Sylvan
On 6/21/05, Benjamin L. Russell <[EMAIL PROTECTED]> wrote:
> Does anybody know any Haskell tool(s) corresponding to
> Crystal Space 3D ( see
> http://www.crystalspace3d.org/tikiwiki/tiki-view_articles.php
> )?
> 
> To quote from "About Crystal Space" ( see
> http://www.crystalspace3d.org/tikiwiki/tiki-index.php?page=About+Crystal+Space
> ),
> 
> "Crystal Space is a free (LGPL) and portable 3D Game
> Development Kit written in C++. It supports: true six
> degrees of freedom, colored lighting, lightmapped and
> stencil based lighting, shader support (CG, vertex
> programs, fragment programs, ...), mipmapping,
> portals, mirrors, alpha transparency, reflective
> surfaces, 3D sprites (frame based or with skeletal
> animation using cal3d animation library), procedural
> textures, particle systems, halos, volumetric fog,
> scripting (using Python, Perl, Java, or potentially
> other languages), 16-bit and 32-bit display support,
> OpenGL, and software renderer, font support (also with
> freetype), hierarchical transformations, physics
> plugin based on ODE, ... See the extensive list of
> features for more details."
> 
> The reason that I ask is that I would like to learn
> how to write my own version of PlaneShift (a 3D
> fantasy MMORPG written using Crystal Space 3D) with
> Haskell, instead of C++, if possible.  However, I
> haven't been able to find any Haskell tools or
> libraries specific enough for this kind of project.
> 

I haven't looked at Crystal Space in a while, but does it have some
sort of scripting interface? So you write a C++ class which implements
a ton of game-related functions that the game engine then calls to set
up the game etc., and in those member functions you can call Haskell
functions (via FFI).

I'll look into this more this coming fall, if it's possible, I will
write a Haskell scripting interface to Crystal Space then (I'm taking
a course which involves writing plugins to CS).

/S

-- 
Sebastian Sylvan
+46(0)736-818655
UIN: 44640862
___
Haskell mailing list
Haskell@haskell.org
http://www.haskell.org/mailman/listinfo/haskell


Re: [Haskell] Haskell version of Crystal Space 3D?

2005-06-22 Thread Manuel M T Chakravarty
Benjamin L. Russell:
> Does anybody know any Haskell tool(s) corresponding to
> Crystal Space 3D ( see
> http://www.crystalspace3d.org/tikiwiki/tiki-view_articles.php
> )?

The "simplest" solution would probably be to write a Haskell binding to
the Crystal Space 3D library.  However, as Crystal Space 3D is huge,
that's a significant effort.  This would be much like the existing
binding to OpenGL

  http://haskell.org/HOpenGL/

only that Crystal Space 3D provides higher-level functionality.

Manuel

PS: See 

  http://www.haskell.org/tmrwiki/Bzlib2Binding

to get an idea what is involved in producing library bindings.

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


Re: [Haskell] A MonadPlusT with fair operations and pruning

2005-06-22 Thread ajb
G'day all.

Quoting [EMAIL PROTECTED]:

: Since Andrew Bromage wished for that interesting monad, perhaps he has
: in mind a good example of its use.  We are particularly interested in a
: short example illustrating soft-cut (and, perhaps, `once').

No obvious small examples of soft cut spring to mind.  (If Fergus is
listening, he might have a few suggestions...)

In Prolog parlance, there are three types of cut operation:

- A "red cut" is anything which prunes away solutions.  Red cuts are
  usually considered bad style because they have no logical
  interpretation.

- A "green cut" is any cut which does not prune solutions, but which
  may prune different proofs of the same solution.

- A "blue cut" prunes neither solutions, nor proofs.  It's basically
  an efficiency hack, where the programmer inserts a cut to tell the
  Prolog implementation that some piece of code is deterministic when
  the implementation can't infer that.

Green and blue cuts are sometimes collectively called "grue cuts".

The most obvious use for "once" (which I may accidentally call "commit")
is for blue cuts.  This is not so useful in Haskell, but you never know.

The second most obvious use is for those times when some goal isn't
technically deterministic, but you never actually look at the "output".
Mercury automatically inserts these commit operations if it can tell that
the output of some goal is never consulted.

One situation where you might use this is in negation-as-failure:

gnot :: (Logic m) => m a -> m ()
gnot m = ifte (once m) (const gfail) (gsuccess ())

The point of the "once" is that when the "then" branch fails, the system
won't backtrack into m.  There's no point, since it's always going to fail.

Another example of pruning is any situation where you are doing some kind
of search which would normally be intractable, but you have a heuristic.
If the heuristic is "safe" (that is, if whenever it can be applied,
applying it results in no solutions being lost), then the cut is green.
Otherwise it's red.  (But that's sometimes okay; if it's an NP-hard
problem, for example, you just make do with the approximation provided
by the heuristic.)

With soft cuts, you can express it like this:

optimise curState
| isGoalState curState
= gsuccess success
| otherwise
= ifte
(tryHeuristic curState)
(\h -> do-- "then" case
s <- nextStateWithHeuristic h curState
optimise s)
(do  -- "else" case
s <- nextState curState
optimise s)

The soft cut guarantees that you commit to the heuristic if it applies.

As an example, here's a simple (though not THAT short) tic-tac-toe game.
The solution is highly artificial, since the "next move" computation is
effectively deterministic.  A better example might be solving Sudoku
problems, but that's harder to set up than tic-tac-toe.

> {-# OPTIONS -fglasgow-exts #-}
> {-# OPTIONS -fallow-undecidable-instances #-}

The -fallow-undecidable-instances will be explained in a moment.

> module Main where
>
> import Control.Monad
> import Control.Monad.Trans
> import LogicT
> import SFKT
> import Data.List

OK, now the monad that most of the computation will be done in...

> class (Monad m, MonadIO (t m), LogicT t, MonadPlus (t m)) => MyMonT t m
> instance (Monad m, MonadIO (t m), LogicT t, MonadPlus (t m)) => MyMonT t m

This is the reason for -fallow-undecidable-instances.  To make the types
not so unwieldy, we would ideally like typeclass synonyms, but Haskell
doesn't support them.  So this will have to do.

> data Value = B | X | O deriving (Show, Eq, Ord)
> type Player = Value

We're going to overload the Value type with two meanings: It can either
mean a value on the tic-tac-toe board, or it can refer to a player (either
X or O).

Code to switch players:

> otherPlayer :: Player -> Player
> otherPlayer X = O
> otherPlayer O = X

Code to handle the board:

> data Board
> = Board Value Value Value Value Value Value Value Value Value
> deriving (Show, Eq, Ord)
>
> blankBoard :: Board
> blankBoard = Board B B B B B B B B B
>
> -- Return true if the board is a win for player p.
> win :: Value -> Board -> Bool
> win p (Board a b c d e f g h i)
> =  (a == b && b == c && a == p)
> || (d == e && e == f && d == p)
> || (g == h && h == i && g == p)
> || (a == d && d == g && a == p)
> || (b == e && e == h && b == p)
> || (c == f && f == i && c == p)
> || (a == e && e == i && a == p)
> || (c == e && e == g && c == p)
>
> draw :: Board -> Bool
> draw (Board a b c d e f g h i)
> = not (any (==B) [a,b,c,d,e,f,g,h,i])

We also need to encode the desirability of a board state.  We do this
with an enum type such that more desirable states come first in Ord.

> data State = Win | Draw | Lose deriving (Show, Eq, Ord)
>
>