
Hello everyone, I am trying to restructure some of my code to eliminate some O(n^2) operations, and have realized that this will require a change in how my data is represented, but I don't see any standard data types (in Data) that will really suit my needs. Currently I have a sequence of patches is just a list, so when two sequences or patches are reordered, I have an O(n^2) operation (where n is the length of each sequence). I would like to reduce this, since most patches are orthogonal, since they modify a single file, but this isn't possible as long as the data is represented in lists. What I'd like would be to have a data structure that holds an ordered list, but has a mapping from keys to its members, a sort of ordered FiniteMap. Each member would have to match several keys. I don't think this multiplicity of keys can be hidden in a single key, since I want to be able to search by any key in O(log n). Then I'd want to be able to extract its contents matching some keys, extractKeys :: [key] -> OrderedFiniteMap key elem -> [elem] with the above preserving the order of the elements. And to be able to modify only those patches matching a given key modifyOFM :: [key] -> a -> ((elem, a) -> ([key],elem,a)) -> OrderedFiniteMap key elem -> (OrderedFiniteMap key elem, a) where the second argument indicates how the first element to be modified changes, and possibly changes the keys when matching the second element... this is looking pretty complicated... maybe what I want is some sort of a monad. Of course I'd need "normal" access functions too, but those are more obvious. Is there an existing set of algorithms that might serve my needs (or some existing data structure, that would adequately suit my needs)? I really would rather not right my own data structure module for this purpose. Creating multiple references to a given data element to describe its list and all its keys is a bit intimidating... In case I haven't been clear enough, the algorithm I want to speed up looks like (when simplified a tad) commute :: ([Patch], [Patch]) -> Maybe ([Patch], [Patch]) commute (a:as, bs) = case commuteOneMany a bs of Nothing -> Nothing Just (bs', a') -> case commute (as, bs') of Nothing -> Nothing Just (bs'', as') -> Just (bs'', a':as') commuteOneMany a (b:bs) = case commuteOne a b of Nothing -> Nothing Just (b', a') -> case commuteOneMany a' bs of Nothing -> Nothing Just (bs', a'') -> Just (b':bs', a'') commuteOne :: Patch -> Patch -> (Patch, Patch) where there exists a function patchModifies :: Patch -> [Key] such that commuteOne a b | null (patchModifies a `intersect` patchModifies b) = (b, a) Any suggestions would be appreciated. At this point I've gotten myself pretty confused as to what exactly I want to do. :( -- David Roundy http://www.abridgegame.org

On Fri, 12 Dec 2003 07:24:04 -0500
David Roundy
In case I haven't been clear enough, the algorithm I want to speed up looks like (when simplified a tad)
commute :: ([Patch], [Patch]) -> Maybe ([Patch], [Patch]) commute (a:as, bs) = case commuteOneMany a bs of Nothing -> Nothing Just (bs', a') -> case commute (as, bs') of Nothing -> Nothing Just (bs'', as') -> Just (bs'', a':as') commuteOneMany a (b:bs) = case commuteOne a b of Nothing -> Nothing Just (b', a') -> case commuteOneMany a' bs of Nothing -> Nothing Just (bs', a'') -> Just (b':bs', a'') commuteOne :: Patch -> Patch -> (Patch, Patch)
Ack! This code is screaming that you should treat Maybe as a monad. commute :: ([Patch],[Patch]) -> Maybe ([Patch],[Patch]) commute (a:as,bs) = do (bs',a') <- commuteOneMany a bs (bs'',as') <- commute as bs' return (bs'',a':as') commuteOneMany a (b:bs) = do (b',a') <- commuteOne a b (bs',a'') <- commuteOneMany a' bs return (b':bs',a'') This will also provide a migration path if you want a more featureful monad. (or_maybe is mplus, fail or mzero can be used for Nothing when you explicitly want to fail). strict_commute for example can be simplified to strict_commute (NamedP n1 d1 p1) (NamedP n2 d2 p2) = do guard (not (n2 `elem` d1 || n1 `elem` d2)) (p2',p1') <- commute (p1,p2) return (NamedP n2 d2 p2',NamedP n1 d1 p1') strict_commute p2 p1 = msum $ map (\f -> clever_commute f (p2,p1)) fs where fs = [commute_nameconflict, commute_filedir, etc...]

At 14:17 12/12/03 -0500, Derek Elkins wrote:
This will also provide a migration path if you want a more featureful monad. (or_maybe is mplus, fail or mzero can be used for Nothing when you explicitly want to fail).
Is this or_maybe (and friends) actually defined in any of the standard libraries? (Google found only one hit, in an old IRC log.) #g ------------ Graham Klyne For email: http://www.ninebynine.org/#Contact

On Fri, Dec 12, 2003 at 08:55:59PM +0000, Graham Klyne wrote:
At 14:17 12/12/03 -0500, Derek Elkins wrote:
This will also provide a migration path if you want a more featureful monad. (or_maybe is mplus, fail or mzero can be used for Nothing when you explicitly want to fail).
Is this or_maybe (and friends) actually defined in any of the standard libraries? (Google found only one hit, in an old IRC log.)
mplus and mzero are methods in class MonadPlus, which you'll found in module Monad. There is an instance of MonadPlus for Maybe. Best regards, Tom -- .signature: Too many levels of symbolic links

I apologize... my question was unclear. It was not the standard MonadPlus class and functions that I was asking about, but the specific instance for Maybe (i.e. or_maybe). As it happens, a couple of times in the past couple of weeks, I might have used such a function if it were available in the standard libraries. (Thanks, anyway!) #g -- At 11:30 14/12/03 +0100, Tomasz Zielonka wrote:
On Fri, Dec 12, 2003 at 08:55:59PM +0000, Graham Klyne wrote:
At 14:17 12/12/03 -0500, Derek Elkins wrote:
This will also provide a migration path if you want a more featureful monad. (or_maybe is mplus, fail or mzero can be used for Nothing when you explicitly want to fail).
Is this or_maybe (and friends) actually defined in any of the standard libraries? (Google found only one hit, in an old IRC log.)
mplus and mzero are methods in class MonadPlus, which you'll found in module Monad. There is an instance of MonadPlus for Maybe.
Best regards, Tom
-- .signature: Too many levels of symbolic links
------------ Graham Klyne For email: http://www.ninebynine.org/#Contact

On Mon, Dec 15, 2003 at 08:55:10AM +0000, Graham Klyne wrote:
I apologize... my question was unclear.
It was not the standard MonadPlus class and functions that I was asking about, but the specific instance for Maybe (i.e. or_maybe). As it happens, a couple of times in the past couple of weeks, I might have used such a function if it were available in the standard libraries.
My or_maybe is just defined as or_maybe (Just e) _ = Just e or_maybe Nothing f = f which is pretty simple, so you can run a series of calculations (assuming you want to keep the first that has a non-Nothing result) using f = a `or_maybe` b `or_maybe` c -- David Roundy http://www.abridgegame.org

"David" == David Roundy
writes:
David> My or_maybe is just defined as David> or_maybe (Just e) _ = Just e or_maybe Nothing f = f David> which is pretty simple, so you can run a series of calculations David> (assuming you want to keep the first that has a non-Nothing David> result) using David> f = a `or_maybe` b `or_maybe` c The advantage of using "mplus" rather than "or_maybe" is that you can write: f = a `mplus` b `mplus` c and that it will also work with other MonadPlus instances. For example, if you decide that you want to keep several results and work with "[a]" rather than "Maybe a", your "f" function will work as-is and will concatenate the different results. While "Maybe a" holds zero or one value, "[a]" holds zero or more values. Switching between both can something be very practical for functions reuse. Sam -- Samuel Tardieu -- sam@rfc1149.net -- http://www.rfc1149.net/sam

Hi David Roundy wrote:
On Mon, Dec 15, 2003 at 08:55:10AM +0000, Graham Klyne wrote:
I apologize... my question was unclear.
It was not the standard MonadPlus class and functions that I was asking about, but the specific instance for Maybe (i.e. or_maybe). As it happens, a couple of times in the past couple of weeks, I might have used such a function if it were available in the standard libraries.
My or_maybe is just defined as
or_maybe (Just e) _ = Just e or_maybe Nothing f = f
I've always been a little bothered by the MonadPlus class: zero and plus are associated (no pun intended) in my mind with monoidal structure. Is there more to MonadPlus than a clumsy workaround for the lack of quantified constraints? If we could have quantified constraints, e.g. (Monad m, forall x. Monoid (m x)) wouldn't that be better than having Monad-specific monoids? Of course, we can always kludge class MakesMonoid f where makesZero :: f x makesPlus :: f x -> f x -> f x instance MakesMonoid f => Monoid (f x) where mempty = makesZero mappend = makesPlus but that causes serious restrictions on the other monoids we can declare. One useful thing about monoids is that they can be lifted pointwise through product-like structures instance (Monoid x,Monoid y) => Monoid (x,y) instance Monoid t => Monoid (s -> t) -- note this conflicts with the more usual but (I claim) -- less useful Monoid (a -> a) The latter gives us higher-order combinators for the price of first-order operators. For example, given the `or_maybe' monoid, we get for free the operation which prioritizes two partial functions, trying the second only if the first fails. mappend :: (s -> Maybe t) -> (s -> Maybe t) -> (s -> Maybe t) You'd also be amazed how useful the monoid IO () can be... So I guess this is yet another plea for universally quantified constraints. Is there a problem with them? I don't see why (forall x. Monoid (m x)) is harder to check than (Monoid (m FreshName)). Of course, the next thing after quantified constraints is constrained constraints, and a big chunk of lambda-Prolog appearing as one of Haskell's growing collection of heterogeneous compile-time programming languages. What a big can of tasty worms... Cheers Conor

At 07:05 15/12/03 -0500, David Roundy wrote:
My or_maybe is just defined as
or_maybe (Just e) _ = Just e or_maybe Nothing f = f
which is pretty simple...
Indeed... I have been tending to do something similar inline... I'm finding there's a tension between having lots of auxilliary functions and duplicated inline logic when it comes to code readability. If a (simple) function is available from a standard library, that tebds (in my mind) to suggest using the function provided, as that represents a recognized idiom. At 13:21 15/12/03 +0100, Samuel Tardieu wrote:
I think there has been some misunderstanding here.
What the other posters wrote is that it is definitely available, but under the "mplus" name.
Aha? I looked for a MonadPlus instance of Maybe in the prelude, and didn't see it defined there. Is it defined in one of the standard libraries? Ah, now I see it is... I'm almost used to looking to the Control.Monad.<foo> libraries, I didn't think to check Control.Monad. Oops. One day, I'll learn to look in all the right places. #g ------------ Graham Klyne For email: http://www.ninebynine.org/#Contact

"Graham" == Graham Klyne
writes:
Graham> I apologize... my question was unclear. It was not the Graham> standard MonadPlus class and functions that I was asking Graham> about, but the specific instance for Maybe (i.e. or_maybe). Graham> As it happens, a couple of times in the past couple of weeks, Graham> I might have used such a function if it were available in the Graham> standard libraries. I think there has been some misunderstanding here. What the other posters wrote is that it is definitely available, but under the "mplus" name. If you want the "or_maybe" name, you can define it as: or_maybe :: Maybe a -> Maybe a -> Maybe a or_maybe = mplus but you should rather use "mplus" where you would instead use "or_maybe" because not only is "mplus" standard (you have to "import Monad"), also it allows you to use something else than "Maybe" later if you need to. So, in short: the "or_maybe" you are looking for is already available, but you should spell it "mplus". Sam -- Samuel Tardieu -- sam@rfc1149.net -- http://www.rfc1149.net/sam

On Fri, Dec 12, 2003 at 08:55:59PM +0000, Graham Klyne wrote:
At 14:17 12/12/03 -0500, Derek Elkins wrote:
This will also provide a migration path if you want a more featureful monad. (or_maybe is mplus, fail or mzero can be used for Nothing when you explicitly want to fail).
Is this or_maybe (and friends) actually defined in any of the standard libraries? (Google found only one hit, in an old IRC log.)
The or_maybe, which he's suggesting I replace with mplus, is from my code (which obviously Derek has taken a look at). It's just a little function to try one function and if it returns Nothing, then try another. -- David Roundy http://www.abridgegame.org

On Fri, 12 Dec 2003 20:55:59 +0000
Graham Klyne
At 14:17 12/12/03 -0500, Derek Elkins wrote:
This will also provide a migration path if you want a more featureful monad. (or_maybe is mplus, fail or mzero can be used for Nothing when you explicitly want to fail).
Is this or_maybe (and friends) actually defined in any of the standard libraries? (Google found only one hit, in an old IRC log.)
Well, I was somewhat confusing in switching the order, but or_maybe is a specialization of mplus. mplus is the general standard function and or_maybe is David's specialized to Maybe version. http://www.haskell.org/onlinereport/monad.html The idea of the operations of the MonadPlus class is mzero typically stands for some kind of failure and mplus is a choice or a merging. A logic analogy is if a >> b >> c is do a and b and c then a `mplus` b `mplus` c is do a or b or c. mzero would be false and return x would be true. Examples of things that would be instances of MonadPlus are: lists as representing non-determinism where mzero is [] meaning no answers (failure) and mplus being non-deterministic choice represented as (++), parsers with mzero as the always failing parser and mplus as alternation (Parsec's <|>), concurrency with mzero as the process that immediately halts and mplus as par (run two processes in parallel).
participants (7)
-
Conor McBride
-
David Roundy
-
Derek Elkins
-
Graham Klyne
-
Graham Klyne
-
Samuel Tardieu
-
Tomasz Zielonka