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
deriveonPnt; deriveonVelreturnsPnt;deriveonAccreturnsVel.
I don't like:
- the way how
Additiveinstance forD r v uis 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
Additiveinstance forD r v uto avoid using common code withfromD? - Am I wrong about naturality which I meantioned above; is it ok to use wrappers like
Timelike I did inderivefunction?
Any suggestions are appreciated.