Oh, and I just thought of one more approach:
class StreamMonad m where
fetchLine = m
sendLine = String -> m ()
instance StreamMonad IO where
fetchLine = getLine
sendLine = putLine
fetchLineFromStream = lift fetchLine
sendLineToStream = lift . sendLine
type PDState = StateT PD
main = runStateT loop (PD { pdCount = 0, pdList = [] })
loop :: (StreamMonad m) => PDState m a
loop = forever $ fetchLineFromStream >>= runCmd
runCmd :: (StreamMonad m) => String -> PDState m ()
runCmd "Inc" = increment
runCmd "PrintCount" = getCount >>= sendLineToStream
.
.
.
i.e., you could use type-classes instead of passing around a datatype
to specify how to send/fetch lines.
On Oct 6, 2009, at 12:36 AM, Gregory Crosswhite wrote:
It isn't clear what it is that you are trying to generalize the code
to do. If you are trying to generalize it to work with an arbitrary
input/output stream of lines, then unless you are doing arbitrary I/
O it seems to me that all of these instance declarations are
overkill. All that you need is to know how to get a line from the
stream, and how to send a line.
Assuming that this is the case, you have a couple of options. If
you are only going to write to the stream within runCmd, then I'd
just pass in the line writing function as an extra argument:
type PDState = StateT PD
loop :: (m String) -> (String -> m ()) -> PDState m a
loop fetchLine sendLine = forever $ lift fetchLine >>= runCmd (lift
sendLine)
runCmd :: (String -> PDState m ()) -> PDstate m ()
runCmd sendLine cmd =
case cmd of
"Inc" -> increment
"PrintCount" -> getCount >>= sendLine . show
"PrintList" -> getList >>= sendLine . show
...
If you forsee doing reading and writing at other points in your
code, you could use the RWS monad to supply your code not only with
a state but also with an environment with the reading and writing
functions:
data StreamFunctions m = StreamFunctions
{ streamLineFetcher :: m String
, streamLineSender :: String -> m ()
}
fetchLineFromStream = lift $ asks streamLineFetcher
sendLineDownStream cmd = lift (asks streamLineSender >>= return . ($
cmd))
data PDMonad = RWST (StreamFunctions m) () PD m
main = evalRWST loop (StreamFunctions ...) (PD { pdCount = 0, pdList
= [] })
loop :: PDMonad m ()
loop = forever $ fetchLineFromStream >>= runCmd
runCmd :: String -> PDMonad m ()
runCmd "Inc" = increment
runCmd "PrintCount" = getCount >>= sendLineDownStream
runCmd "PrintList" = getList >>= sendLineDownStream
Note that we didn't have to put any additional constraints on the
monad type variable "m", because other than the fact that we can get
a line and send a line within it we don't otherwise care what it
is. If you want to do other arbitrary I/O within this framework,
though, then you will need to add a "MonadIO m" constraint.
Cheers,
Greg
On Oct 5, 2009, at 8:54 PM, Floptical Logic wrote:
Instead of specifying the monad implementation, specify the
interface.
That is, you are using state operations (from MonadState) and IO
operations (from MonadIO). Try removing all the type signatures that
mention PDState and see what you get.
E.g., loop :: (MonadState PD m, MonadIO m) => m a
If I were to make an instance of MonadIO be a parameter to StateT and
I wanted to use the Net monad (from Roll your own IRC bot on the
wiki)
with it, I would need to make Net an instance of MonadIO. What would
this instance look like?
I think the loop function is the least of my worries. I am more
concerned about the runCmd function. What would go in place of print
in runCmd?
Thanks
_______________________________________________
Haskell-Cafe mailing list
[email protected]
http://www.haskell.org/mailman/listinfo/haskell-cafe
_______________________________________________
Haskell-Cafe mailing list
[email protected]
http://www.haskell.org/mailman/listinfo/haskell-cafe
_______________________________________________
Haskell-Cafe mailing list
[email protected]
http://www.haskell.org/mailman/listinfo/haskell-cafe