
Is there a name for a fold that promises to call a function such that only an associative function will always return the same result. Or in other words, it has the property that it promises to call a function "associatively" on a set of data? Thanks! Charlie

On Fri, Oct 23, 2015 at 10:26:08AM -0400, Charles Durham wrote:
Is there a name for a fold that promises to call a function such that only an associative function will always return the same result. Or in other words, it has the property that it promises to call a function "associatively" on a set of data?
I am not sure I am understanding the question correctly. Every Monoid has a single binary operation which happens to be associative and one of the basic fold functions has signature foldMap :: (Foldable t, Monoid m) => (a -> m) -> t a -> m (which does what you expect). Does that answer your question? If not, I'd be grateful if you would provide an example.

Yeah, sorry, should have provided an example to begin with.
Let's say you have a function "thisFold :: (a -> a -> a) -> [a] -> a"
and it says that the function 'f' passed in must be associative.
Then it goes on to use f in "thisFold f [0,1,2]" like "f (1 (f 0 2))".
Obviously f is still associative, but 'thisFold' did not call f
'associatively' on the data. My question is if there is a name for what
property this broke by not calling f 'associatively'.
Does that make sense?
On Fri, Oct 23, 2015 at 11:21 AM, Francesco Ariis
On Fri, Oct 23, 2015 at 10:26:08AM -0400, Charles Durham wrote:
Is there a name for a fold that promises to call a function such that only an associative function will always return the same result. Or in other words, it has the property that it promises to call a function "associatively" on a set of data?
I am not sure I am understanding the question correctly. Every Monoid has a single binary operation which happens to be associative and one of the basic fold functions has signature
foldMap :: (Foldable t, Monoid m) => (a -> m) -> t a -> m
(which does what you expect). Does that answer your question? If not, I'd be grateful if you would provide an example. _______________________________________________ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://mail.haskell.org/cgi-bin/mailman/listinfo/haskell-cafe

On Fri, Oct 23, 2015 at 11:45:13AM -0400, Charles Durham wrote:
Let's say you have a function "thisFold :: (a -> a -> a) -> [a] -> a"
and it says that the function 'f' passed in must be associative.
Then it goes on to use f in "thisFold f [0,1,2]" like "f (1 (f 0 2))". Obviously f is still associative, but 'thisFold' did not call f 'associatively' on the data. My question is if there is a name for what property this broke by not calling f 'associatively'.
Does that make sense?
I don't think it makes sense. You're asking whether there's a *name* for the property it broke, but is there even a property it broke at all? If so, can you write the property down (without naming it)? Tom

I can think of a few properties that folds can honor: 1. Promises to call f on all data (does not have any guarantees on order) 2. Promises to call f on all data in order (like a left fold) 3. Promises to call f "associatively" (perhaps can be formalized as an in order break down of the data into tree structures) I'm assuming at least #1 has a well known name (something completeness?) On Fri, Oct 23, 2015 at 11:49 AM, Tom Ellis < tom-lists-haskell-cafe-2013@jaguarpaw.co.uk> wrote:
On Fri, Oct 23, 2015 at 11:45:13AM -0400, Charles Durham wrote:
Let's say you have a function "thisFold :: (a -> a -> a) -> [a] -> a"
and it says that the function 'f' passed in must be associative.
Then it goes on to use f in "thisFold f [0,1,2]" like "f (1 (f 0 2))". Obviously f is still associative, but 'thisFold' did not call f 'associatively' on the data. My question is if there is a name for what property this broke by not calling f 'associatively'.
Does that make sense?
I don't think it makes sense. You're asking whether there's a *name* for the property it broke, but is there even a property it broke at all? If so, can you write the property down (without naming it)?
Tom _______________________________________________ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://mail.haskell.org/cgi-bin/mailman/listinfo/haskell-cafe

On Fri, Oct 23, 2015 at 12:07:57PM -0400, Charles Durham wrote:
I can think of a few properties that folds can honor:
1. Promises to call f on all data (does not have any guarantees on order) 2. Promises to call f on all data in order (like a left fold) 3. Promises to call f "associatively" (perhaps can be formalized as an in order break down of the data into tree structures)
I'm assuming at least #1 has a well known name (something completeness?)
2. doesn't have any meaning in a pure language, I think. What would it mean to call f on data out of order?

On Fri, Oct 23, 2015 at 05:12:06PM +0100, Tom Ellis wrote:
On Fri, Oct 23, 2015 at 12:07:57PM -0400, Charles Durham wrote:
I can think of a few properties that folds can honor:
1. Promises to call f on all data (does not have any guarantees on order) 2. Promises to call f on all data in order (like a left fold) 3. Promises to call f "associatively" (perhaps can be formalized as an in order break down of the data into tree structures)
I'm assuming at least #1 has a well known name (something completeness?)
2. doesn't have any meaning in a pure language, I think. What would it mean to call f on data out of order?
He gave an example in his previous email: On Fri, Oct 23, 2015 at 11:45:13AM -0400, Charles Durham wrote:
Let's say you have a function "thisFold :: (a -> a -> a) -> [a] -> a"
and it says that the function 'f' passed in must be associative.
Then it goes on to use f in "thisFold f [0,1,2]" like "f (1 (f 0 2))". Obviously f is still associative, but 'thisFold' did not call f 'associatively' on the data.
I guess it boils down to "toList has to make sense". Which for every Foldable instance I can think of does, but it's not really a property, rather what the instance wants to capture.

On Fri, Oct 23, 2015 at 06:38:22PM +0200, Francesco Ariis wrote:
On Fri, Oct 23, 2015 at 05:12:06PM +0100, Tom Ellis wrote:
On Fri, Oct 23, 2015 at 12:07:57PM -0400, Charles Durham wrote:
I can think of a few properties that folds can honor:
1. Promises to call f on all data (does not have any guarantees on order) 2. Promises to call f on all data in order (like a left fold) 3. Promises to call f "associatively" (perhaps can be formalized as an in order break down of the data into tree structures)
I'm assuming at least #1 has a well known name (something completeness?)
2. doesn't have any meaning in a pure language, I think. What would it mean to call f on data out of order?
He gave an example in his previous email:
On Fri, Oct 23, 2015 at 11:45:13AM -0400, Charles Durham wrote:
Let's say you have a function "thisFold :: (a -> a -> a) -> [a] -> a"
and it says that the function 'f' passed in must be associative.
Then it goes on to use f in "thisFold f [0,1,2]" like "f (1 (f 0 2))". Obviously f is still associative, but 'thisFold' did not call f 'associatively' on the data.
Oh, I think I see. Not temporal order, but an order "determined" by `f`. In this case I would just say that property is that "the function factors through `foldl f`", i.e. is `g . foldl f` for some `g`. Tom

Hello All, I have recently encountered 2 situations where I needed an IO action, but only had a monad stack with IO at the bottom. The two examples were: 1. from Control.Concurrent.Async withAsync :: IO a -> (Async a -> IO b) -> IO b 2. from Network.WebSockets runClient :: String -- ^ Host -> Int -- ^ Port -> String -- ^ Path -> (Connection -> IO a) -- ^ Client application -> IO a I need to pass a function that returns an IO action to both these functions. I think my life would be easier if the function signatures were: 1. withAsync :: MonadIO mIO => mIO a -> (Async a -> mIO b) -> mIO b 2. from Network.WebSockets runClient :: MonadIO mIO => -> String -- ^ Host -> Int -- ^ Port -> String -- ^ Path -> (Connection -> mIO a) -- ^ Client application -> mIO a There are many other examples, a notable one are the functions in Control.Exception also always expect an IO action. I know we have libraries to solve this problem, such as lifted-async, lifted-base and the functionality in Control.Monad.Trans.Control. But what are the best practices for writing code that uses Monadic actions? Should I always generalize my type signatures or just expect others to use the libraries when they need to? Also, to some extent it seems trivial to re-write a library like async with the generalized signatures I need. I would just need to apply 'lift' everywhere. Couldn't the compiler do this for me? ;-) Thanks, Dimitri

On Fri, 2015-10-23 at 13:39 -0600, Dimitri DeFigueiredo wrote:
Hello All,
I have recently encountered 2 situations where I needed an IO action, but only had a monad stack with IO at the bottom.
The two examples were:
1. from Control.Concurrent.Async withAsync :: IO a -> (Async a -> IO b) -> IO b
2. from Network.WebSockets runClient :: String -- ^ Host -> Int -- ^ Port -> String -- ^ Path -> (Connection -> IO a) -- ^ Client application -> IO a
I need to pass a function that returns an IO action to both these functions. I think my life would be easier if the function signatures were:
1. withAsync :: MonadIO mIO => mIO a -> (Async a -> mIO b) -> mIO b
2. from Network.WebSockets runClient :: MonadIO mIO => -> String -- ^ Host -> Int -- ^ Port -> String -- ^ Path -> (Connection -> mIO a) -- ^ Client application -> mIO a
There are many other examples, a notable one are the functions in Control.Exception also always expect an IO action. I know we have libraries to solve this problem, such as lifted-async, lifted-base and the functionality in Control.Monad.Trans.Control. But what are the best practices for writing code that uses Monadic actions? Should I always generalize my type signatures or just expect others to use the libraries when they need to?
Also, to some extent it seems trivial to re-write a library like async with the generalized signatures I need. I would just need to apply 'lift' everywhere. Couldn't the compiler do this for me? ;-)
It is hard to implement for `withAsync` because it has to pass the first argument to `forkIO` which doesn't accept `MonadIO`. We need something opposite to `liftIO` to do that. That is why `withAsync` from `lifted-async` requires `MonadBaseControl IO m` context. Semantically, when you want to run `StateT Int IO a` concurrently, you have to decide how the child state will interact with a state of the main computation. E.g. you may decide to copy state and discard any changes made in the child computation. Or you may merge states somehow. Anyway, it is better to be explicit here. Though `withAsync` can be easily generalized to something like withAsync :: MonadBaseControl mIO => mIO a -> (Async a -> mIO b) -> mIO b It will let you minimize number of lifts is client code. But there is other way -- don't use monad transformers based on `IO`. Seriously, in most cases `StateT`, `ExceptT` or other transformers make no sense with `IO` as a base monad. `IO` is already suitable for state passing and error handling, no need to add this functionality via transformers. Thanks, Yuras

On Fri, 2015-10-23 at 13:39 -0600, Dimitri DeFigueiredo wrote:
Hello All,
I have recently encountered 2 situations where I needed an IO action, but only had a monad stack with IO at the bottom.
The two examples were:
1. from Control.Concurrent.Async withAsync :: IO a -> (Async a -> IO b) -> IO b
2. from Network.WebSockets runClient :: String -- ^ Host -> Int -- ^ Port -> String -- ^ Path -> (Connection -> IO a) -- ^ Client application -> IO a
I need to pass a function that returns an IO action to both these functions. I think my life would be easier if the function signatures were:
1. withAsync :: MonadIO mIO => mIO a -> (Async a -> mIO b) -> mIO b
2. from Network.WebSockets runClient :: MonadIO mIO => -> String -- ^ Host -> Int -- ^ Port -> String -- ^ Path -> (Connection -> mIO a) -- ^ Client application -> mIO a
There are many other examples, a notable one are the functions in Control.Exception also always expect an IO action. I know we have libraries to solve this problem, such as lifted-async, lifted-base and the functionality in Control.Monad.Trans.Control. But what are the best practices for writing code that uses Monadic actions? Should I always generalize my type signatures or just expect others to use the libraries when they need to?
Also, to some extent it seems trivial to re-write a library like async with the generalized signatures I need. I would just need to apply 'lift' everywhere. Couldn't the compiler do this for me? ;-)
It is hard to implement for `withAsync` because it has to pass the first argument to `forkIO` which doesn't accept `MonadIO`. We need something opposite to `liftIO` to do that. That is why `withAsync` from `lifted-async` requires `MonadBaseControl IO m` context. It seems that we can just apply my argument transitively then and say
On 10/23/15 2:39 PM, Yuras Shumovich wrote: that forkIO should have had signature: forkIO :: MonadIO mIO => mIO () -> mIO ThreadId instead of forkIO :: IO () -> IO ThreadId An withAsync itself could have been written with more flexibility.
Semantically, when you want to run `StateT Int IO a` concurrently, you have to decide how the child state will interact with a state of the main computation. E.g. you may decide to copy state and discard any changes made in the child computation. Or you may merge states somehow. Anyway, it is better to be explicit here.
Though `withAsync` can be easily generalized to something like
withAsync :: MonadBaseControl mIO => mIO a -> (Async a -> mIO b) -> mIO b
It will let you minimize number of lifts is client code. But there is other way -- don't use monad transformers based on `IO`. Seriously, in most cases `StateT`, `ExceptT` or other transformers make no sense with `IO` as a base monad. `IO` is already suitable for state passing and error handling, no need to add this functionality via transformers. Unfortunately, I am using the pipes library, so I cannot avoid using a monad transformer. Because of the functionality pipes provides, it does make sense for it to be a monad transformer.
So, I'm still unclear whether I should always try to generalize my own monadic code (and complicate my type signatures) and whether this could/should be done automatically by the compiler.
Thanks, Yuras
Thanks, Dimitri

On Fri, 2015-10-23 at 16:25 -0600, Dimitri DeFigueiredo wrote:
On Fri, 2015-10-23 at 13:39 -0600, Dimitri DeFigueiredo wrote:
Hello All,
I have recently encountered 2 situations where I needed an IO action, but only had a monad stack with IO at the bottom.
The two examples were:
1. from Control.Concurrent.Async withAsync :: IO a -> (Async a -> IO b) -> IO b
2. from Network.WebSockets runClient :: String -- ^ Host -> Int -- ^ Port -> String -- ^ Path -> (Connection -> IO a) -- ^ Client application -> IO a
I need to pass a function that returns an IO action to both these functions. I think my life would be easier if the function signatures were:
1. withAsync :: MonadIO mIO => mIO a -> (Async a -> mIO b) -> mIO b
2. from Network.WebSockets runClient :: MonadIO mIO => -> String -- ^ Host -> Int -- ^ Port -> String -- ^ Path -> (Connection -> mIO a) -- ^ Client application -> mIO a
There are many other examples, a notable one are the functions in Control.Exception also always expect an IO action. I know we have libraries to solve this problem, such as lifted- async, lifted-base and the functionality in Control.Monad.Trans.Control. But what are the best practices for writing code that uses Monadic actions? Should I always generalize my type signatures or just expect others to use the libraries when they need to?
Also, to some extent it seems trivial to re-write a library like async with the generalized signatures I need. I would just need to apply 'lift' everywhere. Couldn't the compiler do this for me? ;-)
It is hard to implement for `withAsync` because it has to pass the first argument to `forkIO` which doesn't accept `MonadIO`. We need something opposite to `liftIO` to do that. That is why `withAsync` from `lifted-async` requires `MonadBaseControl IO m` context. It seems that we can just apply my argument transitively then and say
On 10/23/15 2:39 PM, Yuras Shumovich wrote: that forkIO should have had signature: forkIO :: MonadIO mIO => mIO () -> mIO ThreadId instead of forkIO :: IO () -> IO ThreadId
No, you can't implement it. It doesn't have well-defined semantics, see the section about `StateT` in the previous email. In theory you can do it with `MonadBaseControl`, but it practice it is not in base (strictly speaking, it is event not written in Haskell), and base can't depend on monad-control package.
An withAsync itself could have been written with more flexibility.
Semantically, when you want to run `StateT Int IO a` concurrently, you have to decide how the child state will interact with a state of the main computation. E.g. you may decide to copy state and discard any changes made in the child computation. Or you may merge states somehow. Anyway, it is better to be explicit here.
Though `withAsync` can be easily generalized to something like
withAsync :: MonadBaseControl mIO => mIO a -> (Async a -> mIO b) -> mIO b
It will let you minimize number of lifts is client code. But there is other way -- don't use monad transformers based on `IO`. Seriously, in most cases `StateT`, `ExceptT` or other transformers make no sense with `IO` as a base monad. `IO` is already suitable for state passing and error handling, no need to add this functionality via transformers. Unfortunately, I am using the pipes library, so I cannot avoid using a monad transformer. Because of the functionality pipes provides, it does make sense for it to be a monad transformer.
(I'm not a user of pipes myself, so I don't know all the details) AFAIK pipes is a CPS monad. Mixing explicit continuations with a continuation framework is asking for troubles -- it can be done correctly, but it is not trivial. Probably pipes ecosystem contains ready to use building blocks for your task? E.g. pipes-concurrency looks relevant.
So, I'm still unclear whether I should always try to generalize my own monadic code (and complicate my type signatures) and whether this could/should be done automatically by the compiler.
It could not be done by compiler because compiler doesn't not semantics. For example this post describes difficulties with exception handling in CPS monad.
Thanks, Yuras
Thanks,
Dimitri

On Sat, 2015-10-24 at 02:07 +0300, Yuras Shumovich wrote:
It could not be done by compiler because compiler doesn't not semantics. For example this post describes difficulties with exception handling in CPS monad.
Sorry, forgot to insert the actual link: http://www.yesodweb.com/blog/2014/05/exceptions-cont-monads

On Sat, Oct 24, 2015 at 5:25 AM, Dimitri DeFigueiredo < defigueiredo@ucdavis.edu> wrote:
Unfortunately, I am using the pipes library, so I cannot avoid using a monad transformer. Because of the functionality pipes provides, it does make sense for it to be a monad transformer.
Hi Dimitri, This is a very interesting topic, thank you for bringing it up. Unfortunately because of the very generalized way it's presented, it's very hard for anyone else aside from Yuras to give it the attention it deserves. Do you have a concrete example with sample code that you could simplify and present instead? E.g. instead of the multiply-stacked monad transformer embedded in 200 lines that you're facing, can you present an example with 2 monadic layers (the base being IO) in say, 20 lines? -- Kim-Ee

Hi Kim-Ee, Sorry for not making the problem clear enough! Here's an example. It is somewhat contrived, but I think it captures the essence of the problem. Imagine I need to read a .CSV file which may or may not contain column titles on its first line. I'm not interested in the column titles, I just want the rest of the file. I am provided a library function to read the contents of the file (using a "callback"). The library author provided this function in the IO monad. withCSV :: FilePath -> (Handle -> IO r) -> IO r withCSV path action = do putStrLn "opening file" h <- openFile path ReadWriteMode r <- action h hClose h putStrLn "file closed" return r The problem arises because I also want to use the ReaderT monad transformer. My environment information will tell me whether or not to disregard the first (i.e. column title) line. Here's a *failed* attempt at writing this next step: data ColumnHeaders = FirstLine | None getFileContents :: ReaderT ColumnHeaders IO String getFileContents = liftIO $ withCSV "data.csv" myReadFile where myReadFile :: Handle -> IO String myReadFile handle = do header <- ask --- OOOPPSss!!! FAIL! Can't ask. case header of None -> return "" FirstLine -> hGetLine handle -- skip first line text <- hGetContents handle evaluate (length text) -- force lazy IO return text main = do cs <- runReaderT getFileContents FirstLine print cs Unfortunately, I can't write getFileContents as described above because myReadFile is an IO action and cannot access the configuration information available through the Reader. If I could rewrite withCSV I could fix this issue: withCSVLifted :: MonadIO mIO => FilePath -> (Handle -> mIO r) -> mIO r withCSVLifted path action = do liftIO $putStrLn "opening file" h <- liftIO $ openFile path ReadMode r <- action h liftIO $ hClose h liftIO $ putStrLn "file closed" return r The difference between withCSV and withCSVLifted is just a bunch of liftIO operations and a more flexible type signature. The crucial change is that the lifted version allows any function of type (MonadIO mIO => Handle -> mIO r) rather than just (Handle -> IO r). This is general enough to allow me to re-write my configuration step and call ask (from within the callback). getFileContentsLifted :: ReaderT ColumnHeaders IO String getFileContentsLifted = withCSVLifted "data.csv" myReadFile where myReadFile :: Handle -> ReaderT ColumnHeaders IO String myReadFile handle = do header <- ask case header of None -> return "" FirstLine -> liftIO $ hGetLine handle -- skip first line then text <- liftIO $ hGetContents handle liftIO $ evaluate (length text) -- force lazy IO return text Other than calling the respective lifted version of withCSV the only difference between getFileContentsLifted and getFileContents are the extra liftIO calls. It can be very cumbersome to write a working version of getFileContents in the IO monad without easy access to ReaderT's ask. So, my questions were: 1. Should library authors always provide lifted versions of functions that take callbacks? In other words, is withCSVLifted :: MonadIO mIO => FilePath -> (Handle -> mIO r) -> mIO r always better than withCSV :: FilePath -> (Handle -> IO r) -> IO r ? If not, what's the best practice? 2. Once we define the MonadIO class, shouldn't the compiler be able to transform withCSV :: FilePath -> (Handle -> IO r) -> IO r into withCSVLifted :: MonadIO mIO => FilePath -> (Handle -> mIO r) -> mIO r by adding a number of liftIO calls to that class upon request? It seems like the kind of change we would like to automate. This email turned out to be longer than I expected. I hope it is clearer. You can find all the code here: https://gist.github.com/dimitri-xyz/3f9d1f6632479ef59304 Thanks! Dimitri On 10/23/15 7:48 PM, Kim-Ee Yeoh wrote:
On Sat, Oct 24, 2015 at 5:25 AM, Dimitri DeFigueiredo
mailto:defigueiredo@ucdavis.edu> wrote: Unfortunately, I am using the pipes library, so I cannot avoid using a monad transformer. Because of the functionality pipes provides, it does make sense for it to be a monad transformer.
Hi Dimitri,
This is a very interesting topic, thank you for bringing it up.
Unfortunately because of the very generalized way it's presented, it's very hard for anyone else aside from Yuras to give it the attention it deserves.
Do you have a concrete example with sample code that you could simplify and present instead?
E.g. instead of the multiply-stacked monad transformer embedded in 200 lines that you're facing, can you present an example with 2 monadic layers (the base being IO) in say, 20 lines?
-- Kim-Ee

On 10/23/2015 06:07 PM, Charles Durham wrote:
I can think of a few properties that folds can honor:
1. Promises to call f on all data (does not have any guarantees on order)
"Exhaustive"? ... but then that's not really observable in a language like Haskell, except if you monitor CPU heat. Regards,

Basically you want to force an argument to be associative yes?
I don't think there's a way to do that in Haskell, but what you could do is
create a datatype:
data Associative a b = Associative (a -> b)
You could then make "Associative" a Category, or perhaps even an Arrow, so
you could combine Associative functions to make new Associative functions.
But it would still be up to the user to ensure they only promote actual
associative functions to "Associative".
On Sat, Oct 24, 2015 at 8:24 AM, Bardur Arantsson
On 10/23/2015 06:07 PM, Charles Durham wrote:
I can think of a few properties that folds can honor:
1. Promises to call f on all data (does not have any guarantees on order)
"Exhaustive"?
... but then that's not really observable in a language like Haskell, except if you monitor CPU heat.
Regards,
_______________________________________________ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://mail.haskell.org/cgi-bin/mailman/listinfo/haskell-cafe

Yeah, I realize that its probably not conveniently expressible in types or
anything. I was more thinking along the lines of how the Monad laws are
expressed as a side note in the docs, and not type enforced in Haskell
itself.
I just thought it was vague to say that a fold takes an associative
function instead of indicating what kind of topology a fold honors, as the
former is only implying how the fold promises to operate. It would be
surprising to me that this hasn't been formalized mathematically in some
way.
Charlie
On Fri, Oct 23, 2015 at 7:01 PM, Clinton Mead
Basically you want to force an argument to be associative yes?
I don't think there's a way to do that in Haskell, but what you could do is create a datatype:
data Associative a b = Associative (a -> b)
You could then make "Associative" a Category, or perhaps even an Arrow, so you could combine Associative functions to make new Associative functions.
But it would still be up to the user to ensure they only promote actual associative functions to "Associative".
On Sat, Oct 24, 2015 at 8:24 AM, Bardur Arantsson
wrote: On 10/23/2015 06:07 PM, Charles Durham wrote:
I can think of a few properties that folds can honor:
1. Promises to call f on all data (does not have any guarantees on order)
"Exhaustive"?
... but then that's not really observable in a language like Haskell, except if you monitor CPU heat.
Regards,
_______________________________________________ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://mail.haskell.org/cgi-bin/mailman/listinfo/haskell-cafe
_______________________________________________ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://mail.haskell.org/cgi-bin/mailman/listinfo/haskell-cafe

On Fri, Oct 23, 2015 at 6:07 PM, Charles Durham
I can think of a few properties that folds can honor:
1. Promises to call f on all data (does not have any guarantees on order) 2. Promises to call f on all data in order (like a left fold) 3. Promises to call f "associatively" (perhaps can be formalized as an in order break down of the data into tree structures)
For what concerns traversable functors, traversals enjoy properties of "unitarity" and "linearity" which *might* entail what you are interested in: M. Jaskelioff, O. Rypacek - An Investigation of the Laws of Traversals http://arxiv.org/abs/1202.2919 I have never gone through the details of that very interesting paper: the analysis in section 4 gives some intuition, though. I hope this is related to your questions. Cheers, Matteo

The "unitarity" and "linearity" laws are indeed relevant for Charles's
question. But they won't give him his 2. or 3. point. They will exactly
entail the property he mentions in his 1. point: that each data element is
touched exactly once (whereas all permutations of the order will still be
legal).
For proof of that, see http://dx.doi.org/10.1145/2503778.2503781, which
establishes as fact the relevant conjecture from Jaskelioff & Rypacek's
paper.
2015-10-24 10:29 GMT+02:00 Matteo Acerbi
On Fri, Oct 23, 2015 at 6:07 PM, Charles Durham
wrote: I can think of a few properties that folds can honor:
1. Promises to call f on all data (does not have any guarantees on order) 2. Promises to call f on all data in order (like a left fold) 3. Promises to call f "associatively" (perhaps can be formalized as an in order break down of the data into tree structures)
For what concerns traversable functors, traversals enjoy properties of "unitarity" and "linearity" which *might* entail what you are interested in:
M. Jaskelioff, O. Rypacek - An Investigation of the Laws of Traversals http://arxiv.org/abs/1202.2919
I have never gone through the details of that very interesting paper: the analysis in section 4 gives some intuition, though.
I hope this is related to your questions.
Cheers, Matteo
_______________________________________________ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://mail.haskell.org/cgi-bin/mailman/listinfo/haskell-cafe

On Sat, Oct 24, 2015 at 12:56 PM, Janis Voigtländer < janis.voigtlaender@gmail.com> wrote:
The "unitarity" and "linearity" laws are indeed relevant for Charles's question. But they won't give him his 2. or 3. point. They will exactly entail the property he mentions in his 1. point: that each data element is touched exactly once (whereas all permutations of the order will still be legal)
For proof of that, see http://dx.doi.org/10.1145/2503778.2503781, which
establishes as fact the relevant conjecture from Jaskelioff & Rypacek's paper.
Thanks for your clarifying comment, and for the link to this paper: it is very interesting, indeed. In my message I was just trying to point to research that looked relevant, and which seemed to give an answer to at least question 1: for what concerns the other two questions, I have yet to understand them. :-) Question 2 seems to assume the existence of a "default" order, but it seems to me that any such choice would be arbitrary. At least, it seems impossible to capture the property of being "like a left fold" semantically as Charles seemed to be wanting ("I was more thinking along the lines of how the Monad laws are expressed as a side note in the docs"), without actually specifying a reference order of traversal (for example, in the form of an instance of Traversable). For what concerns question 3, I didn't understand the idea of calling a function "associatively". Please let me know if I am missing an obvious interpretation. Best, Matteo

On Sun, Oct 25, 2015 at 12:42 AM, Matteo Acerbi
For what concerns question 3, I didn't understand the idea of calling a function "associatively".
This. Associativity is a property of binary operators. It's not a property of the catamorphism 'calling' on a given binary operator. Also, when Charles writes: "Then it goes on to use f in "thisFold f [0,1,2]" like "f (1 (f 0 2))"" commutativity appears to raise its head. -- Kim-Ee

It has already been established in this thread what Charles meant by 3.
He meant that a fold-function that has the property he is after would
guarantee that it:
a) takes all the content elements from a data structure, say x1,...,xn,
b) builds an application tree with the to-be-folded, binary operation f in
the internal nodes of a binary tree, whose leafs, read from left to right,
form exactly the sequence x1,...,xn,
c) evaluates that application tree.
Do you agree that what I describe above is a property of a given fold-like
function, not of the f handed to that fold-like function?
And do you agree that what I describe above is a property that is weaker
than (and so, in particular different from) for example the property "this
fold-like function is foldl or foldr".
2015-10-24 19:55 GMT+02:00 Kim-Ee Yeoh
On Sun, Oct 25, 2015 at 12:42 AM, Matteo Acerbi
wrote: For what concerns question 3, I didn't understand the idea of calling a function "associatively".
This. Associativity is a property of binary operators. It's not a property of the catamorphism 'calling' on a given binary operator.
Also, when Charles writes: "Then it goes on to use f in "thisFold f [0,1,2]" like "f (1 (f 0 2))""
commutativity appears to raise its head.
-- Kim-Ee

On Sat, Oct 24, 2015 at 8:12 PM, Janis Voigtländer < janis.voigtlaender@gmail.com> wrote:
It has already been established in this thread what Charles meant by 3.
He meant that a fold-function that has the property he is after would guarantee that it:
a) takes all the content elements from a data structure, say x1,...,xn,
b) builds an application tree with the to-be-folded, binary operation f in the internal nodes of a binary tree, whose leafs, read from left to right, form exactly the sequence x1,...,xn,
c) evaluates that application tree.
Do you agree that what I describe above is a property of a given fold-like function, not of the f handed to that fold-like function?
I might lack some basic knowledge, so thanks for asking. What does it mean to take all the content elements from a data structure? If one has f a = Bool -> a, and a value xs :: f Int xs True = 2 xs False = 3 what are x1 and x2? Best, Matteo PS. I won't be able to read the answer before tomorrow. :-)

If one has f a = Bool -> a, and a value
xs :: f Int xs True = 2 xs False = 3
what are x1 and x2?
One answer I could give is: That depends on the definition of the
Traversable instance for the (Bool -> a) type constructor.
Another answer I could give is: Ask the authors of the Traversable
documentation. The first sentence on
https://hackage.haskell.org/package/base-4.8.1.0/docs/Data-Traversable.html
is: "Class of data structures that can be traversed from left to right,
...". So it seems that the authors of that documentation (which I
criticize) assume that they can say -- for any given type constructor, so
also for your (Bool -> a) example -- what "left" means and what "right"
means.
2015-10-24 20:23 GMT+02:00 Matteo Acerbi
On Sat, Oct 24, 2015 at 8:12 PM, Janis Voigtländer < janis.voigtlaender@gmail.com> wrote:
It has already been established in this thread what Charles meant by 3.
He meant that a fold-function that has the property he is after would guarantee that it:
a) takes all the content elements from a data structure, say x1,...,xn,
b) builds an application tree with the to-be-folded, binary operation f in the internal nodes of a binary tree, whose leafs, read from left to right, form exactly the sequence x1,...,xn,
c) evaluates that application tree.
Do you agree that what I describe above is a property of a given fold-like function, not of the f handed to that fold-like function?
I might lack some basic knowledge, so thanks for asking.
What does it mean to take all the content elements from a data structure?
If one has f a = Bool -> a, and a value
xs :: f Int xs True = 2 xs False = 3
what are x1 and x2?
Best, Matteo
PS. I won't be able to read the answer before tomorrow. :-)

Janis Voigtländer writes:
One answer I could give is: That depends on the definition of the Traversable instance for the (Bool -> a) type constructor.
Another answer I could give is: Ask the authors of the Traversable documentation. [..]
Since Charles had not mentioned Traversable in his messages, I still find the original question 2 to be ambiguous. If one has a Traversable instance, then he can say what being left fold-like means for a function. As far as I understand, however, this should be equivalent to the property of being extensionally equal to the foldl1 of the Foldable superclass, provided instances follow the laws. Please, again, correct me if I am wrong. I want to remark that mine is not criticism towards Charles's message: on the contrary, I think that starting a discussion on not completely specified ideas can be very beneficial for everyone, as several people at once will make some effort to get a clearer understanding, sharing their points of view. Thanks for taking the time to explain your interpretation. Best, Matteo

My messages this morning have decoupled the discussion from Traversable, by
specialising to one container type for which left-to-right is predefined.
In my mind, that gets to the heart of what Charles was after, namely the
"calling in an associative manner" thing, which is independent of the
question "how do we know right from left in the first place". Do the
considerations then make sense to you as well?
2015-10-25 10:09 GMT+01:00 Matteo Acerbi
Janis Voigtländer writes:
One answer I could give is: That depends on the definition of the Traversable instance for the (Bool -> a) type constructor.
Another answer I could give is: Ask the authors of the Traversable documentation. [..]
Since Charles had not mentioned Traversable in his messages, I still find the original question 2 to be ambiguous.
If one has a Traversable instance, then he can say what being left fold-like means for a function. As far as I understand, however, this should be equivalent to the property of being extensionally equal to the foldl1 of the Foldable superclass, provided instances follow the laws.
Please, again, correct me if I am wrong.
I want to remark that mine is not criticism towards Charles's message: on the contrary, I think that starting a discussion on not completely specified ideas can be very beneficial for everyone, as several people at once will make some effort to get a clearer understanding, sharing their points of view.
Thanks for taking the time to explain your interpretation.
Best, Matteo

Janis Voigtländer writes:
My messages this morning have decoupled the discussion from Traversable, by specialising to one container type for which left-to-right is predefined.
In my mind, that gets to the heart of what Charles was after, namely the "calling in an associative manner" thing, which is independent of the question "how do we know right from left in the first place". Do the considerations then make sense to you as well?
Yes, they do. The examples related to non-empty lists were most clarifying. I agree that the interesting part was question 3, concerning which I think I have now understood your interpretation. As an exercise, I'll try to express it in my own words. Let's restrict to non-empty lists. I'll use these definitions: data NonEmptyList a = Last a | Cons a (NonEmptyList a) -- or the one from package semigroups data Tree a = Leaf a | Node (Tree a) (Tree a) foldTree :: (a -> a -> a) -> Tree a -> a foldTree f (Leaf a) = a foldTree f (Node x y) = f (foldTree f x) (foldTree f y) (<>) :: NonEmptyList a -> NonEmptyList a -> NonEmptyList a Last a <> ys = Cons a ys Cons a xs <> ys = Cons a (xs <> ys) toNonEmptyList :: Tree a -> NonEmptyList a toNonEmptyList (Leaf a) = Last a toNonEmptyList (Node x y) = toNonEmptyList x <> toNonEmptyList y Given the above, a fold h which calls the first argument "in an associative manner" is a function of type h :: (a -> a -> a) -> NonEmptyList a -> a which can be equivalently expressed in terms of another function h' :: NonEmptyList a -> Tree a such that toNonEmptyList . h' = id as h f = foldTree f . h' . h' is allowed to build an application tree whose shape can be a function of the input list, but its leaves, considered in left-to-right order, must contain precisely the input sequence. Is this correct? Best, Matteo

Yes, nicely put.
2015-10-25 13:03 GMT+01:00 Matteo Acerbi
Janis Voigtländer writes:
My messages this morning have decoupled the discussion from Traversable, by specialising to one container type for which left-to-right is predefined.
In my mind, that gets to the heart of what Charles was after, namely the "calling in an associative manner" thing, which is independent of the question "how do we know right from left in the first place". Do the considerations then make sense to you as well?
Yes, they do.
The examples related to non-empty lists were most clarifying.
I agree that the interesting part was question 3, concerning which I think I have now understood your interpretation.
As an exercise, I'll try to express it in my own words.
Let's restrict to non-empty lists.
I'll use these definitions:
data NonEmptyList a = Last a | Cons a (NonEmptyList a) -- or the one from package semigroups
data Tree a = Leaf a | Node (Tree a) (Tree a)
foldTree :: (a -> a -> a) -> Tree a -> a foldTree f (Leaf a) = a foldTree f (Node x y) = f (foldTree f x) (foldTree f y)
(<>) :: NonEmptyList a -> NonEmptyList a -> NonEmptyList a Last a <> ys = Cons a ys Cons a xs <> ys = Cons a (xs <> ys)
toNonEmptyList :: Tree a -> NonEmptyList a toNonEmptyList (Leaf a) = Last a toNonEmptyList (Node x y) = toNonEmptyList x <> toNonEmptyList y
Given the above, a fold h which calls the first argument "in an associative manner" is a function of type
h :: (a -> a -> a) -> NonEmptyList a -> a
which can be equivalently expressed in terms of another function
h' :: NonEmptyList a -> Tree a
such that
toNonEmptyList . h' = id
as
h f = foldTree f . h'
.
h' is allowed to build an application tree whose shape can be a function of the input list, but its leaves, considered in left-to-right order, must contain precisely the input sequence.
Is this correct?
Best, Matteo

On Sat, Oct 24, 2015 at 08:12:11PM +0200, Janis Voigtländer wrote:
It has already been established in this thread what Charles meant by 3.
He meant that a fold-function that has the property he is after would guarantee that it:
a) takes all the content elements from a data structure, say x1,...,xn,
b) builds an application tree with the to-be-folded, binary operation f in the internal nodes of a binary tree, whose leafs, read from left to right, form exactly the sequence x1,...,xn,
c) evaluates that application tree.
Do you agree that what I describe above is a property of a given fold-like function, not of the f handed to that fold-like function?
And do you agree that what I describe above is a property that is weaker than (and so, in particular different from) for example the property "this fold-like function is foldl or foldr".
I do agree. I would be interested whether you think such a property could differ from my earlier proposed property: "the function factors through `foldl f`", i.e. is `g . foldl f` for some `g`. (Actually when I wrote that I suppose I meant `g . foldl f z` for some `g` and `z`) Tom

I don't think I see what you are getting at, Tom. Let's consider the special case of non-empty lists. One fold-like function that has the property I think Charles meant by 3., would be one that works as follows: foldBalanced :: (a -> a -> a) -> [a] -> a foldBalanced f [x] = x foldBalanced f [x,y] = f x y foldBalanced f [x,y,z] = f x (f y z) foldBalanced f [x,y,z,u] = f (f x y) (f z u) ... -- I hope you can see the pattern (building f-application trees that are as balanced as possible) I don't see how this function can be written as g . foldl f z for some g and z. 2015-10-25 0:55 GMT+02:00 Tom Ellis < tom-lists-haskell-cafe-2013@jaguarpaw.co.uk>:
On Sat, Oct 24, 2015 at 08:12:11PM +0200, Janis Voigtländer wrote:
It has already been established in this thread what Charles meant by 3.
He meant that a fold-function that has the property he is after would guarantee that it:
a) takes all the content elements from a data structure, say x1,...,xn,
b) builds an application tree with the to-be-folded, binary operation f in the internal nodes of a binary tree, whose leafs, read from left to right, form exactly the sequence x1,...,xn,
c) evaluates that application tree.
Do you agree that what I describe above is a property of a given fold-like function, not of the f handed to that fold-like function?
And do you agree that what I describe above is a property that is weaker than (and so, in particular different from) for example the property "this fold-like function is foldl or foldr".
I do agree. I would be interested whether you think such a property could differ from my earlier proposed property:
"the function factors through `foldl f`", i.e. is `g . foldl f` for some `g`.
(Actually when I wrote that I suppose I meant `g . foldl f z` for some `g` and `z`)
Tom _______________________________________________ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://mail.haskell.org/cgi-bin/mailman/listinfo/haskell-cafe

On Sun, Oct 25, 2015 at 06:58:23AM +0100, Janis Voigtländer wrote:
I don't think I see what you are getting at, Tom. Let's consider the special case of non-empty lists. One fold-like function that has the property I think Charles meant by 3., would be one that works as follows:
foldBalanced :: (a -> a -> a) -> [a] -> a foldBalanced f [x] = x foldBalanced f [x,y] = f x y foldBalanced f [x,y,z] = f x (f y z) foldBalanced f [x,y,z,u] = f (f x y) (f z u) ... -- I hope you can see the pattern (building f-application trees that are as balanced as possible)
I don't see how this function can be written as g . foldl f z for some g and z.
Ah, thank you Janis. I think you are clarifying for me the meaning of Chris's original question: Is there a name for a fold that promises to call a function such that only an associative function will always return the same result. Or in other words, it has the property that it promises to call a function "associatively" on a set of data? So is the property that the function (h, say) satifises `h f = g . foldl f z` for all associative `f`? Tom

Chris's original question:
Is there a name for a fold that promises to call a function such that only an associative function will always return the same result. Or in other words, it has the property that it promises to call a function "associatively" on a set of data?
So is the property that the function (h, say) satifises `h f = g . foldl f z` for all associative `f`?
That makes a lot of sense, Tom, as a property of h to satisfy, while quantifying over associative f inside that property. (Instead of as an equation-definition for h in terms of foldl.) I now wonder why any g other than the identity function should be necessary, though. And for the type of non-empty lists, one should also be able to get rid of the z? So, for the special case of non-empty lists, how about expressing the desired property as follows: "The function h must satisfy: for all associative f and all lists xs, it holds that h f xs = foldl1 f xs." Chris's original question would then be whether there is a name for that property. And how to generalize the property to other types than non-empty lists (for example, ones for which it is not clear what "left" and "right" mean) would be a separate concern. 2015-10-25 9:33 GMT+01:00 Tom Ellis < tom-lists-haskell-cafe-2013@jaguarpaw.co.uk>:
On Sun, Oct 25, 2015 at 06:58:23AM +0100, Janis Voigtländer wrote:
I don't think I see what you are getting at, Tom. Let's consider the special case of non-empty lists. One fold-like function that has the property I think Charles meant by 3., would be one that works as follows:
foldBalanced :: (a -> a -> a) -> [a] -> a foldBalanced f [x] = x foldBalanced f [x,y] = f x y foldBalanced f [x,y,z] = f x (f y z) foldBalanced f [x,y,z,u] = f (f x y) (f z u) ... -- I hope you can see the pattern (building f-application trees that are as balanced as possible)
I don't see how this function can be written as g . foldl f z for some g and z.
Ah, thank you Janis. I think you are clarifying for me the meaning of Chris's original question:
Is there a name for a fold that promises to call a function such that only an associative function will always return the same result. Or in other words, it has the property that it promises to call a function "associatively" on a set of data?
So is the property that the function (h, say) satifises `h f = g . foldl f z` for all associative `f`?
Tom _______________________________________________ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://mail.haskell.org/cgi-bin/mailman/listinfo/haskell-cafe

On Sun, Oct 25, 2015 at 10:06:00AM +0100, Janis Voigtländer wrote:
Chris's original question:
Is there a name for a fold that promises to call a function such that only an associative function will always return the same result. Or in other words, it has the property that it promises to call a function "associatively" on a set of data?
So is the property that the function (h, say) satifises `h f = g . foldl f z` for all associative `f`?
That makes a lot of sense, Tom, as a property of h to satisfy, while quantifying over associative f inside that property. (Instead of as an equation-definition for h in terms of foldl.)
I now wonder why any g other than the identity function should be necessary, though. And for the type of non-empty lists, one should also be able to get rid of the z?
Chris said "Is there a name for a fold", which I originally misunderstood as "Is there a name for a function". I'm not quite sure how to define "fold", but if it agrees with your definition of "fold" then your characterization below should be fine.
So, for the special case of non-empty lists, how about expressing the desired property as follows: "The function h must satisfy: for all associative f and all lists xs, it holds that h f xs = foldl1 f xs."
Tom

On Sun, Oct 25, 2015 at 1:12 AM, Janis Voigtländer < janis.voigtlaender@gmail.com> wrote:
It has already been established in this thread what Charles meant by 3.
He meant that a fold-function that has the property he is after would guarantee that it:
a) takes all the content elements from a data structure, say x1,...,xn,
b) builds an application tree with the to-be-folded, binary operation f in the internal nodes of a binary tree, whose leafs, read from left to right, form exactly the sequence x1,...,xn,
c) evaluates that application tree.
Isn't this what Charles meant by his 2nd property:
2. Promises to call f on all data in order (like a left fold)
What about his 3rd? Do you agree that what I describe above is a property of a given fold-like
function, not of the f handed to that fold-like function?
Before discussing a property of X, isnt it worth asking what X even means? The folds whose meanings are crystal clear are the arrows out of initial objects in the category of F-algebras. They are crystal clear because they couple as one with the data definition spelled out in full. In the quest for useful generalizations of catamorphisms, that coupling with the data definition continues to be assumed. Observe, for instance:
a) takes all the content elements from a data structure, say x1,...,xn,
Does a foliar data structure have a canonical flattening out of its leaves? Are there symmetric canonicalizations? How is one selected over the others? Is the meaning of "all" referentially transparent? That turns out to be a subtle point, as this convo shows: http://haskell.1045720.n5.nabble.com/A-Proposed-Law-for-Foldable-tp5765339.h... With the theory of F-algebras, we started with precise notions of data and folds came for free. But data can be overspecified. And also, the folds among swathes of data suggest useful generalizations. So now, a raft of proto-precise and necessarily psychological notions of Foldable waded in, and since then it's been fun playing sorting games with shape blocks and holes to squeeze them into. Fun is good. It's a stage in the journey to knowledge. And do you agree that what I describe above is a property that is weaker
than (and so, in particular different from) for example the property "this fold-like function is foldl or foldr".
2015-10-24 19:55 GMT+02:00 Kim-Ee Yeoh
: On Sun, Oct 25, 2015 at 12:42 AM, Matteo Acerbi
wrote: For what concerns question 3, I didn't understand the idea of calling a function "associatively".
This. Associativity is a property of binary operators. It's not a property of the catamorphism 'calling' on a given binary operator.
Also, when Charles writes: "Then it goes on to use f in "thisFold f [0,1,2]" like "f (1 (f 0 2))""
commutativity appears to raise its head.
-- Kim-Ee

Kim-Ee, I think you are overcomplicating things (and on the specific question of 2. vs. 3.: no, what I described was specifically meant to capture Charles's 3., not 2. point; note that my "application trees" could be balanced in any way, rather than being completely left-nested). In fact, the discussion of "arbitrary data structures" (in this thread in general) distracts a lot from the properties under consideration, and from even first finding out whether they are properties of foldLike or of f in foldLike f. So, let's specialize. Let's consider only the case of non-empty lists. Then, candidate functions for "foldlike functions" will be functions of this type: foldLike : (a -> a -> a) -> [a] -> a Here are some candidates (I give only an equation for four element lists in each case, but I assume everyone has enough imagination to see how these could be extended to other lists in an intended way): foldLike1 f [a,b,c,d] = [] -- throws away stuff foldLike2 f [a,b,c,d] = f a (f b (f c d)) -- we have all ancountered this one foldLike3 f [a,b,c,d] = f (f (f a b) c) d -- also looks familiar foldLike4 f [a,b,c,d] = f (f a b) (f c d) -- that's a "new" one, but looks good foldLike5 f [a,b,c,d] = f a a -- probably not a very popular one foldLike6 f [a,b,c,d] = f (f c a) (f b d) -- a reasonable one, for example there's a Traversable instance that leads to this one; but still, it's not one that Charles would like, I think So now we can ask which of these satisfy Charles's 1., 2., 3. points. Can't we? There was:
1. Promises to call f on all data (does not have any guarantees on order)
This is satisfied by foldLike2, foldLike3, foldLike4, and foldLike6, but not by the others.
2. Promises to call f on all data in order (like a left fold)
This is satisfied by foldLike3, but not by the others.
3. Promises to call f "associatively" (perhaps can be formalized as an in order break down of the data into tree structures)
This is satisfied by foldLike2, foldLike3, and foldLike4, but not by the
others.
Since I am able to tell, for a given foldLike candidate, whether or not it
satisfies 3. (for example, I could specifically see that foldLike6 does not
satisfy 3., while it does satisfy 1.), it cannot be maintained that 3. has
no meaning.
Note: Nothing in the above makes any assumptions about f. Whether or not f
is an associative function is irrelevant for what is asked here.
2015-10-25 4:19 GMT+01:00 Kim-Ee Yeoh
On Sun, Oct 25, 2015 at 1:12 AM, Janis Voigtländer < janis.voigtlaender@gmail.com> wrote:
It has already been established in this thread what Charles meant by 3.
He meant that a fold-function that has the property he is after would guarantee that it:
a) takes all the content elements from a data structure, say x1,...,xn,
b) builds an application tree with the to-be-folded, binary operation f in the internal nodes of a binary tree, whose leafs, read from left to right, form exactly the sequence x1,...,xn,
c) evaluates that application tree.
Isn't this what Charles meant by his 2nd property:
2. Promises to call f on all data in order (like a left fold)
What about his 3rd?
Do you agree that what I describe above is a property of a given fold-like
function, not of the f handed to that fold-like function?
Before discussing a property of X, isnt it worth asking what X even means?
The folds whose meanings are crystal clear are the arrows out of initial objects in the category of F-algebras.
They are crystal clear because they couple as one with the data definition spelled out in full.
In the quest for useful generalizations of catamorphisms, that coupling with the data definition continues to be assumed.
Observe, for instance:
a) takes all the content elements from a data structure, say x1,...,xn,
Does a foliar data structure have a canonical flattening out of its leaves? Are there symmetric canonicalizations? How is one selected over the others?
Is the meaning of "all" referentially transparent? That turns out to be a subtle point, as this convo shows:
http://haskell.1045720.n5.nabble.com/A-Proposed-Law-for-Foldable-tp5765339.h...
With the theory of F-algebras, we started with precise notions of data and folds came for free.
But data can be overspecified. And also, the folds among swathes of data suggest useful generalizations.
So now, a raft of proto-precise and necessarily psychological notions of Foldable waded in, and since then it's been fun playing sorting games with shape blocks and holes to squeeze them into.
Fun is good. It's a stage in the journey to knowledge.
And do you agree that what I describe above is a property that is weaker
than (and so, in particular different from) for example the property "this fold-like function is foldl or foldr".
2015-10-24 19:55 GMT+02:00 Kim-Ee Yeoh
: On Sun, Oct 25, 2015 at 12:42 AM, Matteo Acerbi
wrote:
For what concerns question 3, I didn't understand the idea of calling a function "associatively".
This. Associativity is a property of binary operators. It's not a property of the catamorphism 'calling' on a given binary operator.
Also, when Charles writes: "Then it goes on to use f in "thisFold f [0,1,2]" like "f (1 (f 0 2))""
commutativity appears to raise its head.
-- Kim-Ee

On Sun, Oct 25, 2015 at 1:17 PM, Janis Voigtländer < janis.voigtlaender@gmail.com> wrote:
Kim-Ee, I think you are overcomplicating things
No. Matteo cited a paper on traversables and you added a rejoinder. So it wasn't me who introduced data abstraction. Also, OP explicitly asked about a fold "on a set of data". Only later, when requested for an example, did he give lists. In fact, the discussion of "arbitrary data structures" (in this thread in
general) distracts a lot from the properties under consideration, and from even first finding out whether they are properties of foldLike or of f in foldLike f.
So, let's specialize. Let's consider only the case of non-empty lists.
And look at what we have: A definitive answer to OP's question: Question: What is a fold of type "(a -> a -> a) -> [a] -> a" that promises to call its first parameter "associatively"? Answer: It is a fold equivalent to a fold1 (left or right, it doesn't matter). That's nice. But is that all we can come up with? Does it really do justice to the original question? Viz. "Is there a name for a fold that promises to call a function such that only an associative function will always return the same result. Or in other words, it has the property that it promises to call a function "associatively" on a set of data?" The challenge becomes: * generalize the result to fearsomely complicated "arbitrary data structures" * answer the original question in a holistic spirit
Then, candidate functions for "foldlike functions" will be functions of this type:
foldLike : (a -> a -> a) -> [a] -> a
Here are some candidates (I give only an equation for four element lists in each case, but I assume everyone has enough imagination to see how these could be extended to other lists in an intended way):
foldLike1 f [a,b,c,d] = [] -- throws away stuff foldLike2 f [a,b,c,d] = f a (f b (f c d)) -- we have all ancountered this one foldLike3 f [a,b,c,d] = f (f (f a b) c) d -- also looks familiar foldLike4 f [a,b,c,d] = f (f a b) (f c d) -- that's a "new" one, but looks good foldLike5 f [a,b,c,d] = f a a -- probably not a very popular one foldLike6 f [a,b,c,d] = f (f c a) (f b d) -- a reasonable one, for example there's a Traversable instance that leads to this one; but still, it's not one that Charles would like, I think
So now we can ask which of these satisfy Charles's 1., 2., 3. points. Can't we?
There was:
1. Promises to call f on all data (does not have any guarantees on order)
This is satisfied by foldLike2, foldLike3, foldLike4, and foldLike6, but not by the others.
2. Promises to call f on all data in order (like a left fold)
This is satisfied by foldLike3, but not by the others.
3. Promises to call f "associatively" (perhaps can be formalized as an in order break down of the data into tree structures)
This is satisfied by foldLike2, foldLike3, and foldLike4, but not by the others.
Since I am able to tell, for a given foldLike candidate, whether or not it satisfies 3. (for example, I could specifically see that foldLike6 does not satisfy 3., while it does satisfy 1.), it cannot be maintained that 3. has no meaning.
Note: Nothing in the above makes any assumptions about f. Whether or not f is an associative function is irrelevant for what is asked here.
2015-10-25 4:19 GMT+01:00 Kim-Ee Yeoh
: On Sun, Oct 25, 2015 at 1:12 AM, Janis Voigtländer < janis.voigtlaender@gmail.com> wrote:
It has already been established in this thread what Charles meant by 3.
He meant that a fold-function that has the property he is after would guarantee that it:
a) takes all the content elements from a data structure, say x1,...,xn,
b) builds an application tree with the to-be-folded, binary operation f in the internal nodes of a binary tree, whose leafs, read from left to right, form exactly the sequence x1,...,xn,
c) evaluates that application tree.
Isn't this what Charles meant by his 2nd property:
2. Promises to call f on all data in order (like a left fold)
What about his 3rd?
Do you agree that what I describe above is a property of a given
fold-like function, not of the f handed to that fold-like function?
Before discussing a property of X, isnt it worth asking what X even means?
The folds whose meanings are crystal clear are the arrows out of initial objects in the category of F-algebras.
They are crystal clear because they couple as one with the data definition spelled out in full.
In the quest for useful generalizations of catamorphisms, that coupling with the data definition continues to be assumed.
Observe, for instance:
a) takes all the content elements from a data structure, say x1,...,xn,
Does a foliar data structure have a canonical flattening out of its leaves? Are there symmetric canonicalizations? How is one selected over the others?
Is the meaning of "all" referentially transparent? That turns out to be a subtle point, as this convo shows:
http://haskell.1045720.n5.nabble.com/A-Proposed-Law-for-Foldable-tp5765339.h...
With the theory of F-algebras, we started with precise notions of data and folds came for free.
But data can be overspecified. And also, the folds among swathes of data suggest useful generalizations.
So now, a raft of proto-precise and necessarily psychological notions of Foldable waded in, and since then it's been fun playing sorting games with shape blocks and holes to squeeze them into.
Fun is good. It's a stage in the journey to knowledge.
And do you agree that what I describe above is a property that is weaker
than (and so, in particular different from) for example the property "this fold-like function is foldl or foldr".
2015-10-24 19:55 GMT+02:00 Kim-Ee Yeoh
: On Sun, Oct 25, 2015 at 12:42 AM, Matteo Acerbi < matteo.acerbi@gmail.com> wrote:
For what concerns question 3, I didn't understand the idea of calling a function "associatively".
This. Associativity is a property of binary operators. It's not a property of the catamorphism 'calling' on a given binary operator.
Also, when Charles writes: "Then it goes on to use f in "thisFold f [0,1,2]" like "f (1 (f 0 2))""
commutativity appears to raise its head.
-- Kim-Ee

Kim-Ee, I think you are overcomplicating things
No.
Your message contained lots of category-theory-speak that wasn’t called for.
Question: What is a fold of type “(a -> a -> a) -> [a] -> a” that promises
to call its first parameter “associatively”?
Answer: It is a fold equivalent to a fold1 (left or right, it doesn’t
matter).
No, it seems you haven’t understood the answer. At least, that was not the
answer.
2015-10-28 13:41 GMT+01:00 Kim-Ee Yeoh
On Sun, Oct 25, 2015 at 1:17 PM, Janis Voigtländer < janis.voigtlaender@gmail.com> wrote:
Kim-Ee, I think you are overcomplicating things
No.
Matteo cited a paper on traversables and you added a rejoinder. So it wasn't me who introduced data abstraction.
Also, OP explicitly asked about a fold "on a set of data". Only later, when requested for an example, did he give lists.
In fact, the discussion of "arbitrary data structures" (in this thread in
general) distracts a lot from the properties under consideration, and from even first finding out whether they are properties of foldLike or of f in foldLike f.
So, let's specialize. Let's consider only the case of non-empty lists.
And look at what we have: A definitive answer to OP's question:
Question: What is a fold of type "(a -> a -> a) -> [a] -> a" that promises to call its first parameter "associatively"?
Answer: It is a fold equivalent to a fold1 (left or right, it doesn't matter).
That's nice.
But is that all we can come up with? Does it really do justice to the original question? Viz.
"Is there a name for a fold that promises to call a function such that only an associative function will always return the same result. Or in other words, it has the property that it promises to call a function "associatively" on a set of data?"
The challenge becomes:
* generalize the result to fearsomely complicated "arbitrary data structures" * answer the original question in a holistic spirit
Then, candidate functions for "foldlike functions" will be functions of this type:
foldLike : (a -> a -> a) -> [a] -> a
Here are some candidates (I give only an equation for four element lists in each case, but I assume everyone has enough imagination to see how these could be extended to other lists in an intended way):
foldLike1 f [a,b,c,d] = [] -- throws away stuff foldLike2 f [a,b,c,d] = f a (f b (f c d)) -- we have all ancountered this one foldLike3 f [a,b,c,d] = f (f (f a b) c) d -- also looks familiar foldLike4 f [a,b,c,d] = f (f a b) (f c d) -- that's a "new" one, but looks good foldLike5 f [a,b,c,d] = f a a -- probably not a very popular one foldLike6 f [a,b,c,d] = f (f c a) (f b d) -- a reasonable one, for example there's a Traversable instance that leads to this one; but still, it's not one that Charles would like, I think
So now we can ask which of these satisfy Charles's 1., 2., 3. points. Can't we?
There was:
1. Promises to call f on all data (does not have any guarantees on order)
This is satisfied by foldLike2, foldLike3, foldLike4, and foldLike6, but not by the others.
2. Promises to call f on all data in order (like a left fold)
This is satisfied by foldLike3, but not by the others.
3. Promises to call f "associatively" (perhaps can be formalized as an in order break down of the data into tree structures)
This is satisfied by foldLike2, foldLike3, and foldLike4, but not by the others.
Since I am able to tell, for a given foldLike candidate, whether or not it satisfies 3. (for example, I could specifically see that foldLike6 does not satisfy 3., while it does satisfy 1.), it cannot be maintained that 3. has no meaning.
Note: Nothing in the above makes any assumptions about f. Whether or not f is an associative function is irrelevant for what is asked here.
2015-10-25 4:19 GMT+01:00 Kim-Ee Yeoh
: On Sun, Oct 25, 2015 at 1:12 AM, Janis Voigtländer < janis.voigtlaender@gmail.com> wrote:
It has already been established in this thread what Charles meant by 3.
He meant that a fold-function that has the property he is after would guarantee that it:
a) takes all the content elements from a data structure, say x1,...,xn,
b) builds an application tree with the to-be-folded, binary operation f in the internal nodes of a binary tree, whose leafs, read from left to right, form exactly the sequence x1,...,xn,
c) evaluates that application tree.
Isn't this what Charles meant by his 2nd property:
2. Promises to call f on all data in order (like a left fold)
What about his 3rd?
Do you agree that what I describe above is a property of a given
fold-like function, not of the f handed to that fold-like function?
Before discussing a property of X, isnt it worth asking what X even means?
The folds whose meanings are crystal clear are the arrows out of initial objects in the category of F-algebras.
They are crystal clear because they couple as one with the data definition spelled out in full.
In the quest for useful generalizations of catamorphisms, that coupling with the data definition continues to be assumed.
Observe, for instance:
a) takes all the content elements from a data structure, say x1,...,xn,
Does a foliar data structure have a canonical flattening out of its leaves? Are there symmetric canonicalizations? How is one selected over the others?
Is the meaning of "all" referentially transparent? That turns out to be a subtle point, as this convo shows:
http://haskell.1045720.n5.nabble.com/A-Proposed-Law-for-Foldable-tp5765339.h...
With the theory of F-algebras, we started with precise notions of data and folds came for free.
But data can be overspecified. And also, the folds among swathes of data suggest useful generalizations.
So now, a raft of proto-precise and necessarily psychological notions of Foldable waded in, and since then it's been fun playing sorting games with shape blocks and holes to squeeze them into.
Fun is good. It's a stage in the journey to knowledge.
And do you agree that what I describe above is a property that is weaker
than (and so, in particular different from) for example the property "this fold-like function is foldl or foldr".
2015-10-24 19:55 GMT+02:00 Kim-Ee Yeoh
: On Sun, Oct 25, 2015 at 12:42 AM, Matteo Acerbi < matteo.acerbi@gmail.com> wrote:
For what concerns question 3, I didn't understand the idea of calling a function "associatively".
This. Associativity is a property of binary operators. It's not a property of the catamorphism 'calling' on a given binary operator.
Also, when Charles writes: "Then it goes on to use f in "thisFold f [0,1,2]" like "f (1 (f 0 2))""
commutativity appears to raise its head.
-- Kim-Ee

On Wed, Oct 28, 2015 at 7:50 PM, Janis Voigtländer < janis.voigtlaender@gmail.com> wrote:
Your message contained lots of category-theory-speak that wasn’t called for.
Wait, what? You're alluding to my mention of F-algebras? Now I know that your discussion with Matteo that cited two papers is pertinent and also kinda off on the side. As we both know, those papers go far deeper into CT than F-algebras, which is like, baby stuff in comparison. Baby stuff that they are, F-algebras are nice because it's a theory of data where the folds fall out for free. It's a rock solid theory in a sea of nebulous generalizations about fold. That's why I mentioned them. Question: What is a fold of type “(a -> a -> a) -> [a] -> a” that promises
to call its first parameter “associatively”?
Answer: It is a fold equivalent to a fold1 (left or right, it doesn’t matter).
No, it seems you haven’t understood the answer. At least, that was not the answer.
Well, look. I thought otherwise, but I may be wrong. I frequently am. And if I am wrong, I want to be put right. Let's examine the facts. In an earlier response to Tom, you wrote: 'So, for the special case of non-empty lists, how about expressing the desired property as follows: "The function h must satisfy: for all associative f and all lists xs, it holds that h f xs = foldl1 f xs."' I thought impeccable the logic you used to arrive at this. Over two eta-contractions, I get h = foldl. The folds are monotyped, the lists finite, and so foldl = foldr. Putting it all together, finally: The property of the fold in question is that it is equivalent to a fold (left or right, it doesn't matter which).
2015-10-28 13:41 GMT+01:00 Kim-Ee Yeoh
: On Sun, Oct 25, 2015 at 1:17 PM, Janis Voigtländer < janis.voigtlaender@gmail.com> wrote:
Kim-Ee, I think you are overcomplicating things
No.
Matteo cited a paper on traversables and you added a rejoinder. So it wasn't me who introduced data abstraction.
Also, OP explicitly asked about a fold "on a set of data". Only later, when requested for an example, did he give lists.
In fact, the discussion of "arbitrary data structures" (in this thread in
general) distracts a lot from the properties under consideration, and from even first finding out whether they are properties of foldLike or of f in foldLike f.
So, let's specialize. Let's consider only the case of non-empty lists.
And look at what we have: A definitive answer to OP's question:
Question: What is a fold of type "(a -> a -> a) -> [a] -> a" that promises to call its first parameter "associatively"?
Answer: It is a fold equivalent to a fold1 (left or right, it doesn't matter).
That's nice.
But is that all we can come up with? Does it really do justice to the original question? Viz.
"Is there a name for a fold that promises to call a function such that only an associative function will always return the same result. Or in other words, it has the property that it promises to call a function "associatively" on a set of data?"
The challenge becomes:
* generalize the result to fearsomely complicated "arbitrary data structures" * answer the original question in a holistic spirit
Then, candidate functions for "foldlike functions" will be functions of this type:
foldLike : (a -> a -> a) -> [a] -> a
Here are some candidates (I give only an equation for four element lists in each case, but I assume everyone has enough imagination to see how these could be extended to other lists in an intended way):
foldLike1 f [a,b,c,d] = [] -- throws away stuff foldLike2 f [a,b,c,d] = f a (f b (f c d)) -- we have all ancountered this one foldLike3 f [a,b,c,d] = f (f (f a b) c) d -- also looks familiar foldLike4 f [a,b,c,d] = f (f a b) (f c d) -- that's a "new" one, but looks good foldLike5 f [a,b,c,d] = f a a -- probably not a very popular one foldLike6 f [a,b,c,d] = f (f c a) (f b d) -- a reasonable one, for example there's a Traversable instance that leads to this one; but still, it's not one that Charles would like, I think
So now we can ask which of these satisfy Charles's 1., 2., 3. points. Can't we?
There was:
1. Promises to call f on all data (does not have any guarantees on order)
This is satisfied by foldLike2, foldLike3, foldLike4, and foldLike6, but not by the others.
2. Promises to call f on all data in order (like a left fold)
This is satisfied by foldLike3, but not by the others.
3. Promises to call f "associatively" (perhaps can be formalized as an in order break down of the data into tree structures)
This is satisfied by foldLike2, foldLike3, and foldLike4, but not by the others.
Since I am able to tell, for a given foldLike candidate, whether or not it satisfies 3. (for example, I could specifically see that foldLike6 does not satisfy 3., while it does satisfy 1.), it cannot be maintained that 3. has no meaning.
Note: Nothing in the above makes any assumptions about f. Whether or not f is an associative function is irrelevant for what is asked here.
2015-10-25 4:19 GMT+01:00 Kim-Ee Yeoh
: On Sun, Oct 25, 2015 at 1:12 AM, Janis Voigtländer < janis.voigtlaender@gmail.com> wrote:
It has already been established in this thread what Charles meant by 3.
He meant that a fold-function that has the property he is after would guarantee that it:
a) takes all the content elements from a data structure, say x1,...,xn,
b) builds an application tree with the to-be-folded, binary operation f in the internal nodes of a binary tree, whose leafs, read from left to right, form exactly the sequence x1,...,xn,
c) evaluates that application tree.
Isn't this what Charles meant by his 2nd property:
2. Promises to call f on all data in order (like a left fold)
What about his 3rd?
Do you agree that what I describe above is a property of a given
fold-like function, not of the f handed to that fold-like function?
Before discussing a property of X, isnt it worth asking what X even means?
The folds whose meanings are crystal clear are the arrows out of initial objects in the category of F-algebras.
They are crystal clear because they couple as one with the data definition spelled out in full.
In the quest for useful generalizations of catamorphisms, that coupling with the data definition continues to be assumed.
Observe, for instance:
a) takes all the content elements from a data structure, say x1,...,xn,
Does a foliar data structure have a canonical flattening out of its leaves? Are there symmetric canonicalizations? How is one selected over the others?
Is the meaning of "all" referentially transparent? That turns out to be a subtle point, as this convo shows:
http://haskell.1045720.n5.nabble.com/A-Proposed-Law-for-Foldable-tp5765339.h...
With the theory of F-algebras, we started with precise notions of data and folds came for free.
But data can be overspecified. And also, the folds among swathes of data suggest useful generalizations.
So now, a raft of proto-precise and necessarily psychological notions of Foldable waded in, and since then it's been fun playing sorting games with shape blocks and holes to squeeze them into.
Fun is good. It's a stage in the journey to knowledge.
And do you agree that what I describe above is a property that is
weaker than (and so, in particular different from) for example the property "this fold-like function is foldl or foldr".
2015-10-24 19:55 GMT+02:00 Kim-Ee Yeoh
: On Sun, Oct 25, 2015 at 12:42 AM, Matteo Acerbi < matteo.acerbi@gmail.com> wrote:
> For what concerns question 3, I didn't understand the idea of > calling a function "associatively". >
This. Associativity is a property of binary operators. It's not a property of the catamorphism 'calling' on a given binary operator.
Also, when Charles writes: "Then it goes on to use f in "thisFold f [0,1,2]" like "f (1 (f 0 2))""
commutativity appears to raise its head.
-- Kim-Ee

As we both know, those papers go far deeper into CT than F-algebras, which is like, baby stuff in comparison.
Actually, one of the papers, the one I co-authored, does not go into category theory to any serious extent. I'd say to none extent at all, actually. Anyway, nothing of that is to say you are not "allowed" to bring CT into the discussion, of course. It just wasn't helpful to what was trying to be figured out. And as an aside, mention of F-algebras is not very relevant either *if* one tries to think about the Foldable class. That class is not about catamorphisms. Like, there isn't any F-algebra (for the base functor F of the Tree type constructor) in foldr : (a -> b -> b) -> b -> Tree a -> b.
In an earlier response to Tom, you wrote:
'So, for the special case of non-empty lists, how about expressing the desired property as follows: "The function h must satisfy: for all associative f and all lists xs, it holds that h f xs = foldl1 f xs."'
I thought impeccable the logic you used to arrive at this.
Over two eta-contractions, I get h = foldl.
Are you sure you have read and respected all the forall-quantifiers in
there?
The statement "for all associative f and all lists xs, it holds that h f xs
= foldl1 f xs" is *not* equivalent to the statement "for all f and all
lists xs, it holds that h f xs = foldl1 f xs". The latter statement is
equivalent (via eta-contractions) to "h = foldl", but the former isn't.
Do I have to give a specific h to make this clearer? One which satisfies
the first statement but is not equivalent to foldl or foldr. Actually, one
was given already earlier in the conversation, to exactly the purpose of
illuminating this whole point.
2015-10-29 2:34 GMT+01:00 Kim-Ee Yeoh
On Wed, Oct 28, 2015 at 7:50 PM, Janis Voigtländer < janis.voigtlaender@gmail.com> wrote:
Your message contained lots of category-theory-speak that wasn’t called for.
Wait, what? You're alluding to my mention of F-algebras?
Now I know that your discussion with Matteo that cited two papers is pertinent and also kinda off on the side. As we both know, those papers go far deeper into CT than F-algebras, which is like, baby stuff in comparison.
Baby stuff that they are, F-algebras are nice because it's a theory of data where the folds fall out for free. It's a rock solid theory in a sea of nebulous generalizations about fold. That's why I mentioned them.
Question: What is a fold of type “(a -> a -> a) -> [a] -> a” that promises
to call its first parameter “associatively”?
Answer: It is a fold equivalent to a fold1 (left or right, it doesn’t matter).
No, it seems you haven’t understood the answer. At least, that was not the answer.
Well, look. I thought otherwise, but I may be wrong. I frequently am. And if I am wrong, I want to be put right. Let's examine the facts.
In an earlier response to Tom, you wrote:
'So, for the special case of non-empty lists, how about expressing the desired property as follows: "The function h must satisfy: for all associative f and all lists xs, it holds that h f xs = foldl1 f xs."'
I thought impeccable the logic you used to arrive at this.
Over two eta-contractions, I get h = foldl.
The folds are monotyped, the lists finite, and so foldl = foldr.
Putting it all together, finally:
The property of the fold in question is that it is equivalent to a fold (left or right, it doesn't matter which).
2015-10-28 13:41 GMT+01:00 Kim-Ee Yeoh
: On Sun, Oct 25, 2015 at 1:17 PM, Janis Voigtländer < janis.voigtlaender@gmail.com> wrote:
Kim-Ee, I think you are overcomplicating things
No.
Matteo cited a paper on traversables and you added a rejoinder. So it wasn't me who introduced data abstraction.
Also, OP explicitly asked about a fold "on a set of data". Only later, when requested for an example, did he give lists.
In fact, the discussion of "arbitrary data structures" (in this thread
in general) distracts a lot from the properties under consideration, and from even first finding out whether they are properties of foldLike or of f in foldLike f.
So, let's specialize. Let's consider only the case of non-empty lists.
And look at what we have: A definitive answer to OP's question:
Question: What is a fold of type "(a -> a -> a) -> [a] -> a" that promises to call its first parameter "associatively"?
Answer: It is a fold equivalent to a fold1 (left or right, it doesn't matter).
That's nice.
But is that all we can come up with? Does it really do justice to the original question? Viz.
"Is there a name for a fold that promises to call a function such that only an associative function will always return the same result. Or in other words, it has the property that it promises to call a function "associatively" on a set of data?"
The challenge becomes:
* generalize the result to fearsomely complicated "arbitrary data structures" * answer the original question in a holistic spirit
Then, candidate functions for "foldlike functions" will be functions of this type:
foldLike : (a -> a -> a) -> [a] -> a
Here are some candidates (I give only an equation for four element lists in each case, but I assume everyone has enough imagination to see how these could be extended to other lists in an intended way):
foldLike1 f [a,b,c,d] = [] -- throws away stuff foldLike2 f [a,b,c,d] = f a (f b (f c d)) -- we have all ancountered this one foldLike3 f [a,b,c,d] = f (f (f a b) c) d -- also looks familiar foldLike4 f [a,b,c,d] = f (f a b) (f c d) -- that's a "new" one, but looks good foldLike5 f [a,b,c,d] = f a a -- probably not a very popular one foldLike6 f [a,b,c,d] = f (f c a) (f b d) -- a reasonable one, for example there's a Traversable instance that leads to this one; but still, it's not one that Charles would like, I think
So now we can ask which of these satisfy Charles's 1., 2., 3. points. Can't we?
There was:
1. Promises to call f on all data (does not have any guarantees on order)
This is satisfied by foldLike2, foldLike3, foldLike4, and foldLike6, but not by the others.
2. Promises to call f on all data in order (like a left fold)
This is satisfied by foldLike3, but not by the others.
3. Promises to call f "associatively" (perhaps can be formalized as an in order break down of the data into tree structures)
This is satisfied by foldLike2, foldLike3, and foldLike4, but not by the others.
Since I am able to tell, for a given foldLike candidate, whether or not it satisfies 3. (for example, I could specifically see that foldLike6 does not satisfy 3., while it does satisfy 1.), it cannot be maintained that 3. has no meaning.
Note: Nothing in the above makes any assumptions about f. Whether or not f is an associative function is irrelevant for what is asked here.
2015-10-25 4:19 GMT+01:00 Kim-Ee Yeoh
: On Sun, Oct 25, 2015 at 1:12 AM, Janis Voigtländer < janis.voigtlaender@gmail.com> wrote:
It has already been established in this thread what Charles meant by 3.
He meant that a fold-function that has the property he is after would guarantee that it:
a) takes all the content elements from a data structure, say x1,...,xn,
b) builds an application tree with the to-be-folded, binary operation f in the internal nodes of a binary tree, whose leafs, read from left to right, form exactly the sequence x1,...,xn,
c) evaluates that application tree.
Isn't this what Charles meant by his 2nd property:
2. Promises to call f on all data in order (like a left fold)
What about his 3rd?
Do you agree that what I describe above is a property of a given
fold-like function, not of the f handed to that fold-like function?
Before discussing a property of X, isnt it worth asking what X even means?
The folds whose meanings are crystal clear are the arrows out of initial objects in the category of F-algebras.
They are crystal clear because they couple as one with the data definition spelled out in full.
In the quest for useful generalizations of catamorphisms, that coupling with the data definition continues to be assumed.
Observe, for instance:
a) takes all the content elements from a data structure, say x1,...,xn,
Does a foliar data structure have a canonical flattening out of its leaves? Are there symmetric canonicalizations? How is one selected over the others?
Is the meaning of "all" referentially transparent? That turns out to be a subtle point, as this convo shows:
http://haskell.1045720.n5.nabble.com/A-Proposed-Law-for-Foldable-tp5765339.h...
With the theory of F-algebras, we started with precise notions of data and folds came for free.
But data can be overspecified. And also, the folds among swathes of data suggest useful generalizations.
So now, a raft of proto-precise and necessarily psychological notions of Foldable waded in, and since then it's been fun playing sorting games with shape blocks and holes to squeeze them into.
Fun is good. It's a stage in the journey to knowledge.
And do you agree that what I describe above is a property that is
weaker than (and so, in particular different from) for example the property "this fold-like function is foldl or foldr".
2015-10-24 19:55 GMT+02:00 Kim-Ee Yeoh
: > > On Sun, Oct 25, 2015 at 12:42 AM, Matteo Acerbi < > matteo.acerbi@gmail.com> wrote: > >> For what concerns question 3, I didn't understand the idea of >> calling a function "associatively". >> > > This. Associativity is a property of binary operators. It's not a > property of the catamorphism 'calling' on a given binary operator. > > Also, when Charles writes: "Then it goes on to use f in "thisFold f > [0,1,2]" like "f (1 (f 0 2))"" > > commutativity appears to raise its head. > > -- Kim-Ee >

On Thu, Oct 29, 2015 at 1:27 PM, Janis Voigtländer < janis.voigtlaender@gmail.com> wrote:
Are you sure you have read and respected all the forall-quantifiers in there?
The statement "for all associative f and all lists xs, it holds that h f xs = foldl1 f xs" is *not* equivalent to the statement "for all f and all lists xs, it holds that h f xs = foldl1 f xs". The latter statement is equivalent (via eta-contractions) to "h = foldl", but the former isn't.
Do I have to give a specific h to make this clearer? One which satisfies the first statement but is not equivalent to foldl or foldr. Actually, one was given already earlier in the conversation, to exactly the purpose of illuminating this whole point.
So you're saying: "The property of the fold in question is that it's equivalent to a fold (left or right, it's all one) __on the space of associative binary operators.__" That's not too far off is it? I deliberately abbreviated for three reasons. The first is that restriction to associative binary operators is inherent in the original question. Recall: "Is there a name for a fold that promises to call a function such that only an associative function will always return the same result." The second reason is that it summarizes the result into an easy take-away. Lastly, the fuller answer can be worked out once we throw a glance at the obviousness that foldl and foldr cannot be equal on the space of non-associative binary operators. -- Kim-Ee

2015-11-03 1:55 GMT+01:00 Kim-Ee Yeoh
On Thu, Oct 29, 2015 at 1:27 PM, Janis Voigtländer < janis.voigtlaender@gmail.com> wrote:
Are you sure you have read and respected all the forall-quantifiers in there?
The statement "for all associative f and all lists xs, it holds that h f xs = foldl1 f xs" is *not* equivalent to the statement "for all f and all lists xs, it holds that h f xs = foldl1 f xs". The latter statement is equivalent (via eta-contractions) to "h = foldl", but the former isn't.
Do I have to give a specific h to make this clearer? One which satisfies the first statement but is not equivalent to foldl or foldr. Actually, one was given already earlier in the conversation, to exactly the purpose of illuminating this whole point.
So you're saying:
"The property of the fold in question is that it's equivalent to a fold (left or right, it's all one) __on the space of associative binary operators.__"
That's not too far off is it?
It is what was meant, yes. With that part in "__ ... __".
I deliberately abbreviated for three reasons.
The first is that restriction to associative binary operators is inherent in the original question. Recall: "Is there a name for a fold that promises to call a function such that only an associative function will always return the same result."
I don't actually see how that question has an inherent restriction of the kind you read into it, that we will never have to even think about what the function does if called with a non-associative operator. On the contrary. Saying that, paraphrasing, "*only* when you call the function with an associative operator, something specific holds", does for sure imply that to work out the condition we have to *also* consider what happens for non-associative operators. Otherwise the "only" is pointless. And in particular in the early messages of the thread, there was discussion and confusion about whether what is sought here is a property of f or of h or of both. So silently making assumptions about one of them seems not a good idea to me. And even later in the thread we have again seen criticism like "but this can't be expressed at all, because Haskell's type system is not strong enough to capture associativity of operators". That criticism does apply when sweeping "on the space of associative binary operators" under the rug as if we could really say "extensional equality of functions" and mean "the functions must give equal results when called on associative operators". (If, but only if, we could express associativity in types, we could write down a function type whose meaning of extensionality agrees with what is claimed.) The second reason is that it summarizes the result into an easy take-away.
Well, "easy" can often be "subtly wrong or at least confusing if glossing over the full meaning".
Lastly, the fuller answer can be worked out once we throw a glance at the obviousness that foldl and foldr cannot be equal on the space of non-associative binary operators.
Yes, the correct answer can be worked out with some thinking.

And look at what we have: A definitive answer to OP's question:
Question: What is a fold of type "(a -> a -> a) -> [a] -> a" that promises to call its first parameter "associatively"?
Answer: It is a fold equivalent to a fold1 (left or right, it doesn't matter).
That's nice.
But is that all we can come up with? Does it really do justice to the original question? Viz.
Hello, Sorry for jumping into the thread, but I've read the previous responses, and I still don't get it (perhaps it's because I'm not a native English speaker): what does "associatively" mean in this context? From what I understand, "associativity" is a property of a function, that f (f a b) c = f a (f b c). Nothing more, nothing less. In order to encode this property in the type of a "fold" function, you'd need dependent types and a type-level proof that a given function is associative. Without dependent types, you can only trust the user to either supply an associative function, or accept wrong results (like REPA does). Am I missing something? Best regards, Marcin Mrotek

There is no point in trying to understand the concept from the name
'calling "associatively"' here. The "-signs around that word were there
precisely because the OP didn't know what to call this. Also, nobody is
trying to encode associativity in the type or anything like that.
What the OP was essentially asking about (as I understand) was:
How do I express (and how do I name) the property X of a fold-like
function, whose (X's) intuitive meaning is: The fold-like function under
consideration takes elements x1,...,xn from a data-structure in
left-to-right order (so, let's assume the data structure is actually a
list, so that there can be no doubt about what left-to-right means) and
then builds a well-bracketed application expression with f on those
elements, where the order of the x1,...,xn should not be changed. (So it
would be okay for the fold-like function to decide to compute (((x1 `f` x2)
`f` x3) `f` ... xn), it would also be okay for the fold-like function to
decide to compute (((x1 `f` x2) `f` (x3 `f` x4)) `f` ... xn), but it would
not be okay for the fold-like function to decide to compute ((((x2 `f` x3)
`f` x1) `f` x4) `f` ... xn).)
That is a property of the fold-like function, not a property of f. Also, it
is not making an assumption about f being associative. It is just saying
what the fold-like function should be allowed to do, and not allowed to do,
given an arbitrary f.
2015-10-28 20:05 GMT+01:00 Marcin Mrotek
And look at what we have: A definitive answer to OP's question:
Question: What is a fold of type "(a -> a -> a) -> [a] -> a" that promises to call its first parameter "associatively"?
Answer: It is a fold equivalent to a fold1 (left or right, it doesn't matter).
That's nice.
But is that all we can come up with? Does it really do justice to the original question? Viz.
Hello,
Sorry for jumping into the thread, but I've read the previous responses, and I still don't get it (perhaps it's because I'm not a native English speaker): what does "associatively" mean in this context? From what I understand, "associativity" is a property of a function, that f (f a b) c = f a (f b c). Nothing more, nothing less. In order to encode this property in the type of a "fold" function, you'd need dependent types and a type-level proof that a given function is associative. Without dependent types, you can only trust the user to either supply an associative function, or accept wrong results (like REPA does). Am I missing something?
Best regards, Marcin Mrotek

I said "associatively" to be a place holder for a property I was trying to
express, but unable to formalize. So yes, from what I understand
associativity is a property of a function and has a formalization.
As for the category theory, this is where I thought that this calling
hierarchy might already be formalized in. I thought it would be nice to say
something to the effect of "This fold has x property and exploits it to
support parallelization". Obviously f does not need to be associative if
the caller of the fold understands that only the x property is promised in
the implementation.
On Wed, Oct 28, 2015 at 3:05 PM, Marcin Mrotek
And look at what we have: A definitive answer to OP's question:
Question: What is a fold of type "(a -> a -> a) -> [a] -> a" that promises to call its first parameter "associatively"?
Answer: It is a fold equivalent to a fold1 (left or right, it doesn't matter).
That's nice.
But is that all we can come up with? Does it really do justice to the original question? Viz.
Hello,
Sorry for jumping into the thread, but I've read the previous responses, and I still don't get it (perhaps it's because I'm not a native English speaker): what does "associatively" mean in this context? From what I understand, "associativity" is a property of a function, that f (f a b) c = f a (f b c). Nothing more, nothing less. In order to encode this property in the type of a "fold" function, you'd need dependent types and a type-level proof that a given function is associative. Without dependent types, you can only trust the user to either supply an associative function, or accept wrong results (like REPA does). Am I missing something?
Best regards, Marcin Mrotek
_______________________________________________ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://mail.haskell.org/cgi-bin/mailman/listinfo/haskell-cafe

So you mean "associatively" meaning "the property that people usually ascribe to Foldable but that can't be expressed in Haskell type system, that the operation passed to foldMap "will be called with each and every element of the container but without ever commuting the elements"? In that case, I get it, but I'd consider it a case against the Foldable type class (i.e. that the type system is not able to express this property) or Haskell's type system, or just leave it be and consider it to be one of the things to be taken on faith. Best regards, Marcin Mrotek

Hi, Charles Durham wrote:
Is there a name for a fold that promises to call a function such that only an associative function will always return the same result. Or in other words, it has the property that it promises to call a function "associatively" on a set of data?
Semigroup homomorphism? Tillmann
participants (12)
-
Bardur Arantsson
-
Charles Durham
-
Clinton Mead
-
Dimitri DeFigueiredo
-
Francesco Ariis
-
Janis Voigtländer
-
Kim-Ee Yeoh
-
Marcin Mrotek
-
Matteo Acerbi
-
Tillmann Rendel
-
Tom Ellis
-
Yuras Shumovich