[Haskell-cafe] Reinventing the wheel? Does any existing package provide an applicatively lifted (>>) ?
Isaac Elliott
isaace71295 at gmail.com
Thu Sep 28 09:44:13 UTC 2017
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.html
).
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, <ietf-dane at dukhovni.org>
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.
-------------- next part --------------
An HTML attachment was scrubbed...
URL: <http://mail.haskell.org/pipermail/haskell-cafe/attachments/20170928/b2af31fc/attachment.html>
More information about the Haskell-Cafe
mailing list