{-# OPTIONS_HADDOCK hide #-} {-# LANGUAGE NoImplicitPrelude #-} module Imj.Graphics.Class.DiscreteInterpolation ( DiscreteInterpolation(..) -- * Reexport , module Imj.Graphics.Class.DiscreteDistance ) where import Imj.Prelude import Data.List(length) import Imj.Graphics.Class.DiscreteDistance import Imj.Util {- | Instances should statisfy the following constraints: * An interpolation between A and B starts at A and ends at B: \( \forall (\, from, to)\, \in v, \) @ d = distance from to interpolate from to 0 == from interpolate from to d == to @ * The interpolation path is composed of strictly distinct points: @ length $ nubOrd $ map (interpolate from to) [0..pred d] == d @ * Given any points A,B belonging the path generated by an interpolation, the interpolation beween A and B will be the points of the path between A and B: \( \forall med \in [\,0,d]\,, \forall low \in [\,0,med]\,, \forall high \in [\,med,d]\,, \) @ distance from med + distance med to == 1 + distance from to medVal = interpolate from to med interpolate from to low == interpolate from medVal low interpolate from to high == interpolate medVal to $ high-med @ -} class (DiscreteDistance v) => DiscreteInterpolation v where -- | Implement this function if you want to interpolate /by value/, i.e the result of -- the interpolation between two \(v\) is a \(v\). interpolate :: v -- ^ first value -> v -- ^ last value -> Int -- ^ the current step -> v -- ^ the interpolated value interpolateSuccessive :: Successive v -> Int -> v interpolateSuccessive (Successive []) _ = error "empty successive" interpolateSuccessive (Successive [a]) _ = a interpolateSuccessive (Successive l@(a:b:_)) i | i <= 0 = a | i >= lf = interpolateSuccessive (Successive $ tail l) $ i-lf | otherwise = interpolate a b i where lf = pred $ distance a b -- | Naïve interpolation. instance DiscreteInterpolation Int where interpolate i i' progress = i + signum (i'-i) * clamp progress 0 (abs (i-i')) -- | Interpolate in parallel between 2 lists : each pair of same-index elements -- is interpolated at the same time. instance (DiscreteInterpolation a) => DiscreteInterpolation ([] a) where interpolate l l' progress = zipWith (\e e' -> interpolate e e' progress) l $ assert (length l == length l') l'