implicit-0.3.0.1: A math-inspired programmatic 2D & 3D CAD system.

Safe HaskellNone
LanguageHaskell2010

Graphics.Implicit.Definitions

Contents

Synopsis

Documentation

newtype Fastℕ Source #

Constructors

Fastℕ Int 
Instances
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
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 ℝ2 = (, ) Source #

both :: (t -> b) -> (t, t) -> (b, b) Source #

apply a function to both items in the provided tuple.

type ℝ3 = (, , ) Source #

allthree :: (t -> b) -> (t, t, t) -> (b, b, b) Source #

apply a function to all three items in the provided tuple.

minℝ :: Source #

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

(⋅) :: InnerSpace a => a -> a -> Scalar a Source #

TODO: Find a better place for this

(⋯*) :: 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)] ---> /\

Constructors

Polyline [ℝ2] 

newtype Polytri Source #

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

Constructors

Polytri (ℝ2, ℝ2, ℝ2) 
Instances
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
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)) 

newtype TriangleMesh Source #

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

Constructors

TriangleMesh [Triangle] 

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 SymbolicObj3 Source #

A symbolic 3D format!

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.

Orphan instances

Show (ℝ3 -> ) Source # 
Instance details

Methods

showsPrec :: Int -> (ℝ3 -> ) -> ShowS #

show :: (ℝ3 -> ) -> String #

showList :: [ℝ3 -> ] -> ShowS #

Show (ℝ2 -> ) Source # 
Instance details

Methods

showsPrec :: Int -> (ℝ2 -> ) -> ShowS #

show :: (ℝ2 -> ) -> String #

showList :: [ℝ2 -> ] -> ShowS #

Show ( -> ℝ2) Source # 
Instance details

Methods

showsPrec :: Int -> ( -> ℝ2) -> ShowS #

show :: ( -> ℝ2) -> String #

showList :: [ -> ℝ2] -> ShowS #

Show ( -> ) Source #

add aditional instances to Show, for when we dump the intermediate form of objects. FIXME: store functions in a dumpable form! These instances cover functions

Instance details

Methods

showsPrec :: Int -> ( -> ) -> ShowS #

show :: ( -> ) -> String #

showList :: [ -> ] -> ShowS #