nurbs-0.1.1.0: NURBS

Safe HaskellNone
LanguageHaskell2010

Linear.NURBS.Types

Synopsis

Documentation

data Weight f a Source

Point with weight

Constructors

Weight 

Fields

_weightPoint :: f a
 
_weightValue :: a
 

Instances

Functor f => Functor (Weight f) Source 
Foldable f => Foldable (Weight f) Source 
Traversable f => Traversable (Weight f) Source 
Affine f => Affine (Weight f) Source 
Metric f => Metric (Weight f) Source 
Additive f => Additive (Weight f) Source 
(Eq a, Eq (f a)) => Eq (Weight f a) Source 
(Ord a, Ord (f a)) => Ord (Weight f a) Source 
(Read a, Read (f a)) => Read (Weight f a) Source 
(Show a, Show (f a)) => Show (Weight f a) Source 
(Metric f, Ord a, Floating a, SimEq a) => SimEq (Weight f a) Source 
type Diff (Weight f) = Weight (Diff f) Source 

weightPoint :: forall f a f. Lens (Weight f a) (Weight f a) (f a) (f a) Source

weightValue :: forall f a. Lens' (Weight f a) a Source

ofWeight :: Additive f => f a -> a -> Weight f a Source

Make point with weight

weight :: (Additive f, Fractional a) => Lens' (Weight f a) a Source

Weight lens

wpoint :: (Additive f, Additive g, Fractional a) => Lens (Weight f a) (Weight g a) (f a) (g a) Source

Point lens

data Span a Source

Knot span

Constructors

Span 

Fields

_spanStart :: a
 
_spanEnd :: a
 

spanStart :: forall a. Lens' (Span a) a Source

spanEnd :: forall a. Lens' (Span a) a Source

data KnotData a Source

Knot evaluation data, used to compute basis functions

Constructors

KnotData 

Fields

_knotDataAt :: a
 
_knotDataSpan :: Span a
 
_knotData :: [(Span a, a)]
 

Instances

Eq a => Eq (KnotData a) Source 
Ord a => Ord (KnotData a) Source 
Read a => Read (KnotData a) Source 
Show a => Show (KnotData a) Source 

knotData :: forall a. Lens' (KnotData a) [(Span a, a)] Source

knotDataAt :: forall a. Lens' (KnotData a) a Source

knotDataSpan :: forall a. Lens' (KnotData a) (Span a) Source

data NURBS f a Source

NURBS

Constructors

NURBS 

Fields

_nurbsPoints :: [Weight f a]
 
_nurbsKnot :: [a]
 
_nurbsDegree :: Int
 

Instances

Functor f => Functor (NURBS f) Source 
Foldable f => Foldable (NURBS f) Source 
(Eq a, Eq (f a)) => Eq (NURBS f a) Source 
(Ord a, Ord (f a)) => Ord (NURBS f a) Source 
(Read a, Read (f a)) => Read (NURBS f a) Source 
(Show a, Show (f a)) => Show (NURBS f a) Source 
(Metric f, Ord a, Floating a, SimEq (f a)) => SimEq (NURBS f a) Source 

nurbsPoints :: forall f a f. Lens (NURBS f a) (NURBS f a) [Weight f a] [Weight f a] Source

nurbsKnot :: forall f a. Lens' (NURBS f a) [a] Source

nurbsDegree :: forall f a. Lens' (NURBS f a) Int Source