
Anyone ever needed this? Me and John Wiegley were discussing a decent name for it, John suggested inv as in involution. E.g. inv reverse (take 10) inv reverse (dropWhile isDigit) trim = inv reverse (dropWhile isSpace) . dropWhile isSpace That seems to be the only use-case I've ever come across. There's also this one: co f g = f g . g which means you can write trim = co (inv reverse) (dropWhile isSpace) but that's optimizing an ever rarer use-case.

On 17 August 2013 19:11, Christopher Done
Anyone ever needed this? Me and John Wiegley were discussing a decent name for it, John suggested inv as in involution. E.g.
In terms of a decent name: as soon as I saw the subject, I thought you were somehow inverting a function :/ In terms of how useful it is, I don't think I tend to use such an idiom.
inv reverse (take 10) inv reverse (dropWhile isDigit) trim = inv reverse (dropWhile isSpace) . dropWhile isSpace
That seems to be the only use-case I've ever come across.
There's also this one:
co f g = f g . g
which means you can write
trim = co (inv reverse) (dropWhile isSpace)
but that's optimizing an ever rarer use-case.
_______________________________________________ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe
-- Ivan Lazar Miljenovic Ivan.Miljenovic@gmail.com http://IvanMiljenovic.wordpress.com

On 17/08/13 10:11, Christopher Done wrote:
Anyone ever needed this? Me and John Wiegley were discussing a decent name for it, John suggested inv as in involution. E.g. First thing I thought was ‘inverse’…
inv reverse (take 10) inv reverse (dropWhile isDigit) trim = inv reverse (dropWhile isSpace) . dropWhile isSpace
That seems to be the only use-case I've ever come across.
I do this a lot as well. Why not skip the ‘g’ all together and have ‘f . reverse . f’ if that's all we're doing? You could even call it fromEnd at that point and we end up with a rather intuitive ‘fromEnd (drop 10)’. Maybe even just have an operator.
There's also this one:
co f g = f g . g
which means you can write
trim = co (inv reverse) (dropWhile isSpace)
but that's optimizing an ever rarer use-case.
Is this a proposal for addition to something or is it just general discussion? -- Mateusz K.

In J (a sort of dialect of APL), there's a thing called "under", written
"&.". The expression "(f &. g) x" is equivalent to "(g^:_1) (f (g x))"
where "g^:_1" is J's "obverse" of g, which in cases where it exists is
usually the inverse of g (
http://www.jsoftware.com/help/dictionary/intro26.htm). Abusing notation
with some weird mixture of Haskell and J, this means that "((+) &. log)"
multiplies numbers by taking logs, adding and exponentiating. You "inv" is
"under" for cases where g == g^-1 (reverse being a good example). In cases
where g /= g^-1, it's obviously a useful operation, but the case where g ==
g^-1 seems a bit specialised. Can you think of any other useful cases than
g == reverse? I guess "inv (1/) sum" is the harmonic mean, but that's
another special case.
On 17 August 2013 11:40, Mateusz Kowalczyk
On 17/08/13 10:11, Christopher Done wrote:
Anyone ever needed this? Me and John Wiegley were discussing a decent name for it, John suggested inv as in involution. E.g. First thing I thought was ‘inverse’…
inv reverse (take 10) inv reverse (dropWhile isDigit) trim = inv reverse (dropWhile isSpace) . dropWhile isSpace
That seems to be the only use-case I've ever come across.
I do this a lot as well. Why not skip the ‘g’ all together and have ‘f . reverse . f’ if that's all we're doing? You could even call it fromEnd at that point and we end up with a rather intuitive ‘fromEnd (drop 10)’. Maybe even just have an operator.
There's also this one:
co f g = f g . g
which means you can write
trim = co (inv reverse) (dropWhile isSpace)
but that's optimizing an ever rarer use-case.
Is this a proposal for addition to something or is it just general discussion?
-- Mateusz K.
_______________________________________________ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe
-- Ian Ross Tel: +43(0)6804451378 ian@skybluetrades.net www.skybluetrades.net

On Sat, Aug 17, 2013 at 11:11:07AM +0200, Christopher Done wrote:
Anyone ever needed this? Me and John Wiegley were discussing a decent name for it, John suggested inv as in involution. E.g.
inv reverse (take 10) inv reverse (dropWhile isDigit) trim = inv reverse (dropWhile isSpace) . dropWhile isSpace
This sounds like a job for a lens, or similar. Tom

Note that at least for the dropWhile example, there is a specialized function, dropWhileEnd, which is most likely more efficient than reversing the list twice. On Aug 17, 2013 3:35 PM, "Tom Ellis" < tom-lists-haskell-cafe-2013@jaguarpaw.co.uk> wrote:
On Sat, Aug 17, 2013 at 11:11:07AM +0200, Christopher Done wrote:
Anyone ever needed this? Me and John Wiegley were discussing a decent name for it, John suggested inv as in involution. E.g.
inv reverse (take 10) inv reverse (dropWhile isDigit) trim = inv reverse (dropWhile isSpace) . dropWhile isSpace
This sounds like a job for a lens, or similar.
Tom
_______________________________________________ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe

Hi, Am Samstag, den 17.08.2013, 11:11 +0200 schrieb Christopher Done:
inv reverse (take 10)
if you want that fast and lazy, check out http://www.joachim-breitner.de/blog/archives/600-On-taking-the-last-n-elemen... Greetings, Joachim -- Joachim “nomeata” Breitner mail@joachim-breitner.de • http://www.joachim-breitner.de/ Jabber: nomeata@joachim-breitner.de • GPG-Key: 0x4743206C Debian Developer: nomeata@debian.org

Christopher Done
Anyone ever needed this? Me and John Wiegley were discussing a decent name for it, John suggested inv as in involution. E.g.
inv reverse (take 10) inv reverse (dropWhile isDigit) trim = inv reverse (dropWhile isSpace) . dropWhile isSpace
That seems to be the only use-case I've ever come across.
And it's here only because reverse^-1 ≡ reverse, is not it? I only can see how f ∘ g ∘ f^-1 can be a pattern.
There's also this one:
co f g = f g . g
which means you can write
trim = co (inv reverse) (dropWhile isSpace)
but that's optimizing an ever rarer use-case.
-- lelf

This is indeed a job for lens, particularly, the Iso type, and the "under" function. Lens conveniently comes with a typeclassed isomorphism called "reversed", which of course has a list instance.
under reversed (take 10) ['a'.. 'z'] "qrstuvwxyz"
-- Dan Burton
On Aug 17, 2013 10:23 AM, "Anton Nikishaev"
Christopher Done
writes: Anyone ever needed this? Me and John Wiegley were discussing a decent name for it, John suggested inv as in involution. E.g.
inv reverse (take 10) inv reverse (dropWhile isDigit) trim = inv reverse (dropWhile isSpace) . dropWhile isSpace
That seems to be the only use-case I've ever come across.
And it's here only because reverse^-1 ≡ reverse, is not it? I only can see how f ∘ g ∘ f^-1 can be a pattern.
There's also this one:
co f g = f g . g
which means you can write
trim = co (inv reverse) (dropWhile isSpace)
but that's optimizing an ever rarer use-case.
-- lelf
_______________________________________________ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe

The lens docs even have an example of another helper function, "involuted" for functions which are their own inverse.
"live" & involuted reverse %~ ('d':) "lived"
inv f g = involuted f %~ g
http://hackage.haskell.org/packages/archive/lens/3.9.0.2/doc/html/Control-Le...
-- Dan Burton
On Sat, Aug 17, 2013 at 1:43 PM, Dan Burton
This is indeed a job for lens, particularly, the Iso type, and the "under" function. Lens conveniently comes with a typeclassed isomorphism called "reversed", which of course has a list instance.
under reversed (take 10) ['a'.. 'z'] "qrstuvwxyz"
-- Dan Burton On Aug 17, 2013 10:23 AM, "Anton Nikishaev"
wrote: Christopher Done
writes: Anyone ever needed this? Me and John Wiegley were discussing a decent name for it, John suggested inv as in involution. E.g.
inv reverse (take 10) inv reverse (dropWhile isDigit) trim = inv reverse (dropWhile isSpace) . dropWhile isSpace
That seems to be the only use-case I've ever come across.
And it's here only because reverse^-1 ≡ reverse, is not it? I only can see how f ∘ g ∘ f^-1 can be a pattern.
There's also this one:
co f g = f g . g
which means you can write
trim = co (inv reverse) (dropWhile isSpace)
but that's optimizing an ever rarer use-case.
-- lelf
_______________________________________________ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe

Hi, as for the nomenclature - mathematically the pattern f^{-1} . g . f is sometimes called "conjugation" [1]. One (trivial) type of occurrence is data Foo a = Foo { unFoo :: a } deriving Show instance Functor Foo where fmap f = Foo . f . unFoo The under function from the lens library [2] allows expressing this as follows: instance Functor Foo where fmap = under (iso Foo unFoo) which is a very elegant way of capturing the essence of the pattern. Best regards, Nikita [1] http://en.wikipedia.org/wiki/Conjugacy_class [2] http://hackage.haskell.org/packages/archive/lens/3.9.0.2/doc/html/Control-Le... On 17/08/13 22:57, Dan Burton wrote:
The lens docs even have an example of another helper function, "involuted" for functions which are their own inverse.
"live" & involuted reverse %~ ('d':) "lived"
inv f g = involuted f %~ g
http://hackage.haskell.org/packages/archive/lens/3.9.0.2/doc/html/Control-Le...
-- Dan Burton
On Sat, Aug 17, 2013 at 1:43 PM, Dan Burton
mailto:danburton.email@gmail.com> wrote: This is indeed a job for lens, particularly, the Iso type, and the "under" function. Lens conveniently comes with a typeclassed isomorphism called "reversed", which of course has a list instance.
>>> under reversed (take 10) ['a'.. 'z'] "qrstuvwxyz"
-- Dan Burton
On Aug 17, 2013 10:23 AM, "Anton Nikishaev"
mailto:me@lelf.lu> wrote: Christopher Done
mailto:chrisdone@gmail.com> writes: > Anyone ever needed this? Me and John Wiegley were discussing a decent > name for it, John suggested inv as in involution. E.g. > > inv reverse (take 10) > inv reverse (dropWhile isDigit) > trim = inv reverse (dropWhile isSpace) . dropWhile isSpace > > That seems to be the only use-case I've ever come across.
And it's here only because reverse^-1 ≡ reverse, is not it? I only can see how f ∘ g ∘ f^-1 can be a pattern.
> There's also this one: > > co f g = f g . g > > which means you can write > > trim = co (inv reverse) (dropWhile isSpace) > > but that's optimizing an ever rarer use-case.
-- lelf
_______________________________________________ Haskell-Cafe mailing list Haskell-Cafe@haskell.org mailto:Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe
_______________________________________________ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe
participants (11)
-
Anton Nikishaev
-
Christopher Done
-
Dan Burton
-
Ian Ross
-
Ivan Lazar Miljenovic
-
Joachim Breitner
-
John Wiegley
-
Mateusz Kowalczyk
-
Nikita Danilenko
-
Tobias Dammers
-
Tom Ellis