implicit-0.4.0.0: A math-inspired programmatic 2D & 3D CAD system.
Safe HaskellNone
LanguageHaskell2010

Graphics.Implicit.Definitions

Synopsis

Documentation

newtype Fastℕ Source #

Constructors

Fastℕ Int 

Instances

Instances details
Enum Fastℕ Source # 
Instance details

Defined in Graphics.Implicit.FastIntUtil

Eq Fastℕ Source # 
Instance details

Defined in Graphics.Implicit.FastIntUtil

Methods

(==) :: Fastℕ -> Fastℕ -> Bool #

(/=) :: Fastℕ -> Fastℕ -> Bool #

Integral Fastℕ Source # 
Instance details

Defined in Graphics.Implicit.FastIntUtil

Num Fastℕ Source # 
Instance details

Defined in Graphics.Implicit.FastIntUtil

Ord Fastℕ Source # 
Instance details

Defined in Graphics.Implicit.FastIntUtil

Read Fastℕ Source # 
Instance details

Defined in Graphics.Implicit.FastIntUtil

Real Fastℕ Source # 
Instance details

Defined in Graphics.Implicit.FastIntUtil

Show Fastℕ Source # 
Instance details

Defined in Graphics.Implicit.FastIntUtil

fromFastℕ :: FastN n => Fastℕ -> n Source #

toFastℕ :: FastN n => n -> Fastℕ Source #

data Source #

Instances

Instances details
Enum Source # 
Instance details

Defined in Graphics.Implicit.IntegralUtil

Methods

succ :: -> #

pred :: -> #

toEnum :: Int -> #

fromEnum :: -> Int #

enumFrom :: -> [] #

enumFromThen :: -> -> [] #

enumFromTo :: -> -> [] #

enumFromThenTo :: -> -> -> [] #

Eq Source # 
Instance details

Defined in Graphics.Implicit.IntegralUtil

Methods

(==) :: -> -> Bool #

(/=) :: -> -> Bool #

Integral Source # 
Instance details

Defined in Graphics.Implicit.IntegralUtil

Methods

quot :: -> -> #

rem :: -> -> #

div :: -> -> #

mod :: -> -> #

quotRem :: -> -> (, ) #

divMod :: -> -> (, ) #

toInteger :: -> Integer #

Num Source # 
Instance details

Defined in Graphics.Implicit.IntegralUtil

Methods

(+) :: -> -> #

(-) :: -> -> #

(*) :: -> -> #

negate :: -> #

abs :: -> #

signum :: -> #

fromInteger :: Integer -> #

Ord Source # 
Instance details

Defined in Graphics.Implicit.IntegralUtil

Methods

compare :: -> -> Ordering #

(<) :: -> -> Bool #

(<=) :: -> -> Bool #

(>) :: -> -> Bool #

(>=) :: -> -> Bool #

max :: -> -> #

min :: -> -> #

Read Source # 
Instance details

Defined in Graphics.Implicit.IntegralUtil

Real Source # 
Instance details

Defined in Graphics.Implicit.IntegralUtil

Methods

toRational :: -> Rational #

Show Source # 
Instance details

Defined in Graphics.Implicit.IntegralUtil

Methods

showsPrec :: Int -> -> ShowS #

show :: -> String #

showList :: [] -> ShowS #

fromℕ :: N n => -> n Source #

toℕ :: N n => n -> Source #

type = Double Source #

A type synonym for Double. When used in the context of positions or sizes, measured in units of millimeters. When used as in the context of a rotation, measured in radians.

type ℝ2 = V2 Source #

A pair of two Doubles. When used as an area or position vector, measured in millimeters squared.

type ℝ3 = V3 Source #

A triple of Doubles. When used as a volume or position vector, measured in millimeters cubed. When used as a rotation, interpreted as Euler angles measured in radians.

minℝ :: Source #

A give up point for dividing ℝs, and for the maximum difference between abs(n) and abs(-n).

class ComponentWiseMultable a Source #

Add multiply and divide operators for two ℝ2s or ℝ3s.

Minimal complete definition

(⋯*), (⋯/)

Instances

Instances details
ComponentWiseMultable ℝ3 Source # 
Instance details

Defined in Graphics.Implicit.Definitions

Methods

(⋯*) :: ℝ3 -> ℝ3 -> ℝ3 Source #

(⋯/) :: ℝ3 -> ℝ3 -> ℝ3 Source #

ComponentWiseMultable ℝ2 Source # 
Instance details

Defined in Graphics.Implicit.Definitions

Methods

(⋯*) :: ℝ2 -> ℝ2 -> ℝ2 Source #

(⋯/) :: ℝ2 -> ℝ2 -> ℝ2 Source #

(⋯*) :: ComponentWiseMultable a => a -> a -> a Source #

(⋯/) :: ComponentWiseMultable a => a -> a -> a Source #

newtype Polyline Source #

A chain of line segments, as in SVG or DXF. eg. [(0,0), (0.5,1), (1,0)] ---> / FIXME: May not be empty. expose to type system.

Constructors

Polyline 

Fields

Instances

Instances details
NFData Polyline Source # 
Instance details

Defined in Graphics.Implicit.Definitions

Methods

rnf :: Polyline -> () #

DiscreteAproxable SymbolicObj2 [Polyline] Source # 
Instance details

Defined in Graphics.Implicit.Export.DiscreteAproxable

newtype Polytri Source #

A triangle in 2D space (a,b,c).

Constructors

Polytri (ℝ2, ℝ2, ℝ2) 

Instances

Instances details
NFData Polytri Source # 
Instance details

Defined in Graphics.Implicit.Definitions

Methods

rnf :: Polytri -> () #

newtype Triangle Source #

A triangle in 3D space (a,b,c) = a triangle with vertices a, b and c

Constructors

Triangle (ℝ3, ℝ3, ℝ3) 

Instances

Instances details
NFData Triangle Source # 
Instance details

Defined in Graphics.Implicit.Definitions

Methods

rnf :: Triangle -> () #

newtype NormedTriangle Source #

A triangle ((v1,n1),(v2,n2),(v3,n3)) has vertices v1, v2, v3 with corresponding normals n1, n2, and n3

Constructors

NormedTriangle ((ℝ3, ℝ3), (ℝ3, ℝ3), (ℝ3, ℝ3)) 

Instances

Instances details
NFData NormedTriangle Source # 
Instance details

Defined in Graphics.Implicit.Definitions

Methods

rnf :: NormedTriangle -> () #

newtype TriangleMesh Source #

A triangle mesh is a bunch of triangles, attempting to be a surface.

Constructors

TriangleMesh 

Fields

newtype NormedTriangleMesh Source #

A normed triangle mesh is a mesh of normed triangles.

type Obj2 = ℝ2 -> Source #

A 2D object.

type Obj3 = ℝ3 -> Source #

A 3D object.

type Box2 = (ℝ2, ℝ2) Source #

A 2D box.

type Box3 = (ℝ3, ℝ3) Source #

A 3D box.

type Boxed2 a = (a, Box2) Source #

A Box containing a 2D object.

type Boxed3 a = (a, Box3) Source #

A Box containing a 3D object.

type BoxedObj2 = Boxed2 Obj2 Source #

A Boxed 2D object

type BoxedObj3 = Boxed3 Obj3 Source #

A Boxed 3D object

data SharedObj obj f a Source #

Means of constructing symbolic objects that are common between the 2D and 3D case. This type is parameterized on obj and vec so that SymbolicObj2 and SymbolicObj3 can instantiate it for their own purposes.

Constructors

Empty

The empty object

Full

The entirely full object

Complement obj 
UnionR [obj] 
DifferenceR obj [obj] 
IntersectR [obj] 
Translate (f a) obj 
Scale (f a) obj 
Mirror (f a) obj

Mirror across the line whose normal is defined by the vector

Outset obj 
Shell obj 
EmbedBoxedObj (f a -> a, (f a, f a)) 
WithRounding obj 

Instances

Instances details
(Show obj, Show (f a)) => Show (SharedObj obj f a) Source # 
Instance details

Defined in Graphics.Implicit.Definitions

Methods

showsPrec :: Int -> SharedObj obj f a -> ShowS #

show :: SharedObj obj f a -> String #

showList :: [SharedObj obj f a] -> ShowS #

Generic (SharedObj obj f a) Source # 
Instance details

Defined in Graphics.Implicit.Definitions

Associated Types

type Rep (SharedObj obj f a) :: Type -> Type #

Methods

from :: SharedObj obj f a -> Rep (SharedObj obj f a) x #

to :: Rep (SharedObj obj f a) x -> SharedObj obj f a #

type Rep (SharedObj obj f a) Source # 
Instance details

Defined in Graphics.Implicit.Definitions

type Rep (SharedObj obj f a) = D1 ('MetaData "SharedObj" "Graphics.Implicit.Definitions" "implicit-0.4.0.0-2QFrzNvv6lKFGu3kPbjLAC" 'False) (((C1 ('MetaCons "Empty" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "Full" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "Complement" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 obj)))) :+: (C1 ('MetaCons "UnionR" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 ) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [obj])) :+: (C1 ('MetaCons "DifferenceR" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 ) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 obj) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [obj]))) :+: C1 ('MetaCons "IntersectR" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 ) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [obj]))))) :+: ((C1 ('MetaCons "Translate" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (f a)) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 obj)) :+: (C1 ('MetaCons "Scale" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (f a)) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 obj)) :+: C1 ('MetaCons "Mirror" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (f a)) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 obj)))) :+: ((C1 ('MetaCons "Outset" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 ) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 obj)) :+: C1 ('MetaCons "Shell" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 ) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 obj))) :+: (C1 ('MetaCons "EmbedBoxedObj" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (f a -> a, (f a, f a)))) :+: C1 ('MetaCons "WithRounding" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 ) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 obj))))))

data V2 a #

A 2-dimensional vector

>>> pure 1 :: V2 Int
V2 1 1
>>> V2 1 2 + V2 3 4
V2 4 6
>>> V2 1 2 * V2 3 4
V2 3 8
>>> sum (V2 1 2)
3

Constructors

V2 !a !a 

Instances

Instances details
Monad V2 
Instance details

Defined in Linear.V2

Methods

(>>=) :: V2 a -> (a -> V2 b) -> V2 b #

(>>) :: V2 a -> V2 b -> V2 b #

return :: a -> V2 a #

Functor V2 
Instance details

Defined in Linear.V2

Methods

fmap :: (a -> b) -> V2 a -> V2 b #

(<$) :: a -> V2 b -> V2 a #

MonadFix V2 
Instance details

Defined in Linear.V2

Methods

mfix :: (a -> V2 a) -> V2 a #

Applicative V2 
Instance details

Defined in Linear.V2

Methods

pure :: a -> V2 a #

(<*>) :: V2 (a -> b) -> V2 a -> V2 b #

liftA2 :: (a -> b -> c) -> V2 a -> V2 b -> V2 c #

(*>) :: V2 a -> V2 b -> V2 b #

(<*) :: V2 a -> V2 b -> V2 a #

Foldable V2 
Instance details

Defined in Linear.V2

Methods

fold :: Monoid m => V2 m -> m #

foldMap :: Monoid m => (a -> m) -> V2 a -> m #

foldMap' :: Monoid m => (a -> m) -> V2 a -> m #

foldr :: (a -> b -> b) -> b -> V2 a -> b #

foldr' :: (a -> b -> b) -> b -> V2 a -> b #

foldl :: (b -> a -> b) -> b -> V2 a -> b #

foldl' :: (b -> a -> b) -> b -> V2 a -> b #

foldr1 :: (a -> a -> a) -> V2 a -> a #

foldl1 :: (a -> a -> a) -> V2 a -> a #

toList :: V2 a -> [a] #

null :: V2 a -> Bool #

length :: V2 a -> Int #

elem :: Eq a => a -> V2 a -> Bool #

maximum :: Ord a => V2 a -> a #

minimum :: Ord a => V2 a -> a #

sum :: Num a => V2 a -> a #

product :: Num a => V2 a -> a #

Traversable V2 
Instance details

Defined in Linear.V2

Methods

traverse :: Applicative f => (a -> f b) -> V2 a -> f (V2 b) #

sequenceA :: Applicative f => V2 (f a) -> f (V2 a) #

mapM :: Monad m => (a -> m b) -> V2 a -> m (V2 b) #

sequence :: Monad m => V2 (m a) -> m (V2 a) #

Distributive V2 
Instance details

Defined in Linear.V2

Methods

distribute :: Functor f => f (V2 a) -> V2 (f a) #

collect :: Functor f => (a -> V2 b) -> f a -> V2 (f b) #

distributeM :: Monad m => m (V2 a) -> V2 (m a) #

collectM :: Monad m => (a -> V2 b) -> m a -> V2 (m b) #

Representable V2 
Instance details

Defined in Linear.V2

Associated Types

type Rep V2 #

Methods

tabulate :: (Rep V2 -> a) -> V2 a #

index :: V2 a -> Rep V2 -> a #

Eq1 V2 
Instance details

Defined in Linear.V2

Methods

liftEq :: (a -> b -> Bool) -> V2 a -> V2 b -> Bool #

Ord1 V2 
Instance details

Defined in Linear.V2

Methods

liftCompare :: (a -> b -> Ordering) -> V2 a -> V2 b -> Ordering #

Read1 V2 
Instance details

Defined in Linear.V2

Methods

liftReadsPrec :: (Int -> ReadS a) -> ReadS [a] -> Int -> ReadS (V2 a) #

liftReadList :: (Int -> ReadS a) -> ReadS [a] -> ReadS [V2 a] #

liftReadPrec :: ReadPrec a -> ReadPrec [a] -> ReadPrec (V2 a) #

liftReadListPrec :: ReadPrec a -> ReadPrec [a] -> ReadPrec [V2 a] #

Show1 V2 
Instance details

Defined in Linear.V2

Methods

liftShowsPrec :: (Int -> a -> ShowS) -> ([a] -> ShowS) -> Int -> V2 a -> ShowS #

liftShowList :: (Int -> a -> ShowS) -> ([a] -> ShowS) -> [V2 a] -> ShowS #

MonadZip V2 
Instance details

Defined in Linear.V2

Methods

mzip :: V2 a -> V2 b -> V2 (a, b) #

mzipWith :: (a -> b -> c) -> V2 a -> V2 b -> V2 c #

munzip :: V2 (a, b) -> (V2 a, V2 b) #

Serial1 V2 
Instance details

Defined in Linear.V2

Methods

serializeWith :: MonadPut m => (a -> m ()) -> V2 a -> m () #

deserializeWith :: MonadGet m => m a -> m (V2 a) #

Hashable1 V2 
Instance details

Defined in Linear.V2

Methods

liftHashWithSalt :: (Int -> a -> Int) -> Int -> V2 a -> Int #

Apply V2 
Instance details

Defined in Linear.V2

Methods

(<.>) :: V2 (a -> b) -> V2 a -> V2 b #

(.>) :: V2 a -> V2 b -> V2 b #

(<.) :: V2 a -> V2 b -> V2 a #

liftF2 :: (a -> b -> c) -> V2 a -> V2 b -> V2 c #

Traversable1 V2 
Instance details

Defined in Linear.V2

Methods

traverse1 :: Apply f => (a -> f b) -> V2 a -> f (V2 b) #

sequence1 :: Apply f => V2 (f b) -> f (V2 b) #

Affine V2 
Instance details

Defined in Linear.Affine

Associated Types

type Diff V2 :: Type -> Type #

Methods

(.-.) :: Num a => V2 a -> V2 a -> Diff V2 a #

(.+^) :: Num a => V2 a -> Diff V2 a -> V2 a #

(.-^) :: Num a => V2 a -> Diff V2 a -> V2 a #

R2 V2 
Instance details

Defined in Linear.V2

Methods

_y :: Lens' (V2 a) a #

_xy :: Lens' (V2 a) (V2 a) #

R1 V2 
Instance details

Defined in Linear.V2

Methods

_x :: Lens' (V2 a) a #

Finite V2 
Instance details

Defined in Linear.V2

Associated Types

type Size V2 :: Nat #

Methods

toV :: V2 a -> V (Size V2) a #

fromV :: V (Size V2) a -> V2 a #

Metric V2 
Instance details

Defined in Linear.V2

Methods

dot :: Num a => V2 a -> V2 a -> a #

quadrance :: Num a => V2 a -> a #

qd :: Num a => V2 a -> V2 a -> a #

distance :: Floating a => V2 a -> V2 a -> a #

norm :: Floating a => V2 a -> a #

signorm :: Floating a => V2 a -> V2 a #

Additive V2 
Instance details

Defined in Linear.V2

Methods

zero :: Num a => V2 a #

(^+^) :: Num a => V2 a -> V2 a -> V2 a #

(^-^) :: Num a => V2 a -> V2 a -> V2 a #

lerp :: Num a => a -> V2 a -> V2 a -> V2 a #

liftU2 :: (a -> a -> a) -> V2 a -> V2 a -> V2 a #

liftI2 :: (a -> b -> c) -> V2 a -> V2 b -> V2 c #

Bind V2 
Instance details

Defined in Linear.V2

Methods

(>>-) :: V2 a -> (a -> V2 b) -> V2 b #

join :: V2 (V2 a) -> V2 a #

Foldable1 V2 
Instance details

Defined in Linear.V2

Methods

fold1 :: Semigroup m => V2 m -> m #

foldMap1 :: Semigroup m => (a -> m) -> V2 a -> m #

toNonEmpty :: V2 a -> NonEmpty a #

ComponentWiseMultable ℝ2 Source # 
Instance details

Defined in Graphics.Implicit.Definitions

Methods

(⋯*) :: ℝ2 -> ℝ2 -> ℝ2 Source #

(⋯/) :: ℝ2 -> ℝ2 -> ℝ2 Source #

Object SymbolicObj2 V2 Source # 
Instance details

Defined in Graphics.Implicit.Primitives

Lift a => Lift (V2 a :: Type) 
Instance details

Defined in Linear.V2

Methods

lift :: V2 a -> Q Exp #

liftTyped :: V2 a -> Q (TExp (V2 a)) #

Unbox a => Vector Vector (V2 a) 
Instance details

Defined in Linear.V2

Methods

basicUnsafeFreeze :: PrimMonad m => Mutable Vector (PrimState m) (V2 a) -> m (Vector (V2 a)) #

basicUnsafeThaw :: PrimMonad m => Vector (V2 a) -> m (Mutable Vector (PrimState m) (V2 a)) #

basicLength :: Vector (V2 a) -> Int #

basicUnsafeSlice :: Int -> Int -> Vector (V2 a) -> Vector (V2 a) #

basicUnsafeIndexM :: Monad m => Vector (V2 a) -> Int -> m (V2 a) #

basicUnsafeCopy :: PrimMonad m => Mutable Vector (PrimState m) (V2 a) -> Vector (V2 a) -> m () #

elemseq :: Vector (V2 a) -> V2 a -> b -> b #

Unbox a => MVector MVector (V2 a) 
Instance details

Defined in Linear.V2

Methods

basicLength :: MVector s (V2 a) -> Int #

basicUnsafeSlice :: Int -> Int -> MVector s (V2 a) -> MVector s (V2 a) #

basicOverlaps :: MVector s (V2 a) -> MVector s (V2 a) -> Bool #

basicUnsafeNew :: PrimMonad m => Int -> m (MVector (PrimState m) (V2 a)) #

basicInitialize :: PrimMonad m => MVector (PrimState m) (V2 a) -> m () #

basicUnsafeReplicate :: PrimMonad m => Int -> V2 a -> m (MVector (PrimState m) (V2 a)) #

basicUnsafeRead :: PrimMonad m => MVector (PrimState m) (V2 a) -> Int -> m (V2 a) #

basicUnsafeWrite :: PrimMonad m => MVector (PrimState m) (V2 a) -> Int -> V2 a -> m () #

basicClear :: PrimMonad m => MVector (PrimState m) (V2 a) -> m () #

basicSet :: PrimMonad m => MVector (PrimState m) (V2 a) -> V2 a -> m () #

basicUnsafeCopy :: PrimMonad m => MVector (PrimState m) (V2 a) -> MVector (PrimState m) (V2 a) -> m () #

basicUnsafeMove :: PrimMonad m => MVector (PrimState m) (V2 a) -> MVector (PrimState m) (V2 a) -> m () #

basicUnsafeGrow :: PrimMonad m => MVector (PrimState m) (V2 a) -> Int -> m (MVector (PrimState m) (V2 a)) #

Bounded a => Bounded (V2 a) 
Instance details

Defined in Linear.V2

Methods

minBound :: V2 a #

maxBound :: V2 a #

Eq a => Eq (V2 a) 
Instance details

Defined in Linear.V2

Methods

(==) :: V2 a -> V2 a -> Bool #

(/=) :: V2 a -> V2 a -> Bool #

Floating a => Floating (V2 a) 
Instance details

Defined in Linear.V2

Methods

pi :: V2 a #

exp :: V2 a -> V2 a #

log :: V2 a -> V2 a #

sqrt :: V2 a -> V2 a #

(**) :: V2 a -> V2 a -> V2 a #

logBase :: V2 a -> V2 a -> V2 a #

sin :: V2 a -> V2 a #

cos :: V2 a -> V2 a #

tan :: V2 a -> V2 a #

asin :: V2 a -> V2 a #

acos :: V2 a -> V2 a #

atan :: V2 a -> V2 a #

sinh :: V2 a -> V2 a #

cosh :: V2 a -> V2 a #

tanh :: V2 a -> V2 a #

asinh :: V2 a -> V2 a #

acosh :: V2 a -> V2 a #

atanh :: V2 a -> V2 a #

log1p :: V2 a -> V2 a #

expm1 :: V2 a -> V2 a #

log1pexp :: V2 a -> V2 a #

log1mexp :: V2 a -> V2 a #

Fractional a => Fractional (V2 a) 
Instance details

Defined in Linear.V2

Methods

(/) :: V2 a -> V2 a -> V2 a #

recip :: V2 a -> V2 a #

fromRational :: Rational -> V2 a #

Data a => Data (V2 a) 
Instance details

Defined in Linear.V2

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> V2 a -> c (V2 a) #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (V2 a) #

toConstr :: V2 a -> Constr #

dataTypeOf :: V2 a -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (V2 a)) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (V2 a)) #

gmapT :: (forall b. Data b => b -> b) -> V2 a -> V2 a #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> V2 a -> r #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> V2 a -> r #

gmapQ :: (forall d. Data d => d -> u) -> V2 a -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> V2 a -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> V2 a -> m (V2 a) #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> V2 a -> m (V2 a) #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> V2 a -> m (V2 a) #

Num a => Num (V2 a) 
Instance details

Defined in Linear.V2

Methods

(+) :: V2 a -> V2 a -> V2 a #

(-) :: V2 a -> V2 a -> V2 a #

(*) :: V2 a -> V2 a -> V2 a #

negate :: V2 a -> V2 a #

abs :: V2 a -> V2 a #

signum :: V2 a -> V2 a #

fromInteger :: Integer -> V2 a #

Ord a => Ord (V2 a) 
Instance details

Defined in Linear.V2

Methods

compare :: V2 a -> V2 a -> Ordering #

(<) :: V2 a -> V2 a -> Bool #

(<=) :: V2 a -> V2 a -> Bool #

(>) :: V2 a -> V2 a -> Bool #

(>=) :: V2 a -> V2 a -> Bool #

max :: V2 a -> V2 a -> V2 a #

min :: V2 a -> V2 a -> V2 a #

Read a => Read (V2 a) 
Instance details

Defined in Linear.V2

Show a => Show (V2 a) 
Instance details

Defined in Linear.V2

Methods

showsPrec :: Int -> V2 a -> ShowS #

show :: V2 a -> String #

showList :: [V2 a] -> ShowS #

Ix a => Ix (V2 a) 
Instance details

Defined in Linear.V2

Methods

range :: (V2 a, V2 a) -> [V2 a] #

index :: (V2 a, V2 a) -> V2 a -> Int #

unsafeIndex :: (V2 a, V2 a) -> V2 a -> Int #

inRange :: (V2 a, V2 a) -> V2 a -> Bool #

rangeSize :: (V2 a, V2 a) -> Int #

unsafeRangeSize :: (V2 a, V2 a) -> Int #

Generic (V2 a) 
Instance details

Defined in Linear.V2

Associated Types

type Rep (V2 a) :: Type -> Type #

Methods

from :: V2 a -> Rep (V2 a) x #

to :: Rep (V2 a) x -> V2 a #

Semigroup a => Semigroup (V2 a) 
Instance details

Defined in Linear.V2

Methods

(<>) :: V2 a -> V2 a -> V2 a #

sconcat :: NonEmpty (V2 a) -> V2 a #

stimes :: Integral b => b -> V2 a -> V2 a #

Monoid a => Monoid (V2 a) 
Instance details

Defined in Linear.V2

Methods

mempty :: V2 a #

mappend :: V2 a -> V2 a -> V2 a #

mconcat :: [V2 a] -> V2 a #

Storable a => Storable (V2 a) 
Instance details

Defined in Linear.V2

Methods

sizeOf :: V2 a -> Int #

alignment :: V2 a -> Int #

peekElemOff :: Ptr (V2 a) -> Int -> IO (V2 a) #

pokeElemOff :: Ptr (V2 a) -> Int -> V2 a -> IO () #

peekByteOff :: Ptr b -> Int -> IO (V2 a) #

pokeByteOff :: Ptr b -> Int -> V2 a -> IO () #

peek :: Ptr (V2 a) -> IO (V2 a) #

poke :: Ptr (V2 a) -> V2 a -> IO () #

Binary a => Binary (V2 a) 
Instance details

Defined in Linear.V2

Methods

put :: V2 a -> Put #

get :: Get (V2 a) #

putList :: [V2 a] -> Put #

Serial a => Serial (V2 a) 
Instance details

Defined in Linear.V2

Methods

serialize :: MonadPut m => V2 a -> m () #

deserialize :: MonadGet m => m (V2 a) #

Serialize a => Serialize (V2 a) 
Instance details

Defined in Linear.V2

Methods

put :: Putter (V2 a) #

get :: Get (V2 a) #

NFData a => NFData (V2 a) 
Instance details

Defined in Linear.V2

Methods

rnf :: V2 a -> () #

Hashable a => Hashable (V2 a) 
Instance details

Defined in Linear.V2

Methods

hashWithSalt :: Int -> V2 a -> Int #

hash :: V2 a -> Int #

Unbox a => Unbox (V2 a) 
Instance details

Defined in Linear.V2

Ixed (V2 a) 
Instance details

Defined in Linear.V2

Methods

ix :: Index (V2 a) -> Traversal' (V2 a) (IxValue (V2 a)) #

Epsilon a => Epsilon (V2 a) 
Instance details

Defined in Linear.V2

Methods

nearZero :: V2 a -> Bool #

Random a => Random (V2 a) 
Instance details

Defined in Linear.V2

Methods

randomR :: RandomGen g => (V2 a, V2 a) -> g -> (V2 a, g) #

random :: RandomGen g => g -> (V2 a, g) #

randomRs :: RandomGen g => (V2 a, V2 a) -> g -> [V2 a] #

randoms :: RandomGen g => g -> [V2 a] #

Generic1 V2 
Instance details

Defined in Linear.V2

Associated Types

type Rep1 V2 :: k -> Type #

Methods

from1 :: forall (a :: k). V2 a -> Rep1 V2 a #

to1 :: forall (a :: k). Rep1 V2 a -> V2 a #

FunctorWithIndex (E V2) V2 
Instance details

Defined in Linear.V2

Methods

imap :: (E V2 -> a -> b) -> V2 a -> V2 b #

FoldableWithIndex (E V2) V2 
Instance details

Defined in Linear.V2

Methods

ifoldMap :: Monoid m => (E V2 -> a -> m) -> V2 a -> m #

ifoldMap' :: Monoid m => (E V2 -> a -> m) -> V2 a -> m #

ifoldr :: (E V2 -> a -> b -> b) -> b -> V2 a -> b #

ifoldl :: (E V2 -> b -> a -> b) -> b -> V2 a -> b #

ifoldr' :: (E V2 -> a -> b -> b) -> b -> V2 a -> b #

ifoldl' :: (E V2 -> b -> a -> b) -> b -> V2 a -> b #

TraversableWithIndex (E V2) V2 
Instance details

Defined in Linear.V2

Methods

itraverse :: Applicative f => (E V2 -> a -> f b) -> V2 a -> f (V2 b) #

Each (V2 a) (V2 b) a b 
Instance details

Defined in Linear.V2

Methods

each :: Traversal (V2 a) (V2 b) a b #

Field1 (V2 a) (V2 a) a a 
Instance details

Defined in Linear.V2

Methods

_1 :: Lens (V2 a) (V2 a) a a #

Field2 (V2 a) (V2 a) a a 
Instance details

Defined in Linear.V2

Methods

_2 :: Lens (V2 a) (V2 a) a a #

type Rep V2 
Instance details

Defined in Linear.V2

type Rep V2 = E V2
type Diff V2 
Instance details

Defined in Linear.Affine

type Diff V2 = V2
type Size V2 
Instance details

Defined in Linear.V2

type Size V2 = 2
data MVector s (V2 a) 
Instance details

Defined in Linear.V2

data MVector s (V2 a) = MV_V2 !Int !(MVector s a)
type Rep (V2 a) 
Instance details

Defined in Linear.V2

type Rep (V2 a) = D1 ('MetaData "V2" "Linear.V2" "linear-1.21.9-6oNTW01QwujhmpV2bFQ8C" 'False) (C1 ('MetaCons "V2" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 a) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 a)))
data Vector (V2 a) 
Instance details

Defined in Linear.V2

data Vector (V2 a) = V_V2 !Int !(Vector a)
type Index (V2 a) 
Instance details

Defined in Linear.V2

type Index (V2 a) = E V2
type IxValue (V2 a) 
Instance details

Defined in Linear.V2

type IxValue (V2 a) = a
type Rep1 V2 
Instance details

Defined in Linear.V2

data V3 a #

A 3-dimensional vector

Constructors

V3 !a !a !a 

Instances

Instances details
Monad V3 
Instance details

Defined in Linear.V3

Methods

(>>=) :: V3 a -> (a -> V3 b) -> V3 b #

(>>) :: V3 a -> V3 b -> V3 b #

return :: a -> V3 a #

Functor V3 
Instance details

Defined in Linear.V3

Methods

fmap :: (a -> b) -> V3 a -> V3 b #

(<$) :: a -> V3 b -> V3 a #

MonadFix V3 
Instance details

Defined in Linear.V3

Methods

mfix :: (a -> V3 a) -> V3 a #

Applicative V3 
Instance details

Defined in Linear.V3

Methods

pure :: a -> V3 a #

(<*>) :: V3 (a -> b) -> V3 a -> V3 b #

liftA2 :: (a -> b -> c) -> V3 a -> V3 b -> V3 c #

(*>) :: V3 a -> V3 b -> V3 b #

(<*) :: V3 a -> V3 b -> V3 a #

Foldable V3 
Instance details

Defined in Linear.V3

Methods

fold :: Monoid m => V3 m -> m #

foldMap :: Monoid m => (a -> m) -> V3 a -> m #

foldMap' :: Monoid m => (a -> m) -> V3 a -> m #

foldr :: (a -> b -> b) -> b -> V3 a -> b #

foldr' :: (a -> b -> b) -> b -> V3 a -> b #

foldl :: (b -> a -> b) -> b -> V3 a -> b #

foldl' :: (b -> a -> b) -> b -> V3 a -> b #

foldr1 :: (a -> a -> a) -> V3 a -> a #

foldl1 :: (a -> a -> a) -> V3 a -> a #

toList :: V3 a -> [a] #

null :: V3 a -> Bool #

length :: V3 a -> Int #

elem :: Eq a => a -> V3 a -> Bool #

maximum :: Ord a => V3 a -> a #

minimum :: Ord a => V3 a -> a #

sum :: Num a => V3 a -> a #

product :: Num a => V3 a -> a #

Traversable V3 
Instance details

Defined in Linear.V3

Methods

traverse :: Applicative f => (a -> f b) -> V3 a -> f (V3 b) #

sequenceA :: Applicative f => V3 (f a) -> f (V3 a) #

mapM :: Monad m => (a -> m b) -> V3 a -> m (V3 b) #

sequence :: Monad m => V3 (m a) -> m (V3 a) #

Distributive V3 
Instance details

Defined in Linear.V3

Methods

distribute :: Functor f => f (V3 a) -> V3 (f a) #

collect :: Functor f => (a -> V3 b) -> f a -> V3 (f b) #

distributeM :: Monad m => m (V3 a) -> V3 (m a) #

collectM :: Monad m => (a -> V3 b) -> m a -> V3 (m b) #

Representable V3 
Instance details

Defined in Linear.V3

Associated Types

type Rep V3 #

Methods

tabulate :: (Rep V3 -> a) -> V3 a #

index :: V3 a -> Rep V3 -> a #

Eq1 V3 
Instance details

Defined in Linear.V3

Methods

liftEq :: (a -> b -> Bool) -> V3 a -> V3 b -> Bool #

Ord1 V3 
Instance details

Defined in Linear.V3

Methods

liftCompare :: (a -> b -> Ordering) -> V3 a -> V3 b -> Ordering #

Read1 V3 
Instance details

Defined in Linear.V3

Methods

liftReadsPrec :: (Int -> ReadS a) -> ReadS [a] -> Int -> ReadS (V3 a) #

liftReadList :: (Int -> ReadS a) -> ReadS [a] -> ReadS [V3 a] #

liftReadPrec :: ReadPrec a -> ReadPrec [a] -> ReadPrec (V3 a) #

liftReadListPrec :: ReadPrec a -> ReadPrec [a] -> ReadPrec [V3 a] #

Show1 V3 
Instance details

Defined in Linear.V3

Methods

liftShowsPrec :: (Int -> a -> ShowS) -> ([a] -> ShowS) -> Int -> V3 a -> ShowS #

liftShowList :: (Int -> a -> ShowS) -> ([a] -> ShowS) -> [V3 a] -> ShowS #

MonadZip V3 
Instance details

Defined in Linear.V3

Methods

mzip :: V3 a -> V3 b -> V3 (a, b) #

mzipWith :: (a -> b -> c) -> V3 a -> V3 b -> V3 c #

munzip :: V3 (a, b) -> (V3 a, V3 b) #

Serial1 V3 
Instance details

Defined in Linear.V3

Methods

serializeWith :: MonadPut m => (a -> m ()) -> V3 a -> m () #

deserializeWith :: MonadGet m => m a -> m (V3 a) #

Hashable1 V3 
Instance details

Defined in Linear.V3

Methods

liftHashWithSalt :: (Int -> a -> Int) -> Int -> V3 a -> Int #

Apply V3 
Instance details

Defined in Linear.V3

Methods

(<.>) :: V3 (a -> b) -> V3 a -> V3 b #

(.>) :: V3 a -> V3 b -> V3 b #

(<.) :: V3 a -> V3 b -> V3 a #

liftF2 :: (a -> b -> c) -> V3 a -> V3 b -> V3 c #

Traversable1 V3 
Instance details

Defined in Linear.V3

Methods

traverse1 :: Apply f => (a -> f b) -> V3 a -> f (V3 b) #

sequence1 :: Apply f => V3 (f b) -> f (V3 b) #

Affine V3 
Instance details

Defined in Linear.Affine

Associated Types

type Diff V3 :: Type -> Type #

Methods

(.-.) :: Num a => V3 a -> V3 a -> Diff V3 a #

(.+^) :: Num a => V3 a -> Diff V3 a -> V3 a #

(.-^) :: Num a => V3 a -> Diff V3 a -> V3 a #

R3 V3 
Instance details

Defined in Linear.V3

Methods

_z :: Lens' (V3 a) a #

_xyz :: Lens' (V3 a) (V3 a) #

R2 V3 
Instance details

Defined in Linear.V3

Methods

_y :: Lens' (V3 a) a #

_xy :: Lens' (V3 a) (V2 a) #

R1 V3 
Instance details

Defined in Linear.V3

Methods

_x :: Lens' (V3 a) a #

Finite V3 
Instance details

Defined in Linear.V3

Associated Types

type Size V3 :: Nat #

Methods

toV :: V3 a -> V (Size V3) a #

fromV :: V (Size V3) a -> V3 a #

Metric V3 
Instance details

Defined in Linear.V3

Methods

dot :: Num a => V3 a -> V3 a -> a #

quadrance :: Num a => V3 a -> a #

qd :: Num a => V3 a -> V3 a -> a #

distance :: Floating a => V3 a -> V3 a -> a #

norm :: Floating a => V3 a -> a #

signorm :: Floating a => V3 a -> V3 a #

Additive V3 
Instance details

Defined in Linear.V3

Methods

zero :: Num a => V3 a #

(^+^) :: Num a => V3 a -> V3 a -> V3 a #

(^-^) :: Num a => V3 a -> V3 a -> V3 a #

lerp :: Num a => a -> V3 a -> V3 a -> V3 a #

liftU2 :: (a -> a -> a) -> V3 a -> V3 a -> V3 a #

liftI2 :: (a -> b -> c) -> V3 a -> V3 b -> V3 c #

Bind V3 
Instance details

Defined in Linear.V3

Methods

(>>-) :: V3 a -> (a -> V3 b) -> V3 b #

join :: V3 (V3 a) -> V3 a #

Foldable1 V3 
Instance details

Defined in Linear.V3

Methods

fold1 :: Semigroup m => V3 m -> m #

foldMap1 :: Semigroup m => (a -> m) -> V3 a -> m #

toNonEmpty :: V3 a -> NonEmpty a #

ComponentWiseMultable ℝ3 Source # 
Instance details

Defined in Graphics.Implicit.Definitions

Methods

(⋯*) :: ℝ3 -> ℝ3 -> ℝ3 Source #

(⋯/) :: ℝ3 -> ℝ3 -> ℝ3 Source #

Object SymbolicObj3 V3 Source # 
Instance details

Defined in Graphics.Implicit.Primitives

Lift a => Lift (V3 a :: Type) 
Instance details

Defined in Linear.V3

Methods

lift :: V3 a -> Q Exp #

liftTyped :: V3 a -> Q (TExp (V3 a)) #

Unbox a => Vector Vector (V3 a) 
Instance details

Defined in Linear.V3

Methods

basicUnsafeFreeze :: PrimMonad m => Mutable Vector (PrimState m) (V3 a) -> m (Vector (V3 a)) #

basicUnsafeThaw :: PrimMonad m => Vector (V3 a) -> m (Mutable Vector (PrimState m) (V3 a)) #

basicLength :: Vector (V3 a) -> Int #

basicUnsafeSlice :: Int -> Int -> Vector (V3 a) -> Vector (V3 a) #

basicUnsafeIndexM :: Monad m => Vector (V3 a) -> Int -> m (V3 a) #

basicUnsafeCopy :: PrimMonad m => Mutable Vector (PrimState m) (V3 a) -> Vector (V3 a) -> m () #

elemseq :: Vector (V3 a) -> V3 a -> b -> b #

Unbox a => MVector MVector (V3 a) 
Instance details

Defined in Linear.V3

Methods

basicLength :: MVector s (V3 a) -> Int #

basicUnsafeSlice :: Int -> Int -> MVector s (V3 a) -> MVector s (V3 a) #

basicOverlaps :: MVector s (V3 a) -> MVector s (V3 a) -> Bool #

basicUnsafeNew :: PrimMonad m => Int -> m (MVector (PrimState m) (V3 a)) #

basicInitialize :: PrimMonad m => MVector (PrimState m) (V3 a) -> m () #

basicUnsafeReplicate :: PrimMonad m => Int -> V3 a -> m (MVector (PrimState m) (V3 a)) #

basicUnsafeRead :: PrimMonad m => MVector (PrimState m) (V3 a) -> Int -> m (V3 a) #

basicUnsafeWrite :: PrimMonad m => MVector (PrimState m) (V3 a) -> Int -> V3 a -> m () #

basicClear :: PrimMonad m => MVector (PrimState m) (V3 a) -> m () #

basicSet :: PrimMonad m => MVector (PrimState m) (V3 a) -> V3 a -> m () #

basicUnsafeCopy :: PrimMonad m => MVector (PrimState m) (V3 a) -> MVector (PrimState m) (V3 a) -> m () #

basicUnsafeMove :: PrimMonad m => MVector (PrimState m) (V3 a) -> MVector (PrimState m) (V3 a) -> m () #

basicUnsafeGrow :: PrimMonad m => MVector (PrimState m) (V3 a) -> Int -> m (MVector (PrimState m) (V3 a)) #

Bounded a => Bounded (V3 a) 
Instance details

Defined in Linear.V3

Methods

minBound :: V3 a #

maxBound :: V3 a #

Eq a => Eq (V3 a) 
Instance details

Defined in Linear.V3

Methods

(==) :: V3 a -> V3 a -> Bool #

(/=) :: V3 a -> V3 a -> Bool #

Floating a => Floating (V3 a) 
Instance details

Defined in Linear.V3

Methods

pi :: V3 a #

exp :: V3 a -> V3 a #

log :: V3 a -> V3 a #

sqrt :: V3 a -> V3 a #

(**) :: V3 a -> V3 a -> V3 a #

logBase :: V3 a -> V3 a -> V3 a #

sin :: V3 a -> V3 a #

cos :: V3 a -> V3 a #

tan :: V3 a -> V3 a #

asin :: V3 a -> V3 a #

acos :: V3 a -> V3 a #

atan :: V3 a -> V3 a #

sinh :: V3 a -> V3 a #

cosh :: V3 a -> V3 a #

tanh :: V3 a -> V3 a #

asinh :: V3 a -> V3 a #

acosh :: V3 a -> V3 a #

atanh :: V3 a -> V3 a #

log1p :: V3 a -> V3 a #

expm1 :: V3 a -> V3 a #

log1pexp :: V3 a -> V3 a #

log1mexp :: V3 a -> V3 a #

Fractional a => Fractional (V3 a) 
Instance details

Defined in Linear.V3

Methods

(/) :: V3 a -> V3 a -> V3 a #

recip :: V3 a -> V3 a #

fromRational :: Rational -> V3 a #

Data a => Data (V3 a) 
Instance details

Defined in Linear.V3

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> V3 a -> c (V3 a) #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (V3 a) #

toConstr :: V3 a -> Constr #

dataTypeOf :: V3 a -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (V3 a)) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (V3 a)) #

gmapT :: (forall b. Data b => b -> b) -> V3 a -> V3 a #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> V3 a -> r #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> V3 a -> r #

gmapQ :: (forall d. Data d => d -> u) -> V3 a -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> V3 a -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> V3 a -> m (V3 a) #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> V3 a -> m (V3 a) #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> V3 a -> m (V3 a) #

Num a => Num (V3 a) 
Instance details

Defined in Linear.V3

Methods

(+) :: V3 a -> V3 a -> V3 a #

(-) :: V3 a -> V3 a -> V3 a #

(*) :: V3 a -> V3 a -> V3 a #

negate :: V3 a -> V3 a #

abs :: V3 a -> V3 a #

signum :: V3 a -> V3 a #

fromInteger :: Integer -> V3 a #

Ord a => Ord (V3 a) 
Instance details

Defined in Linear.V3

Methods

compare :: V3 a -> V3 a -> Ordering #

(<) :: V3 a -> V3 a -> Bool #

(<=) :: V3 a -> V3 a -> Bool #

(>) :: V3 a -> V3 a -> Bool #

(>=) :: V3 a -> V3 a -> Bool #

max :: V3 a -> V3 a -> V3 a #

min :: V3 a -> V3 a -> V3 a #

Read a => Read (V3 a) 
Instance details

Defined in Linear.V3

Show a => Show (V3 a) 
Instance details

Defined in Linear.V3

Methods

showsPrec :: Int -> V3 a -> ShowS #

show :: V3 a -> String #

showList :: [V3 a] -> ShowS #

Ix a => Ix (V3 a) 
Instance details

Defined in Linear.V3

Methods

range :: (V3 a, V3 a) -> [V3 a] #

index :: (V3 a, V3 a) -> V3 a -> Int #

unsafeIndex :: (V3 a, V3 a) -> V3 a -> Int #

inRange :: (V3 a, V3 a) -> V3 a -> Bool #

rangeSize :: (V3 a, V3 a) -> Int #

unsafeRangeSize :: (V3 a, V3 a) -> Int #

Generic (V3 a) 
Instance details

Defined in Linear.V3

Associated Types

type Rep (V3 a) :: Type -> Type #

Methods

from :: V3 a -> Rep (V3 a) x #

to :: Rep (V3 a) x -> V3 a #

Semigroup a => Semigroup (V3 a) 
Instance details

Defined in Linear.V3

Methods

(<>) :: V3 a -> V3 a -> V3 a #

sconcat :: NonEmpty (V3 a) -> V3 a #

stimes :: Integral b => b -> V3 a -> V3 a #

Monoid a => Monoid (V3 a) 
Instance details

Defined in Linear.V3

Methods

mempty :: V3 a #

mappend :: V3 a -> V3 a -> V3 a #

mconcat :: [V3 a] -> V3 a #

Storable a => Storable (V3 a) 
Instance details

Defined in Linear.V3

Methods

sizeOf :: V3 a -> Int #

alignment :: V3 a -> Int #

peekElemOff :: Ptr (V3 a) -> Int -> IO (V3 a) #

pokeElemOff :: Ptr (V3 a) -> Int -> V3 a -> IO () #

peekByteOff :: Ptr b -> Int -> IO (V3 a) #

pokeByteOff :: Ptr b -> Int -> V3 a -> IO () #

peek :: Ptr (V3 a) -> IO (V3 a) #

poke :: Ptr (V3 a) -> V3 a -> IO () #

Binary a => Binary (V3 a) 
Instance details

Defined in Linear.V3

Methods

put :: V3 a -> Put #

get :: Get (V3 a) #

putList :: [V3 a] -> Put #

Serial a => Serial (V3 a) 
Instance details

Defined in Linear.V3

Methods

serialize :: MonadPut m => V3 a -> m () #

deserialize :: MonadGet m => m (V3 a) #

Serialize a => Serialize (V3 a) 
Instance details

Defined in Linear.V3

Methods

put :: Putter (V3 a) #

get :: Get (V3 a) #

NFData a => NFData (V3 a) 
Instance details

Defined in Linear.V3

Methods

rnf :: V3 a -> () #

Hashable a => Hashable (V3 a) 
Instance details

Defined in Linear.V3

Methods

hashWithSalt :: Int -> V3 a -> Int #

hash :: V3 a -> Int #

Unbox a => Unbox (V3 a) 
Instance details

Defined in Linear.V3

Ixed (V3 a) 
Instance details

Defined in Linear.V3

Methods

ix :: Index (V3 a) -> Traversal' (V3 a) (IxValue (V3 a)) #

Epsilon a => Epsilon (V3 a) 
Instance details

Defined in Linear.V3

Methods

nearZero :: V3 a -> Bool #

Random a => Random (V3 a) 
Instance details

Defined in Linear.V3

Methods

randomR :: RandomGen g => (V3 a, V3 a) -> g -> (V3 a, g) #

random :: RandomGen g => g -> (V3 a, g) #

randomRs :: RandomGen g => (V3 a, V3 a) -> g -> [V3 a] #

randoms :: RandomGen g => g -> [V3 a] #

Generic1 V3 
Instance details

Defined in Linear.V3

Associated Types

type Rep1 V3 :: k -> Type #

Methods

from1 :: forall (a :: k). V3 a -> Rep1 V3 a #

to1 :: forall (a :: k). Rep1 V3 a -> V3 a #

FunctorWithIndex (E V3) V3 
Instance details

Defined in Linear.V3

Methods

imap :: (E V3 -> a -> b) -> V3 a -> V3 b #

FoldableWithIndex (E V3) V3 
Instance details

Defined in Linear.V3

Methods

ifoldMap :: Monoid m => (E V3 -> a -> m) -> V3 a -> m #

ifoldMap' :: Monoid m => (E V3 -> a -> m) -> V3 a -> m #

ifoldr :: (E V3 -> a -> b -> b) -> b -> V3 a -> b #

ifoldl :: (E V3 -> b -> a -> b) -> b -> V3 a -> b #

ifoldr' :: (E V3 -> a -> b -> b) -> b -> V3 a -> b #

ifoldl' :: (E V3 -> b -> a -> b) -> b -> V3 a -> b #

TraversableWithIndex (E V3) V3 
Instance details

Defined in Linear.V3

Methods

itraverse :: Applicative f => (E V3 -> a -> f b) -> V3 a -> f (V3 b) #

Each (V3 a) (V3 b) a b 
Instance details

Defined in Linear.V3

Methods

each :: Traversal (V3 a) (V3 b) a b #

Field1 (V3 a) (V3 a) a a 
Instance details

Defined in Linear.V3

Methods

_1 :: Lens (V3 a) (V3 a) a a #

Field2 (V3 a) (V3 a) a a 
Instance details

Defined in Linear.V3

Methods

_2 :: Lens (V3 a) (V3 a) a a #

Field3 (V3 a) (V3 a) a a 
Instance details

Defined in Linear.V3

Methods

_3 :: Lens (V3 a) (V3 a) a a #

type Rep V3 
Instance details

Defined in Linear.V3

type Rep V3 = E V3
type Diff V3 
Instance details

Defined in Linear.Affine

type Diff V3 = V3
type Size V3 
Instance details

Defined in Linear.V3

type Size V3 = 3
data MVector s (V3 a) 
Instance details

Defined in Linear.V3

data MVector s (V3 a) = MV_V3 !Int !(MVector s a)
type Rep (V3 a) 
Instance details

Defined in Linear.V3

data Vector (V3 a) 
Instance details

Defined in Linear.V3

data Vector (V3 a) = V_V3 !Int !(Vector a)
type Index (V3 a) 
Instance details

Defined in Linear.V3

type Index (V3 a) = E V3
type IxValue (V3 a) 
Instance details

Defined in Linear.V3

type IxValue (V3 a) = a
type Rep1 V3 
Instance details

Defined in Linear.V3

data SymbolicObj2 Source #

A symbolic 2D object format. We want to have symbolic objects so that we can accelerate rendering & give ideal meshes for simple cases.

Instances

Instances details
Show SymbolicObj2 Source # 
Instance details

Defined in Graphics.Implicit.Definitions

Generic SymbolicObj2 Source # 
Instance details

Defined in Graphics.Implicit.Definitions

Associated Types

type Rep SymbolicObj2 :: Type -> Type #

Semigroup SymbolicObj2 Source #

Semigroup under union.

Instance details

Defined in Graphics.Implicit.Definitions

Monoid SymbolicObj2 Source #

Monoid under union.

Instance details

Defined in Graphics.Implicit.Definitions

DiscreteAproxable SymbolicObj2 DynamicImage Source # 
Instance details

Defined in Graphics.Implicit.Export.DiscreteAproxable

Object SymbolicObj2 V2 Source # 
Instance details

Defined in Graphics.Implicit.Primitives

DiscreteAproxable SymbolicObj2 [Polyline] Source # 
Instance details

Defined in Graphics.Implicit.Export.DiscreteAproxable

type Rep SymbolicObj2 Source # 
Instance details

Defined in Graphics.Implicit.Definitions

data SymbolicObj3 Source #

A symbolic 3D format!

Instances

Instances details
Show SymbolicObj3 Source # 
Instance details

Defined in Graphics.Implicit.Definitions

Generic SymbolicObj3 Source # 
Instance details

Defined in Graphics.Implicit.Definitions

Associated Types

type Rep SymbolicObj3 :: Type -> Type #

Semigroup SymbolicObj3 Source #

Semigroup under union.

Instance details

Defined in Graphics.Implicit.Definitions

Monoid SymbolicObj3 Source #

Monoid under union.

Instance details

Defined in Graphics.Implicit.Definitions

DiscreteAproxable SymbolicObj3 DynamicImage Source # 
Instance details

Defined in Graphics.Implicit.Export.DiscreteAproxable

DiscreteAproxable SymbolicObj3 NormedTriangleMesh Source # 
Instance details

Defined in Graphics.Implicit.Export.DiscreteAproxable

DiscreteAproxable SymbolicObj3 TriangleMesh Source # 
Instance details

Defined in Graphics.Implicit.Export.DiscreteAproxable

Object SymbolicObj3 V3 Source # 
Instance details

Defined in Graphics.Implicit.Primitives

type Rep SymbolicObj3 Source # 
Instance details

Defined in Graphics.Implicit.Definitions

type Rep SymbolicObj3 = D1 ('MetaData "SymbolicObj3" "Graphics.Implicit.Definitions" "implicit-0.4.0.0-2QFrzNvv6lKFGu3kPbjLAC" 'False) (((C1 ('MetaCons "Cube" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 ℝ3)) :+: C1 ('MetaCons "Sphere" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 ))) :+: (C1 ('MetaCons "Cylinder" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 ) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 ) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 ))) :+: (C1 ('MetaCons "Rotate3" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Quaternion )) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 SymbolicObj3)) :+: C1 ('MetaCons "Transform3" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (M44 )) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 SymbolicObj3))))) :+: ((C1 ('MetaCons "Extrude" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 SymbolicObj2) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 )) :+: C1 ('MetaCons "ExtrudeM" 'PrefixI 'False) ((S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Either ( -> ))) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 ExtrudeMScale)) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Either ℝ2 ( -> ℝ2))) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 SymbolicObj2) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Either (ℝ2 -> ))))))) :+: (C1 ('MetaCons "RotateExtrude" 'PrefixI 'False) ((S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 ) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Either ℝ2 ( -> ℝ2)))) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Either ( -> ))) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 SymbolicObj2))) :+: (C1 ('MetaCons "ExtrudeOnEdgeOf" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 SymbolicObj2) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 SymbolicObj2)) :+: C1 ('MetaCons "Shared3" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (SharedObj SymbolicObj3 V3 )))))))

data ExtrudeMScale Source #

Constructors

C1  
C2 ℝ2 
Fn ( -> Either ℝ2) 

Instances

Instances details
Show ExtrudeMScale Source # 
Instance details

Defined in Graphics.Implicit.Definitions

Generic ExtrudeMScale Source # 
Instance details

Defined in Graphics.Implicit.Definitions

Associated Types

type Rep ExtrudeMScale :: Type -> Type #

type Rep ExtrudeMScale Source # 
Instance details

Defined in Graphics.Implicit.Definitions

fromℕtoℝ :: -> Source #

Convert from our Integral to our Rational.

fromFastℕtoℝ :: Fastℕ -> Source #

Convert from our Fast Integer (int32) to ℝ.

fromℝtoFloat :: -> Float Source #

Convert from our rational to a float, for output to a file.