{-# LANGUAGE DeriveAnyClass #-}
{-# LANGUAGE DeriveGeneric #-}
{-# LANGUAGE FlexibleContexts #-}
{-# LANGUAGE StandaloneDeriving #-}
{-# LANGUAGE TypeFamilies #-}
{-# LANGUAGE TypeOperators #-}
{-# LANGUAGE UndecidableInstances #-}
module Numeric.Function.Piecewise
(
Piecewise
, zero
, fromInterval
, fromAscPieces
, toAscPieces
, intervals
, mapPieces
, mergeBy
, trim
, evaluate
, translateWith
, zipPointwise
) where
import Control.DeepSeq
( NFData
)
import GHC.Generics
( Generic
)
import qualified Data.Function.Class as Fun
data Piece a o = Piece
{ forall a o. Piece a o -> a
basepoint :: a
, forall a o. Piece a o -> o
object :: o
}
deriving (Piece a o -> Piece a o -> Bool
(Piece a o -> Piece a o -> Bool)
-> (Piece a o -> Piece a o -> Bool) -> Eq (Piece a o)
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
forall a o. (Eq a, Eq o) => Piece a o -> Piece a o -> Bool
$c== :: forall a o. (Eq a, Eq o) => Piece a o -> Piece a o -> Bool
== :: Piece a o -> Piece a o -> Bool
$c/= :: forall a o. (Eq a, Eq o) => Piece a o -> Piece a o -> Bool
/= :: Piece a o -> Piece a o -> Bool
Eq, Int -> Piece a o -> ShowS
[Piece a o] -> ShowS
Piece a o -> String
(Int -> Piece a o -> ShowS)
-> (Piece a o -> String)
-> ([Piece a o] -> ShowS)
-> Show (Piece a o)
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
forall a o. (Show a, Show o) => Int -> Piece a o -> ShowS
forall a o. (Show a, Show o) => [Piece a o] -> ShowS
forall a o. (Show a, Show o) => Piece a o -> String
$cshowsPrec :: forall a o. (Show a, Show o) => Int -> Piece a o -> ShowS
showsPrec :: Int -> Piece a o -> ShowS
$cshow :: forall a o. (Show a, Show o) => Piece a o -> String
show :: Piece a o -> String
$cshowList :: forall a o. (Show a, Show o) => [Piece a o] -> ShowS
showList :: [Piece a o] -> ShowS
Show, (forall x. Piece a o -> Rep (Piece a o) x)
-> (forall x. Rep (Piece a o) x -> Piece a o)
-> Generic (Piece a o)
forall x. Rep (Piece a o) x -> Piece a o
forall x. Piece a o -> Rep (Piece a o) x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
forall a o x. Rep (Piece a o) x -> Piece a o
forall a o x. Piece a o -> Rep (Piece a o) x
$cfrom :: forall a o x. Piece a o -> Rep (Piece a o) x
from :: forall x. Piece a o -> Rep (Piece a o) x
$cto :: forall a o x. Rep (Piece a o) x -> Piece a o
to :: forall x. Rep (Piece a o) x -> Piece a o
Generic, Piece a o -> ()
(Piece a o -> ()) -> NFData (Piece a o)
forall a. (a -> ()) -> NFData a
forall a o. (NFData a, NFData o) => Piece a o -> ()
$crnf :: forall a o. (NFData a, NFData o) => Piece a o -> ()
rnf :: Piece a o -> ()
NFData)
data Piecewise o
= Pieces [Piece (Fun.Domain o) o]
deriving ((forall x. Piecewise o -> Rep (Piecewise o) x)
-> (forall x. Rep (Piecewise o) x -> Piecewise o)
-> Generic (Piecewise o)
forall x. Rep (Piecewise o) x -> Piecewise o
forall x. Piecewise o -> Rep (Piecewise o) x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
forall o x. Rep (Piecewise o) x -> Piecewise o
forall o x. Piecewise o -> Rep (Piecewise o) x
$cfrom :: forall o x. Piecewise o -> Rep (Piecewise o) x
from :: forall x. Piecewise o -> Rep (Piecewise o) x
$cto :: forall o x. Rep (Piecewise o) x -> Piecewise o
to :: forall x. Rep (Piecewise o) x -> Piecewise o
Generic)
deriving instance (Show (Fun.Domain o), Show o) => Show (Piecewise o)
deriving instance (NFData (Fun.Domain o), NFData o) => NFData (Piecewise o)
zero :: Piecewise o
zero :: forall o. Piecewise o
zero = [Piece (Domain o) o] -> Piecewise o
forall o. [Piece (Domain o) o] -> Piecewise o
Pieces []
fromInterval
:: (Ord (Fun.Domain o), Num o)
=> (Fun.Domain o, Fun.Domain o) -> o -> Piecewise o
fromInterval :: forall o.
(Ord (Domain o), Num o) =>
(Domain o, Domain o) -> o -> Piecewise o
fromInterval (Domain o
x,Domain o
y) o
o = [Piece (Domain o) o] -> Piecewise o
forall o. [Piece (Domain o) o] -> Piecewise o
Pieces [Domain o -> o -> Piece (Domain o) o
forall a o. a -> o -> Piece a o
Piece Domain o
start o
o, Domain o -> o -> Piece (Domain o) o
forall a o. a -> o -> Piece a o
Piece Domain o
end o
0]
where
start :: Domain o
start = Domain o -> Domain o -> Domain o
forall a. Ord a => a -> a -> a
min Domain o
x Domain o
y
end :: Domain o
end = Domain o -> Domain o -> Domain o
forall a. Ord a => a -> a -> a
max Domain o
x Domain o
y
fromAscPieces :: Ord (Fun.Domain o) => [(Fun.Domain o, o)] -> Piecewise o
fromAscPieces :: forall o. Ord (Domain o) => [(Domain o, o)] -> Piecewise o
fromAscPieces = [Piece (Domain o) o] -> Piecewise o
forall o. [Piece (Domain o) o] -> Piecewise o
Pieces ([Piece (Domain o) o] -> Piecewise o)
-> ([(Domain o, o)] -> [Piece (Domain o) o])
-> [(Domain o, o)]
-> Piecewise o
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ((Domain o, o) -> Piece (Domain o) o)
-> [(Domain o, o)] -> [Piece (Domain o) o]
forall a b. (a -> b) -> [a] -> [b]
map ((Domain o -> o -> Piece (Domain o) o)
-> (Domain o, o) -> Piece (Domain o) o
forall a b c. (a -> b -> c) -> (a, b) -> c
uncurry Domain o -> o -> Piece (Domain o) o
forall a o. a -> o -> Piece a o
Piece)
toAscPieces :: Ord (Fun.Domain o) => Piecewise o -> [(Fun.Domain o, o)]
toAscPieces :: forall o. Ord (Domain o) => Piecewise o -> [(Domain o, o)]
toAscPieces (Pieces [Piece (Domain o) o]
xos) = [ (Domain o
x, o
o) | Piece Domain o
x o
o <- [Piece (Domain o) o]
xos ]
intervals :: Piecewise o -> [(Fun.Domain o, Fun.Domain o)]
intervals :: forall o. Piecewise o -> [(Domain o, Domain o)]
intervals (Pieces [Piece (Domain o) o]
ys) =
[Domain o] -> [Domain o] -> [(Domain o, Domain o)]
forall a b. [a] -> [b] -> [(a, b)]
zip ((Piece (Domain o) o -> Domain o)
-> [Piece (Domain o) o] -> [Domain o]
forall a b. (a -> b) -> [a] -> [b]
map Piece (Domain o) o -> Domain o
forall a o. Piece a o -> a
basepoint [Piece (Domain o) o]
ys) (Int -> [Domain o] -> [Domain o]
forall a. Int -> [a] -> [a]
drop Int
1 ([Domain o] -> [Domain o]) -> [Domain o] -> [Domain o]
forall a b. (a -> b) -> a -> b
$ (Piece (Domain o) o -> Domain o)
-> [Piece (Domain o) o] -> [Domain o]
forall a b. (a -> b) -> [a] -> [b]
map Piece (Domain o) o -> Domain o
forall a o. Piece a o -> a
basepoint [Piece (Domain o) o]
ys)
mapPieces
:: Fun.Domain o ~ Fun.Domain o'
=> (o -> o') -> Piecewise o -> Piecewise o'
mapPieces :: forall o o'.
(Domain o ~ Domain o') =>
(o -> o') -> Piecewise o -> Piecewise o'
mapPieces o -> o'
f (Pieces [Piece (Domain o) o]
ps) = [Piece (Domain o') o'] -> Piecewise o'
forall o. [Piece (Domain o) o] -> Piecewise o
Pieces [ Domain o' -> o' -> Piece (Domain o') o'
forall a o. a -> o -> Piece a o
Piece Domain o'
x (o -> o'
f o
o) | Piece Domain o'
x o
o <- [Piece (Domain o) o]
[Piece (Domain o') o]
ps ]
mergeBy :: Num o => (o -> o -> Bool) -> Piecewise o -> Piecewise o
mergeBy :: forall o. Num o => (o -> o -> Bool) -> Piecewise o -> Piecewise o
mergeBy o -> o -> Bool
eq (Pieces [Piece (Domain o) o]
pieces) = [Piece (Domain o) o] -> Piecewise o
forall o. [Piece (Domain o) o] -> Piecewise o
Pieces ([Piece (Domain o) o] -> Piecewise o)
-> [Piece (Domain o) o] -> Piecewise o
forall a b. (a -> b) -> a -> b
$ o -> [Piece (Domain o) o] -> [Piece (Domain o) o]
go o
0 [Piece (Domain o) o]
pieces
where
go :: o -> [Piece (Domain o) o] -> [Piece (Domain o) o]
go o
_ [] = []
go o
before (Piece (Domain o) o
p : [Piece (Domain o) o]
ps)
| o
before o -> o -> Bool
`eq` Piece (Domain o) o -> o
forall a o. Piece a o -> o
object Piece (Domain o) o
p = o -> [Piece (Domain o) o] -> [Piece (Domain o) o]
go o
before [Piece (Domain o) o]
ps
| Bool
otherwise = Piece (Domain o) o
p Piece (Domain o) o -> [Piece (Domain o) o] -> [Piece (Domain o) o]
forall a. a -> [a] -> [a]
: o -> [Piece (Domain o) o] -> [Piece (Domain o) o]
go (Piece (Domain o) o -> o
forall a o. Piece a o -> o
object Piece (Domain o) o
p) [Piece (Domain o) o]
ps
trim :: (Eq o, Num o) => Piecewise o -> Piecewise o
trim :: forall o. (Eq o, Num o) => Piecewise o -> Piecewise o
trim = (o -> o -> Bool) -> Piecewise o -> Piecewise o
forall o. Num o => (o -> o -> Bool) -> Piecewise o -> Piecewise o
mergeBy o -> o -> Bool
forall a. Eq a => a -> a -> Bool
(==)
instance (Fun.Function o, Num o, Ord (Fun.Domain o), Num (Fun.Codomain o))
=> Fun.Function (Piecewise o)
where
type instance Domain (Piecewise o) = Fun.Domain o
type instance Codomain (Piecewise o) = Fun.Codomain o
eval :: Piecewise o -> Domain (Piecewise o) -> Codomain (Piecewise o)
eval = Piecewise o -> Domain o -> Codomain o
Piecewise o -> Domain (Piecewise o) -> Codomain (Piecewise o)
forall o.
(Function o, Num o, Ord (Domain o), Num (Codomain o)) =>
Piecewise o -> Domain o -> Codomain o
evaluate
evaluate
:: (Fun.Function o, Num o, Ord (Fun.Domain o), Num (Fun.Codomain o))
=> Piecewise o -> Fun.Domain o -> Fun.Codomain o
evaluate :: forall o.
(Function o, Num o, Ord (Domain o), Num (Codomain o)) =>
Piecewise o -> Domain o -> Codomain o
evaluate (Pieces [Piece (Domain o) o]
pieces) Domain o
x = o -> [Piece (Domain o) o] -> Codomain o
go o
0 [Piece (Domain o) o]
pieces
where
go :: o -> [Piece (Domain o) o] -> Codomain o
go o
before [] = o -> Domain o -> Codomain o
forall f. Function f => f -> Domain f -> Codomain f
Fun.eval o
before Domain o
x
go o
before (Piece (Domain o) o
p:[Piece (Domain o) o]
ps)
| Piece (Domain o) o -> Domain o
forall a o. Piece a o -> a
basepoint Piece (Domain o) o
p Domain o -> Domain o -> Bool
forall a. Ord a => a -> a -> Bool
<= Domain o
x = o -> [Piece (Domain o) o] -> Codomain o
go (Piece (Domain o) o -> o
forall a o. Piece a o -> o
object Piece (Domain o) o
p) [Piece (Domain o) o]
ps
| Bool
otherwise = o -> Domain o -> Codomain o
forall f. Function f => f -> Domain f -> Codomain f
Fun.eval o
before Domain o
x
translateWith
:: (Ord (Fun.Domain o), Num (Fun.Domain o), Num o)
=> (Fun.Domain o -> o -> o)
-> Fun.Domain o -> Piecewise o -> Piecewise o
translateWith :: forall o.
(Ord (Domain o), Num (Domain o), Num o) =>
(Domain o -> o -> o) -> Domain o -> Piecewise o -> Piecewise o
translateWith Domain o -> o -> o
trans Domain o
y (Pieces [Piece (Domain o) o]
pieces) =
[Piece (Domain o) o] -> Piecewise o
forall o. [Piece (Domain o) o] -> Piecewise o
Pieces [ Domain o -> o -> Piece (Domain o) o
forall a o. a -> o -> Piece a o
Piece (Domain o
x Domain o -> Domain o -> Domain o
forall a. Num a => a -> a -> a
+ Domain o
y) (Domain o -> o -> o
trans Domain o
y o
o) | Piece Domain o
x o
o <- [Piece (Domain o) o]
pieces ]
zipPointwise
:: (Ord (Fun.Domain o), Num o)
=> (o -> o -> o)
-> Piecewise o -> Piecewise o -> Piecewise o
zipPointwise :: forall o.
(Ord (Domain o), Num o) =>
(o -> o -> o) -> Piecewise o -> Piecewise o -> Piecewise o
zipPointwise o -> o -> o
f (Pieces [Piece (Domain o) o]
xs') (Pieces [Piece (Domain o) o]
ys') =
[Piece (Domain o) o] -> Piecewise o
forall o. [Piece (Domain o) o] -> Piecewise o
Pieces ([Piece (Domain o) o] -> Piecewise o)
-> [Piece (Domain o) o] -> Piecewise o
forall a b. (a -> b) -> a -> b
$ o
-> [Piece (Domain o) o]
-> o
-> [Piece (Domain o) o]
-> [Piece (Domain o) o]
go o
0 [Piece (Domain o) o]
xs' o
0 [Piece (Domain o) o]
ys'
where
go :: o
-> [Piece (Domain o) o]
-> o
-> [Piece (Domain o) o]
-> [Piece (Domain o) o]
go o
_ [] o
_ [] = []
go o
_ (Piece Domain o
x o
ox : [Piece (Domain o) o]
xstail) o
yhang [] =
Domain o -> o -> Piece (Domain o) o
forall a o. a -> o -> Piece a o
Piece Domain o
x (o -> o -> o
f o
ox o
yhang) Piece (Domain o) o -> [Piece (Domain o) o] -> [Piece (Domain o) o]
forall a. a -> [a] -> [a]
: o
-> [Piece (Domain o) o]
-> o
-> [Piece (Domain o) o]
-> [Piece (Domain o) o]
go o
ox [Piece (Domain o) o]
xstail o
yhang []
go o
xhang [] o
_ (Piece Domain o
y o
oy : [Piece (Domain o) o]
ystail) =
Domain o -> o -> Piece (Domain o) o
forall a o. a -> o -> Piece a o
Piece Domain o
y (o -> o -> o
f o
xhang o
oy) Piece (Domain o) o -> [Piece (Domain o) o] -> [Piece (Domain o) o]
forall a. a -> [a] -> [a]
: o
-> [Piece (Domain o) o]
-> o
-> [Piece (Domain o) o]
-> [Piece (Domain o) o]
go o
xhang [] o
oy [Piece (Domain o) o]
ystail
go o
xhang xs :: [Piece (Domain o) o]
xs@(Piece Domain o
x o
ox : [Piece (Domain o) o]
xstail) o
yhang ys :: [Piece (Domain o) o]
ys@(Piece Domain o
y o
oy : [Piece (Domain o) o]
ystail) =
case Domain o -> Domain o -> Ordering
forall a. Ord a => a -> a -> Ordering
compare Domain o
x Domain o
y of
Ordering
LT -> Domain o -> o -> Piece (Domain o) o
forall a o. a -> o -> Piece a o
Piece Domain o
x (o -> o -> o
f o
ox o
yhang) Piece (Domain o) o -> [Piece (Domain o) o] -> [Piece (Domain o) o]
forall a. a -> [a] -> [a]
: o
-> [Piece (Domain o) o]
-> o
-> [Piece (Domain o) o]
-> [Piece (Domain o) o]
go o
ox [Piece (Domain o) o]
xstail o
yhang [Piece (Domain o) o]
ys
Ordering
EQ -> Domain o -> o -> Piece (Domain o) o
forall a o. a -> o -> Piece a o
Piece Domain o
x (o -> o -> o
f o
ox o
oy ) Piece (Domain o) o -> [Piece (Domain o) o] -> [Piece (Domain o) o]
forall a. a -> [a] -> [a]
: o
-> [Piece (Domain o) o]
-> o
-> [Piece (Domain o) o]
-> [Piece (Domain o) o]
go o
ox [Piece (Domain o) o]
xstail o
oy [Piece (Domain o) o]
ystail
Ordering
GT -> Domain o -> o -> Piece (Domain o) o
forall a o. a -> o -> Piece a o
Piece Domain o
y (o -> o -> o
f o
xhang o
oy ) Piece (Domain o) o -> [Piece (Domain o) o] -> [Piece (Domain o) o]
forall a. a -> [a] -> [a]
: o
-> [Piece (Domain o) o]
-> o
-> [Piece (Domain o) o]
-> [Piece (Domain o) o]
go o
xhang [Piece (Domain o) o]
xs o
oy [Piece (Domain o) o]
ystail
instance (Ord (Fun.Domain o), Num o) => Num (Piecewise o) where
+ :: Piecewise o -> Piecewise o -> Piecewise o
(+) = (o -> o -> o) -> Piecewise o -> Piecewise o -> Piecewise o
forall o.
(Ord (Domain o), Num o) =>
(o -> o -> o) -> Piecewise o -> Piecewise o -> Piecewise o
zipPointwise o -> o -> o
forall a. Num a => a -> a -> a
(+)
* :: Piecewise o -> Piecewise o -> Piecewise o
(*) = (o -> o -> o) -> Piecewise o -> Piecewise o -> Piecewise o
forall o.
(Ord (Domain o), Num o) =>
(o -> o -> o) -> Piecewise o -> Piecewise o -> Piecewise o
zipPointwise o -> o -> o
forall a. Num a => a -> a -> a
(*)
negate :: Piecewise o -> Piecewise o
negate = (o -> o) -> Piecewise o -> Piecewise o
forall o o'.
(Domain o ~ Domain o') =>
(o -> o') -> Piecewise o -> Piecewise o'
mapPieces o -> o
forall a. Num a => a -> a
negate
abs :: Piecewise o -> Piecewise o
abs = (o -> o) -> Piecewise o -> Piecewise o
forall o o'.
(Domain o ~ Domain o') =>
(o -> o') -> Piecewise o -> Piecewise o'
mapPieces o -> o
forall a. Num a => a -> a
abs
signum :: Piecewise o -> Piecewise o
signum = (o -> o) -> Piecewise o -> Piecewise o
forall o o'.
(Domain o ~ Domain o') =>
(o -> o') -> Piecewise o -> Piecewise o'
mapPieces o -> o
forall a. Num a => a -> a
signum
fromInteger :: Integer -> Piecewise o
fromInteger Integer
0 = Piecewise o
forall o. Piecewise o
zero
fromInteger Integer
_ = String -> Piecewise o
forall a. HasCallStack => String -> a
error String
"TODO: fromInteger not implemented"