]> gitweb.michael.orlitzky.com - numerical-analysis.git/blob - src/Piecewise.hs
Add a preliminary Piecewise module.
[numerical-analysis.git] / src / Piecewise.hs
1 {-# LANGUAGE ScopedTypeVariables #-}
2
3 module Piecewise (
4 Piecewise(..),
5 evaluate,
6 evaluate',
7 from_intervals )
8 where
9
10 import qualified Algebra.Additive as Additive ( C )
11 import Control.Arrow ( first )
12 import NumericPrelude
13 import qualified Prelude as P
14
15 -- | A predicate is basically a function that returns True or
16 -- False. In this case, the predicate is used to determine which
17 -- piece of a 'Piecewise' function we want to use.
18 type Predicate a = (a -> Bool)
19
20
21 -- | One piece of a piecewise function. The predicate determines
22 -- whether or not the point lies within this piece, and the second
23 -- component (a function) is what we'll evaluate if it does.
24 type Piece a = (Predicate a, (a -> a))
25
26 -- | A representation of piecewise functions of one variable. A first
27 -- approach might use a list of intervals paired with the function's
28 -- value on those intervals. Rather than limit ourselves to a list
29 -- of intervals, we allow the use of any predicate. The simple
30 -- intervals case can be implemented with the predicate, \"is x
31 -- between x1 and x2?\".
32 data Piecewise a =
33 Piecewise { pieces :: [Piece a] }
34
35
36 -- | Evaluate a piecewise function at a point. If the point is within
37 -- the domain of the function, the function is evaluated at the
38 -- point and the result is returned wrapped in a 'Just'. If the
39 -- point is outside of the domain, 'Nothing' is returned.
40 evaluate :: Piecewise a -> a -> Maybe a
41 evaluate (Piecewise pieces) x =
42 foldl f Nothing pieces
43 where
44 f (Just y) _ = Just y
45 f Nothing (p,g) = if p x then Just (g x) else Nothing
46
47
48 -- | Evaluate a piecewise function at a point. If the point is within
49 -- the domain of the function, the function is evaluated at the
50 -- point and the result is returned. If the point is outside of the
51 -- domain, zero is returned.
52 evaluate' :: (Additive.C a) => Piecewise a -> a -> a
53 evaluate' pw x =
54 case evaluate pw x of
55 Nothing -> zero
56 Just result -> result
57
58
59 -- | Construct a piecewise function from a list of intervals paired
60 -- with functions. This is a convenience function that automatically
61 -- converts intervals to \"contained in\" predicates.
62 --
63 -- Examples:
64 --
65 -- >>> let p1 = ((-1,0), \x -> -x) :: ((Double,Double), Double->Double)
66 -- >>> let p2 = ((0,1), \x -> x) :: ((Double,Double), Double->Double)
67 -- >>> let ivs = [p1, p2]
68 -- >>> let pw = from_intervals ivs
69 -- >>> evaluate' pw (-0.5)
70 -- 0.5
71 -- >>> evaluate' pw 0.5
72 -- 0.5
73 --
74 from_intervals :: forall a. (Ord a) => [((a,a), (a -> a))] -> Piecewise a
75 from_intervals =
76 Piecewise . map (first f)
77 where
78 f :: (a,a) -> Predicate a
79 f (x1,x2) x = x1 <= x && x <= x2