Skip to content

Instantly share code, notes, and snippets.

@mchakravarty
Created July 18, 2013 03:14
Show Gist options
  • Save mchakravarty/6026456 to your computer and use it in GitHub Desktop.
Save mchakravarty/6026456 to your computer and use it in GitHub Desktop.
Arbitrary-dimensional bezier curves with statically checked consistency of dimensions. This is a variant of https://github.com/hrldcpr/Bezier.hs using type-indexed lists (aka vectors) implemented with GADTs and data kinds.
{-# LANGUAGE GADTs, DataKinds, KindSignatures, StandaloneDeriving #-}
module BezierVec (bezier) where
infixr :::
-- encoding of natural numbers (zero and successor of a natural)
data Nat = Z | S Nat
-- indexed vectors are lists whose first type argument encodes the length of the list
data Vec (n :: Nat) e where
Nil :: Vec Z e
(:::) :: e -> Vec n e -> Vec (S n) e
deriving instance Show e => Show (Vec n e)
-- zipWith that statically enforces that both arguments have the same length
zipWithVec :: (a -> b -> c) -> Vec n a -> Vec n b -> Vec n c
zipWithVec _ Nil Nil = Nil
zipWithVec f (x:::xs) (y:::ys) = f x y ::: zipWithVec f xs ys
-- point of arbitrary dimension is just a vector of coordinates:
type Point d = Vec d
-- parametric line between two points (matching dimensionality is statically checked)
line :: Num a => Point d a -> Point d a -> a -> Point d a
line p q t = zipWithVec interpolate p q
where interpolate a b = (1 - t)*a + t*b
-- bezier of just one point is fixed at that point,
-- and bezier of a list of points is just linear interpolation
-- between bezier of the initial part of the list
-- and bezier of the tail of the list:
bezier :: Num a => [Point d a] -> a -> Point d a
bezier [p] t = p
bezier ps t = line (bezier (init ps) t)
(bezier (tail ps) t)
t
Sign up for free to join this conversation on GitHub. Already have an account? Sign in to comment