Are there arithmetic composition of functions?

By arithmetic I mean the everyday arithmetic operations used in engineering. In signal processing for example, we write a lot of expressions like f(t)=g(t)+h(t)+g'(t) or f(t)=g(t)*h(t). I feel it would be very natural to have in haskell something like g::Float->Float --define g here h::Float->Float --define h here f::Float->Float f = g+h --instead of f t = g t+h t --Of course, f = g+h is defined as f t = g t+h t I guess as long as all operands have the same number of arrows in there types then they should have the potential to be composed like this. Or g::Float->Float->Float --define g here h::Float->Float->Float --define h here f::Float->Float->Float f = g+h --means f x y = g x y + h x y -- f = g+h is defined as f x = g x+h x which in turn is defined as f x y = g x y+h x y This should be easy to implement, with TH perhaps. And I thought there would be a library (not in the language itself, of course) for this, but I haven't find one. Can someone tell me whether there is some implementation of such composition? If there isn't then I may build one.

import Control.Applicative f, g :: Float -> Float f x = x + 1 g x = 2 * x h = (+) <$> f <*> g Cheers, =) -- Felipe.

If you are willing to depend on a recent version of base where Num is no longer a subclass of Eq and Show, it is also fine to do this: instance Num a => Num (r -> a) where (f + g) x = f x + g x fromInteger = const . fromInteger and so on.

Hi,
If you are feeling adventurous enough, you can define a num instance for
functions:
{-# LANGUAGE FlexibleInstances #-}
instance Num a => Num (a -> a) where
f + g = \ x -> f x + g x
f - g = \ x -> f x - g x
f * g = \ x -> f x * g x
abs f = abs . f
signum f = signum . f
fromInteger = const . fromInteger
ghci> let f x = x * 2
ghci> let g x = x * 3
ghci> (f + g) 3
15
ghci> (f+g+2) 2
17
HTH,
Ozgur
On 19 March 2012 16:57,
By arithmetic I mean the everyday arithmetic operations used in engineering. In signal processing for example, we write a lot of expressions like f(t)=g(t)+h(t)+g'(t) or f(t)=g(t)*h(t). I feel it would be very natural to have in haskell something like g::Float->Float --define g here h::Float->Float --define h here f::Float->Float f = g+h --instead of f t = g t+h t --Of course, f = g+h is defined as f t = g t+h t

The 17 at the end should be 12, or the 2 passed into (f+g+2) should be 3.
On Mon, Mar 19, 2012 at 10:38 AM, Ozgur Akgun
Hi,
If you are feeling adventurous enough, you can define a num instance for functions:
{-# LANGUAGE FlexibleInstances #-}
instance Num a => Num (a -> a) where f + g = \ x -> f x + g x f - g = \ x -> f x - g x f * g = \ x -> f x * g x abs f = abs . f signum f = signum . f fromInteger = const . fromInteger
ghci> let f x = x * 2 ghci> let g x = x * 3 ghci> (f + g) 3 15 ghci> (f+g+2) 2 17
HTH, Ozgur
On 19 March 2012 16:57,
wrote: By arithmetic I mean the everyday arithmetic operations used in engineering. In signal processing for example, we write a lot of expressions like f(t)=g(t)+h(t)+g'(t) or f(t)=g(t)*h(t). I feel it would be very natural to have in haskell something like g::Float->Float --define g here h::Float->Float --define h here f::Float->Float f = g+h --instead of f t = g t+h t --Of course, f = g+h is defined as f t = g t+h t
_______________________________________________ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe

On Mar 19, 2012 11:40 AM, "Ozgur Akgun"
{-# LANGUAGE FlexibleInstances #-}
instance Num a => Num (a -> a) where
You don't want (a -> a) there. You want (b -> a). There is nothing about this that requires functions to come from a numeric type, much less the same one. -- Chris Smith

Hi Chris,
On 19 March 2012 17:58, Chris Smith
On Mar 19, 2012 11:40 AM, "Ozgur Akgun"
wrote: {-# LANGUAGE FlexibleInstances #-}
instance Num a => Num (a -> a) where
You don't want (a -> a) there. You want (b -> a). There is nothing about this that requires functions to come from a numeric type, much less the same one.
Thanks for catching this one, you are absolutely correct. I was carried away by the original post using "Float -> Float" for the example functions. Cheers, Ozgur

This instance can be made more general without changing the code; change
the first line to
instance Num a => Num (e -> a) where
I think this version doesn't even require FlexibleInstances.
This lets you do
f x = if x then 2 else 3
g x = if x then 5 else 10
-- f + g = \x -> if x then 7 else 13
-- ryan
On Mon, Mar 19, 2012 at 10:38 AM, Ozgur Akgun
Hi,
If you are feeling adventurous enough, you can define a num instance for functions:
{-# LANGUAGE FlexibleInstances #-}
instance Num a => Num (a -> a) where f + g = \ x -> f x + g x f - g = \ x -> f x - g x f * g = \ x -> f x * g x abs f = abs . f signum f = signum . f fromInteger = const . fromInteger
ghci> let f x = x * 2 ghci> let g x = x * 3 ghci> (f + g) 3 15 ghci> (f+g+2) 2 17
HTH, Ozgur
On 19 March 2012 16:57,
wrote: By arithmetic I mean the everyday arithmetic operations used in engineering. In signal processing for example, we write a lot of expressions like f(t)=g(t)+h(t)+g'(t) or f(t)=g(t)*h(t). I feel it would be very natural to have in haskell something like g::Float->Float --define g here h::Float->Float --define h here f::Float->Float f = g+h --instead of f t = g t+h t --Of course, f = g+h is defined as f t = g t+h t
_______________________________________________ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe

Oh man, I came late to this party.
I'll throw what little weight I have here behind Jerry's argument. Yes,
this change to base is not Haskell2010 compatible, but it's still a good
change and I hope that Haskell2012 or 2013 or whatever the next version of
the standard that comes out incorporates it.
As to why it's a good change:
(1) People were doing it anyways with bogus Eq instances; the syntactic
benefit of being able to use integer literals is huge; using the standard
+/-/* etc functions is a nice bonus. For an example, see
http://twanvl.nl/blog/haskell/simple-reflection-of-expressions
(2) Pattern matching on numeric literals is what requires Eq, and combined
with (1) leads to fragile code. Now, for example,
fac 0 = 1
fac n = n * fac (n-1)
Now the type of fac explicitly states that it requires Eq to work; with the
'hack' version of Eq in the expressions above, "fac x" doesn't terminate
and instead gives x * (x-1) * (x-1-1) * ... forever. Other versions (like
the version in this thread with Num (e -> a)) turn fac into a function that
always returns bottom.
-- ryan
On Tue, Mar 20, 2012 at 12:02 PM, Ryan Ingram
This instance can be made more general without changing the code; change the first line to
instance Num a => Num (e -> a) where
I think this version doesn't even require FlexibleInstances.
This lets you do
f x = if x then 2 else 3 g x = if x then 5 else 10
-- f + g = \x -> if x then 7 else 13
-- ryan
On Mon, Mar 19, 2012 at 10:38 AM, Ozgur Akgun
wrote: Hi,
If you are feeling adventurous enough, you can define a num instance for functions:
{-# LANGUAGE FlexibleInstances #-}
instance Num a => Num (a -> a) where f + g = \ x -> f x + g x f - g = \ x -> f x - g x f * g = \ x -> f x * g x abs f = abs . f signum f = signum . f fromInteger = const . fromInteger
ghci> let f x = x * 2 ghci> let g x = x * 3 ghci> (f + g) 3 15 ghci> (f+g+2) 2 17
HTH, Ozgur
On 19 March 2012 16:57,
wrote: By arithmetic I mean the everyday arithmetic operations used in engineering. In signal processing for example, we write a lot of expressions like f(t)=g(t)+h(t)+g'(t) or f(t)=g(t)*h(t). I feel it would be very natural to have in haskell something like g::Float->Float --define g here h::Float->Float --define h here f::Float->Float f = g+h --instead of f t = g t+h t --Of course, f = g+h is defined as f t = g t+h t
_______________________________________________ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe

One problem with hooking functions into the Haskell numeric classes is right at the beginning: class (Eq a, Show a) => Num a where (+) (-) (*) negate abs signum fromInteger where functions are for good reason not members of Eq or Show. Look at http://www.haskell.org/haskellwiki/Numeric_Prelude for a different set of numeric classes that should suit you better.

On Mon, Mar 19, 2012 at 7:16 PM, Richard O'Keefe
One problem with hooking functions into the Haskell numeric classes is right at the beginning:
class (Eq a, Show a) => Num a
This is true in base 4.4, but is no longer true in base 4.5. Hence my earlier comment about if you're willing to depend on a recent version of base. Effectively, this means requiring a recent GHC, since I'm pretty sure base is not independently installable. -- Chris Smith

On 20/03/2012, at 2:21 PM, Chris Smith wrote:
On Mon, Mar 19, 2012 at 7:16 PM, Richard O'Keefe
wrote: One problem with hooking functions into the Haskell numeric classes is right at the beginning:
class (Eq a, Show a) => Num a
This is true in base 4.4, but is no longer true in base 4.5.
I didn't say "GHC", I said "Haskell". class (Eq a, Show a) => Num a where (+), (-), (⋆) :: a -> a -> a negate :: a -> a abs, signum :: a -> a fromInteger :: Integer -> a -- Minimal complete definition: -- All, except negate or (-) x - y = x + negate y negate x = 0 - x comes straight from the Haskell 2010 report: http://www.haskell.org/onlinereport/haskell2010/haskellch9.html#x16-1710009 There are other Haskell compilers than GHC.

On 12-03-19 10:05 PM, Richard O'Keefe wrote:
http://www.haskell.org/onlinereport/haskell2010/haskellch9.html#x16-1710009
Haskell 2010 is already beginning to be out of date. http://thread.gmane.org/gmane.comp.lang.haskell.libraries/16125/focus=16324 http://thread.gmane.org/gmane.comp.lang.haskell.glasgow.user/21065/focus=210...

On 21/03/2012, at 9:06 AM, Albert Y. C. Lai wrote:
On 12-03-19 10:05 PM, Richard O'Keefe wrote:
http://www.haskell.org/onlinereport/haskell2010/haskellch9.html#x16-1710009
Haskell 2010 is already beginning to be out of date.
Was there any point in me pointing out that the latest release of a well known Haskell compiler downloaded and installed YESTERDAY still conformed to Haskell 2010, not this change? Was there any point in me pointing out that the latest release of the Haskell Platform downloaded YESTERDAY still conformed to Haskell 2010, not this change? Or was I shouting into the wind? The change is a Good Thing. No disagreement there. The latest GHC supports it, and that's a Good Thing. No disagreement there. Some time there will be a new version of the Haskell Platform incorporating new versions of the library and compiler, and that will be a Good Thing too. The point I was making remains valid: right NOW, using current releases of things other than GHC, the odds are that you will have to manually upgrade your system, and (a) you might not know how to do that (as I don't know how to upgrade UHC), and (b) until the change is more widely adopted, your shiny new code will work for some people but not others.

Richard O'Keefe:
class (Eq a, Show a) => Num a where (+) (-) (*) negate abs signum fromInteger
where functions are for good reason not members of Eq or Show.
This is an old song, changed several times. I have no intention to discuss, but please, Richard O'Keefe: WHICH *GOOD* REASONS?? Thank you. Jerzy Karczmarczuk

On 20 March 2012 12:27, Jerzy Karczmarczuk
Richard O'Keefe:
class (Eq a, Show a) => Num a where (+) (-) (*) negate abs signum fromInteger
where functions are for good reason not members of Eq or Show.
This is an old song, changed several times. I have no intention to discuss, but please, Richard O'Keefe: WHICH GOOD REASONS??
Because there are no sensible ways of writing such instances? -- Ivan Lazar Miljenovic Ivan.Miljenovic@gmail.com http://IvanMiljenovic.wordpress.com

On 20/03/2012, at 2:27 PM, Jerzy Karczmarczuk wrote:
Richard O'Keefe:
class (Eq a, Show a) => Num a where (+) (-) (*) negate abs signum fromInteger
where functions are for good reason not members of Eq or Show.
This is an old song, changed several times. I have no intention to discuss, but please, Richard O'Keefe: WHICH GOOD REASONS??
It is still there in the Haskell 2010 report. The UHC user manual at http://www.cs.uu.nl/groups/ST/Projects/ehc/ehc-user-doc.pdf lists differences between UHC and both Haskell 98 and Haskell 2010, but is completely silent about any change to the interface of class Num, and in fact compiling a test program that does 'instance Num Foo' where Foo is *not* an instance of Eq or Show gives me this response: [1/1] Compiling Haskell mynum (mynum.hs) EH analyses: Type checking mynum.hs:3-11: Predicates remain unproven: preds: UHC.Base.Eq mynum.Foo: This is with ehc-1.1.3, Revision 2422:2426M, the latest binary release, downloaded and installed today. The release date was the 31st of January this year. GHC 7.0.3 doesn't like it either. I know ghc 7.4.1 is out, but I use the Haskell Platform, and the currently shipping version says plainly at http://hackage.haskell.org/platform/contents.html that it provides GHC 7.0.4. You may have no intention of discussing the issue, but it seems to *me* that "this will not work in 2012 Haskell compiler mostly conforming to Haskell 2010 because Haskell 2010 says it shouldn't work" is a pretty sound position to take.

I don't understand this discussion. He explicitly said "If you are
willing to depend on a recent version of base". More precisely, he
meant GHC 7.4 which includes the latest version of base. Yes, this is
incompatible with the Haskell2010 standard, but it did go through the
library submission process (unless I'm mistaken).
It is also easy to add nonsense instances for functions to make this
work with the Haskell2010 definition of the Num class.
instance Eq (a -> b) where
f == g = error "Cannot compare two functions (undecidable for
infinite domains)"
instance Show (a -> b) where show _ = "<function>"
Yes, these instances are not very useful, but they let you get around
this unnecessary restriction of the Num class. (I expect this to be
fixed in future versions of the Haskell standard.)
On 20 March 2012 02:37, Richard O'Keefe
On 20/03/2012, at 2:27 PM, Jerzy Karczmarczuk wrote:
Richard O'Keefe:
class (Eq a, Show a) => Num a where (+) (-) (*) negate abs signum fromInteger
where functions are for good reason not members of Eq or Show.
This is an old song, changed several times. I have no intention to discuss, but please, Richard O'Keefe: WHICH GOOD REASONS??
It is still there in the Haskell 2010 report.
The UHC user manual at http://www.cs.uu.nl/groups/ST/Projects/ehc/ehc-user-doc.pdf lists differences between UHC and both Haskell 98 and Haskell 2010, but is completely silent about any change to the interface of class Num, and in fact compiling a test program that does 'instance Num Foo' where Foo is *not* an instance of Eq or Show gives me this response:
[1/1] Compiling Haskell mynum (mynum.hs) EH analyses: Type checking mynum.hs:3-11: Predicates remain unproven: preds: UHC.Base.Eq mynum.Foo:
This is with ehc-1.1.3, Revision 2422:2426M, the latest binary release, downloaded and installed today. The release date was the 31st of January this year.
GHC 7.0.3 doesn't like it either. I know ghc 7.4.1 is out, but I use the Haskell Platform, and the currently shipping version says plainly at http://hackage.haskell.org/platform/contents.html that it provides GHC 7.0.4.
You may have no intention of discussing the issue, but it seems to *me* that "this will not work in 2012 Haskell compiler mostly conforming to Haskell 2010 because Haskell 2010 says it shouldn't work" is a pretty sound position to take.
_______________________________________________ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe
-- Push the envelope. Watch it bend.

Richard O'Keefe :
You may have no intention of discussing the issue, but it seems to*me* that "this will not work in 2012 Haskell compiler mostly conforming to Haskell 2010 because Haskell 2010 says it shouldn't work" is a pretty sound position to take. The existence of standards is not an answer concerning their "goodness". The numerical properties of objects are orthogonal to their "external representation", and often to the possibility of asking whether they are equal.
I used Haskell to work with *abstract* vectors in Hilbert space (quantum states). Here, the linearity, the possibility to copute the representants (Dirac brackets : scalar products), etc. is essential. And they are functional objects. In a slightly more abstract than usual approach to differential geometry, the concept of vector is far from a classical data structure. It IS a linear mapping, or, say a differential operator. Again a functional object. There are approaches to stream processing, where streams are functions, and some people would like to add them independently of their instantiations as sequences of numbers. == I think that many people agree that Num was not the best idea... This class combines the addition with the multiplication, which is not explicitly natural, and it has been done probably because of the simplicity of the "vision" of the Authors : there are integer numbers, there are reals (which ask for a special class with division), and that's it. You cannot compute the exponential [using the standard name] of a power series, unless you declare this series, which may be a list of rational coefficients, a "Floating". Thank you. Jerzy Karczmarczuk

On 21/03/2012, at 2:14 AM, Jerzy Karczmarczuk wrote:
The existence of standards is not an answer concerning their "goodness".
Whoever said it was? Not me! But the existence of implementations that conform to standards *IS* an answer concerning 'will this WORK?' I do appreciate that the latest and greatest version of 'base' can do all sorts of things. However, I _don't_ know how to install that so that UHC and GHC will both use it. I'm no different from all the other Haskellers who've been frustrated by Num wanting Eq and Show, which I would have thought was an obviously bad idea from the beginning. I have my own potential uses for Eq-less Nums. But I want it to *work* and to work in more than one Haskell compiler.

On 3/19/12 12:57 PM, sdiyazg@sjtu.edu.cn wrote:
By arithmetic I mean the everyday arithmetic operations used in engineering. In signal processing for example, we write a lot of expressions like f(t)=g(t)+h(t)+g'(t) or f(t)=g(t)*h(t). I feel it would be very natural to have in haskell something like
You should take a look at Ralf Hinze's _The Lifting Lemma_: http://www.cs.ox.ac.uk/ralf.hinze/WG2.8/26/slides/ralf.pdf The fact that you can lift arithmetic to work on functions comes from the fact that for every type T, the type (T->) is a monad and therefore is an applicative functor. The output type of the function doesn't matter, except inasmuch as the arithmetic operations themselves care. This pattern has been observed repeatedly, even long before Haskell was around. But one reason it's not too common in production Haskell code is that it's all too easy to make a mistake when programming (e.g., you don't mean to be adding functions but you accidentally forget some argument), and if you're using this trick implicitly by providing a Num instance, then you can get arcane/unexpected/unhelpful error messages during type checking. But then you do get some fun line noise :) twiceTheSumOf = (+) + (+) squareTheSumOf = (+) * (+) cubeTheSumOf = (+) * (+) * (+) -- N.B., the names only make sense if all arguments -- are numeric literals. Don't look at the types. addThreeThings = (+) . (+) addFourThings = (+) . (+) . (+) addFiveThings = (+) . (+) . (+) . (+) -- Live well, ~wren

This general applicative pattern for numbers is packed up in the
applicative-numbers package [1].
In addition to Ralf's paper, there's a discussion in section 10 of
*Denotational design with type class morphisms* [2] and an application in
sections 2 & 4 of *Beautiful differentiation* [3].
[1]: http://hackage.haskell.org/package/applicative-numbers
[2]: http://conal.net/papers/type-class-morphisms/
[3]: http://conal.net/papers/beautiful-differentiation/
-- Conal
On Mon, Mar 19, 2012 at 9:58 PM, wren ng thornton
On 3/19/12 12:57 PM, sdiyazg@sjtu.edu.cn wrote:
By arithmetic I mean the everyday arithmetic operations used in engineering. In signal processing for example, we write a lot of expressions like f(t)=g(t)+h(t)+g'(t) or f(t)=g(t)*h(t). I feel it would be very natural to have in haskell something like
You should take a look at Ralf Hinze's _The Lifting Lemma_:
http://www.cs.ox.ac.uk/ralf.**hinze/WG2.8/26/slides/ralf.pdfhttp://www.cs.ox.ac.uk/ralf.hinze/WG2.8/26/slides/ralf.pdf
The fact that you can lift arithmetic to work on functions comes from the fact that for every type T, the type (T->) is a monad and therefore is an applicative functor. The output type of the function doesn't matter, except inasmuch as the arithmetic operations themselves care.
This pattern has been observed repeatedly, even long before Haskell was around. But one reason it's not too common in production Haskell code is that it's all too easy to make a mistake when programming (e.g., you don't mean to be adding functions but you accidentally forget some argument), and if you're using this trick implicitly by providing a Num instance, then you can get arcane/unexpected/unhelpful error messages during type checking.
But then you do get some fun line noise :)
twiceTheSumOf = (+) + (+) squareTheSumOf = (+) * (+) cubeTheSumOf = (+) * (+) * (+)
-- N.B., the names only make sense if all arguments -- are numeric literals. Don't look at the types. addThreeThings = (+) . (+) addFourThings = (+) . (+) . (+) addFiveThings = (+) . (+) . (+) . (+)
-- Live well, ~wren
______________________________**_________________ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/**mailman/listinfo/haskell-cafehttp://www.haskell.org/mailman/listinfo/haskell-cafe

Hi, sdiyazg@sjtu.edu.cn wrote:
I feel it would be very natural to have in haskell something like g::Float->Float --define g here h::Float->Float --define h here f::Float->Float f = g+h --instead of f t = g t+h t --Of course, f = g+h is defined as f t = g t+h t
One approach to achieve this is to define your own version of +, using the equation in the last comment of the above code snippet: (g .+. h) t = g t + h t Now you can write the following: f = g .+. h You could now implement .*., ./. and so on. (I use the dots in the operator names because the operator is applied pointwise). The implementations would look like this: (g .+. h) t = g t + h t (g .*. h) t = g t * h t (g ./. h) t = g t / h t This is a bit more low-tech than the proposals in the other answers, but might be good enough for some applications. Tillmann

Wow, there are so many people interested in this:) After reading the replies and some trail and error, now I think I need to look into Numeric Prelude first. I hadn't known of NP until reading Richard O'Keefe's reply. I will also try purely syntactic expansion with TH, but I haven't used TH seriously anyway. On a side note, if we consider typeclasses as predicates on types, then (especially with the extensions enabled) the type system looks extremely like a obfuscated logic programming language.With existential types it even starts to look like a first-order thereom prover. At present we can easily express different flavors of conjunction, but expressing disjunction is hard. And that's why the Prelude can cause problems here.

.
On a side note, if we consider typeclasses as predicates on types, then
At present we can easily express different flavors of conjunction, but expressing disjunction is hard. And that's why the Prelude can cause
(especially with the extensions enabled) the type system looks extremely like a obfuscated logic programming language.With existential types it even starts to look like a first-order thereom prover. problems here.
See http://www.cse.chalmers.se/~hallgren/Papers/wm01.html It gets even more fun with GADTs and, particularly, type families, which are explicitly designed with type level proofs in mind -- Don
participants (15)
-
Albert Y. C. Lai
-
Chris Smith
-
Conal Elliott
-
David Thomas
-
Don Stewart
-
Felipe Almeida Lessa
-
Ivan Lazar Miljenovic
-
Jerzy Karczmarczuk
-
Ozgur Akgun
-
Richard O'Keefe
-
Ryan Ingram
-
sdiyazg@sjtu.edu.cn
-
Thomas Schilling
-
Tillmann Rendel
-
wren ng thornton