Logo Questions Linux Laravel Mysql Ubuntu Git Menu
 

Is there an elegant way to have functions return functions of the same type (in a tuple)

I'm using haskell to implement a pattern involving functions that return a value, and themselves (or a function of the same type). Right now I've implemented this like so:

newtype R a = R (a , a -> R a)

-- some toy functions to demonstrate    
alpha :: String -> R String
alpha str
    | str == reverse str = R (str , omega)
    | otherwise          = R (reverse str , alpha)

omega :: String -> R String
omega (s:t:r)
    | s == t    = R (s:t:r , alpha)
    | otherwise = R (s:s:t:r , omega)

The driving force for these types of functions is a function called cascade:

cascade :: (a -> R a) -> [a] -> [a]
cascade _ [] = []
cascade f (l:ls) = el : cascade g ls where
    R (el , g) = f l

Which takes a seed function and a list, and returns a list created by applying the seed function to the first element of the list, applying the function returned by that to the second element of the list, and so on and so forth.

This works--however, in the process of using this for slightly more useful things, I noticed that a lot of times I had the basic units of which are functions that returned functions other than themselves only rarely; and explicitly declaring a function to return itself was becoming somewhat tedious. I'd rather be able to use something like a Monad's return function, however, I have no idea what bind would do for functions of these types, especially since I never intended these to be linked with anything other than the function they return in the first place.

Trying to shoehorn this into a Monad started worrying me about whether or not what I was doing was useful, so, in short, what I want to know is:

  • Is what I'm doing a Bad Thing? if not,
  • Has what I'm doing been done before/am I reinventing the wheel here? if not,
  • Is there an elegant way to do this, or have I already reached this and am being greedy by wanting some kind of return analogue?

(Incidentally, besides, 'functions that return themeselves' or 'recursive data structure (of functions)', I'm not quite sure what this kind of pattern is called, and has made trying to do effective research in it difficult--if anyone could give me a name for this pattern (if it indeed has one), that alone would be very helpful)

like image 334
Lily Avatar asked Feb 21 '13 23:02

Lily


People also ask

Can a Python function return different types?

In Python, you can return multiple values by simply return them separated by commas. In Python, comma-separated values are considered tuples without parentheses, except where required by syntax. For this reason, the function in the above example returns a tuple with each value as an element.

Can a function return more than one thing?

If we want the function to return multiple values of same data types, we could return the pointer to array of that data types. We can also make the function return multiple values by using the arguments of the function.

Can a function return multiple list in Python?

You can return multiple values from a function in Python. To do so, return a data structure that contains multiple values, like a list containing the number of miles to run each week.

How many values can be returned from a function?

To that end, a function can only return one object.


2 Answers

As a high-level consideration, I'd say that your type represents a stateful stream transformer. What's a bit confusing here is that your type is defined as

newtype R a = R (a , a -> R a)

instead of

newtype R a = R (a -> (R a, a))

which would be a bit more natural in the streaming context because you typically don't "produce" something if you haven't received anything yet. Your functions would then have simpler types too:

alpha, omage :: R String
cascade :: R a -> [a] -> [a]

If we try to generalize this idea of a stream transformer, we soon realize that the case where we transform a list of as into a list of as is just a special case. With the proper infrastructure in place we could just as well produce a list of bs. So we try to generalize the type R:

newtype R a b = R (a -> (R a b, b))

I've seen this kind of structure being called a Circuit, which happens to be a full-blown arrow. Arrows are a generalization of the concept of functions and are an even more powerful construct than monads. I can't pretend to understand the category-theoretical background, but it's definitely interesting to play with them. For example, the trivial transformation is just Cat.id:

import Control.Category
import Control.Arrow
import Prelude hiding ((.), id)
import qualified Data.List as L

-- ... Definition of Circuit and instances

cascade :: Circuit a b -> [a] -> [b]
cascade cir = snd . L.mapAccumL unCircuit cir

--
ghci> cascade (Cat.id) [1,2,3,4] 
[1,2,3,4]

We can also simulate state by parameterizing the circuit we return as the continuation:

countingCircuit :: (a -> b) -> Circuit a (Int, b)
countingCircuit f = cir 0
    where cir i = Circuit $ \x -> (cir (i+1), (i, f x))

--
ghci> cascade (countingCircuit (+5)) [10,3,2,11]
[(0,15),(1,8),(2,7),(3,16)]

And the fact that our circuit type is a category gives us a nice way to compose circuits:

ghci> cascade (countingCircuit (+5) . arr (*2)) [10,3,2,11]
[(0,25),(1,11),(2,9),(3,27)]
like image 98
Niklas B. Avatar answered Nov 03 '22 06:11

Niklas B.


It looks like what you have is a simplified version of a stream. That is to say, a representation of an infinite stream of values. I don't think you can easily define this as a monad, because you use the same type for your seed as for your elements, which makes defining fmap difficult (it seems that you would need to invert the function provided to fmap so as to be able to recover the seed). You can make this a monad by making the seed type independent of the element type like so

{-# LANGUAGE ExistentialQuantification #-}
data Stream a = forall s. Stream a s (s -> Stream a)

This will allow you to define a Functor and Monad instance as follows

unfold :: (b -> (a, b)) -> b -> Stream a
unfold f b = Stream a b' (unfold f)
    where (a, b') = f b

shead :: Stream a -> a
shead (Stream a _ _) = a

stail :: Stream a -> Stream a
stail (Stream _ b f) = f b

diag :: Stream (Stream a) -> Stream a
diag = unfold f
    where f str = (shead $ shead str, stail $ fmap stail str)

sjoin :: Stream (Stream a) -> Stream a
sjoin = diag

instance Functor Stream where
    fmap f (Stream a b g) = Stream (f a) b (fmap f . g)

instance Monad Stream where
    return   = unfold (\x -> (x, x))
    xs >>= f = diag $ fmap f xs

Note that this only obeys the Monad laws when viewed as a set, as it does not preserve element ordering.

This explanation of the stream monad uses infinite lists, which works just as well in Haskell since they can be generated in a lazy fashion. If you check out the documentation for the Stream type in the vector library, you will find a more complicated version, so that it can be used in efficient stream fusion.

like image 33
sabauma Avatar answered Nov 03 '22 06:11

sabauma