
I was talking to a few people about this on #haskell, and it was suggested I ask here. I should say that I'm playing around here; don't mistake this for an urgent request or a serious problem. Suppose I wanted to implement automatic differentiation of simple functions on real numbers; then I'd take the operations from Num, Fractional, and Floating, and define how to perform them on pairs of values and their differentials, and then I'd write a differentiate function... but finding an appropriate type for that function seems to be a challenge. We have: 1. Differentiating a function of the most general type (Num a => a -> a) should produce a result of type (Num a => a -> a). 2. Differentiating a function of the more specific type (Fractional a => a -> a) should produce a result of that type (Fractional a => a -> a). 3. Differentiating a function of the most specific type (Floating a => a -> a) should produce a result of type (Floating a => a -> a). 4. BUT, differentiating a function which is of a more specific type than (Floating a => a -> a) is not, in general, possible. So differentiate should have type A a => (forall b. A b => b -> b) -> a -> a, but ONLY if the type class A is a superclass of Floating. Two partial solutions are: I can just define the differentiate function for Floating; but that means if I differentiate (\x -> x + 1), the result is a function only on floating point numbers, which is less than desirable. Or, I can define several functions: say, diffNum, diffFractional, and diffFloating... all of which have precisely the same implementation, but different types and require copy/paste to make them work. Any thoughts? For reference, here's the code I kludged together. (Again, I'm only playing around... so I wrote this very quickly and may have gotten some things wrong; don't use my code without checking it first! In particular, I know that this code produces derivative functions whose domain is too large.)
data AD a = AD a a deriving Eq
instance Show a => Show (AD a) where show (AD x e) = show x ++ " + " ++ show e ++ " eps"
instance Num a => Num (AD a) where (AD x e) + (AD y f) = AD (x + y) (e + f) (AD x e) - (AD y f) = AD (x - y) (e - f) (AD x e) * (AD y f) = AD (x * y) (e * y + x * f) negate (AD x e) = AD (negate x) (negate e) abs (AD 0 _) = error "not differentiable: |0|" abs (AD x e) = AD (abs x) (e * signum x) signum (AD 0 e) = error "not differentiable: signum(0)" signum (AD x e) = AD (signum x) 0 fromInteger i = AD (fromInteger i) 0
instance Fractional a => Fractional (AD a) where (AD x e) / (AD y f) = AD (x / y) ((e * y - x * f) / (y * y)) recip (AD x e) = AD (1 / x) ((-e) / (x * x)) fromRational x = AD (fromRational x) 0
instance Floating a => Floating (AD a) where pi = AD pi 0 exp (AD x e) = AD (exp x) (e * exp x) sqrt (AD x e) = AD (sqrt x) (e / (2 * sqrt x)) log (AD x e) = AD (log x) (e / x) (AD x e) ** (AD y f) = AD (x ** y) (e * y * (x ** (y-1)) + f * (x ** y) * log x) sin (AD x e) = AD (sin x) (e * cos x) cos (AD x e) = AD (cos x) (-e * sin x) asin (AD x e) = AD (asin x) (e / sqrt (1 - x ** 2)) acos (AD x e) = AD (acos x) (-e / sqrt (1 - x ** 2)) atan (AD x e) = AD (atan x) (e / (1 + x ** 2)) sinh (AD x e) = AD (sinh x) (e * cosh x) cosh (AD x e) = AD (cosh x) (e * sinh x) asinh (AD x e) = AD (asinh x) (e / sqrt (x^2 + 1)) acosh (AD x e) = AD (acosh x) (e / sqrt (x^2 - 1)) atanh (AD x e) = AD (atanh x) (e / (1 - x^2))
diffNum :: Num b => (forall a. Num a => a -> a) -> b -> b diffFractional :: Fractional b => (forall a. Fractional a => a -> a) -> b -> b diffFloating :: Floating b => (forall a. Floating a => a -> a) -> b -> b
diffNum f x = let AD y dy = f (AD x 1) in dy diffFractional f x = let AD y dy = f (AD x 1) in dy diffFloating f x = let AD y dy = f (AD x 1) in dy
-- Chris Smith

I'll repeat, just for the heck of it, that what I want is a type something like: diff :: forall A a. (A :> Floating, A a) => (forall b. A b => b -> b) -> b -> b where A is quantified over all type classes, and :> denotes "is a superclass of". The syntax is made up, of course, and entirely unworkable since (:>) is a user-definable contructor name... but that's the intuition anyway. -- Chris Smith

On Nov 29, 2007 4:02 AM, Chris Smith
I was talking to a few people about this on #haskell, and it was suggested I ask here. I should say that I'm playing around here; don't mistake this for an urgent request or a serious problem.
Suppose I wanted to implement automatic differentiation of simple functions on real numbers; then I'd take the operations from Num, Fractional, and Floating, and define how to perform them on pairs of values and their differentials, and then I'd write a differentiate function... but finding an appropriate type for that function seems to be a challenge.
We have:
1. Differentiating a function of the most general type (Num a => a -> a) should produce a result of type (Num a => a -> a).
I don't see why this should be true. Int -> Int is an instance of this type, but derivatives require limits, which integers don't have. Do you intend to output the difference sequence of the function in this case? But then Double -> Double is also an instance of this type. Do you intend to approximate the real derivative when it's specialized to this? Instead of worrying about the types, first tell us what semantics you want. Luke

On Nov 29, 2007 4:31 AM, Luke Palmer
On Nov 29, 2007 4:02 AM, Chris Smith
wrote: I was talking to a few people about this on #haskell, and it was suggested I ask here. I should say that I'm playing around here; don't mistake this for an urgent request or a serious problem.
Suppose I wanted to implement automatic differentiation of simple functions on real numbers; then I'd take the operations from Num, Fractional, and Floating, and define how to perform them on pairs of values and their differentials, and then I'd write a differentiate function... but finding an appropriate type for that function seems to be a challenge.
Oh, I think I totally missed the point. I missed the word "simple". I think the problem is that a function of type Num a => a -> a can be any function whatsoever, it does not have to be a simple combination of operators (it could, for example, use show, do a string transformation, and then read the result). So while you can do your AD type, I think a function which differentiates (Num a => a -> a) is not possible using this approach. You must resort to numerical methods... Luke
We have:
1. Differentiating a function of the most general type (Num a => a -> a) should produce a result of type (Num a => a -> a).
I don't see why this should be true. Int -> Int is an instance of this type, but derivatives require limits, which integers don't have. Do you intend to output the difference sequence of the function in this case?
But then Double -> Double is also an instance of this type. Do you intend to approximate the real derivative when it's specialized to this?
Instead of worrying about the types, first tell us what semantics you want.
Luke

The question I asked is about how to type the differentiation function. Whether the function is correct is a different question, which I'm happy to talk about; but understand that it's just an example I was playing with. Luke Palmer wrote:
Oh, I think I totally missed the point. I missed the word "simple".
No, I don't think you did miss the point in terms of what the code is doing. I said simple because I'm not thinking about vector-valued or multidimensional functions, partial derivatives, gradients, etc. This is on functions from numbers to numbers, where "numbers" are defined by the three type classes Num, Fractional, and Floating. I (probably incorrectly) used "simple" to say so.
I think the problem is that a function of type Num a => a -> a can be any function whatsoever, it does not have to be a simple combination of operators (it could, for example, use show, do a string transformation, and then read the result).
Well, no you couldn't read the result directly, since Num is a subclass of only Eq and Show. You could read as an integer and then use fromInteger to do so, but that the code I wrote would treat the result as a constant, so the derivative would always be reported as zero. I realize this is strictly an incorrect implementation of fromInteger (and fromRational in the Fractional class), but at the same time, there is no correct implementation. For functions that refrain from using fromInteger or fromRational except on constants, and modulo any coding errors (as I said, I didn't implement this cautiously), this should give you the correct derivative for any function when the derivative exists. What it doesn't do is evaluate properly to bottom/NaN when the derivative fails to exist. Part of that is my lazy lack of interest in writing the code correctly. For example, log (-1) is NaN, but my code will give you (-1) as the derivative, suggesting (incorrectly, of course) that log is undefined but still differentiable at that point. But another part of it is endemic; for example, f x = if signum x == (-1) then (-x) else x redefines the absolute value function, which is not differentiable at 0, but this implementation will claim f'(0) = 1, and there's no obvious way to avoid it without changing a lot. -- Chris Smith

Luke Palmer wrote:
I don't see why this should be true. Int -> Int is an instance of this type, but derivatives require limits, which integers don't have. Do you intend to output the difference sequence of the function in this case?
But then Double -> Double is also an instance of this type. Do you intend to approximate the real derivative when it's specialized to this?
Instead of worrying about the types, first tell us what semantics you want.
I intend to naively treat each function as being from the reals to the reals, and then take advantage of the fact (which is proven by the type system in the code I posted) that when the derivative is evaluated at integer inputs for functions defined using only ring operations, the result is an integer (and similarly for rationals and field operations). Note that the functions here are defined over real numbers rather than *merely* intervals, because the type given for diffNum, for example, requires that the first parameter be no more specific than Num a => a -> a... so one may not actually pass in a function of type Int -> Int and expect the code to compile. -- Chris Smith

On Nov 28, 2007 9:20 PM, Chris Smith
I intend to naively treat each function as being from the reals to the reals, and then take advantage of the fact (which is proven by the type system in the code I posted) that when the derivative is evaluated at integer inputs for functions defined using only ring operations, the result is an integer (and similarly for rationals and field operations).
I must be missing the point of something. What's wrong with
diff f x = let AD y dy = f (AD x 1) in dy
? In ghci we get *Main> :t diff (\x -> 2*x) (2::Int) diff (\x -> 2*x) (2::Int) :: Int *Main> :t diff (\x -> 2*x) (2::Float) diff (\x -> 2*x) (2::Float) :: Float I've used almost exactly that line of code myself a few times. -- Dan

Dan Piponi wrote:
I must be missing the point of something. What's wrong with
diff f x = let AD y dy = f (AD x 1) in dy
?
In ghci we get
*Main> :t diff (\x -> 2*x) (2::Int) diff (\x -> 2*x) (2::Int) :: Int *Main> :t diff (\x -> 2*x) (2::Float) diff (\x -> 2*x) (2::Float) :: Float
I've used almost exactly that line of code myself a few times.
Yep, that does what I want. Thank you (and Stefan, and ghci's :t) for pointing it out. If this were a practical thing, I'd certainly decide that's the best option and move on. But since this is me trying to figure out the Right Answer (tm), that still doesn't look like it. (Though I suspect if there were a Right Answer, it would have been pointed out by now.)
From my perspective, what's wrong with it what Stefan mentioned when he suggested it: it breaks abstraction. Even if I don't expose the type AD (i.e., it's an implementation detail and the user of a library shouldn't care that it even exists), the inferred type signature for diff depends on it.
Prelude AD> :t diff diff :: forall a t. (Num a) => (AD.AD a -> AD.AD t) -> a -> t But what's AD? If it's exported, then at least it will show up in Haddock with a list of its instances, so the type is merely misleading. but if it's not exported, then the type is just plain not useful. So I want the parameter to be more restricted. No one is going to write a function that *only* works on AD types. Instead, the parameter to diff ought to be required to be polymorphic. The rank n type does that, but it loses the ability to get the most general possible result type. -- Chris Smith

Chris,
So I want the parameter to be more restricted. No one is going to write a function that *only* works on AD types.
But exporting AD doesn't force people to write functions that work on AD types, people can write whatever functions they like. They're only constrained if they want to pass the function into 'diff', at which point it needs to work on AD. When you specify that a function has type a -> b, you're entering into a bargain. You're saying that whatever object of type a you pass in, you'll get a type b object back. "a -> b" is a statement of that contract. Now your automatic differentiation code can't differentiate any old function. It can only differentiate functions built out of the finite set of primitives you've implemented (and other "polymorphic enough" functions). So you have quite a complex contract to write. You want to say "for any function you give me that is built out of these functions (and other ...), and no others, I can give you back the derivative". You need to say this somewhere otherwise it's like a contract for a house purchase that doesn't bother to say where the boundary line to the next house is (*). Luckily, there's a nice way to express this. We can just say diff :: (AD a -> AD a) -> a -> a. So AD needs to be exported. It's an essential part of the language for expressing your bargain, and I think it *is* the Right Answer, and an elegant and compact way to express a difficult contract. -- Dan (*) I admit that I have bought a house like this, but it's not a good thing.

Hi Dan, thanks for answering. Dan Piponi wrote:
When you specify that a function has type a -> b, you're entering into a bargain. You're saying that whatever object of type a you pass in, you'll get a type b object back. "a -> b" is a statement of that contract.
Sure, that much makes perfect sense, and we agree on it.
Now your automatic differentiation code can't differentiate any old function. It can only differentiate functions built out of the finite set of primitives you've implemented (and other "polymorphic enough" functions).
Sure. To be more specific, here's the contract I would really like. 1. You need to pass in a polymorphic function a -> a, where a is, at *most*, restricted to being an instance of Floating. This part I can already express via rank-N types. For example, the diffFloating function in my original post enforces this part of the contract. 2. I can give you back the derivative, of any type b -> b, so long as b is an instance of Num, and b can be generalized to the type a from condition 1. It's that last part that I can't seem to express, without introducing this meaningless type called AD. There need be no type called AD involved in this contract at all. Indeed, the only role that AD plays in this whole exercise is to be an artifact of the implementation I've chosen. I could change my implementation; I could use Jerzy's implementation with a lazy infinite list of nth-order derivatives... or perhaps I could implement all the operations of Floating and its superclasses as data constructors, get back an expression tree, and launch Mathematica via unsafePerformIO to calculate its derivative symbolically, and then return a function that interprets the result. And who knows what other implementations I can come up with? In other words, the type AD is not actually related to the task at hand. [...]
Luckily, there's a nice way to express this. We can just say diff :: (AD a -> AD a) -> a -> a. So AD needs to be exported. It's an essential part of the language for expressing your bargain, and I think it *is* the Right Answer, and an elegant and compact way to express a difficult contract.
Really? If you really mean you think it's the right answer, then I'll have to back up and try to understand how. It seems pretty clear to me that it breaks abstraction in a way that is really rather dangerous. If you mean you think it's good enough, then yes, I pretty much have conluded it's at least the best that's going to happen; I'm just not entirely comfortable with it. -- Chris Smith

Chris,
I could change my implementation; I could use Jerzy's implementation...launch Mathematica...
But all of these could be implemented by introducing a different type constructor called AD for each one. You could switch the implementation of AD on the user and they wouldn't have to change a line of their code. I've no doubt there's a real problem you're trying to solve, but I'm trying to figure out what it is. Can you post an example piece of code that would break if you exposed AD, and which means you need to hide it? (I fully understand the idea of abstracting over the algorithm, I'm just trying to pin down exactly why you need the abstraction, and what breaks if you don't have it.) -- Dan

I must be missing something, because to me the contract seems to be much simpler to express (than the Functor + Isomorphism route you seem to me to be heading towards): diff :: (Eq x, Dense x, Subtractible x, Subtractible y, Divisible y x yOverX) => (x -> y) -> x -> yOverX class Dense a where addEpsilon :: a -> a class Subtractible a where takeAway :: a -> a -> a class Divisible a b c | a b -> c where divide :: a -> b -> c Then diff is just: diff f a = if dx == dx' then error "Zero denom" else dydx where a' = addEpsilon a dx = a' `takeAway` a dx' = a `takeAway` a' dy = f a' `takeAway` f a dydx = dy `divide` dx With the instances: instance Dense Double where addEpsilon x = x * 1.0000001 + 1.0e-10 instance Dense Int where addEpsilon x = x + 1 instance Subtractible Double where takeAway x y = x - y instance Subtractible Int where takeAway x y = x - y instance Divisible Double Double Double where divide x y = x / y instance Divisible Int Int Int where divide x y = x `div` y and throwing in {-# OPTIONS_GHC -fglasgow-exts #-}, I get: *Diff> diff sin (0.0::Double) 1.0 *Diff> diff (\x -> x*7+5) (4::Int) 7 Dan Weston Chris Smith wrote:
Hi Dan, thanks for answering.
Dan Piponi wrote:
When you specify that a function has type a -> b, you're entering into a bargain. You're saying that whatever object of type a you pass in, you'll get a type b object back. "a -> b" is a statement of that contract.
Sure, that much makes perfect sense, and we agree on it.
Now your automatic differentiation code can't differentiate any old function. It can only differentiate functions built out of the finite set of primitives you've implemented (and other "polymorphic enough" functions).
Sure. To be more specific, here's the contract I would really like.
1. You need to pass in a polymorphic function a -> a, where a is, at *most*, restricted to being an instance of Floating. This part I can already express via rank-N types. For example, the diffFloating function in my original post enforces this part of the contract.
2. I can give you back the derivative, of any type b -> b, so long as b is an instance of Num, and b can be generalized to the type a from condition 1. It's that last part that I can't seem to express, without introducing this meaningless type called AD.
There need be no type called AD involved in this contract at all. Indeed, the only role that AD plays in this whole exercise is to be an artifact of the implementation I've chosen. I could change my implementation; I could use Jerzy's implementation with a lazy infinite list of nth-order derivatives... or perhaps I could implement all the operations of Floating and its superclasses as data constructors, get back an expression tree, and launch Mathematica via unsafePerformIO to calculate its derivative symbolically, and then return a function that interprets the result. And who knows what other implementations I can come up with? In other words, the type AD is not actually related to the task at hand.
[...]
Luckily, there's a nice way to express this. We can just say diff :: (AD a -> AD a) -> a -> a. So AD needs to be exported. It's an essential part of the language for expressing your bargain, and I think it *is* the Right Answer, and an elegant and compact way to express a difficult contract.
Really? If you really mean you think it's the right answer, then I'll have to back up and try to understand how. It seems pretty clear to me that it breaks abstraction in a way that is really rather dangerous.
If you mean you think it's good enough, then yes, I pretty much have conluded it's at least the best that's going to happen; I'm just not entirely comfortable with it.

On Thu, Nov 29, 2007 at 04:25:43PM -0800, Dan Weston wrote:
I must be missing something, because to me the contract seems to be much simpler to express (than the Functor + Isomorphism route you seem to me to be heading towards): ... diff f a = if dx == dx' then error "Zero denom" else dydx where a' = addEpsilon a dx = a' `takeAway` a dx' = a `takeAway` a' dy = f a' `takeAway` f a dydx = dy `divide` dx
But this is just a finite-difference derivative, which is generally accurate to... well, a lot less than an analytic derivative. e.g try computing diff cos 1e-30 you'll get a garbage answer, while AD or symbolic differentiation will give you the correct answer, 1e-30. So for derivatives you actually intend to use, it's much better to use AD or symbolic differentiation, or just compute the derivatives by hand. Anything but finite difference (except at a carefully examined check for better derivatives). -- David Roundy Department of Physics Oregon State University

On 30 Nov 2007, cdsmith@twu.net wrote:
Sure. To be more specific, here's the contract I would really like.
1. You need to pass in a polymorphic function a -> a, where a is, at *most*, restricted to being an instance of Floating. This part I can already express via rank-N types. For example, the diffFloating function in my original post enforces this part of the contract.
It seems to me that you need the type system to ensure that the function is differentiable. For this, you have to export the type (though not the constructor as long as you don't want users to be able to extend it). Am I missing something? Jed

On Wed, Nov 28, 2007 at 09:02:20PM -0700, Chris Smith wrote:
I was talking to a few people about this on #haskell, and it was suggested I ask here. I should say that I'm playing around here; don't mistake this for an urgent request or a serious problem.
Suppose I wanted to implement automatic differentiation of simple functions on real numbers; then I'd take the operations from Num, Fractional, and Floating, and define how to perform them on pairs of values and their differentials, and then I'd write a differentiate function... but finding an appropriate type for that function seems to be a challenge.
We have:
1. Differentiating a function of the most general type (Num a => a -> a) should produce a result of type (Num a => a -> a).
2. Differentiating a function of the more specific type (Fractional a => a -> a) should produce a result of that type (Fractional a => a -> a).
3. Differentiating a function of the most specific type (Floating a => a -> a) should produce a result of type (Floating a => a -> a).
4. BUT, differentiating a function which is of a more specific type than (Floating a => a -> a) is not, in general, possible.
So differentiate should have type A a => (forall b. A b => b -> b) -> a -> a, but ONLY if the type class A is a superclass of Floating.
Two partial solutions are: I can just define the differentiate function for Floating; but that means if I differentiate (\x -> x + 1), the result is a function only on floating point numbers, which is less than desirable. Or, I can define several functions: say, diffNum, diffFractional, and diffFloating... all of which have precisely the same implementation, but different types and require copy/paste to make them work.
Any thoughts?
You can get all the features you want if you are willing to weaken the problem in the encapsulation dimension. diffAnything :: (AD a a -> AD a a) -> a -> a diffAnything f x = case (f (AD x 1)) of AD _ d -> d Now, you can handle all of the above cases transparently, at the cost of needing to export the AD type constructor (but not the data constructor). And it's H98 to boot. Stefan

On Wed, 28 Nov 2007, Chris Smith wrote:
data AD a = AD a a deriving Eq
instance Show a => Show (AD a) where show (AD x e) = show x ++ " + " ++ show e ++ " eps"
instance Num a => Num (AD a) where (AD x e) + (AD y f) = AD (x + y) (e + f) (AD x e) - (AD y f) = AD (x - y) (e - f) (AD x e) * (AD y f) = AD (x * y) (e * y + x * f) negate (AD x e) = AD (negate x) (negate e) abs (AD 0 _) = error "not differentiable: |0|" abs (AD x e) = AD (abs x) (e * signum x) signum (AD 0 e) = error "not differentiable: signum(0)" signum (AD x e) = AD (signum x) 0 fromInteger i = AD (fromInteger i) 0
instance Fractional a => Fractional (AD a) where (AD x e) / (AD y f) = AD (x / y) ((e * y - x * f) / (y * y)) recip (AD x e) = AD (1 / x) ((-e) / (x * x)) fromRational x = AD (fromRational x) 0
instance Floating a => Floating (AD a) where pi = AD pi 0 exp (AD x e) = AD (exp x) (e * exp x) sqrt (AD x e) = AD (sqrt x) (e / (2 * sqrt x)) log (AD x e) = AD (log x) (e / x) (AD x e) ** (AD y f) = AD (x ** y) (e * y * (x ** (y-1)) + f * (x ** y) * log x) sin (AD x e) = AD (sin x) (e * cos x) cos (AD x e) = AD (cos x) (-e * sin x) asin (AD x e) = AD (asin x) (e / sqrt (1 - x ** 2)) acos (AD x e) = AD (acos x) (-e / sqrt (1 - x ** 2)) atan (AD x e) = AD (atan x) (e / (1 + x ** 2)) sinh (AD x e) = AD (sinh x) (e * cosh x) cosh (AD x e) = AD (cosh x) (e * sinh x) asinh (AD x e) = AD (asinh x) (e / sqrt (x^2 + 1)) acosh (AD x e) = AD (acosh x) (e / sqrt (x^2 - 1)) atanh (AD x e) = AD (atanh x) (e / (1 - x^2))
diffNum :: Num b => (forall a. Num a => a -> a) -> b -> b diffFractional :: Fractional b => (forall a. Fractional a => a -> a) -> b -> b diffFloating :: Floating b => (forall a. Floating a => a -> a) -> b -> b
diffNum f x = let AD y dy = f (AD x 1) in dy diffFractional f x = let AD y dy = f (AD x 1) in dy diffFloating f x = let AD y dy = f (AD x 1) in dy
Why do the functions have different number types after differentiation? I thought, that just 'diff' diff :: (AD a -> AD a) -> (a -> a) diff f x = let AD y dy = f (AD x 1) in dy must work. What you do, looks like numbers with errors, but I suspect you are right that 'automatic differentiation' is the term used for those kinds of computations.

On Thu, 29 Nov 2007, Henning Thielemann wrote:
On Wed, 28 Nov 2007, Chris Smith wrote:
diffNum :: Num b => (forall a. Num a => a -> a) -> b -> b diffFractional :: Fractional b => (forall a. Fractional a => a -> a) -> b -> b diffFloating :: Floating b => (forall a. Floating a => a -> a) -> b -> b
diffNum f x = let AD y dy = f (AD x 1) in dy diffFractional f x = let AD y dy = f (AD x 1) in dy diffFloating f x = let AD y dy = f (AD x 1) in dy
Why do the functions have different number types after differentiation? I thought, that just 'diff'
diff :: (AD a -> AD a) -> (a -> a) diff f x = let AD y dy = f (AD x 1) in dy
must work. What you do, looks like numbers with errors, but I suspect you are right that 'automatic differentiation' is the term used for those kinds of computations.
I like to add that I have written some code for working with Taylor expansions of functions, that is, with all derivatives of a function. You can get the derivatives of composed functions by composing the Taylor series of the elementary functions: http://darcs.haskell.org/htam/src/PowerSeries/Taylor.hs E.g. *PowerSeries.Taylor> take 10 $ exp `compose` sin (pi/2) :: [Double] [2.718281828459045,1.664412599305428e-16,-1.3591409142295225,-1.109608399536952e-16,0.45304697140984085,4.299732548205689e-17,-0.11703713428087555,-1.2516118554300737e-17,2.5551309845882386e-2,3.0070240853853573e-18] Computes the (truncated) Taylor series for (exp . sin) at pi/2.
participants (8)
-
Chris Smith
-
Dan Piponi
-
Dan Weston
-
David Roundy
-
Henning Thielemann
-
Jed Brown
-
Luke Palmer
-
Stefan O'Rear