Num instnace for [Double]

Hey, I am working a lot with timeseries (with instances at discrete moments) of doubles. So I use [Double]. Now I want to be able to do stuff like timeSeries3 = timeSeries1 + timeSeries2 So I was thinking, I create a newtype newtype TimeSeries a = TimeSeries [a] Now, can I somehow autoderive List, Monad, MonadPlus for TimeSeries? Also I would like to derive from Num. Most of the things can be done pointwise! What about fromInteger??? Should that just be a list with one element? Or does it simple not make sense? Thanks! Nathan

Nathan Hüsken
Hey,
I am working a lot with timeseries (with instances at discrete moments) of doubles. So I use [Double].
You may want to consider using a more efficient type than [Double] if your data is at all large. Unless you really want the laziness that lists offer you might be better off using vectors.
Now I want to be able to do stuff like
timeSeries3 = timeSeries1 + timeSeries2
So I was thinking, I create a newtype
newtype TimeSeries a = TimeSeries [a]
Now, can I somehow autoderive List, Monad, MonadPlus for TimeSeries?
As far as I'm aware, List is not a typeclass. You can conveniently derive newtype instances with GeneralizedNewtypeDeriving[1] in most cases. That being said you need to decide what sort of semantics you want your type to have. In the case of Appplicative, you have a choice between ZipList (which would make point-wise operations straightforward) and standard list (making non-determinism straightforward). Applicative is tricky in the case of vector-like types as you don't know what length you want your timeseries to be. In the list case you can simply produce a non-terminating series. One way around this (although perhaps not the best way) would be to introduce a constructor to represent a homogenous timeseries. This might look something like, import qualified Data.Vector as V import Control.Applicative data TimeSeries a = Pure a | Moments (V.Vector a) deriving (Show) instance Functor TimeSeries where fmap f (Pure a) = Pure (f a) fmap f (Moments as) = Moments (fmap f as) instance Applicative TimeSeries where pure = Pure Pure a <*> Pure b = Pure (a b) Pure a <*> Moments bs = Moments $ fmap a bs Moments as <*> Pure b = Moments $ fmap ($ b) as Moments as <*> Moments bs = Moments $ V.zipWith ($) as bs fromList :: [a] -> TimeSeries a fromList = Moments . V.fromList times :: TimeSeries Int times = fromList [1,5,9,2,5] main = do print $ (+) <$> pure 4 <*> times Of course, this presents the possibility of trying to perform a point-wise operation on differently sizes series. Zip-like functions will typically truncate their output to the shortest of their arguments, opening the possibility for silent data loss. One (hacky) way around this would be to accept a partial Applicative instance, returning bottom in the event of incompatible series. Another approach would be to parametrize the type on the length of the series with type-level naturals[3]. This still leaves open the possibility of performing actions on series of incompatible stride or offset, but at least you can be certain your series are of compatible shapes.
Also I would like to derive from Num. Most of the things can be done pointwise!
What about fromInteger??? Should that just be a list with one element? Or does it simple not make sense?
I probably wouldn't use the Num typeclass here for this reason, among others. If you give you type the right Applicative instance the operations you are after should be easily performed. Cheers, - Ben [1] http://www.haskell.org/ghc/docs/7.4.1/html/users_guide/deriving.html [2] http://hackage.haskell.org/package/linear

Hey Thanks for the answer one thing to discuss remains for me: With applicative I could add TimeSeries like this: print $ (+) <$> pure 4 <*> times (+) <$> times1 <*> times2 ok .. but actually I find that (for this case) clumpsy. I would much prefer to write times1 + times2 (especially in complex cases): (times1 + times2)/(times3 * times4) Don't you agree? Or do I oversee something? Thanks! Nathan Am 10/2/2013 6:27 PM, schrieb Ben Gamari:
Nathan Hüsken
writes: Hey,
I am working a lot with timeseries (with instances at discrete moments) of doubles. So I use [Double].
You may want to consider using a more efficient type than [Double] if your data is at all large. Unless you really want the laziness that lists offer you might be better off using vectors.
Now I want to be able to do stuff like
timeSeries3 = timeSeries1 + timeSeries2
So I was thinking, I create a newtype
newtype TimeSeries a = TimeSeries [a]
Now, can I somehow autoderive List, Monad, MonadPlus for TimeSeries?
As far as I'm aware, List is not a typeclass. You can conveniently derive newtype instances with GeneralizedNewtypeDeriving[1] in most cases. That being said you need to decide what sort of semantics you want your type to have. In the case of Appplicative, you have a choice between ZipList (which would make point-wise operations straightforward) and standard list (making non-determinism straightforward).
Applicative is tricky in the case of vector-like types as you don't know what length you want your timeseries to be. In the list case you can simply produce a non-terminating series. One way around this (although perhaps not the best way) would be to introduce a constructor to represent a homogenous timeseries. This might look something like,
import qualified Data.Vector as V import Control.Applicative
data TimeSeries a = Pure a | Moments (V.Vector a) deriving (Show)
instance Functor TimeSeries where fmap f (Pure a) = Pure (f a) fmap f (Moments as) = Moments (fmap f as)
instance Applicative TimeSeries where pure = Pure Pure a <*> Pure b = Pure (a b) Pure a <*> Moments bs = Moments $ fmap a bs Moments as <*> Pure b = Moments $ fmap ($ b) as Moments as <*> Moments bs = Moments $ V.zipWith ($) as bs
fromList :: [a] -> TimeSeries a fromList = Moments . V.fromList
times :: TimeSeries Int times = fromList [1,5,9,2,5]
main = do print $ (+) <$> pure 4 <*> times
Of course, this presents the possibility of trying to perform a point-wise operation on differently sizes series. Zip-like functions will typically truncate their output to the shortest of their arguments, opening the possibility for silent data loss. One (hacky) way around this would be to accept a partial Applicative instance, returning bottom in the event of incompatible series.
Another approach would be to parametrize the type on the length of the series with type-level naturals[3]. This still leaves open the possibility of performing actions on series of incompatible stride or offset, but at least you can be certain your series are of compatible shapes.
Also I would like to derive from Num. Most of the things can be done pointwise!
What about fromInteger??? Should that just be a list with one element? Or does it simple not make sense? I probably wouldn't use the Num typeclass here for this reason, among others. If you give you type the right Applicative instance the operations you are after should be easily performed.
Cheers,
- Ben
[1] http://www.haskell.org/ghc/docs/7.4.1/html/users_guide/deriving.html [2] http://hackage.haskell.org/package/linear

Nathan Hüsken
Hey Thanks for the answer one thing to discuss remains for me: With applicative I could add TimeSeries like this:
print $ (+) <$> pure 4 <*> times (+) <$> times1 <*> times2
ok .. but actually I find that (for this case) clumpsy. I would much prefer to write times1 + times2 (especially in complex cases):
(times1 + times2)/(times3 * times4)
Don't you agree? Or do I oversee something?
I admit that applicative notation isn't quite as convenient as working with arithmetic expressions. As I've said in the past, overloading Num isn't terribly desireable as you'll pretty much need to resign yourself to partial implementations of some of the class members. A middle path would be to instead define your own combinators for the operations you need. For instance, %+% :: Num a => TimeSeries a -> TimeSeries a -> TimeSeries a %+% a b = (+) <$> a <*> b %*% :: Num a => TimeSeries a -> TimeSeries a -> TimeSeries a %*% a b = (*) <$> a <*> b ... For at least some of these you could (ab)use the additive group classes provided by vector-space[1] and linear[2] although there's no such class for point-wise multiplication. Cheers, - Ben [1] http://hackage.haskell.org/package/vector-space-0.7.1/docs/Data-AdditiveGrou... [2] http://hackage.haskell.org/package/linear-1.3/docs/Linear-Vector.html
participants (2)
-
Ben Gamari
-
Nathan Hüsken