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

Achim Schneider barsoap at web.de
Sun Jan 6 05:13:09 EST 2008


Jonathan Cast <jonathanccast at fastmail.fm> wrote:

> On 4 Jan 2008, at 2:00 AM, Nicholls, Mark wrote:
> 
> > You may be right...but learning is not an atomic thing....wherever 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. 



More information about the Haskell-Cafe mailing list