[Haskell-cafe] seems like I'm on the wrong track

Daniel Fischer daniel.is.fischer at web.de
Tue Dec 1 21:55:07 EST 2009


Am Mittwoch 02 Dezember 2009 03:28:04 schrieb Michael Mossey:
> Daniel Fischer wrote:
> >> getNumber :: String -> AssignedNumbers -> (Int,AssignedNumbers)
> >
> > Yeah, that screams State Monad.
>
> Hi, thanks for all the advice.
>
> I was hoping my AssignedNumbers "class" would be useful with many data
> structures. In other words I would have
>
> data State1 = State1 { a :: AssignedNumbers, b :: AssignedNumbers, ... }
> data State2 = State2 { c :: AssignedNumbers, d :: AssignedNumbers, ... }
>
> func1 :: State State1 Int
> func1 = do
>     ... something using a and b ...
>
> func2 :: State State2 Int
> func2 = do
>     ... something using c and d ...
>
> So I thought maybe I could defined a function like
>
> nextNumber :: MonadState s m => (s -> AssignedNumbers) -> (AssignedNumbers
> -> s) -> m Int
> nextNumber retreive putBack = ...
>
> and have it be useful in both "State State1 a" and "State State2 a" monads,
> but defining the retrieve and putBack functions isn't pretty.
>
> I will try to grok Robert's reply also. Maybe he has something addressing
> this.

Definitely.

data AssignType = Oscillator | Table | Thingamajig
    deriving (Eq, Ord, Ix)

data MusicState
    = MS
    { assignedNumbers :: Array AssignType AssignedNumbers
    , other stuff
    } deriving (Everything you need)

fetchNumber :: String -> AssignType -> State MusicState Int
fetchNumber str ty = do
    an <- gets ((! ty) . assignedNumbers)
    let (i,newAn) = getNumber str an
    modify (\ms -> ms{ assignedNumbers = assignedNumbers ms // [(ty,newAn)] })
    return i

doSomeMusicStuff aString1 aString2 = do
    o <- fetchNumber aString1 Oscillator
    t <- fetchNumber aString2 Table
    return (o,t)

>
> Mike



More information about the Haskell-Cafe mailing list