Safe Haskell | Safe-Inferred |
---|---|
Language | Haskell2010 |
Graphics.Implicit
Synopsis
- type ℝ = Double
- type ℝ2 = V2 ℝ
- type ℝ3 = V3 ℝ
- data SymbolicObj2
- data SymbolicObj3
- data ExtrudeMScale
- class (Applicative f, Eq a, Eq (f a), Foldable f, Num a, Num (f a)) => Object obj f a | obj -> f a
- translate :: Object obj f a => f a -> obj -> obj
- scale :: Object obj f a => f a -> obj -> obj
- mirror :: Object obj f a => f a -> obj -> obj
- complement :: Object obj f a => obj -> obj
- union :: Object obj f a => [obj] -> obj
- unionR :: Object obj f a => ℝ -> [obj] -> obj
- intersect :: Object obj f a => [obj] -> obj
- intersectR :: Object obj f a => ℝ -> [obj] -> obj
- difference :: Object obj f a => obj -> [obj] -> obj
- differenceR :: Object obj f a => ℝ -> obj -> [obj] -> obj
- implicit :: Object obj f a => (f a -> a) -> (f a, f a) -> obj
- shell :: Object obj f a => ℝ -> obj -> obj
- outset :: Object obj f a => ℝ -> obj -> obj
- emptySpace :: Object obj f a => obj
- fullSpace :: Object obj f a => obj
- withRounding :: Object obj f a => ℝ -> obj -> obj
- square :: Bool -> ℝ2 -> SymbolicObj2
- rect :: ℝ2 -> ℝ2 -> SymbolicObj2
- circle :: ℝ -> SymbolicObj2
- polygon :: [ℝ2] -> SymbolicObj2
- rotate :: ℝ -> SymbolicObj2 -> SymbolicObj2
- transform :: M33 ℝ -> SymbolicObj2 -> SymbolicObj2
- pack2 :: ℝ2 -> ℝ -> [SymbolicObj2] -> Maybe SymbolicObj2
- cube :: Bool -> ℝ3 -> SymbolicObj3
- rect3 :: ℝ3 -> ℝ3 -> SymbolicObj3
- sphere :: ℝ -> SymbolicObj3
- cylinder :: ℝ -> ℝ -> SymbolicObj3
- cylinder2 :: ℝ -> ℝ -> ℝ -> SymbolicObj3
- rotate3 :: ℝ3 -> SymbolicObj3 -> SymbolicObj3
- rotate3V :: ℝ -> ℝ3 -> SymbolicObj3 -> SymbolicObj3
- pack3 :: ℝ2 -> ℝ -> [SymbolicObj3] -> Maybe SymbolicObj3
- transform3 :: M44 ℝ -> SymbolicObj3 -> SymbolicObj3
- extrude :: SymbolicObj2 -> ℝ -> SymbolicObj3
- extrudeM :: Either ℝ (ℝ -> ℝ) -> ExtrudeMScale -> Either ℝ2 (ℝ -> ℝ2) -> SymbolicObj2 -> Either ℝ (ℝ2 -> ℝ) -> SymbolicObj3
- extrudeOnEdgeOf :: SymbolicObj2 -> SymbolicObj2 -> SymbolicObj3
- rotateExtrude :: ℝ -> Either ℝ2 (ℝ -> ℝ2) -> Either ℝ (ℝ -> ℝ) -> SymbolicObj2 -> SymbolicObj3
- runOpenscad :: ScadOpts -> [String] -> String -> IO (VarLookup, [SymbolicObj2], [SymbolicObj3], [Message])
- writeSVG :: ℝ -> FilePath -> SymbolicObj2 -> IO ()
- writePNG2 :: ℝ -> FilePath -> SymbolicObj2 -> IO ()
- writeDXF2 :: ℝ -> FilePath -> SymbolicObj2 -> IO ()
- writeSCAD2 :: ℝ -> FilePath -> SymbolicObj2 -> IO ()
- writeGCodeHacklabLaser :: ℝ -> FilePath -> SymbolicObj2 -> IO ()
- writeSTL :: ℝ -> FilePath -> SymbolicObj3 -> IO ()
- writeBinSTL :: ℝ -> FilePath -> SymbolicObj3 -> IO ()
- writeOBJ :: ℝ -> FilePath -> SymbolicObj3 -> IO ()
- writeTHREEJS :: ℝ -> FilePath -> SymbolicObj3 -> IO ()
- writeSCAD3 :: ℝ -> FilePath -> SymbolicObj3 -> IO ()
- writePNG3 :: ℝ -> FilePath -> SymbolicObj3 -> IO ()
- data V2 a = V2 !a !a
- data V3 a = V3 !a !a !a
- data Quaternion a = Quaternion !a !(V3 a)
Types
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.
A pair of two Double
s. When used as an area or position vector, measured
in millimeters squared.
A triple of Double
s. When used as a volume or position vector, measured
in millimeters cubed. When used as a rotation, interpreted as Euler angles
measured in radians.
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
data SymbolicObj3 Source #
A symbolic 3D format!
Instances
data ExtrudeMScale Source #
Instances
Shared operations
class (Applicative f, Eq a, Eq (f a), Foldable f, Num a, Num (f a)) => Object obj f a | obj -> f a Source #
Operations available on both 2D and 3D objects. The obvious omission of
rotation operations from this class are a technical limitation, and are
instead provided by rotate
and rotate3
.
Library users shouldn't need to provide new instances of this class.
Minimal complete definition
Instances
Object SymbolicObj2 V2 ℝ Source # | |
Defined in Graphics.Implicit.Primitives Methods _Shared :: Prism' SymbolicObj2 (SharedObj SymbolicObj2 V2 ℝ) Source # getBox :: SymbolicObj2 -> (V2 ℝ, V2 ℝ) Source # getImplicit' :: ObjectContext -> SymbolicObj2 -> V2 ℝ -> ℝ Source # | |
Object SymbolicObj3 V3 ℝ Source # | |
Defined in Graphics.Implicit.Primitives Methods _Shared :: Prism' SymbolicObj3 (SharedObj SymbolicObj3 V3 ℝ) Source # getBox :: SymbolicObj3 -> (V3 ℝ, V3 ℝ) Source # getImplicit' :: ObjectContext -> SymbolicObj3 -> V3 ℝ -> ℝ Source # |
Arguments
:: Object obj f a | |
=> f a | Vector to translate by |
-> obj | Object to translate |
-> obj | Resulting object |
Translate an object by a vector of appropriate dimension.
Arguments
:: Object obj f a | |
=> f a | Amount to scale by |
-> obj | Object to scale |
-> obj | Resulting scaled object |
Scale an object
Arguments
:: Object obj f a | |
=> f a | Vector defining the hyperplane |
-> obj | Object to mirror |
-> obj | Resulting object |
Mirror an object across the hyperplane whose normal is a given vector.
Arguments
:: Object obj f a | |
=> obj | Object to complement |
-> obj | Result |
Complement an Object
Arguments
:: Object obj f a | |
=> ℝ | The radius (in mm) of rounding |
-> [obj] | objects to union |
-> obj | Resulting object |
Rounded union
Arguments
:: Object obj f a | |
=> ℝ | The radius (in mm) of rounding |
-> [obj] | Objects to intersect |
-> obj | Resulting object |
Rounded minimum
difference :: Object obj f a => obj -> [obj] -> obj Source #
Arguments
:: Object obj f a | |
=> ℝ | The radius (in mm) of rounding |
-> obj | Base object |
-> [obj] | Objects to subtract from the base |
-> obj | Resulting object |
Rounded difference
Arguments
:: Object obj f a | |
=> (f a -> a) | Implicit function |
-> (f a, f a) | Bounding box |
-> obj | Resulting object |
Make a shell of an object.
Outset of an object.
emptySpace :: Object obj f a => obj Source #
The object that fills no space
withRounding :: Object obj f a => ℝ -> obj -> obj Source #
Set the current object-rounding value for the given object. The rounding value is measured in units of distance, and describes the radius of rounded corners.
This can be used to change the shape of more primitive forms, for example,
we can make a cube with rounded corners via withRounding 5 (
.cube
True
20)
applies the rounding withRounding
r objr
all primitives objects in
obj
, so long as they have the same dimensionality. That is to say,
the current object-rounding value set in 3D will not apply to extruded 2D
shapes.
2D primitive shapes
Arguments
:: Bool | Centered? |
-> ℝ2 | Size |
-> SymbolicObj2 | Resulting square (bottom right = (0,0) ) |
A square
Arguments
:: ℝ2 | Bottom left corner |
-> ℝ2 | Top right corner |
-> SymbolicObj2 | Resulting square |
A rectangle
Arguments
:: ℝ | radius of the circle |
-> SymbolicObj2 | resulting circle |
Arguments
:: [ℝ2] | Verticies of the polygon |
-> SymbolicObj2 | Resulting polygon |
A 2D polygon
2D operations
rotate :: ℝ -> SymbolicObj2 -> SymbolicObj2 Source #
transform :: M33 ℝ -> SymbolicObj2 -> SymbolicObj2 Source #
Transform a 2D object using a 3x3 matrix representing affine transformation (OpenSCAD multmatrix)
Arguments
:: ℝ2 | Area to pack |
-> ℝ | Separation between objects |
-> [SymbolicObj2] | Objects to pack |
-> Maybe SymbolicObj2 |
|
Attempt to pack multiple 2D objects into a fixed area.
3D primitive shapes
Arguments
:: Bool | Centered? |
-> ℝ3 | Size |
-> SymbolicObj3 | Resuting cube. (0,0,0) is bottom left if |
A cube
Arguments
:: ℝ3 | Bottom.. corner |
-> ℝ3 | Top right... corner |
-> SymbolicObj3 | Resuting cube |
A rectangular prism
Arguments
:: ℝ | Radius of the sphere |
-> SymbolicObj3 | Resulting sphere |
Arguments
:: ℝ | Radius of the cylinder |
-> ℝ | Height of the cylinder |
-> SymbolicObj3 | Resulting cylinder |
Arguments
:: ℝ | Radius of the cylinder |
-> ℝ | Second radius of the cylinder |
-> ℝ | Height of the cylinder |
-> SymbolicObj3 | Resulting cylinder |
A conical frustum --- ie. a cylinder with different radii at either end.
3D operations
rotate3 :: ℝ3 -> SymbolicObj3 -> SymbolicObj3 Source #
Rotate a 3D object via an Euler angle, measured in radians, along the world axis.
Arguments
:: ℝ | Angle of rotation |
-> ℝ3 | Axis of rotation |
-> SymbolicObj3 | |
-> SymbolicObj3 |
Rotate a 3D object along an arbitrary axis.
Arguments
:: ℝ2 | Area to pack |
-> ℝ | Separation between objects |
-> [SymbolicObj3] | Objects to pack |
-> Maybe SymbolicObj3 |
|
Attempt to pack multiple 3D objects into a fixed area. The z
coordinate
of each object is dropped, and the resulting packed objects will all be on
the same plane.
FIXME: shouldn't this pack into a 3d area, or have a 3d equivalent?
transform3 :: M44 ℝ -> SymbolicObj3 -> SymbolicObj3 Source #
Transform a 3D object using a 4x4 matrix representing affine transformation (OpenSCAD multmatrix)
Extrusions into 3D
Arguments
:: SymbolicObj2 | |
-> ℝ | Extrusion height |
-> SymbolicObj3 |
Extrude a 2d object upwards. The current object-rounding value set by
withRounding
is used to round the caps, but is not used by the 2D object.
Arguments
:: Either ℝ (ℝ -> ℝ) | twist |
-> ExtrudeMScale | scale |
-> Either ℝ2 (ℝ -> ℝ2) | translate |
-> SymbolicObj2 | object to extrude |
-> Either ℝ (ℝ2 -> ℝ) | height to extrude to |
-> SymbolicObj3 |
The current object-rounding value set by withRounding
is used to round
the caps, but is not used by the 2D object.
OpenScad support
runOpenscad :: ScadOpts -> [String] -> String -> IO (VarLookup, [SymbolicObj2], [SymbolicObj3], [Message]) Source #
Small wrapper of our parser to handle parse errors, etc.
2D exporters
Arguments
:: ℝ | Rendering resolution, in millimeters. Smaller values produce exports more faithful to the implicit model, at the expense of taking O(n^-2) more time. |
-> FilePath | |
-> SymbolicObj2 | |
-> IO () |
Arguments
:: ℝ | Rendering resolution, in millimeters. Smaller values produce exports more faithful to the implicit model, at the expense of taking O(n^-2) more time. |
-> FilePath | |
-> SymbolicObj2 | |
-> IO () |
Arguments
:: ℝ | Rendering resolution, in millimeters. Smaller values produce exports more faithful to the implicit model, at the expense of taking O(n^-2) more time. |
-> FilePath | |
-> SymbolicObj2 | |
-> IO () |
Arguments
:: ℝ | Rendering resolution, in millimeters. Smaller values produce exports more faithful to the implicit model, at the expense of taking O(n^-2) more time. |
-> FilePath | |
-> SymbolicObj2 | |
-> IO () |
writeGCodeHacklabLaser Source #
Arguments
:: ℝ | Rendering resolution, in millimeters. Smaller values produce exports more faithful to the implicit model, at the expense of taking O(n^-2) more time. |
-> FilePath | |
-> SymbolicObj2 | |
-> IO () |
3D exporters
Arguments
:: ℝ | Rendering resolution, in millimeters. Smaller values produce exports more faithful to the implicit model, at the expense of taking O(n^-3) more time. |
-> FilePath | |
-> SymbolicObj3 | |
-> IO () |
Arguments
:: ℝ | Rendering resolution, in millimeters. Smaller values produce exports more faithful to the implicit model, at the expense of taking O(n^-3) more time. |
-> FilePath | |
-> SymbolicObj3 | |
-> IO () |
Arguments
:: ℝ | Rendering resolution, in millimeters. Smaller values produce exports more faithful to the implicit model, at the expense of taking O(n^-3) more time. |
-> FilePath | |
-> SymbolicObj3 | |
-> IO () |
Arguments
:: ℝ | Rendering resolution, in millimeters. Smaller values produce exports more faithful to the implicit model, at the expense of taking O(n^-3) more time. |
-> FilePath | |
-> SymbolicObj3 | |
-> IO () |
Arguments
:: ℝ | Rendering resolution, in millimeters. Smaller values produce exports more faithful to the implicit model, at the expense of taking O(n^-3) more time. |
-> FilePath | |
-> SymbolicObj3 | |
-> IO () |
Arguments
:: ℝ | Rendering resolution, in millimeters. Smaller values produce exports more faithful to the implicit model, at the expense of taking O(n^-3) more time. |
-> FilePath | |
-> SymbolicObj3 | |
-> IO () |
Export a PNG of the SymbolicObj3
. The projection is with a front-facing
camera, so the coordinate system is (left to right, front to back, down to
up)
.
Linear re-exports
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
Representable V2 | |
MonadFix V2 | |
MonadZip V2 | |
Foldable V2 | |
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 # elem :: Eq a => a -> V2 a -> Bool # maximum :: Ord a => V2 a -> a # | |
Eq1 V2 | |
Ord1 V2 | |
Read1 V2 | |
Show1 V2 | |
Traversable V2 | |
Applicative V2 | |
Functor V2 | |
Monad V2 | |
Serial1 V2 | |
Defined in Linear.V2 Methods serializeWith :: MonadPut m => (a -> m ()) -> V2 a -> m () # deserializeWith :: MonadGet m => m a -> m (V2 a) # | |
Distributive V2 | |
Foldable1 V2 | |
Defined in Linear.V2 Methods fold1 :: Semigroup m => V2 m -> m # foldMap1 :: Semigroup m => (a -> m) -> V2 a -> m # foldMap1' :: Semigroup m => (a -> m) -> V2 a -> m # toNonEmpty :: V2 a -> NonEmpty a # maximum :: Ord a => V2 a -> a # minimum :: Ord a => V2 a -> a # foldrMap1 :: (a -> b) -> (a -> b -> b) -> V2 a -> b # foldlMap1' :: (a -> b) -> (b -> a -> b) -> V2 a -> b # foldlMap1 :: (a -> b) -> (b -> a -> b) -> V2 a -> b # foldrMap1' :: (a -> b) -> (a -> b -> b) -> V2 a -> b # | |
Hashable1 V2 | |
ComponentWiseMultable ℝ2 Source # | |
Affine V2 | |
Metric V2 | |
Finite V2 | |
R1 V2 | |
R2 V2 | |
Additive V2 | |
Apply V2 | |
Bind V2 | |
Traversable1 V2 | |
Generic1 V2 | |
Object SymbolicObj2 V2 ℝ Source # | |
Defined in Graphics.Implicit.Primitives Methods _Shared :: Prism' SymbolicObj2 (SharedObj SymbolicObj2 V2 ℝ) Source # getBox :: SymbolicObj2 -> (V2 ℝ, V2 ℝ) Source # getImplicit' :: ObjectContext -> SymbolicObj2 -> V2 ℝ -> ℝ Source # | |
Unbox a => Vector Vector (V2 a) | |
Defined in Linear.V2 Methods basicUnsafeFreeze :: Mutable Vector s (V2 a) -> ST s (Vector (V2 a)) # basicUnsafeThaw :: Vector (V2 a) -> ST s (Mutable Vector s (V2 a)) # basicLength :: Vector (V2 a) -> Int # basicUnsafeSlice :: Int -> Int -> Vector (V2 a) -> Vector (V2 a) # basicUnsafeIndexM :: Vector (V2 a) -> Int -> Box (V2 a) # basicUnsafeCopy :: Mutable Vector s (V2 a) -> Vector (V2 a) -> ST s () # | |
Unbox a => MVector MVector (V2 a) | |
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 :: Int -> ST s (MVector s (V2 a)) # basicInitialize :: MVector s (V2 a) -> ST s () # basicUnsafeReplicate :: Int -> V2 a -> ST s (MVector s (V2 a)) # basicUnsafeRead :: MVector s (V2 a) -> Int -> ST s (V2 a) # basicUnsafeWrite :: MVector s (V2 a) -> Int -> V2 a -> ST s () # basicClear :: MVector s (V2 a) -> ST s () # basicSet :: MVector s (V2 a) -> V2 a -> ST s () # basicUnsafeCopy :: MVector s (V2 a) -> MVector s (V2 a) -> ST s () # basicUnsafeMove :: MVector s (V2 a) -> MVector s (V2 a) -> ST s () # basicUnsafeGrow :: MVector s (V2 a) -> Int -> ST s (MVector s (V2 a)) # | |
Data a => Data (V2 a) | |
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) # 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) # | |
Storable a => Storable (V2 a) | |
Monoid a => Monoid (V2 a) | |
Semigroup a => Semigroup (V2 a) | |
Bounded a => Bounded (V2 a) | |
Floating a => Floating (V2 a) | |
Generic (V2 a) | |
Ix a => Ix (V2 a) | |
Num a => Num (V2 a) | |
Read a => Read (V2 a) | |
Fractional a => Fractional (V2 a) | |
Show a => Show (V2 a) | |
Binary a => Binary (V2 a) | |
Serial a => Serial (V2 a) | |
Serialize a => Serialize (V2 a) | |
NFData a => NFData (V2 a) | |
Eq a => Eq (V2 a) | |
Ord a => Ord (V2 a) | |
Hashable a => Hashable (V2 a) | |
Ixed (V2 a) | |
Epsilon a => Epsilon (V2 a) | |
Random a => Random (V2 a) | |
Unbox a => Unbox (V2 a) | |
Defined in Linear.V2 | |
FoldableWithIndex (E V2) V2 | |
FunctorWithIndex (E V2) V2 | |
TraversableWithIndex (E V2) V2 | |
Lift a => Lift (V2 a :: Type) | |
Each (V2 a) (V2 b) a b | |
Field1 (V2 a) (V2 a) a a | |
Field2 (V2 a) (V2 a) a a | |
type Rep V2 | |
type Diff V2 | |
Defined in Linear.Affine | |
type Size V2 | |
type Rep1 V2 | |
Defined in Linear.V2 type Rep1 V2 = D1 ('MetaData "V2" "Linear.V2" "linear-1.22-RQ2AYz1OLxFCpCY5CLqBO" 'False) (C1 ('MetaCons "V2" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) Par1 :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) Par1)) | |
data MVector s (V2 a) | |
type Rep (V2 a) | |
Defined in Linear.V2 type Rep (V2 a) = D1 ('MetaData "V2" "Linear.V2" "linear-1.22-RQ2AYz1OLxFCpCY5CLqBO" '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))) | |
type Index (V2 a) | |
type IxValue (V2 a) | |
data Vector (V2 a) | |
A 3-dimensional vector
Constructors
V3 !a !a !a |
Instances
Representable V3 | |
MonadFix V3 | |
MonadZip V3 | |
Foldable V3 | |
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 # elem :: Eq a => a -> V3 a -> Bool # maximum :: Ord a => V3 a -> a # | |
Eq1 V3 | |
Ord1 V3 | |
Read1 V3 | |
Show1 V3 | |
Traversable V3 | |
Applicative V3 | |
Functor V3 | |
Monad V3 | |
Serial1 V3 | |
Defined in Linear.V3 Methods serializeWith :: MonadPut m => (a -> m ()) -> V3 a -> m () # deserializeWith :: MonadGet m => m a -> m (V3 a) # | |
Distributive V3 | |
Foldable1 V3 | |
Defined in Linear.V3 Methods fold1 :: Semigroup m => V3 m -> m # foldMap1 :: Semigroup m => (a -> m) -> V3 a -> m # foldMap1' :: Semigroup m => (a -> m) -> V3 a -> m # toNonEmpty :: V3 a -> NonEmpty a # maximum :: Ord a => V3 a -> a # minimum :: Ord a => V3 a -> a # foldrMap1 :: (a -> b) -> (a -> b -> b) -> V3 a -> b # foldlMap1' :: (a -> b) -> (b -> a -> b) -> V3 a -> b # foldlMap1 :: (a -> b) -> (b -> a -> b) -> V3 a -> b # foldrMap1' :: (a -> b) -> (a -> b -> b) -> V3 a -> b # | |
Hashable1 V3 | |
ComponentWiseMultable ℝ3 Source # | |
Affine V3 | |
Metric V3 | |
Finite V3 | |
R1 V3 | |
R2 V3 | |
R3 V3 | |
Additive V3 | |
Apply V3 | |
Bind V3 | |
Traversable1 V3 | |
Generic1 V3 | |
Object SymbolicObj3 V3 ℝ Source # | |
Defined in Graphics.Implicit.Primitives Methods _Shared :: Prism' SymbolicObj3 (SharedObj SymbolicObj3 V3 ℝ) Source # getBox :: SymbolicObj3 -> (V3 ℝ, V3 ℝ) Source # getImplicit' :: ObjectContext -> SymbolicObj3 -> V3 ℝ -> ℝ Source # | |
Unbox a => Vector Vector (V3 a) | |
Defined in Linear.V3 Methods basicUnsafeFreeze :: Mutable Vector s (V3 a) -> ST s (Vector (V3 a)) # basicUnsafeThaw :: Vector (V3 a) -> ST s (Mutable Vector s (V3 a)) # basicLength :: Vector (V3 a) -> Int # basicUnsafeSlice :: Int -> Int -> Vector (V3 a) -> Vector (V3 a) # basicUnsafeIndexM :: Vector (V3 a) -> Int -> Box (V3 a) # basicUnsafeCopy :: Mutable Vector s (V3 a) -> Vector (V3 a) -> ST s () # | |
Unbox a => MVector MVector (V3 a) | |
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 :: Int -> ST s (MVector s (V3 a)) # basicInitialize :: MVector s (V3 a) -> ST s () # basicUnsafeReplicate :: Int -> V3 a -> ST s (MVector s (V3 a)) # basicUnsafeRead :: MVector s (V3 a) -> Int -> ST s (V3 a) # basicUnsafeWrite :: MVector s (V3 a) -> Int -> V3 a -> ST s () # basicClear :: MVector s (V3 a) -> ST s () # basicSet :: MVector s (V3 a) -> V3 a -> ST s () # basicUnsafeCopy :: MVector s (V3 a) -> MVector s (V3 a) -> ST s () # basicUnsafeMove :: MVector s (V3 a) -> MVector s (V3 a) -> ST s () # basicUnsafeGrow :: MVector s (V3 a) -> Int -> ST s (MVector s (V3 a)) # | |
Data a => Data (V3 a) | |
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) # 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) # | |
Storable a => Storable (V3 a) | |
Monoid a => Monoid (V3 a) | |
Semigroup a => Semigroup (V3 a) | |
Bounded a => Bounded (V3 a) | |
Floating a => Floating (V3 a) | |
Generic (V3 a) | |
Ix a => Ix (V3 a) | |
Num a => Num (V3 a) | |
Read a => Read (V3 a) | |
Fractional a => Fractional (V3 a) | |
Show a => Show (V3 a) | |
Binary a => Binary (V3 a) | |
Serial a => Serial (V3 a) | |
Serialize a => Serialize (V3 a) | |
NFData a => NFData (V3 a) | |
Eq a => Eq (V3 a) | |
Ord a => Ord (V3 a) | |
Hashable a => Hashable (V3 a) | |
Ixed (V3 a) | |
Epsilon a => Epsilon (V3 a) | |
Random a => Random (V3 a) | |
Unbox a => Unbox (V3 a) | |
Defined in Linear.V3 | |
FoldableWithIndex (E V3) V3 | |
FunctorWithIndex (E V3) V3 | |
TraversableWithIndex (E V3) V3 | |
Lift a => Lift (V3 a :: Type) | |
Each (V3 a) (V3 b) a b | |
Field1 (V3 a) (V3 a) a a | |
Field2 (V3 a) (V3 a) a a | |
Field3 (V3 a) (V3 a) a a | |
type Rep V3 | |
type Diff V3 | |
Defined in Linear.Affine | |
type Size V3 | |
type Rep1 V3 | |
Defined in Linear.V3 type Rep1 V3 = D1 ('MetaData "V3" "Linear.V3" "linear-1.22-RQ2AYz1OLxFCpCY5CLqBO" 'False) (C1 ('MetaCons "V3" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) Par1 :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) Par1 :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) Par1))) | |
data MVector s (V3 a) | |
type Rep (V3 a) | |
Defined in Linear.V3 type Rep (V3 a) = D1 ('MetaData "V3" "Linear.V3" "linear-1.22-RQ2AYz1OLxFCpCY5CLqBO" 'False) (C1 ('MetaCons "V3" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 a) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 a) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 a)))) | |
type Index (V3 a) | |
type IxValue (V3 a) | |
data Vector (V3 a) | |
data Quaternion a #
Quaternions
Constructors
Quaternion !a !(V3 a) |