Reinventing the wheel? Does any existing package provide an applicatively lifted (>>) ?

When generating a report file from a database I found it much more efficient (significantly shorter runtime) to represent each row by an I/O action that prints the row, rather than to construct a Row object that to print and throw away. But the naive way to construct the I/O action can be tedious to maintain once the column count gets appreciably high: newtype Foo = Foo { _foo :: IO () } instance FromRow Foo where fromRow = Foo <$> (rowPrinter <$> field <*> field <*> field <*> ... <*> field) where rowPrinter :: Type1 -> Type2 -> Type3 -> ... -> TypeN -> IO () rowPrinter p1 p2 p3 ... pN = do printP1 printP2 printP3 ... printPN So I decided to applicatively decompose the rowPrinter function (with the actual name of "andthen" to be determined later) as: rowPrinter = (printP1 <$> field) `andthen` (printP2 <$> field) `andthen` (printP3 <$> field) `andthen` ... (printPN <$> field) which avoids the need to package the column printers explicitly into a single function, and may be somewhat more efficient a well. What was not immediately obvious to me was whether there's an "off the shelf" implementation of "andthen" I could just reuse. The necessary operator satisfies: andthen (f (m a)) (f (m b)) = f (ma >> mb) or, equivalently: a `andthen` b = (>>) <$> a <*> b for which http://pointree.io dutifully gives me: andthen = (<*>) . ((>>) <$>) Its type signature is: Prelude> :set prompt "l> " l> :m + Control.Applicative l> :m + Control.Monad l> :t ((<*>) . ((>>) <$>)) ((<*>) . ((>>) <$>)) :: (Monad m, Applicative f) => f (m a) -> f (m b) -> f (m b) l> It seems to me that this would have been done before, and the operator would already be present in some package, but I'm having trouble finding it. (Due to the hidden constructors of FromRow defining a Semigroup does not work out here, so I can't use (<>), which also inconveniently conflicts with Monoid (<>)). So my question is whether the operator in question is already available, under some name in some package, or else suggested names for it if new. -- Viktor.

Hey Victor,
If you're not actually the Monad instance of IO,
then `andThen` is (*>) for `Compose RowParser IO a` (
https://hackage.haskell.org/package/base-4.10.0.0/docs/Data-Functor-Compose....
).
So `rowPrinter` would be
rowPrinter =
getCompose $
Compose (printP1 <$> field) *>
Compose (printP2 <$> field) *>
...
Compose (printPn <$> field)
It's a bit more verbose, but I think it's the best answer.
On Thu, 28 Sep. 2017, 6:54 pm Viktor Dukhovni,
When generating a report file from a database I found it much more efficient (significantly shorter runtime) to represent each row by an I/O action that prints the row, rather than to construct a Row object that to print and throw away.
But the naive way to construct the I/O action can be tedious to maintain once the column count gets appreciably high:
newtype Foo = Foo { _foo :: IO () } instance FromRow Foo where fromRow = Foo <$> (rowPrinter <$> field <*> field <*> field <*> ... <*> field) where rowPrinter :: Type1 -> Type2 -> Type3 -> ... -> TypeN -> IO () rowPrinter p1 p2 p3 ... pN = do printP1 printP2 printP3 ... printPN
So I decided to applicatively decompose the rowPrinter function (with the actual name of "andthen" to be determined later) as:
rowPrinter = (printP1 <$> field) `andthen` (printP2 <$> field) `andthen` (printP3 <$> field) `andthen` ... (printPN <$> field)
which avoids the need to package the column printers explicitly into a single function, and may be somewhat more efficient a well.
What was not immediately obvious to me was whether there's an "off the shelf" implementation of "andthen" I could just reuse. The necessary operator satisfies:
andthen (f (m a)) (f (m b)) = f (ma >> mb)
or, equivalently:
a `andthen` b = (>>) <$> a <*> b
for which http://pointree.io dutifully gives me:
andthen = (<*>) . ((>>) <$>)
Its type signature is:
Prelude> :set prompt "l> " l> :m + Control.Applicative l> :m + Control.Monad l> :t ((<*>) . ((>>) <$>)) ((<*>) . ((>>) <$>)) :: (Monad m, Applicative f) => f (m a) -> f (m b) -> f (m b) l>
It seems to me that this would have been done before, and the operator would already be present in some package, but I'm having trouble finding it.
(Due to the hidden constructors of FromRow defining a Semigroup does not work out here, so I can't use (<>), which also inconveniently conflicts with Monoid (<>)).
So my question is whether the operator in question is already available, under some name in some package, or else suggested names for it if new.
-- Viktor.
_______________________________________________ Haskell-Cafe mailing list To (un)subscribe, modify options or view archives go to: http://mail.haskell.org/cgi-bin/mailman/listinfo/haskell-cafe Only members subscribed via the mailman list are allowed to post.

On Sep 28, 2017, at 5:44 AM, Isaac Elliott
wrote: If you're not actually the Monad instance of IO,
Can you explain that qualification?
then `andThen` is (*>) for `Compose RowParser IO a` (https://hackage.haskell.org/package/base-4.10.0.0/docs/Data-Functor-Compose....).
So `rowPrinter` would be
rowPrinter = getCompose $ Compose (printP1 <$> field) *> Compose (printP2 <$> field) *> ... Compose (printPn <$> field)
It's a bit more verbose, but I think it's the best answer.
Indeed this works, and looks more clear than some new unfamiliar operator. This seems to have no measurable run-time cost. Is it reasonable to expect that under the covers no objects boxed as (Compose _) are ever created, and that Compose here is just compile-time syntactic sugar for applying (*>) at the desired layer, so that: getCompose $ Compose (Foo Bar a) *> Compose (Foo Bar b) *> Compose (Foo Bar c) ... *> Compose (Foo Bar z) just compiles down to Foo (Bar a *> Bar b *> Bar c *> ... *> Bar z)? Where, in my case, Foo is "RowParser" and Bar is IO? -- Viktor.

On Fri, Sep 29, 2017 at 2:56 AM Viktor Dukhovni
Can you explain that qualification?
I mean that you don't need to use (>>=) on the IO inside the RowParser. The composition of two Applicatives is also an Applicative. If you upgrade one to Monad this is no longer true. Since you're only using (>>) (which is really an Applicative operation in disguise), we don't need to worry here.
Indeed this works, and looks more clear than some new unfamiliar operator. This seems to have no measurable run-time cost. Is it reasonable to expect that under the covers no objects boxed as (Compose _) are ever created, and that Compose here is just compile-time syntactic sugar for applying (*>) at the desired layer, so that:
getCompose $ Compose (Foo Bar a) *> Compose (Foo Bar b) *> Compose (Foo Bar c) ... *> Compose (Foo Bar z)
just compiles down to Foo (Bar a *> Bar b *> Bar c *> ... *> Bar z)? Where, in my case, Foo is "RowParser" and Bar is IO?
If we tried to write a typeclass instance for "composition of applicatives", it might look something like this: instance (Applicative f, Applicative g) => forall a. Applicative (f (g a)) where ... But we're not allowed to write such an instance. To get around this, a newtype is created: newtype Compose f g a = Compose { getCompose :: f (g a) } and a valid instance can be written: instance (Applicative f, Applicative g) => Applicative (Compose f g) where pure = Compose . pure . pure a <*> b = Compose $ liftA2 (<*>) a b You are correct in assuming it has no runtime cost- at runtime the `f (g a)` is passed around as normal, but at compile time, `Compose f g a` is considered distinct to `f (g a)`. Due to this typeclass instance, getCompose $ Compose a *> Compose b *> Compose c is equivalent to liftA2 (*>) (liftA2 (*>) a b) c

or, equivalently:
a `andthen` b = (>>) <$> a <*> b
for which http://pointree.io dutifully gives me:
andthen = (<*>) . ((>>) <$>)
That link is not working for me, and Google isn't finding it, and it sounds
like a useful thing.
On Thu, Sep 28, 2017 at 1:55 AM, Viktor Dukhovni
When generating a report file from a database I found it much more efficient (significantly shorter runtime) to represent each row by an I/O action that prints the row, rather than to construct a Row object that to print and throw away.
But the naive way to construct the I/O action can be tedious to maintain once the column count gets appreciably high:
newtype Foo = Foo { _foo :: IO () } instance FromRow Foo where fromRow = Foo <$> (rowPrinter <$> field <*> field <*> field <*> ... <*> field) where rowPrinter :: Type1 -> Type2 -> Type3 -> ... -> TypeN -> IO () rowPrinter p1 p2 p3 ... pN = do printP1 printP2 printP3 ... printPN
So I decided to applicatively decompose the rowPrinter function (with the actual name of "andthen" to be determined later) as:
rowPrinter = (printP1 <$> field) `andthen` (printP2 <$> field) `andthen` (printP3 <$> field) `andthen` ... (printPN <$> field)
which avoids the need to package the column printers explicitly into a single function, and may be somewhat more efficient a well.
What was not immediately obvious to me was whether there's an "off the shelf" implementation of "andthen" I could just reuse. The necessary operator satisfies:
andthen (f (m a)) (f (m b)) = f (ma >> mb)
or, equivalently:
a `andthen` b = (>>) <$> a <*> b
for which http://pointree.io dutifully gives me:
andthen = (<*>) . ((>>) <$>)
Its type signature is:
Prelude> :set prompt "l> " l> :m + Control.Applicative l> :m + Control.Monad l> :t ((<*>) . ((>>) <$>)) ((<*>) . ((>>) <$>)) :: (Monad m, Applicative f) => f (m a) -> f (m b) -> f (m b) l>
It seems to me that this would have been done before, and the operator would already be present in some package, but I'm having trouble finding it.
(Due to the hidden constructors of FromRow defining a Semigroup does not work out here, so I can't use (<>), which also inconveniently conflicts with Monoid (<>)).
So my question is whether the operator in question is already available, under some name in some package, or else suggested names for it if new.
-- Viktor.
_______________________________________________ Haskell-Cafe mailing list To (un)subscribe, modify options or view archives go to: http://mail.haskell.org/cgi-bin/mailman/listinfo/haskell-cafe Only members subscribed via the mailman list are allowed to post.
-- Jeff Brown | Jeffrey Benjamin Brown Website https://msu.edu/~brown202/ | Facebook https://www.facebook.com/mejeff.younotjeff | LinkedIn https://www.linkedin.com/in/jeffreybenjaminbrown(spammy, so I often miss messages here) | Github https://github.com/jeffreybenjaminbrown

Am 28.09.2017 um 12:57 schrieb Jeffrey Brown:
or, equivalently:
a `andthen` b = (>>) <$> a <*> b
for which http://pointree.io http://pointree.io/ dutifully gives me:
andthen = (<*>) . ((>>) <$>)
That link is not working for me, and Google isn't finding it, and it sounds like a useful thing.
Theres just an `f` missing. Correct link is probably http://pointfree.io/

It should be free instead of tree:
http://pointfree.io/
Regards,
On Thu, Sep 28, 2017 at 4:27 PM, Jeffrey Brown
or, equivalently:
a `andthen` b = (>>) <$> a <*> b
for which http://pointree.io dutifully gives me:
andthen = (<*>) . ((>>) <$>)
That link is not working for me, and Google isn't finding it, and it sounds like a useful thing.
On Thu, Sep 28, 2017 at 1:55 AM, Viktor Dukhovni
wrote: When generating a report file from a database I found it much more efficient (significantly shorter runtime) to represent each row by an I/O action that prints the row, rather than to construct a Row object that to print and throw away.
But the naive way to construct the I/O action can be tedious to maintain once the column count gets appreciably high:
newtype Foo = Foo { _foo :: IO () } instance FromRow Foo where fromRow = Foo <$> (rowPrinter <$> field <*> field <*> field <*> ... <*> field) where rowPrinter :: Type1 -> Type2 -> Type3 -> ... -> TypeN -> IO () rowPrinter p1 p2 p3 ... pN = do printP1 printP2 printP3 ... printPN
So I decided to applicatively decompose the rowPrinter function (with the actual name of "andthen" to be determined later) as:
rowPrinter = (printP1 <$> field) `andthen` (printP2 <$> field) `andthen` (printP3 <$> field) `andthen` ... (printPN <$> field)
which avoids the need to package the column printers explicitly into a single function, and may be somewhat more efficient a well.
What was not immediately obvious to me was whether there's an "off the shelf" implementation of "andthen" I could just reuse. The necessary operator satisfies:
andthen (f (m a)) (f (m b)) = f (ma >> mb)
or, equivalently:
a `andthen` b = (>>) <$> a <*> b
for which http://pointree.io dutifully gives me:
andthen = (<*>) . ((>>) <$>)
Its type signature is:
Prelude> :set prompt "l> " l> :m + Control.Applicative l> :m + Control.Monad l> :t ((<*>) . ((>>) <$>)) ((<*>) . ((>>) <$>)) :: (Monad m, Applicative f) => f (m a) -> f (m b) -> f (m b) l>
It seems to me that this would have been done before, and the operator would already be present in some package, but I'm having trouble finding it.
(Due to the hidden constructors of FromRow defining a Semigroup does not work out here, so I can't use (<>), which also inconveniently conflicts with Monoid (<>)).
So my question is whether the operator in question is already available, under some name in some package, or else suggested names for it if new.
-- Viktor.
_______________________________________________ Haskell-Cafe mailing list To (un)subscribe, modify options or view archives go to: http://mail.haskell.org/cgi-bin/mailman/listinfo/haskell-cafe Only members subscribed via the mailman list are allowed to post.
-- Jeff Brown | Jeffrey Benjamin Brown Website https://msu.edu/~brown202/ | Facebook https://www.facebook.com/mejeff.younotjeff | LinkedIn https://www.linkedin.com/in/jeffreybenjaminbrown(spammy, so I often miss messages here) | Github https://github.com/jeffreybenjaminbrown
_______________________________________________ Haskell-Cafe mailing list To (un)subscribe, modify options or view archives go to: http://mail.haskell.org/cgi-bin/mailman/listinfo/haskell-cafe Only members subscribed via the mailman list are allowed to post.
-- Sibi, sibi@psibi.in WWW: psibi.in http://www.psibi.in Twitter/github/identi.ca: psibi GPG Fingerpint: A241 B3D6 F4FD D40D D7DE B1C6 D19E 3E0E BB55 7613 Registered Linux User ID: 534664
participants (5)
-
Isaac Elliott
-
Jeffrey Brown
-
Norbert Melzer
-
Sibi
-
Viktor Dukhovni