
Not really seeing why Unique is in the IO monad, not deeply understanding the use of Haskell extensions in the State source, and wanting to try to learn a bit more about monads, I thought I'd try to write my own monad for the first time: something for producing a series of unique labels. This is how it turned out: ========================================================================== module Label (Label, Labeller, newLabel) where import Monad newtype Label = Label Int deriving (Eq, Ord) newtype Labeller a = Labeller (Int -> (Int, a)) instance Monad Labeller where return r = Labeller (\n -> (n, r)) (Labeller g) >>= y = let f m = let (r, n) = g m Labeller h = y n in h r in Labeller f newLabel :: Labeller Label newLabel = Labeller (\n -> (n + 1, Label n)) runLabeller :: Labeller a -> a runLabeller (Labeller l) = snd (l minBound) labelTest :: Labeller [Int] labelTest = do Label a <- newLabel Label b <- newLabel Label c <- newLabel Label d <- newLabel return [a,b,c,d] main = print (runLabeller labelTest) ========================================================================== I was thinking that maybe, (a) People could point out to me where I'm still confused, as revealed by my code. Is it needlessly complicated? (b) My code may be instructive to someone else. -- Mark

On Thu, 26 Jun 2003 14:40:51 -0400 (EDT) Mark Carroll wrote:
Not really seeing why Unique is in the IO monad,
What Unique? The one in the GHC source? If so, it seems that it's so you can create multiple unique supplies that don't overlap. Since the unique supply isn't a monad transformer or over IO computations, you couldn't simply stay in one UniqueSupply computation for the whole program. Anyways, it's only creation that is in the IO monad.
not deeply understanding the use of Haskell extensions in the State source,
I'm assuming Control.Monad.State's source in which case -no- extensions are used for -State- (well, at least I don't see any quickly glancing). Extensions are used for the -MonadState class-. For the MonadState class they are pretty much necessary. Multiparameter type classes are necessary because the state type depends on the monad (get would have type forall s.Monad m => m -> s otherwise which is rather meaningless), the function dependencies tell the type checker that the state type is completely determined by the monad type.
and wanting to try to learn a bit more about monads,
I'm not a big supporter of reading (arbitrary) sourcecode to learn a language (at least early on). It isn't aimed at being didactic, there are compromises/irrelevant details/added complexities/hidden assumptions, even if it's well-documented the documentation is still going to assume the reader has a certain level of competence and is not going to document the why or how of day to day things (e.g. accumulating parameters), and finally it may simply be a poor (or at least not polished) example of coding.
I thought I'd try to write my own monad for the first time: something for producing a series of unique labels. This is how it turned out:
===================================================================== ===== module Label (Label, Labeller, newLabel) where import Monad
newtype Label = Label Int deriving (Eq, Ord)
why not Show as well?
(a) People could point out to me where I'm still confused, as revealed by my code. Is it needlessly complicated?
It could hardly be made simpler, well except for simply wrapping State with appropriate functions/types ;). You may want to watch out for laziness though, e.g. last $ sequence $ replicate 1000 newLabel is Label (1+1+1+1+1+1+1+1+1+...minBound) as opposed to Label (999+minBound) (I'm pretty sure, well modulo what the compiler might do). The simplest fix would be making Int a strict field (adding ! to it) or changing newLabel to n `seq` (n+1,Label n).

not deeply understanding the use of Haskell extensions in the State source,
I'm assuming Control.Monad.State's source in which case -no- extensions are used for -State- (well, at least I don't see any quickly glancing). Extensions are used for the -MonadState class-.
The portable parts of Control.Monad.State (that are sufficient for most cases) should be in an extra module (maybe called Control.Monad.StateTypes). In addition further non-overloaded names for put, get, gets and modify would be needed (maybe putState, getState, etc.) There's no point to write your own "instance Monad ..." just because you want (or have) to be Haskell98 compliant. The previous "newtype Labeller a = Labeller (Int -> (Int, a))" (the result tuple is reversed within Control.Monad.State) would simply become (untested): newtype Labeller a = State Int a newLabel = do { n <- get; put (n + 1); return (Label n) } runLabeller l = execState l minBound Christian

The previous "newtype Labeller a = Labeller (Int -> (Int, a))" (the result tuple is reversed within Control.Monad.State) would simply become (untested):
newtype Labeller a = State Int a
newLabel = do { n <- get; put (n + 1); return (Label n) }
runLabeller l = execState l minBound
it must be "evalState" instead of "execState"

On Friday, 2003-06-27, 12:55, CEST, Christian Maeder wrote:
[...]
The portable parts of Control.Monad.State (that are sufficient for most cases) should be in an extra module (maybe called Control.Monad.StateTypes). In addition further non-overloaded names for put, get, gets and modify would be needed (maybe putState, getState, etc.)
Hello, I fear, this would complicate the module structure too much. And it will become unnecessary because some time (in the near future?) multi-parameter classes with functional dependencies will be a standardized feature which is supported by all major Haskell implementations. I hope, at least. ;-)
[...]
Wolfgang

The portable parts of Control.Monad.State (that are sufficient for most cases) should be in an extra module (maybe called Control.Monad.StateTypes). In addition further non-overloaded names for put, get, gets and modify would be needed (maybe putState, getState, etc.)
I fear, this would complicate the module structure too much.
I only suggest to split a (comparatively large) module Control.Monad.State into two modules. I think that is rather appropriate. (I'm willing to supply these modules.) I've already extracted a portable part, because I wanted to try out the nhc98 tracer. Christian

On Thursday, 2003-06-26, 23:57, CEST, Derek Elkins wrote:
[...]
not deeply understanding the use of Haskell extensions in the State source,
I'm assuming Control.Monad.State's source in which case -no- extensions are used for -State- (well, at least I don't see any quickly glancing). Extensions are used for the -MonadState class-. For the MonadState class they are pretty much necessary. Multiparameter type classes are necessary because the state type depends on the monad (get would have type forall s.Monad m => m -> s otherwise which is rather meaningless), the function dependencies tell the type checker that the state type is completely determined by the monad type.
Hello, why not swap the state and the monad parameter of StateT? The definition would become something like the following: newtype StateT m s a = StateT (s -> m (a,s)) With this we could create a MonadState class which doesn't use type system extensions. It could be defined like this: class MonadState m where get :: m s s put :: s -> m s () Note that m now has kind * -> * -> *. Note also that this restricts the MonadState class because only state transformers which can work with every state type are now possible as instances. But, at least, State and our modified StateT can be instantiated without problem. The problem arises when we try to make a MonadTrans instance for our new StateT because MonadTrans needs a type of kind * -> * -> * whoose first argument is a monad. But we can create a different MonadTrans class based on the kind of functional dependency usage we just dropped for MonadState. We just write: class MonadTrans (Monad m, Monad tm) => m tm | tm -> m where lift :: m a -> tm a Instead of writing instance MonadTrans T where ... we would now write instance Monad m => MonadTrans m (T m) where ... and for our new StateT type we would write instance Monad m => MonadTrans m (StateT m s) where ... The new MonadTrans class would be more powerful. This would have the nice effect that we don't need MonadIO anymore. Instead of writing MonadIO m we could just use MonadTrans IO m Changing MonadTrans this way would help me with my parser module.¹ I have a type Parser which needs three parameters, a "base monad", a token type and an output type. The base monad parameter has the same purpose as the monad parameter in ReaderT, WriterT, StateT etc. The lift function makes sense for my parser type, so I want a MonadTrans instance. This would restrict me to the parameter order token - base monad - output which is rather unfortunate for me. The reason is that there are parser functions which fulfill the arrow axioms. The arrow type is a parser applied to a specific base monad. So I want to write something like instance Monad baseMonad => Arrow (Parser baseMonad) where ... which implies that the base monad must be the first parameter. This brings me to another point. One year ago we had a discussion on The Haskell Mailing List concerning arrows. (The subject of the mails was just "arrows".) The point was that it seemed strange to me that first and second are included in the basic arrow class Arrow while left and right have their extra class ArrowChoice. Not only that it seemed strange to me but it made it impossible to make Parser baseMonad an instance of Arrow. Parser baseMonad has nice implementations of pure and (>>>) but none of first or second. Currently, I use my own Arrow module which provides an arrow class, that doesn't include first and second. I'm really not happy with using a replacement for a module from the hierarchical libraries. Is there any chance of changing the class structure of Control.Arrow?
[...]
Wolfgang ¹ The parser module is part of Seaweed. It's the module Seaweed.Core.Parsing. The source code of Seaweed can be accessed via this URI: http://cvs.sourceforge.net/cgi-bin/viewcvs.cgi/seaweed/code/ There is also the module Seaweed.Core.Parsing.Utilities which provides several useful things implemented on top of the core parsing module.

In article <200306271927.36405.wolfgang@jeltsch.net>,
Wolfgang Jeltsch
This brings me to another point. One year ago we had a discussion on The Haskell Mailing List concerning arrows. (The subject of the mails was just "arrows".) The point was that it seemed strange to me that first and second are included in the basic arrow class Arrow while left and right have their extra class ArrowChoice. Not only that it seemed strange to me but it made it impossible to make Parser baseMonad an instance of Arrow. Parser baseMonad has nice implementations of pure and (>>>) but none of first or second.
I agree. My own Arrow module hierarchy looks more or less like this: class Compositor comp where identity :: comp a a compose :: comp b c -> comp a b -> comp a c class (Compositor arrow) => Arrow arrow where arrFunction :: (p -> q) -> arrow p q -- | corresponds to Hughes\' \'Arrow\' class (Arrow arrow) => ProductArrow arrow where arrApply :: arrow p (q -> r) -> arrow p q -> arrow p r arrProduct :: arrow p q -> arrow p r -> arrow p (q,r) arrProduct = liftA2 (,) class (Arrow arrow) => CoproductArrow arrow where arrCoproduct :: arrow p r -> arrow q r -> arrow (Either p q) r -- | corresponds to Hughes\' \'ArrowChoice\' class (ProductArrow arrow,CoproductArrow arrow) => FullArrow arrow instance (ProductArrow arrow,CoproductArrow arrow) => FullArrow arrow class (Arrow arrow) => ArrowFix arrow where arrFix :: arrow (p,q) q -> arrow p q class (FullArrow arrow) => ApplyArrow arrow where arrApplyArrow :: arrow (arrow p q,p) q Note the symmetry between ProductArrow and CoproductArrow. See <http://cvs.sourceforge.net/cgi-bin/viewcvs.cgi/*checkout*/hbase/Source/H Base/Category/Arrow.hs?rev=HEAD&content-type=text/plain> for all the details. -- Ashley Yakeley, Seattle WA

Ashley Yakeley wrote:
Wolfgang Jeltsch wrote:
This brings me to another point. One year ago we had a discussion on The Haskell Mailing List concerning arrows. (The subject of the mails was just "arrows".) The point was that it seemed strange to me that first and second are included in the basic arrow class Arrow while left and right have their extra class ArrowChoice. Not only that it seemed strange to me but it made impossible to make Parser baseMonad an instance of Arrow. Parser baseMonad has nice implementations of pure and (>>>) but none of first or second.
I agree. My own Arrow module hierarchy looks more or less like this:
class Compositor comp where [...] class (Compositor arrow) => Arrow arrow where [...] class (Arrow arrow) => ProductArrow arrow where [...] class (Arrow arrow) => CoproductArrow arrow where [...] class (ProductArrow arrow,CoproductArrow arrow) => FullArrow arrow instance (ProductArrow arrow,CoproductArrow arrow) => FullArrow arrow class (Arrow arrow) => ArrowFix arrow where [...] class (FullArrow arrow) => ApplyArrow arrow where [...]
On that topic, see below for what mine looks like
(from HXML,

On Fri, Jun 27, 2003 at 07:27:36PM +0200, Wolfgang Jeltsch wrote:
This brings me to another point. One year ago we had a discussion on The Haskell Mailing List concerning arrows. (The subject of the mails was just "arrows".) The point was that it seemed strange to me that first and second are included in the basic arrow class Arrow while left and right have their extra class ArrowChoice. Not only that it seemed strange to me but it made it impossible to make Parser baseMonad an instance of Arrow. Parser baseMonad has nice implementations of pure and (>>>) but none of first or second.
Your parser type is strange candidate for an arrow: the input (token) type occurs in both positive and negative positions in the type. And does it satisfy identity >>> f = f?
Currently, I use my own Arrow module which provides an arrow class, that doesn't include first and second. I'm really not happy with using a replacement for a module from the hierarchical libraries. Is there any chance of changing the class structure of Control.Arrow?
The point about symmetry is a fair one, but unfortunately the Haskell class system imposes a cost on fine-grained class hierarchies, so we must ask what would be gained. You may have extra instances, but are there extra client programs written to the new interfaces? John Hughes asked this last time, and you pointed out instance PreArrow a => Functor (a b) where fmap f a = a >>> arr f but is that it?

In article <20030630150455.GA8927@soi.city.ac.uk>,
Ross Paterson
The point about symmetry is a fair one, but unfortunately the Haskell class system imposes a cost on fine-grained class hierarchies,
It does? -- Ashley Yakeley, Seattle WA

On Thu, Jul 10, 2003 at 02:00:37AM -0700, Ashley Yakeley wrote:
In article <20030630150455.GA8927@soi.city.ac.uk>, Ross Paterson
wrote: The point about symmetry is a fair one, but unfortunately the Haskell class system imposes a cost on fine-grained class hierarchies,
It does?
There are more instances and methods for people to define, even if some of them imply others. As it happens, I would like yet another intermediate class: class BiFunctor a where bimap :: (b' -> b) -> (c -> c') -> a b c -> a b' c' (and I have a client for the class: a useful subset of the arrow notation needs only this, in fact only the contravariant part.) Clearly any arrow is also an instance of this class: bimap b c f = arr b >>> f >>> arr c but you still have to define bimap even if the type is also an arrow. Subclasses in Haskell cover a range of relationships, including this sense where things in the subclass automatically belong to the superclass. Other examples include Eq => Ord and Functor vs Monad. In such cases it would be handy if the subclass could define defaults for the superclass methods (e.g. Ord defining (==)), so that the superclass instance could be optional.

On Thu, Jul 10, 2003 at 02:33:25PM +0100, Ross Paterson wrote:
Subclasses in Haskell cover a range of relationships, including this sense where things in the subclass automatically belong to the superclass. Other examples include Eq => Ord and Functor vs Monad. In such cases it would be handy if the subclass could define defaults for the superclass methods (e.g. Ord defining (==)), so that the superclass instance could be optional.
I agree, but this needs to be carefully thought out. For instance, remember to consider the case that there is more than one default instance for a given method of a superclass. I am reminded of multiple inheritance considerations. (These difficulties came up before when I was thinking about the numeric heirarchy, and was the reason I proposed a heirarchy which was much less fine-grained than, e.g., in Mechvelliani's proposal.) Peace, Dylan

On Thursday, 2003-07-10, 15:33, Ross Paterson wrote:
[...]
There are more instances and methods for people to define, even if some of them imply others.
As it happens, I would like yet another intermediate class:
class BiFunctor a where bimap :: (b' -> b) -> (c -> c') -> a b c -> a b' c'
(and I have a client for the class: a useful subset of the arrow notation needs only this, in fact only the contravariant part.)
Clearly any arrow is also an instance of this class:
bimap b c f = arr b >>> f >>> arr c
but you still have to define bimap even if the type is also an arrow.
Subclasses in Haskell cover a range of relationships, including this sense where things in the subclass automatically belong to the superclass. Other examples include Eq => Ord and Functor vs Monad. In such cases it would be handy if the subclass could define defaults for the superclass methods (e.g. Ord defining (==)), so that the superclass instance could be optional.
Exactly. Maybe, the problem is not the existence of many classes but the lack of such an "defaults for superclass methods" feature. Wolfgang

On Thursday, 2003-07-10, 15:33, Ross Paterson wrote:
[...]
Subclasses in Haskell cover a range of relationships, including this sense where things in the subclass automatically belong to the superclass. Other examples include Eq => Ord and Functor vs Monad.
By the way, I strongly vote for Functor being a superclass of Monad in Haskell 2.
[...]
Wolfgang

In article <200307102002.31955.wolfgang@jeltsch.net>,
Wolfgang Jeltsch
By the way, I strongly vote for Functor being a superclass of Monad in Haskell 2.
I recently created my own Monad class in HBase instead of using the Prelude one. The hierarchy looks something like this: class HasReturn f where return :: a -> f a class Functor f where fmap :: (a -> b) -> f a -> f b class (Functor f) => FunctorApply f where fApply :: f (a -> b) -> f a -> f b fPassTo :: f a -> f (a -> b) -> f b (>>) :: f a -> f b -> f b class (FunctorApply f,HasReturn f) => FunctorApplyReturn f instance (FunctorApply f,HasReturn f) => FunctorApplyReturn f class (FunctorApplyReturn f) => Monad f where (>>=) :: f a -> (a -> f b) -> f b class (Functor f) => ExtractableFunctor f where fExtract :: (FunctorApplyReturn g) => f (g a) -> g (f a) fToList :: f a -> [a] -- has default definition (exercise for the reader) Certain standard monadic functions, such as LiftM2, actually apply to classes higher up the hierarchy (FunctorApply, in this case). FunctorApplyReturn is a particularly useful class for "manipulating things in a box" when the box isn't quite a Monad. I'm glad to hear there isn't a _serious_ cost (i.e. performance penalty) for fine-grained hierarchies. Yeah, so if you want to define your own Monad, you have to define all the other instances too. I ease this by providing functions such as monad_fmap and monad_fApply etc. that you can use for your instances. -- Ashley Yakeley, Seattle WA

I'm glad to hear there isn't a _serious_ cost (i.e. performance penalty) for fine-grained hierarchies.
One cost which doesn't seem to have been mentioned is the programmer cost. With the current Haskell Prelude, a matrix operation (say) might have type: invert :: Num a => Matrix a -> Matrix a but, if we had one operation per class, the type might be: invert :: (Add a, Subtract a, FromInteger a, Eq a, Multiply a) => Matrix a -> Matrix a More flexible but quite unwieldy. One way to overcome part of this problem would be to generalize the idea of 'type synonyms' to allow 'context synonyms'. For example, we have type synonyms like: type Point = (Int,Int) we could have 'context synonyms' like: class Num a => (Add a, Subtract a, FromInteger a, Eq a, Multiply a, ...) Adding context synonyms would make it possible to write types concisely when using fine-grained class hierarchies and would also be useful with extensions like Hugs' T-REX or implicit parameters. Adding context synonyms would not help with type error messages though. When using TREX to encode an abstract syntax tree for the C language, I once got an error message that was over two pages long (i.e., about 4000 characters long). The error message amounted to saying that one list of fields didn't match another list of fields but with two pages of field names to look at, it was impossible to say what the differences between the types were. Things would not be that bad with the example types above but they would certainly be harder than the current error messages. -- Alastair Reid

In article <200307121058.21556.alastair@reid-hoffmann.net>,
Alastair Reid
One way to overcome part of this problem would be to generalize the idea of 'type synonyms' to allow 'context synonyms'. For example, we have type synonyms like:
type Point = (Int,Int)
we could have 'context synonyms' like:
class Num a => (Add a, Subtract a, FromInteger a, Eq a, Multiply a, ...)
That would be quite unnecessary. Simply write this: class (Add a, Subtract a, FromInteger a, Eq a, Multiply a, ...) => Num a; instance (Add a, Subtract a, FromInteger a, Eq a, Multiply a, ...) => Num a; And now you can write this: invert :: Num a => Matrix a -> Matrix a I use this idiom quite frequently for "joining" classes together. -- Ashley Yakeley, Seattle WA

Alastair Reid
I'm glad to hear there isn't a _serious_ cost (i.e. performance penalty) for fine-grained hierarchies.
One cost which doesn't seem to have been mentioned is the programmer cost.
With the current Haskell Prelude, a matrix operation (say) might have type:
invert :: Num a => Matrix a -> Matrix a
but, if we had one operation per class, the type might be:
invert :: (Add a, Subtract a, FromInteger a, Eq a, Multiply a) => Matrix a -> Matrix a
More flexible but quite unwieldy.
IIRC, Clean essentially has this. Though it's more like invert :: (+ a, - a, FromInteger a, = a, * a) => Matrix a -> Matrix a (I may be wrong about the syntax and the specifics :-) - Hari -- Raja R Harinath ------------------------------ harinath@cs.umn.edu

At 10:58 12/07/03 +0100, Alastair Reid wrote:
we could have 'context synonyms' like:
class Num a => (Add a, Subtract a, FromInteger a, Eq a, Multiply a, ...)
Adding context synonyms would make it possible to write types concisely when using fine-grained class hierarchies and would also be useful with extensions like Hugs' T-REX or implicit parameters.
I must be missing something... isn't the effect achieved by:
class (Add a, Subtract a, FromInteger a, Eq a, Multiply a, ...) => Num a
?
I guess it would be nice if declaring an instance of Num could specify the
methods for Add, Subtract, etc...), but that seems a small thing, and I'm
not sure it wouldn't introduce other problems.
#g
-------------------
Graham Klyne

Dnia pon 14. lipca 2003 10:18, Graham Klyne napisał:
I must be missing something... isn't the effect achieved by: class (Add a, Subtract a, FromInteger a, Eq a, Multiply a, ...) => Num a ?
It doesn't provide instances of Num for anything which is already an instance of the other classes. And in Haskell 98 they must be defined separately for each type, instance (...) => Num a doesn't work. -- __("< Marcin Kowalczyk \__/ qrczak@knm.org.pl ^^ http://qrnik.knm.org.pl/~qrczak/

In article <200307141536.39157.qrczak@knm.org.pl>,
Marcin 'Qrczak' Kowalczyk
It doesn't provide instances of Num for anything which is already an instance of the other classes. And in Haskell 98 they must be defined separately for each type, instance (...) => Num a doesn't work.
It works in extended Haskell however, so I suspect it lays to rest the question of needing some other language extension. -- Ashley Yakeley, Seattle WA

On Tue, Jul 15, 2003 at 01:07:12AM -0700, Ashley Yakeley wrote:
In article <200307141536.39157.qrczak@knm.org.pl>, Marcin 'Qrczak' Kowalczyk
wrote: It doesn't provide instances of Num for anything which is already an instance of the other classes. And in Haskell 98 they must be defined separately for each type, instance (...) => Num a doesn't work.
It works in extended Haskell however, so I suspect it lays to rest the question of needing some other language extension.
I disagree! This method (putting each function in its own class) does not address two related points: a) Being able to declare default values for a method declared in a superclass; b) Being able to refine a type heirarchy without the users noticing (and without explosion of the number of instance declarations required). Peace, Dylan

In article <20030710133324.GA2318@soi.city.ac.uk>,
Ross Paterson
As it happens, I would like yet another intermediate class:
class BiFunctor a where bimap :: (b' -> b) -> (c -> c') -> a b c -> a b' c'
This can be decomposed into: fmap :: (c -> c') -> a b c -> a b c' cofmap2 :: (b' -> b) -> a b c -> a b' c bimap :: (Cofunctor2 a,Functor (a b)) => (b' -> b) -> (c -> c') -> a b c -> a b' c' bimap bb cc = (cofmap2 bb) . (fmap cc) It would be nice to be able to write this: class (Cofunctor2 a,forall b. Functor (a b)) => BiFunctor a instance (Cofunctor2 a,forall b. Functor (a b)) => BiFunctor a Unfortunately, foralls are not allowed in class or instance contexts... -- Ashley Yakeley, Seattle WA

At a casual glance, your Labeller looks to me like a state transformer monad. I've found that the State transformer monad in the hierarchical libraries can be useful for this kind of thing; the following example is part of a larger program, so it can't be run in isolation, but I hope it shows some possibilities. Points to note: + the initial state is an empty list, part of the 'runState' call in 'rdfQuerySubs2' + fmapM is used to sequence the monad over a fairly complex data structure, based on a FunctorM class described in a message by Tomasz Zielonka sent to the Haskell mailing list on 4 June 2003. The signature of fmapM is: fmapM :: Monad m => (a -> m b) -> (t a -> m (t b)) where, in this case, instantiates as fmapM :: (RDFLabel -> State [RDFLabel] RDFLabel) -> (RDFGraph -> State [RDFLabel] RDFGraph) + 'mapNode' returns the monad instance that collects unbound variables. The key method is update which, as its name suggests, updates the state. + The library type State handles most of the coding detail for the monad itself, leaving the application code to focus on using it. [[ import Control.Monad.State ( State(..), modify ) ... -- This function applies a substitution for a single set of variable -- bindings, returning the result and a list of unbound variables. -- It uses a state transformer monad to collect the list of unbound -- variables. rdfQuerySubs2 :: RDFQueryBinding -> RDFGraph -> (RDFGraph,[RDFLabel]) rdfQuerySubs2 varb gr = runState ( fmapM (mapNode varb) gr ) [] -- Auxiliary monad function for rdfQuerySubs2. -- This returns a state transformer Monad which in turn returns the -- substituted node value based on the supplied query variable bindings. -- The monad state is a list of labels which accumulates all those -- variables seen for which no substitution was available. mapNode :: RDFQueryBinding -> RDFLabel -> State [RDFLabel] RDFLabel mapNode varb lab = case qbMap varb lab of Just v -> return v Nothing -> if isQueryVar lab then do { modify (addVar lab) ; return lab } else return lab ]] At 14:40 26/06/03 -0400, Mark Carroll wrote:
Not really seeing why Unique is in the IO monad, not deeply understanding the use of Haskell extensions in the State source, and wanting to try to learn a bit more about monads, I thought I'd try to write my own monad for the first time: something for producing a series of unique labels. This is how it turned out:
========================================================================== module Label (Label, Labeller, newLabel) where import Monad
newtype Label = Label Int deriving (Eq, Ord)
newtype Labeller a = Labeller (Int -> (Int, a))
instance Monad Labeller where return r = Labeller (\n -> (n, r)) (Labeller g) >>= y = let f m = let (r, n) = g m Labeller h = y n in h r in Labeller f
newLabel :: Labeller Label
newLabel = Labeller (\n -> (n + 1, Label n))
runLabeller :: Labeller a -> a
runLabeller (Labeller l) = snd (l minBound)
labelTest :: Labeller [Int]
labelTest = do Label a <- newLabel Label b <- newLabel Label c <- newLabel Label d <- newLabel return [a,b,c,d]
main = print (runLabeller labelTest) ==========================================================================
I was thinking that maybe,
(a) People could point out to me where I'm still confused, as revealed by my code. Is it needlessly complicated?
(b) My code may be instructive to someone else.
-- Mark
_______________________________________________ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe
-------------------
Graham Klyne
participants (12)
-
Alastair Reid
-
Ashley Yakeley
-
Christian Maeder
-
Derek Elkins
-
Dylan Thurston
-
Graham Klyne
-
Joe English
-
Marcin 'Qrczak' Kowalczyk
-
Mark Carroll
-
Raja R Harinath
-
Ross Paterson
-
Wolfgang Jeltsch