Re: [Haskell-cafe] Re: Is there anyone out there who can translate C# generics into Haskell?

2008-01-09 Thread Jules Bean

Achim Schneider wrote:

Yes, you see, that was my first Haskell program bigger than 20 lines,
there's no possibility to get the state out of the IO Monad, at least
without writing a high-level interface to glut and gl, and then there's
this thing that _every_ game works with input callbacks, one, global,
state update function (where it doesn't _really_ matter whether you're
passing and returning a state or updating a state) and one function
that translates the state into some graphics representation.


Understood.

My objection was not about having an IORef somewhere (you need it to 
thread via the callback), but about making each component an IORef when 
one big IORef makes more sense.


It makes plenty of sense to try to write precise type signatures, 
including not having IO in the type of functions which don't do IO.


For ramblings about the annoyance of having to use IORefs to thread your 
custom monad state through callbacks, take a look at


http://www.haskell.org/pipermail/haskell-cafe/2007-July/028501.html

which sketches a typeclass solution

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


Re: [Haskell-cafe] Re: Is there anyone out there who can translate C# generics into Haskell?

2008-01-08 Thread Jules Bean

Achim Schneider wrote:

things like


data State = State 
{ winSize   :: IORef Size

, t :: IORef Int
, fps   :: IORef Float
, showFPS   :: IORef Bool
, showHelp  :: IORef Bool
, grabMouse :: IORef Bool
, mousePos  :: IORef (Maybe Position)
, mouseDelta :: IORef Position
, viewRot   :: IORef Vec3
, angle':: IORef GLfloat
, ballPos   :: IORef Vec2
, ballVel   :: IORef Vec2
}



Yuck!

I'm not sure whether this is a real example or not, but if it's real, 
get rid of all those IORefs. Make State a simple type, and use (IORef 
State) as needed for callbacks, and hide that fact in other code.


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


Re: [Haskell-cafe] Re: Is there anyone out there who can translate C# generics into Haskell?

2008-01-08 Thread Don Stewart
jules:
 Achim Schneider wrote:
 things like
 
 
 data State = State 
 { winSize   :: IORef Size
 , t :: IORef Int
 , fps   :: IORef Float
 , showFPS   :: IORef Bool
 , showHelp  :: IORef Bool
 , grabMouse :: IORef Bool
 , mousePos  :: IORef (Maybe Position)
 , mouseDelta :: IORef Position
 , viewRot   :: IORef Vec3
 , angle':: IORef GLfloat
 , ballPos   :: IORef Vec2
 , ballVel   :: IORef Vec2
 }
 
 
 Yuck!
 
 I'm not sure whether this is a real example or not, but if it's real, 
 get rid of all those IORefs. Make State a simple type, and use (IORef 
 State) as needed for callbacks, and hide that fact in other code.

I agree, this is very-unHaskelly :)

The State type should be a simple purely functional structured, threaded
through your code via a StateT or some such. Not a bunch of pointers
in IO.

See xmonad for examples of this in highly effectful programs,

http://code.haskell.org/xmonad/XMonad/Core.hs

newtype X a = X (ReaderT XConf (StateT XState IO) a)

(Carries read-only and updatable state components)

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


[Haskell-cafe] Re: Is there anyone out there who can translate C# generics into Haskell?

2008-01-08 Thread Achim Schneider
Don Stewart [EMAIL PROTECTED] wrote:

 jules:
  Achim Schneider wrote:
  things like
  
  
  data State = State 
  { winSize   :: IORef Size
  , t :: IORef Int
  , fps   :: IORef Float
  , showFPS   :: IORef Bool
  , showHelp  :: IORef Bool
  , grabMouse :: IORef Bool
  , mousePos  :: IORef (Maybe Position)
  , mouseDelta :: IORef Position
  , viewRot   :: IORef Vec3
  , angle':: IORef GLfloat
  , ballPos   :: IORef Vec2
  , ballVel   :: IORef Vec2
  }
  
  
  Yuck!
  
  I'm not sure whether this is a real example or not, but if it's
  real, get rid of all those IORefs. Make State a simple type, and
  use (IORef State) as needed for callbacks, and hide that fact in
  other code.
 
 I agree, this is very-unHaskelly :)
 
 The State type should be a simple purely functional structured,
 threaded through your code via a StateT or some such. Not a bunch of
 pointers in IO.
 
 See xmonad for examples of this in highly effectful programs,
 
 http://code.haskell.org/xmonad/XMonad/Core.hs
 
 newtype X a = X (ReaderT XConf (StateT XState IO) a)
 
 (Carries read-only and updatable state components)
 
Yes, you see, that was my first Haskell program bigger than 20 lines,
there's no possibility to get the state out of the IO Monad, at least
without writing a high-level interface to glut and gl, and then there's
this thing that _every_ game works with input callbacks, one, global,
state update function (where it doesn't _really_ matter whether you're
passing and returning a state or updating a state) and one function
that translates the state into some graphics representation.

That said, I think it's not very Haskell-like to do something elegantly
in 1000 lines when you can do it in 100 lines and still have it look
nicer than C.

If the update function of this particular one ever gets more
complicated than

idle :: State - IdleCallback
idle state = do
t0 - get $ t state
t1 - get elapsedTime
t state $= t1
let td = fromIntegral t1 - fromIntegral t0
fps state $= 1/td * 1000
 
(bpx, bpy) - get $ ballPos state
(bvx, bvy) - get $ ballVel state

ballPos state $= (bpx + bvx*td, bpy + bvy*td)   
postRedisplay Nothing

, I'll think of something.

-- 
(c) this sig last receiving data processing entity. Inspect headers for
past copyright information. All rights reserved. Unauthorised copying,
hiring, renting, public performance and/or broadcasting of this
signature prohibited. 

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


Re: [Haskell-cafe] Re: Is there anyone out there who can translate C# generics into Haskell?

2008-01-08 Thread Stefan O'Rear
On Tue, Jan 08, 2008 at 09:10:59PM +0100, Achim Schneider wrote:
 Don Stewart [EMAIL PROTECTED] wrote:
 
  jules:
   Achim Schneider wrote:
   things like
   
   
   data State = State 
   { winSize   :: IORef Size
   , t :: IORef Int
   , fps   :: IORef Float
   , showFPS   :: IORef Bool
   , showHelp  :: IORef Bool
   , grabMouse :: IORef Bool
   , mousePos  :: IORef (Maybe Position)
   , mouseDelta :: IORef Position
   , viewRot   :: IORef Vec3
   , angle':: IORef GLfloat
   , ballPos   :: IORef Vec2
   , ballVel   :: IORef Vec2
   }
   
   
   Yuck!
   
   I'm not sure whether this is a real example or not, but if it's
   real, get rid of all those IORefs. Make State a simple type, and
   use (IORef State) as needed for callbacks, and hide that fact in
   other code.
  
  I agree, this is very-unHaskelly :)
  
  The State type should be a simple purely functional structured,
  threaded through your code via a StateT or some such. Not a bunch of
  pointers in IO.
  
  See xmonad for examples of this in highly effectful programs,
  
  http://code.haskell.org/xmonad/XMonad/Core.hs
  
  newtype X a = X (ReaderT XConf (StateT XState IO) a)
  
  (Carries read-only and updatable state components)
  
 Yes, you see, that was my first Haskell program bigger than 20 lines,
 there's no possibility to get the state out of the IO Monad, at least
 without writing a high-level interface to glut and gl, and then there's
 this thing that _every_ game works with input callbacks, one, global,
 state update function (where it doesn't _really_ matter whether you're
 passing and returning a state or updating a state) and one function
 that translates the state into some graphics representation.
 
 That said, I think it's not very Haskell-like to do something elegantly
 in 1000 lines when you can do it in 100 lines and still have it look
 nicer than C.

I would use IORef State.  Making illegal states unrepresentable greatly
helps with code prettiness; the original State allowed internal
aliasing, which is quite definitely silly.

I think this should be written somewhere as a general rule - when you
have a mutable structure, use a reference to a record, not a record of
references.

Stefan


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


[Haskell-cafe] Re: Is there anyone out there who can translate C# generics into Haskell?

2008-01-08 Thread Achim Schneider
Stefan O'Rear [EMAIL PROTECTED] wrote:

 On Tue, Jan 08, 2008 at 09:10:59PM +0100, Achim Schneider wrote:
  That said, I think it's not very Haskell-like to do something
  elegantly in 1000 lines when you can do it in 100 lines and still
  have it look nicer than C.
 
 I would use IORef State.  Making illegal states unrepresentable
 greatly helps with code prettiness; the original State allowed
 internal aliasing, which is quite definitely silly.
 
 I think this should be written somewhere as a general rule - when you
 have a mutable structure, use a reference to a record, not a record of
 references.
 

So it would be, instead of 

---$---

idle :: State - IdleCallback
idle state = do
(bpx, bpy) - get $ ballPos state
(bvx, bvy) - get $ ballVel state

ballPos state $= (bpx + bvx*td, bpy + bvy*td)   

---$---

type StateRef = IORef State'

idle' :: StateRef - IdleCallback
idle' st = do
state - get st
let (bpx, bpy) = ballPos' state
(bvx, bvy) = ballVel' state

st $= state {ballPos' = (bpx+bvx, bpy+bvy)}

---$---
or, while I'm at it
---$---

moveBall :: State' - State'
moveBall state =  state {ballPos' = (bpx+bvx, bpy+bvy)}
where (bpx, bpy) = ballPos' state
  (bvx, bvy) = ballVel' state

idle'' :: StateRef - IdleCallback
idle'' st = st $~ moveBall

---$---

With the multiple IORef-Model, moveBall looks like this:

moveBall :: Vec2 - Vec2 - Vec2
moveBall (bpx, bpy) (bvx,bvy) = (bpx+bvx, bpy+bvy)

which is IMHO pure Haskell.

On the other hand, with the one IORef-Model, the draw function could
not possibly mangle any state, which would be a good thing, doing such
things can result in keyboards being smashed over heads by team
colleagues.

I'll think about it and then let you know how to properly tackle the
awkward GLpong squad.

Generally, in game programming you can have so many state-related bugs
that it's infeasible to detect them all statically. You also cheat
much, doing stage magic instead of the real stuff, and trading off
things all the time.

-- 
(c) this sig last receiving data processing entity. Inspect headers for
past copyright information. All rights reserved. Unauthorised copying,
hiring, renting, public performance and/or broadcasting of this
signature prohibited. 

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


Re: [Haskell-cafe] Re: Is there anyone out there who can translate C# generics into Haskell?

2008-01-08 Thread Jonathan Cast

On 8 Jan 2008, at 3:38 PM, Achim Schneider wrote:

---$---
or, while I'm at it
---$---

moveBall :: State' - State'
moveBall state =  state {ballPos' = (bpx+bvx, bpy+bvy)}
where (bpx, bpy) = ballPos' state
  (bvx, bvy) = ballVel' state

idle'' :: StateRef - IdleCallback
idle'' st = st $~ moveBall

---$---

With the multiple IORef-Model, moveBall looks like this:

moveBall :: Vec2 - Vec2 - Vec2
moveBall (bpx, bpy) (bvx,bvy) = (bpx+bvx, bpy+bvy)


You can use this with the single IORef model, using the lifting function

liftMove :: (Vec2 - Vec2 - Vec2) - IORef State - IO ()
liftMove move r = withIORef r $ \ st - st{ballPos = moveBall  
(ballPos st) (ballVel st) }


liftMove and moveBall can then be maintained separately; liftMove is  
part of your state framework (the outer layer of your program);  
moveBall is part of the algorithm specification (the inner layer of  
your program).


jcc

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


[Haskell-cafe] Re: Is there anyone out there who can translate C# generics into Haskell?

2008-01-06 Thread Achim Schneider
Jonathan Cast [EMAIL PROTECTED] wrote:

 On 4 Jan 2008, at 2:00 AM, Nicholls, Mark wrote:
 
  You may be right...but learning is not an atomic thingwherever I
  start I will get strange things happening.
 
 The best place to start learning Haskell is with the simplest type  
 features, not the most complicated.  And it's the simplest features  
 that are most unlike OO.
 
 Yes, Haskell will be `strange'.  But if you think you're `the  
 intersection' between Haskell and OO, you'll think things are  
 familiar, and you'll be surprised when they turn  out to be  
 different.  I'd concentrate on watching out for differences --- but  
 then I can't imagine how finding `familiar' ideas would help.
 
just a sec...

things like


data State = State 
{ winSize   :: IORef Size
, t :: IORef Int
, fps   :: IORef Float
, showFPS   :: IORef Bool
, showHelp  :: IORef Bool
, grabMouse :: IORef Bool
, mousePos  :: IORef (Maybe Position)
, mouseDelta :: IORef Position
, viewRot   :: IORef Vec3
, angle':: IORef GLfloat
, ballPos   :: IORef Vec2
, ballVel   :: IORef Vec2
}

makeState :: IO State
makeState = do
size - newIORef $ Size 0 0 
t' - newIORef 0
fps' - newIORef 0
sfps - newIORef False
gm - newIORef False
mp - newIORef Nothing
md - newIORef $ Position 0 0
sh - newIORef False
v - newIORef (0, 0, 0)
a - newIORef 0
bp - newIORef (0, 0)
bv - newIORef (0.002, 0.002) 
{ winSize = size
, t = t', fps = fps'
, showFPS = sfps, showHelp = sh
, grabMouse = gm, mousePos = mp, mouseDelta = md
, viewRot = v, angle' = a
, ballPos = bp, ballVel = bv
}

and

keyboard state (Char 'f') Down_ _ = showFPS state $~ not

modRot :: State - View - IO ()
modRot state (dx,dy,dz) = do
(x, y, z) - get $ viewRot state
viewRot state $= (x + dx, y + dy, z + dz)
postRedisplay Nothing

come to mind.

But then this has more to do with Monads than with classes. IO, in
particular, and GL and GLUT, which are state machines and
thus predestined for OOP.

-- 
(c) this sig last receiving data processing entity. Inspect headers for
past copyright information. All rights reserved. Unauthorised copying,
hiring, renting, public performance and/or broadcasting of this
signature prohibited. 

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


Re: [Haskell-cafe] Re: Is there anyone out there who can translate C# generics into Haskell?

2008-01-06 Thread Jonathan Cast

On 6 Jan 2008, at 2:13 AM, Achim Schneider wrote:


Jonathan Cast [EMAIL PROTECTED] wrote:


On 4 Jan 2008, at 2:00 AM, Nicholls, Mark wrote:


You may be right...but learning is not an atomic thingwherever I
start I will get strange things happening.


The best place to start learning Haskell is with the simplest type
features, not the most complicated.  And it's the simplest features
that are most unlike OO.

Yes, Haskell will be `strange'.  But if you think you're `the
intersection' between Haskell and OO, you'll think things are
familiar, and you'll be surprised when they turn  out to be
different.  I'd concentrate on watching out for differences --- but
then I can't imagine how finding `familiar' ideas would help.


just a sec...

things like


C++ translated into Haskell


come to mind.

But then this has more to do with Monads than with classes. IO, in
particular, and GL and GLUT, which are state machines and
thus predestined for OOP.


Your example is very unintuitive and unidiomatic Haskell.  The  
reference to GL makes me think this is for a `low-level' binding to  
an imperative library, no?  Those are scarcely good places to learn  
Haskell.


jcc

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


[Haskell-cafe] Re: Is there anyone out there who can translate C# generics into Haskell?

2008-01-06 Thread Achim Schneider
Jonathan Cast [EMAIL PROTECTED] wrote:

 On 6 Jan 2008, at 2:13 AM, Achim Schneider wrote:
 
  Jonathan Cast [EMAIL PROTECTED] wrote:
 
  On 4 Jan 2008, at 2:00 AM, Nicholls, Mark wrote:
 
  You may be right...but learning is not an atomic
  thingwherever I start I will get strange things happening.
 
  The best place to start learning Haskell is with the simplest type
  features, not the most complicated.  And it's the simplest features
  that are most unlike OO.
 
  Yes, Haskell will be `strange'.  But if you think you're `the
  intersection' between Haskell and OO, you'll think things are
  familiar, and you'll be surprised when they turn  out to be
  different.  I'd concentrate on watching out for differences --- but
  then I can't imagine how finding `familiar' ideas would help.
 
  just a sec...
 
  things like
 
 C++ translated into Haskell
 
  come to mind.
 
  But then this has more to do with Monads than with classes. IO, in
  particular, and GL and GLUT, which are state machines and
  thus predestined for OOP.
 
 Your example is very unintuitive and unidiomatic Haskell.  The  
 reference to GL makes me think this is for a `low-level' binding to  
 an imperative library, no?  Those are scarcely good places to learn  
 Haskell.
 
Well, I learnt a lot, knowing GL quite well already and seeing how easy
everything fit together and how easy it was to abstract things away,
like stuffing a bunch of IO actions consisting of GL primitives into a
map, automatically generating and managing display-lists... 

I don't speak C++, btw, just C and Java.

You can't just take years of programming experience and then start
again with calculating Fibonacci numbers, just this time implemented
functionally... There's always this creepy feeling that you understand
everything, although you didn't understand a thing. 

Shivers run down my spine when I think about how 

let amb = 0.2
ambm = 0.2
spec = 0.7
preservingMatrix $ do
materialDiffuse FrontAndBack $= Color4 ambm ambm ambm 0.3
materialSpecular FrontAndBack $= Color4 spec spec spec 0.7
materialShininess FrontAndBack $= 50
border 30 40 (depth * 10) 0.01 True

looks like in C.

or, for that matter, what atrocious code gcc generates if you
parametrise calls to vertex3f with functions.

-- 
(c) this sig last receiving data processing entity. Inspect headers for
past copyright information. All rights reserved. Unauthorised copying,
hiring, renting, public performance and/or broadcasting of this
signature prohibited. 

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