diagrams-lib-1.4.2.1: Embedded domain-specific language for declarative graphics

Copyright(c) 2011 diagrams-lib team (see LICENSE)
LicenseBSD-style (see LICENSE)
Maintainerdiagrams-discuss@googlegroups.com
Safe HaskellNone
LanguageHaskell2010

Diagrams.ThreeD.Shapes

Contents

Description

Various three-dimensional shapes.

Synopsis

Skinned class

class Skinned t where Source #

Types which can be rendered as 3D Diagrams.

Minimal complete definition

skin

Methods

skin :: (Renderable t b, N t ~ n, TypeableFloat n) => t -> QDiagram b V3 n Any Source #

Instances

(RealFloat n, Ord n) => Skinned (CSG n) Source # 

Methods

skin :: (Renderable (CSG n) b, (* ~ N (CSG n)) n, TypeableFloat n) => CSG n -> QDiagram b V3 n Any Source #

Skinned (Frustum n) Source # 

Methods

skin :: (Renderable (Frustum n) b, (* ~ N (Frustum n)) n, TypeableFloat n) => Frustum n -> QDiagram b V3 n Any Source #

OrderedField n => Skinned (Box n) Source # 

Methods

skin :: (Renderable (Box n) b, (* ~ N (Box n)) n, TypeableFloat n) => Box n -> QDiagram b V3 n Any Source #

OrderedField n => Skinned (Ellipsoid n) Source # 

Methods

skin :: (Renderable (Ellipsoid n) b, (* ~ N (Ellipsoid n)) n, TypeableFloat n) => Ellipsoid n -> QDiagram b V3 n Any Source #

Basic 3D shapes

sphere :: Num n => Ellipsoid n Source #

A sphere of radius 1 with its center at the origin.

data Box n Source #

Constructors

Box (Transformation V3 n) 

Instances

OrderedField n => Enveloped (Box n) Source # 

Methods

getEnvelope :: Box n -> Envelope (V (Box n)) (N (Box n)) #

(Fractional n, Ord n) => Traced (Box n) Source # 

Methods

getTrace :: Box n -> Trace (V (Box n)) (N (Box n)) #

Fractional n => Transformable (Box n) Source # 

Methods

transform :: Transformation (V (Box n)) (N (Box n)) -> Box n -> Box n #

OrderedField n => Skinned (Box n) Source # 

Methods

skin :: (Renderable (Box n) b, (* ~ N (Box n)) n, TypeableFloat n) => Box n -> QDiagram b V3 n Any Source #

Fractional n => Renderable (Box n) NullBackend Source # 

Methods

render :: NullBackend -> Box n -> Render NullBackend (V (Box n)) (N (Box n)) #

(Num n, Ord n) => HasQuery (Box n) Any Source # 

Methods

getQuery :: Box n -> Query (V (Box n)) (N (Box n)) Any Source #

type V (Box n) Source # 
type V (Box n) = V3
type N (Box n) Source # 
type N (Box n) = n

cube :: Num n => Box n Source #

A cube with side length 1, in the positive octant, with one vertex at the origin.

data Frustum n Source #

Constructors

Frustum n n (Transformation V3 n) 

Instances

(OrderedField n, RealFloat n) => Enveloped (Frustum n) Source # 

Methods

getEnvelope :: Frustum n -> Envelope (V (Frustum n)) (N (Frustum n)) #

(RealFloat n, Ord n) => Traced (Frustum n) Source # 

Methods

getTrace :: Frustum n -> Trace (V (Frustum n)) (N (Frustum n)) #

Fractional n => Transformable (Frustum n) Source # 

Methods

transform :: Transformation (V (Frustum n)) (N (Frustum n)) -> Frustum n -> Frustum n #

Skinned (Frustum n) Source # 

Methods

skin :: (Renderable (Frustum n) b, (* ~ N (Frustum n)) n, TypeableFloat n) => Frustum n -> QDiagram b V3 n Any Source #

Fractional n => Renderable (Frustum n) NullBackend Source # 

Methods

render :: NullBackend -> Frustum n -> Render NullBackend (V (Frustum n)) (N (Frustum n)) #

OrderedField n => HasQuery (Frustum n) Any Source # 

Methods

getQuery :: Frustum n -> Query (V (Frustum n)) (N (Frustum n)) Any Source #

type V (Frustum n) Source # 
type V (Frustum n) = V3
type N (Frustum n) Source # 
type N (Frustum n) = n

frustum :: Num n => n -> n -> Frustum n Source #

A frustum of a right circular cone. It has height 1 oriented along the positive z axis, and radii r0 and r1 at Z=0 and Z=1. cone and cylinder are special cases.

cone :: Num n => Frustum n Source #

A cone with its base centered on the origin, with radius 1 at the base, height 1, and it's apex on the positive Z axis.

cylinder :: Num n => Frustum n Source #

A circular cylinder of radius 1 with one end cap centered on the origin, and extending to Z=1.

Constructive solid geometry

data CSG n Source #

A tree of Constructive Solid Geometry operations and the primitives that can be used in them.

Instances

RealFloat n => Enveloped (CSG n) Source #

The Envelope for an Intersection or Difference is simply the Envelope of the Union. This is wrong but easy to implement.

Methods

getEnvelope :: CSG n -> Envelope (V (CSG n)) (N (CSG n)) #

(RealFloat n, Ord n) => Traced (CSG n) Source # 

Methods

getTrace :: CSG n -> Trace (V (CSG n)) (N (CSG n)) #

Fractional n => Transformable (CSG n) Source # 

Methods

transform :: Transformation (V (CSG n)) (N (CSG n)) -> CSG n -> CSG n #

(RealFloat n, Ord n) => Skinned (CSG n) Source # 

Methods

skin :: (Renderable (CSG n) b, (* ~ N (CSG n)) n, TypeableFloat n) => CSG n -> QDiagram b V3 n Any Source #

(Floating n, Ord n) => HasQuery (CSG n) Any Source # 

Methods

getQuery :: CSG n -> Query (V (CSG n)) (N (CSG n)) Any Source #

type V (CSG n) Source # 
type V (CSG n) = V3
type N (CSG n) Source # 
type N (CSG n) = n

union :: (CsgPrim a, CsgPrim b) => a n -> b n -> CSG n Source #

intersection :: (CsgPrim a, CsgPrim b) => a n -> b n -> CSG n Source #

difference :: (CsgPrim a, CsgPrim b) => a n -> b n -> CSG n Source #