I'm trying to implement point, velocity and acceleration types.
They should be connected by some derive
function which:
- takes time and velocity and returns a point increment;
- takes time and acceleration and returns a velocity increment.
In pseudocode, it should look like this:
derive :: Time -> Velocity -> Point
derive :: Time -> Acceleration -> Velocity
Time
is a type representing a time as floating value.
Point
, Velocity
and Acceleration
are vectors.
So I don't want to
- mix time values with any other floating values;
- mix vectors representing points with velocity vectors and etc.
I came up with following solution.
{-# LANGUAGE KindSignatures, DataKinds, TypeOperators #-}
import Control.Comonad
import GHC.TypeLits
import Linear
import Linear.V2
-- Type of real numbers.
type R = Double
-- Type of vectors.
type Vector = V2
-- Wrapper to distinguish time values from other values.
newtype Time a = Time { fromTime :: a }
-- Time is intended to be a wrapper. But to implement a derive function,
-- I need a common way to extract value from wrapper. That's why Time
-- must be a Comonad's instance:
instance Functor Time where
fmap f = Time . f . fromTime
instance Comonad Time where
extract = fromTime
duplicate = Time
{- Type of derivative.
Type (D r v u a) means a derivation of (u a) by (v a) with rank r.
-}
newtype D (r :: Nat) (v :: * -> *) (u :: * -> *) a = D { fromD :: (u a) }
-- Using type D the point, velocity and acceleration types can be defined:
type Pnt = D 0 Time Vector R
type Vel = D 1 Time Vector R
type Acc = D 2 Time Vector R
-- Even if I don't want to mix points with velocities,
-- I do want them to behave like vectors. So I want
-- them to be Additive:
instance Functor u => Functor (D r v u) where
fmap f = D . fmap f . fromD
instance Additive u => Additive (D r v u) where
-- I didn't found a way how to make this Additive instance better.
-- Applicative instance for (D r v u) doesn't help.
zero = D $ zero
x ^+^ y = D $ (fromD x) ^+^ (fromD y)
x ^-^ y = D $ (fromD x) ^-^ (fromD y)
lerp a x y = D $ lerp a (fromD x) (fromD y)
liftU2 f x y = D $ liftU2 f (fromD x) (fromD y)
liftI2 f x y = D $ liftI2 f (fromD x) (fromD y)
-- Now derive function can be implemented:
derive ::
(Comonad v, Functor u, Num a) =>
v a -> D (r + 1) v u a -> D r v u a
derive dv du = D $ (extract dv) *^ (fromD du)
This solution pretty mush does what I want:
- I can't call
derive
onPnt
; derive
onVel
returnsPnt
;derive
onAcc
returnsVel
.
I don't like:
- the way how
Additive
instance forD r v u
is implemented. - the fact that to derive a vector of real numbes I need to extract time value from a wrapper. It doesn't feel natural.
So ...
- How can I edit an
Additive
instance forD r v u
to avoid using common code withfromD
? - Am I wrong about naturality which I meantioned above; is it ok to use wrappers like
Time
like I did inderive
function?
Any suggestions are appreciated.
1 Answer 1
Use GeneralizedNewtypeDeriving
if you use the same instance as the wrapped type anyway. Together with DeriveFunctor
, we can get rid of much boilerplate (comments omitted, changes noted with -- <--
):
{-# LANGUAGE KindSignatures, DataKinds, TypeOperators #-}
{-# LANGUAGE GeneralizedNewtypeDeriving, DeriveFunctor #-} -- <--
import Control.Comonad
import GHC.TypeLits
import Linear
import Linear.V2
type R = Double
type Vector = V2
newtype Time a = Time { fromTime :: a } deriving (Functor, Num) -- <--
instance Comonad Time where
extract = fromTime
duplicate = Time
newtype D (r :: Nat) (v :: * -> *) (u :: * -> *) a = D { fromD :: (u a) }
deriving (Functor, Applicative, Additive) -- <--
type Pnt = D 0 Time Vector R
type Vel = D 1 Time Vector R
type Acc = D 2 Time Vector R
derive ::
(Comonad v, Functor u, Num a) =>
v a -> D (r + 1) v u a -> D r v u a
derive dv du = D $ (extract dv) *^ (fromD du)
This immediately gets rid of your Additive
problem. Also, now that Time
is a Num
instance, you can use derive
like this:
derive 3 (pure 3 :: Vel)
Unfortunately, Num
also contains (*)
, so you'll be able to multiply time values, which doesn't really make sense in this case. Alas, there is no other way to get fromInteger
otherwise.
However, let's have a look at the wrapper, D
and derive
. The type of derive
is a little bit too general. It allows you to do stuff like this:
ghci> import Data.Tree ghci> derive (Node 10 []) (pure 2 :: D 2 Tree Vector Double) D {fromD = V2 20.0 20.0} -- if we add Show to D's instances
Could this be a valid use case? Who knows. Is it likely to be a valid use case? Rather not. Get back to the original inspiration for derive
:
derive :: Time -> Velocity -> Point
derive :: Time -> Acceleration -> Velocity
We expect the first argument always to be some kind of time measurement. We also expect the vector to be conform to the time's unit(*). From this point of view, it makes sense to encode the Time
in D
. However, this yields the question why the other side of the spacetime, space, isn't encoded in D
too.
(*) strictly speaking, we're not encoding time's unit but only type.
Either way, you probably want to allow only Time
values. Furthermore, you want to make clear what unit Time
uses. We could use a phantom type, e.g.
{-# LANGUAGE DataKinds, KindSignatures, GeneralizedNumtypeDeriving #-}
data TimeUnit = Milliseconds | Seconds | Minutes | Hours
newtype Time (* :: TimeUnit) a = Time {fromTime :: a} deriving (Show, Num)
which makes sure that we don't mix different times:
> (Time 3 :: Time 'Seconds Double) + (Time 10 :: Time 'Minutes Double)
Couldn't match type ‘'Minutes’ with ‘'Seconds’
Expected type: Time 'Seconds Double
Actual type: Time 'Minutes Double
In the second argument of ‘(+)’, namely
‘(Time 10 :: Time Minutes Double)’
In the expression:
(Time 3 :: Time Seconds Double) + (Time 10 :: Time Minutes Double)
But that's out of scope for this review. Instead, we can simply say that Time
's unit is seconds, disallow creating Time
values with its data constructor, and provide some helper functions:
module Movement
( Time, getSeconds
, seconds, minutes
, ...
)
where
newtype Time a = Time { getSeconds :: a }
seconds :: Num a => a -> Time a
seconds = Time
minutes :: Num a => a -> Time a
minutes = seconds . (60 *)
derive :: (Functor u, Num a) => Time a -> D (r + 1) u a -> D r u a
derive (Time s) du = D $ s *^ (fromD du)
Alright. Let's reflect all changes:
- used
GeneralizedNewtypeDeriving
to get rid of boilerplate (major change) - instead of allowing general
Comonad
s, only allowTime
(*) - removed
Time
fromD
, sincederive
fixes it (*) - make the unit of time explicit with "smart" constructors and remove the
Time
data constructor from the exports.
(*) You can still use those techniques internally, but a public interface should be hard to use wrong if possible. After all, that's the reason you're using r :: Nat
and derive :: ... -> D (r + 1) ... -> D r
, right?
We end up with the following code:
{-# LANGUAGE KindSignatures, DataKinds, TypeOperators #-}
{-# LANGUAGE GeneralizedNewtypeDeriving, DeriveFunctor #-}
module Movement
( Time, getSeconds
, R, Vector,
, D(..), Pnt, Vel, Acc
, seconds, minutes
, derive
)
where
import GHC.TypeLits
import Linear
import Linear.V2
type R = Double
type Vector = V2
newtype Time a = Time { getSeconds :: a } deriving (Functor)
newtype D (r :: Nat) (u :: * -> *) a = D { fromD :: (u a) }
deriving (Functor, Applicative, Additive, Show)
type Pnt = D 0 Vector R
type Vel = D 1 Vector R
type Acc = D 2 Vector R
seconds :: Num a => a -> Time a
seconds = Time
minutes :: Num a => a -> Time a
minutes = seconds . (60 *)
derive :: (Functor u, Num a) => Time a -> D (r + 1) u a -> D r u a
derive (Time s) du = D $ s *^ (fromD du)
Am I wrong about naturality which I meantioned above; is it ok to use wrappers like Time like I did in derive function?
Using wrappers is fine. For example, the UniversalTime
in the time
package is just a wrapper around Rational
. And although it doesn't export its constructor, DiffTime
is also just a newtype
of Pico
.
Maybe it feels more natural with the helper functions:
someCalculation :: Vec
someCalculation =
let time = seconds 120
acc = D (V2 10 10) -- (*)
in derive time acc
(*) This example will probably inspire you to provide Num a => a -> a -> D r V2 a
functions.
-
\$\begingroup\$ Thanks for review! Actually, I tried to make
D
general enough to do not stick to time only. But I didn't mention that in question and I don't see how could I practically use it. I like the way how you modified time. And generalized deriving shorted code pretty well leaving only reasonable parts. \$\endgroup\$user21974– user219742016年07月08日 08:07:36 +00:00Commented Jul 8, 2016 at 8:07