Here's why functions should return functions

Hi Folks, Recently I had a small epiphany: when creating functions, design them to return functions rather than non-function values (Integer, Bool, list, tuple, etc.). Here's why: Consider a function that returns, say, the integer four ( 4 ). The type of the value returned by the function is this: 4 :: Num a => a That is, the value returned is not a function, it is a number. However, there are advantages to returning a function rather than a number. Recall the composition operator ( . ) Its operands are functions, e.g. (+1) . (*3) In programming, one school of thought is that programs should be written as a chain of function compositions: a . b . c . d . e . f Composition is intimately connected to a branch of mathematics called Category Theory: Category theory is based on composition as a fundamental operation in much the same way that classical set theory is based on the 'element of' or membership relation. ["Category Theory for Computing Science" by Michael Barr and Charles Wells] By designing programs in this fashion--as a chain of compositions--you have Category Theory's vast body of knowledge to help you and give rigor to your programs. Let's revisit the function mentioned above, the one that returns the integer four ( 4 ). If the function were to return the four cloaked in a function then that returned value could be used in a composition. That would very useful. Here's a data type that lifts non-function values to functions: data Lift a = Function a deriving (Show) The constructor ( Function ) is a function, as its type signature shows: Function :: a -> Lift a So rather than returning 4, return Function 4. Here's a function that converts any value to a function: lift :: a -> Lift a lift = Function Thus, lift 4 returns Function 4 Given the Lift data type and the lift function we can now start chaining functions together. Here the value four is lifted and then composed with a successor function: (successor . lift) 4 returns Function 5 where successor is defined as: successor :: Num a => Lift a -> Lift a successor (Function a) = lift (a + 1) Notice that successor returns a function, not a non-function value. Consequently, the result of successor can also be used in a composition. For example, here the value four is lifted, composed with successor, and then square is applied: (square . successor . lift) 4 returns Function 25 where square is defined as: square :: Num a => Lift a -> Lift a square (Function a) = lift (a * a) Once again notice that square also returns a function, not a non-function value. Consequently, the result of square can be used in a composition. At some point we are finished manipulating the value four and want to just see the result, not the result wrapped in a constructor. So we can create a function to return the non-function value: value :: Lift a -> a value (Function a) = a Here's an example: (value . square . successor . lift) 4 returns 25 Comments welcome. /Roger

"Costello, Roger L."
Recently I had a small epiphany: when creating functions, design them to return functions rather than non-function values (Integer, Bool, list, tuple, etc.).
Here's why:
Consider a function that returns, say, the integer four ( 4 ). The type of the value returned by the function is this:
4 :: Num a => a
This is not a Haskell function (even though it does actually compile to a function, unless you use specialization). If it doesn't involve the (->) type constructor, then it's not a function.
That is, the value returned is not a function, it is a number.
If you were to say x = 4, then 'x' is not a function. It's a value equal to 4. The equality sign in Haskell is not an assignment and doesn't introduce a function definition. It introduces an equation, so "x = y" means that x is /the same/ as y.
However, there are advantages to returning a function rather than a number.
Recall the composition operator ( . )
[...]
There is a design pattern, where you compose functions ((->)) or function-like objects (Category/Arrow). In this design pattern you work with constant functions to introduce values. This is used in FRP, for example: integral 0 . pure 4 This is the integral of the constant 4 with respect to time.
Here's a data type that lifts non-function values to functions:
[...]
No, it doesn't.
data Lift a = Function a deriving (Show)
You have just reinvented an awkward version (data instead of newtype) of the identity functor, which is both a monad (a -> Identity a) and a comonad (Identity a -> a). I don't see what it buys you given 'const'. Haskell is a language to study new ways of thinking, so it's great that you think, but you should really first learn the language properly. You will find it helpful to learn the various type classes for categorical programming, in particular Category, Applicative and Arrow. There is the reader monad, in which you would write the following: fmap (^2) . fmap succ . pure 4 or equivalently: fmap ((^2) . succ) . pure 4 The reader monad is defined as: instance Applicative (e ->) instance Functor (e ->) instance Monad (e ->) Since (->) forms a category, you have composition and an identity morphism (the identity function). In other words, you have just invented an awkward way to write what can already be written nicely using existing stuff. Greets, Ertugrul -- Not to be or to be and (not to be or to be and (not to be or to be and (not to be or to be and ... that is the list monad.

@Ertugrul, you don't need to be rude. @Costello, I like your idea. But I don't see an advantage to using "Function 4" over simply "4": What's the advantage of using this: (value . square . sucessor . lift) 4 data Lift a = Function a lift = Function sucesor (Function a) = lift (a + 1) square (Function a) = lift (a * a) value (Function a) = a Over this: (square . sucessor) 4 sucessor = (+1) square a = a * a For me, it looks like we are wrapping a value inside a container and dewrapping it every time we want to use it's value, then rewrap to return. Could you elaborate an example that your Lift a datatype is better suited than just the raw value? I can only see the use of a value lifted as a function when you want to get the same result no matter what are the chain of functions, for example, the use of the const function: const 4 . square . sucessor $ 4 Thiago.

Thiago Negri wrote:
What's the advantage of using this: (value . square . successor . lift) 4 data Lift a = Function a lift = Function successor (Function a) = lift (a + 1) square (Function a) = lift (a * a) value (Function a) = a
Over this: (square . successor) 4 successor = (+1) square a = a * a
Oops! There's no advantage, that I can see, of the former over the latter. Thanks Thiago for pointing this out. This is very helpful. It helps me to avoid continuing on a wrong course of thought. /Roger

Thiago Negri
@Ertugrul, you don't need to be rude.
Sorry if this sounded rude, but it really wasn't supposed to be. As said, I liked Costello's attempt. I just found that the solution is already in the base library in a way that doesn't require wrapping things up in a constructor.
@Costello,
I like your idea. But I don't see an advantage to using "Function 4" over simply "4":
What's the advantage of using this: (value . square . sucessor . lift) 4 data Lift a = Function a lift = Function sucesor (Function a) = lift (a + 1) square (Function a) = lift (a * a) value (Function a) = a
Over this: (square . sucessor) 4 sucessor = (+1) square a = a * a
I think that Costello is really referring to something called function-level programming where you don't have values, but only so-called functionals and composition. A value is then represented by a constant function, which is exactly what 'const' and 'pure' are. This is the essence of SKI calculus. It gets rid of all lambda abstractions. The remainder is then an (unintelligible) expression of S and K applications, but Haskell also has the power of Category, so this can actually become readable code. Greets, Ertugrul -- Not to be or to be and (not to be or to be and (not to be or to be and (not to be or to be and ... that is the list monad.

On Sun, 29 Jul 2012, Ertugrul Söylemez
"Costello, Roger L."
wrote: Recently I had a small epiphany: when creating functions, design them to return functions rather than non-function values (Integer, Bool, list, tuple, etc.).
Here's why:
Consider a function that returns, say, the integer four ( 4 ). The type of the value returned by the function is this:
4 :: Num a => a
This is not a Haskell function (even though it does actually compile to a function, unless you use specialization). If it doesn't involve the (->) type constructor, then it's not a function.
That is, the value returned is not a function, it is a number.
If you were to say x = 4, then 'x' is not a function. It's a value equal to 4. The equality sign in Haskell is not an assignment and doesn't introduce a function definition. It introduces an equation, so "x = y" means that x is /the same/ as y.
However, there are advantages to returning a function rather than a number.
Recall the composition operator ( . )
[...]
There is a design pattern, where you compose functions ((->)) or function-like objects (Category/Arrow). In this design pattern you work with constant functions to introduce values. This is used in FRP, for example:
integral 0 . pure 4
This is the integral of the constant 4 with respect to time.
Here's a data type that lifts non-function values to functions:
[...]
No, it doesn't.
data Lift a = Function a deriving (Show)
You have just reinvented an awkward version (data instead of newtype) of the identity functor, which is both a monad (a -> Identity a) and a comonad (Identity a -> a). I don't see what it buys you given 'const'.
Haskell is a language to study new ways of thinking, so it's great that you think, but you should really first learn the language properly. You will find it helpful to learn the various type classes for categorical programming, in particular Category, Applicative and Arrow. There is the reader monad, in which you would write the following:
fmap (^2) . fmap succ . pure 4
or equivalently:
fmap ((^2) . succ) . pure 4
The reader monad is defined as:
instance Applicative (e ->) instance Functor (e ->) instance Monad (e ->)
Since (->) forms a category, you have composition and an identity morphism (the identity function).
In other words, you have just invented an awkward way to write what can already be written nicely using existing stuff.
Greets, Ertugrul
-- Not to be or to be and (not to be or to be and (not to be or to be and (not to be or to be and ... that is the list monad.
There is, in most sub-systems of mathematics, whether like recent type theory or not, a general function, let us call it mcf which in Scheme notation may be defined by executing (define mcf (lambda (a) (lambda (x) a))) Now in Haskell I know that one, perhaps the, parallel definition must result in a polymorphic function. What is this definition? How polymorphic is it? What implicit constraints are on a? Does "lazy vs eager" come in here? Are there options to ghc which might modify how Haskell handles the definition? Of course, my questions are too many and I hope just for some indications of the first things a beginner should study. oo--JS. PS. Below is a short Scheme session showing some of the behavior of Scheme. SCM version 5d9, Copyright (C) 1990-2002 Free Software Foundation. SCM comes with ABSOLUTELY NO WARRANTY; for details type `(terms)'. This is free software, and you are welcome to redistribute it under certain conditions; type `(terms)' for details. ;loading /usr/local/lib/slib/require ;done loading /usr/local/lib/slib/require.scm
(define mcf (lambda (a) (lambda (x) a))) #<unspecified> (define const-17 (mcf 17)) #<unspecified> (const-17 "abc") 17 (define const-1+ (mcf 1+)) #<unspecified> (const-1+ "abc") #
((const-1+ "abc") 200) 201 ((const-1+ 56) 200) 201 (quit) ;EXIT
Process scheme finished

Jay Sulzberger
There is, in most sub-systems of mathematics, whether like recent type theory or not, a general function, let us call it mcf which in Scheme notation may be defined by executing
(define mcf (lambda (a) (lambda (x) a)))
Now in Haskell I know that one, perhaps the, parallel definition must result in a polymorphic function.
First let's ensure that we are talking about the same function. I'm reading "mcf" as "make constant function". From what I read the Haskell equivalent would be this function: const a _ = a It may make it not fully polymorphic, but if you don't provide a type signature, then the following fully polymorphic type will be inferred: const :: a -> b -> a
What is this definition?
Well, this is the constant function, though with slightly unusual (but sensible) semantics for Scheme. Because Scheme syntax requires explicit currying the name "make constant function" would also be sensible. It is because of the lack of side effects that we call the function simply 'const' in Haskell. Otherwise most functions would be prefixed with "make".
What implicit constraints are on a?
None.
Does "lazy vs eager" come in here?
Yes. Even though you have written a curried version of 'const' there, Scheme is still a strict language, which means that the result of the inner lambda will depend on its argument 'x'. This means: -- Haskell: const a ⊥ = a -- in other words: loop = loop -- an infinite loop const a loop = a ; Scheme: ((mcf a) ⊥) = ⊥ (define (loop) (loop)) ; an infinite loop ((mcf a) (loop)) = (loop) This is the semantic difference. To relate this to "lazy vs. eager" it's important to understand how a nonstrict language like Haskell is usually evaluated: Lazy evaluation will defer the evaluation of the inner lambda's argument (which is an unnamed '_' here) until it is required. Since it is never required it is never evaluated and the unevaluated thunk is garbage-collected immediately, unless it is used elsewhere. A strict language like Scheme is usually evaluated eagerly. This means that the inner lambda is not entered, until the argument is fully evaluated.
Are there options to ghc which might modify how Haskell handles the definition?
There are optimization flags, which could change the performance of the definition, but a proper Haskell compiler like GHC must ensure that semantics are not changed.
Of course, my questions are too many and I hope just for some indications of the first things a beginner should study.
No worries. I'm happy to help. =) Greets, Ertugrul -- Not to be or to be and (not to be or to be and (not to be or to be and (not to be or to be and ... that is the list monad.

On Mon, 30 Jul 2012, Ertugrul Söylemez
Jay Sulzberger
wrote: There is, in most sub-systems of mathematics, whether like recent type theory or not, a general function, let us call it mcf which in Scheme notation may be defined by executing
(define mcf (lambda (a) (lambda (x) a)))
Now in Haskell I know that one, perhaps the, parallel definition must result in a polymorphic function.
First let's ensure that we are talking about the same function. I'm reading "mcf" as "make constant function". From what I read the Haskell equivalent would be this function:
const a _ = a
It may make it not fully polymorphic, but if you don't provide a type signature, then the following fully polymorphic type will be inferred:
const :: a -> b -> a
This is good.
What is this definition?
Well, this is the constant function, though with slightly unusual (but sensible) semantics for Scheme. Because Scheme syntax requires explicit currying the name "make constant function" would also be sensible. It is because of the lack of side effects that we call the function simply 'const' in Haskell. Otherwise most functions would be prefixed with "make".
Ah, yes. Certainly all functions with more than one input.
What implicit constraints are on a?
None.
I am encouraged by this.
Does "lazy vs eager" come in here?
Yes. Even though you have written a curried version of 'const' there, Scheme is still a strict language, which means that the result of the inner lambda will depend on its argument 'x'. This means:
-- Haskell: const a ⊥ = a
-- in other words: loop = loop -- an infinite loop const a loop = a
; Scheme: ((mcf a) ⊥) = ⊥
(define (loop) (loop)) ; an infinite loop ((mcf a) (loop)) = (loop)
Yes, I see, I think. I think, if we were doing a finer analysis, we might write ((mcf a) (loop)) ~> [(mcf a) waiting] (loop) where [ waiting] indicates that when loop finishes executing, and returns, ah, something, perhaps nothing, the constant function (mcf a) will accept that returned thing. (To be clear: above line is not Scheme nor indeed is it a phrase of any standard programming system.) We here avoid mentioning (\omega + 1) ;)
This is the semantic difference. To relate this to "lazy vs. eager" it's important to understand how a nonstrict language like Haskell is usually evaluated: Lazy evaluation will defer the evaluation of the inner lambda's argument (which is an unnamed '_' here) until it is required. Since it is never required it is never evaluated and the unevaluated thunk is garbage-collected immediately, unless it is used elsewhere.
A strict language like Scheme is usually evaluated eagerly. This means that the inner lambda is not entered, until the argument is fully evaluated.
Yes.
Are there options to ghc which might modify how Haskell handles the definition?
There are optimization flags, which could change the performance of the definition, but a proper Haskell compiler like GHC must ensure that semantics are not changed.
Of course, my questions are too many and I hope just for some indications of the first things a beginner should study.
No worries. I'm happy to help. =)
Greets, Ertugrul
Thanks, Ertugrul! oo--JS.

"Carlos J. G. Duarte"
So, what is the usefulness of that "const" function anyway? (go easy on me, I'm just beginning on this)
There are many functions in Haskell, which you wouldn't define in most other languages, including: const :: a -> b -> a flip :: (a -> b -> c) -> (b -> a -> c) id :: a -> a They become useful when used as arguments to combinators. Some examples: maybe 8 (const 16) foldl' (flip (-)) 0 id &&& length In use: maybe 8 (const 16) (Just 3) = 16 = const 16 3 maybe 8 (const 16) Nothing = 8 foldl' (flip (-)) 0 [1,2,3] = flip (-) (flip (-) (flip (-) 0 1) 2) 3 = (-) 3 ((-) 2 ((-) 1 0)) = 3 - (2 - (1 - 0)) map (id &&& length) ["abc", "de", "f"] = [("abc", 3), ("de", 2), ("f", 1)] Greets, Ertugrul -- Not to be or to be and (not to be or to be and (not to be or to be and (not to be or to be and ... that is the list monad.
participants (5)
-
Carlos J. G. Duarte
-
Costello, Roger L.
-
Ertugrul Söylemez
-
Jay Sulzberger
-
Thiago Negri