Vis-1.0.0: Painless 3D graphics, no affiliation with gloss
Safe HaskellSafe-Inferred
LanguageHaskell2010

Vis.VisObject

Synopsis

Documentation

data VisObject a Source #

Instances

Instances details
Functor VisObject Source # 
Instance details

Defined in Vis.VisObject

Methods

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

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

Generic (VisObject a) Source # 
Instance details

Defined in Vis.VisObject

Associated Types

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

Methods

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

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

Binary a => Binary (VisObject a) Source # 
Instance details

Defined in Vis.VisObject

Methods

put :: VisObject a -> Put #

get :: Get (VisObject a) #

putList :: [VisObject a] -> Put #

type Rep (VisObject a) Source # 
Instance details

Defined in Vis.VisObject

type Rep (VisObject a) = D1 ('MetaData "VisObject" "Vis.VisObject" "Vis-1.0.0-FwQfBMNitksJIapZIBfVJt" 'False) ((((C1 ('MetaCons "VisObjects" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [VisObject a])) :+: C1 ('MetaCons "Trans" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (V3 a)) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (VisObject a)))) :+: (C1 ('MetaCons "RotQuat" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Quaternion a)) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (VisObject a))) :+: (C1 ('MetaCons "RotDcm" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (M33 a)) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (VisObject a))) :+: C1 ('MetaCons "RotEulerRad" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Euler a)) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (VisObject a)))))) :+: ((C1 ('MetaCons "RotEulerDeg" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Euler a)) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (VisObject a))) :+: (C1 ('MetaCons "Scale" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (a, a, a)) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (VisObject a))) :+: C1 ('MetaCons "Cylinder" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (a, a)) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Color)))) :+: (C1 ('MetaCons "Box" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (a, a, a)) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Flavour) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Color))) :+: (C1 ('MetaCons "Cube" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 a) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Flavour) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Color))) :+: C1 ('MetaCons "Sphere" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 a) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Flavour) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Color))))))) :+: (((C1 ('MetaCons "Ellipsoid" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (a, a, a)) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Flavour) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Color))) :+: (C1 ('MetaCons "Line" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe a)) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [V3 a]) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Color))) :+: C1 ('MetaCons "Line'" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe a)) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [(V3 a, Color)])))) :+: (C1 ('MetaCons "Arrow" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (a, a)) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (V3 a)) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Color))) :+: (C1 ('MetaCons "Axes" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (a, a))) :+: C1 ('MetaCons "Plane" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (V3 a)) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Color) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Color)))))) :+: ((C1 ('MetaCons "Triangle" 'PrefixI 'False) ((S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (V3 a)) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (V3 a))) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (V3 a)) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Color))) :+: (C1 ('MetaCons "Quad" 'PrefixI 'False) ((S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (V3 a)) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (V3 a))) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (V3 a)) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (V3 a)) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Color)))) :+: C1 ('MetaCons "Text3d" 'PrefixI 'False) ((S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 String) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (V3 a))) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 BitmapFont) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Color))))) :+: (C1 ('MetaCons "Text2d" 'PrefixI 'False) ((S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 String) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (a, a))) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 BitmapFont) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Color))) :+: (C1 ('MetaCons "Points" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [V3 a]) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe GLfloat)) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Color))) :+: C1 ('MetaCons "ObjModel" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 LoadedObjModel) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Color)))))))

data LoadedObjModel Source #

Instances

Instances details
Generic LoadedObjModel Source # 
Instance details

Defined in Vis.VisObject

Associated Types

type Rep LoadedObjModel :: Type -> Type #

Binary LoadedObjModel Source # 
Instance details

Defined in Vis.VisObject

type Rep LoadedObjModel Source # 
Instance details

Defined in Vis.VisObject

loadObjModel :: Foldable f => f (V3 Double, V3 Double) -> LoadedObjModel Source #

turn a list of vertexnormal tuples into vertexnormal arrays

data Euler a Source #

3-2-1 Euler angle rotation sequence

Constructors

Euler 

Fields

Instances

Instances details
Functor Euler Source # 
Instance details

Defined in Vis.VisObject

Methods

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

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

Generic (Euler a) Source # 
Instance details

Defined in Vis.VisObject

Associated Types

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

Methods

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

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

Show a => Show (Euler a) Source # 
Instance details

Defined in Vis.VisObject

Methods

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

show :: Euler a -> String #

showList :: [Euler a] -> ShowS #

Binary a => Binary (Euler a) Source # 
Instance details

Defined in Vis.VisObject

Methods

put :: Euler a -> Put #

get :: Get (Euler a) #

putList :: [Euler a] -> Put #

Eq a => Eq (Euler a) Source # 
Instance details

Defined in Vis.VisObject

Methods

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

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

Ord a => Ord (Euler a) Source # 
Instance details

Defined in Vis.VisObject

Methods

compare :: Euler a -> Euler a -> Ordering #

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

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

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

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

max :: Euler a -> Euler a -> Euler a #

min :: Euler a -> Euler a -> Euler a #

type Rep (Euler a) Source # 
Instance details

Defined in Vis.VisObject

type Rep (Euler a) = D1 ('MetaData "Euler" "Vis.VisObject" "Vis-1.0.0-FwQfBMNitksJIapZIBfVJt" 'False) (C1 ('MetaCons "Euler" 'PrefixI 'True) (S1 ('MetaSel ('Just "eYaw") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 a) :*: (S1 ('MetaSel ('Just "ePitch") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 a) :*: S1 ('MetaSel ('Just "eRoll") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 a))))

Orphan instances

Binary Flavour Source # 
Instance details

Methods

put :: Flavour -> Put #

get :: Get Flavour #

putList :: [Flavour] -> Put #

Binary BitmapFont Source # 
Instance details

Binary Color Source # 
Instance details

Methods

put :: Color -> Put #

get :: Get Color #

putList :: [Color] -> Put #