-- Hoogle documentation, generated by Haddock -- See Hoogle, http://www.haskell.org/hoogle/ -- | Core libraries for diagrams EDSL -- -- The core modules underlying diagrams, an embedded domain-specific -- language for compositional, declarative drawing. @package diagrams-core @version 0.6.0.2 -- | Type family for identifying associated vector spaces. module Diagrams.Core.V -- | Many sorts of objects have an associated vector space in which they -- "live". The type function V maps from object types to the -- associated vector space. -- | A type for points (as distinct from vectors). module Diagrams.Core.Points -- | Point is a newtype wrapper around vectors used to represent -- points, so we don't get them mixed up. The distinction between vectors -- and points is important: translations affect points, but leave vectors -- unchanged. Points are instances of the AffineSpace class from -- Data.AffineSpace. newtype Point v :: * -> * P :: v -> Point v -- | The origin of the vector space v. origin :: AdditiveGroup v => Point v -- | Scale a point by a scalar. (*.) :: VectorSpace v => Scalar v -> Point v -> Point v -- | This module defines a type of names which can be used for referring to -- locations within diagrams, and related types. module Diagrams.Core.Names -- | Atomic names. AName is just an existential wrapper around -- things which are Typeable, Ord and Show. data AName AName :: a -> AName -- | A (qualified) name is a (possibly empty) sequence of atomic names. newtype Name Name :: [AName] -> Name -- | Class for those types which can be used as names. They must support -- Typeable (to facilitate extracting them from existential -- wrappers), Ord (for comparison and efficient storage) and -- Show. class (Typeable a, Ord a, Show a) => IsName a where toName = Name . (: []) . AName toName :: IsName a => a -> Name -- | Convenient operator for writing qualified names with atomic components -- of different types. Instead of writing toName a1 <> toName -- a2 <> toName a3 you can just write a1 .> a2 .> -- a3. (.>) :: (IsName a1, IsName a2) => a1 -> a2 -> Name -- | Instances of Qualifiable are things which can be qualified by -- prefixing them with a name. class Qualifiable q (|>) :: (Qualifiable q, IsName a) => a -> q -> q instance [overlap ok] Typeable AName instance [overlap ok] Typeable Name instance [overlap ok] Eq Name instance [overlap ok] Ord Name instance [overlap ok] Semigroup Name instance [overlap ok] Monoid Name instance [overlap ok] Qualifiable Name instance [overlap ok] IsName Name instance [overlap ok] Show Name instance [overlap ok] Show AName instance [overlap ok] Ord AName instance [overlap ok] Eq AName instance [overlap ok] IsName AName instance [overlap ok] (IsName a, IsName b, IsName c) => IsName (a, b, c) instance [overlap ok] (IsName a, IsName b) => IsName (a, b) instance [overlap ok] IsName a => IsName [a] instance [overlap ok] IsName String instance [overlap ok] IsName Integer instance [overlap ok] IsName Double instance [overlap ok] IsName Float instance [overlap ok] IsName Int instance [overlap ok] IsName Char instance [overlap ok] IsName Bool instance [overlap ok] IsName () -- | Types which have an intrinsic notion of a "local origin", i.e. -- things which are not invariant under translation. module Diagrams.Core.HasOrigin -- | Class of types which have an intrinsic notion of a "local origin", -- i.e. things which are not invariant under translation, and which allow -- the origin to be moved. -- -- One might wonder why not just use Transformable instead of -- having a separate class for HasOrigin; indeed, for types which -- are instances of both we should have the identity -- --
--   moveOriginTo (origin .^+ v) === translate (negateV v)
--   
-- -- The reason is that some things (e.g. vectors, Trails) are -- transformable but are translationally invariant, i.e. have no origin. class VectorSpace (V t) => HasOrigin t moveOriginTo :: HasOrigin t => Point (V t) -> t -> t -- | Move the local origin by a relative vector. moveOriginBy :: HasOrigin t => V t -> t -> t -- | Translate the object by the translation that sends the origin to the -- given point. Note that this is dual to moveOriginTo, i.e. we -- should have -- --
--   moveTo (origin .^+ v) === moveOriginTo (origin .^- v)
--   
-- -- For types which are also Transformable, this is essentially -- the same as translate, i.e. -- --
--   moveTo (origin .^+ v) === translate v
--   
moveTo :: HasOrigin t => Point (V t) -> t -> t -- | A flipped variant of moveTo, provided for convenience. Useful -- when writing a function which takes a point as an argument, such as -- when using withName and friends. place :: HasOrigin t => t -> Point (V t) -> t instance HasOrigin a => HasOrigin (Map k a) instance (HasOrigin a, Ord a) => HasOrigin (Set a) instance HasOrigin a => HasOrigin [a] instance (HasOrigin a, HasOrigin b, V a ~ V b) => HasOrigin (a, b) instance VectorSpace v => HasOrigin (Point v) -- | Diagrams defines the core library of primitives forming the -- basis of an embedded domain-specific language for describing and -- rendering diagrams. -- -- The Transform module defines generic transformations -- parameterized by any vector space. module Diagrams.Core.Transform -- | (v1 :-: v2) is a linear map paired with its inverse. data (:-:) u v (:-:) :: (u :-* v) -> (v :-* u) -> :-: u v -- | Create an invertible linear map from two functions which are assumed -- to be linear inverses. (<->) :: (HasLinearMap u, HasLinearMap v) => (u -> v) -> (v -> u) -> (u :-: v) -- | Invert a linear map. linv :: (u :-: v) -> (v :-: u) -- | Apply a linear map to a vector. lapp :: (VectorSpace v, Scalar u ~ Scalar v, HasLinearMap u) => (u :-: v) -> u -> v -- | General (affine) transformations, represented by an invertible linear -- map, its transpose, and a vector representing a translation -- component. -- -- By the transpose of a linear map we mean simply the linear map -- corresponding to the transpose of the map's matrix representation. For -- example, any scale is its own transpose, since scales are represented -- by matrices with zeros everywhere except the diagonal. The transpose -- of a rotation is the same as its inverse. -- -- The reason we need to keep track of transposes is because it turns out -- that when transforming a shape according to some linear map L, the -- shape's normal vectors transform according to L's inverse -- transpose. This is exactly what we need when transforming bounding -- functions, which are defined in terms of perpendicular (i.e. -- normal) hyperplanes. data Transformation v Transformation :: (v :-: v) -> (v :-: v) -> v -> Transformation v -- | Invert a transformation. inv :: HasLinearMap v => Transformation v -> Transformation v -- | Get the transpose of a transformation (ignoring the translation -- component). transp :: Transformation v -> (v :-: v) -- | Get the translational component of a transformation. transl :: Transformation v -> v -- | Apply a transformation to a vector. Note that any translational -- component of the transformation will not affect the vector, since -- vectors are invariant under translation. apply :: HasLinearMap v => Transformation v -> v -> v -- | Apply a transformation to a point. papply :: HasLinearMap v => Transformation v -> Point v -> Point v -- | Create a general affine transformation from an invertible linear -- transformation and its transpose. The translational component is -- assumed to be zero. fromLinear :: AdditiveGroup v => (v :-: v) -> (v :-: v) -> Transformation v -- | HasLinearMap is a poor man's class constraint synonym, just to -- help shorten some of the ridiculously long constraint sets. class (HasBasis v, HasTrie (Basis v), VectorSpace v) => HasLinearMap v -- | Type class for things t which can be transformed. class HasLinearMap (V t) => Transformable t transform :: Transformable t => Transformation (V t) -> t -> t -- | TransInv is a wrapper which makes a transformable type -- translationally invariant; the translational component of -- transformations will no longer affect things wrapped in -- TransInv. newtype TransInv t TransInv :: t -> TransInv t unTransInv :: TransInv t -> t -- | Create a translation. translation :: HasLinearMap v => v -> Transformation v -- | Translate by a vector. translate :: (Transformable t, HasLinearMap (V t)) => V t -> t -> t -- | Create a uniform scaling transformation. scaling :: (HasLinearMap v, Fractional (Scalar v)) => Scalar v -> Transformation v -- | Scale uniformly in every dimension by the given scalar. scale :: (Transformable t, Fractional (Scalar (V t)), Eq (Scalar (V t))) => Scalar (V t) -> t -> t instance Show t => Show (TransInv t) instance Semigroup t => Semigroup (TransInv t) instance Monoid t => Monoid (TransInv t) instance Transformable t => Transformable (TransInv t) instance VectorSpace (V t) => HasOrigin (TransInv t) instance Transformable Rational instance Transformable Double instance Transformable m => Transformable (Deletable m) instance HasLinearMap v => Transformable (Point v) instance Transformable t => Transformable (Map k t) instance (Transformable t, Ord t) => Transformable (Set t) instance Transformable t => Transformable [t] instance (Transformable a, Transformable b, Transformable c, V a ~ V b, V a ~ V c) => Transformable (a, b, c) instance (Transformable a, Transformable b, V a ~ V b) => Transformable (a, b) instance HasLinearMap v => HasOrigin (Transformation v) instance HasLinearMap v => Transformable (Transformation v) instance (HasBasis v, HasTrie (Basis v), VectorSpace v) => HasLinearMap v instance (HasLinearMap v, v ~ V a, Transformable a) => Action (Transformation v) a instance HasLinearMap v => Monoid (Transformation v) instance HasLinearMap v => Semigroup (Transformation v) instance HasLinearMap v => Monoid (v :-: v) instance HasLinearMap v => Semigroup (v :-: v) -- | The Query module defines a type for "queries" on diagrams, -- which are functions from points in a vector space to some monoid. module Diagrams.Core.Query -- | A query is a function that maps points in a vector space to values in -- some monoid. Queries naturally form a monoid, with two queries being -- combined pointwise. -- -- The idea for annotating diagrams with monoidal queries came from the -- graphics-drawingcombinators package, -- http://hackage.haskell.org/package/graphics-drawingcombinators. newtype Query v m Query :: (Point v -> m) -> Query v m runQuery :: Query v m -> Point v -> m instance Functor (Query v) instance Applicative (Query v) instance Semigroup m => Semigroup (Query v m) instance Monoid m => Monoid (Query v m) instance HasLinearMap v => Transformable (Query v m) instance VectorSpace v => HasOrigin (Query v m) -- | A definition of styles for diagrams as extensible, -- heterogeneous collections of attributes. module Diagrams.Core.Style -- | Every attribute must be an instance of AttributeClass, which -- simply guarantees Typeable and Semigroup constraints. -- The Semigroup instance for an attribute determines how it will -- combine with other attributes of the same type. class (Typeable a, Semigroup a) => AttributeClass a -- | An existential wrapper type to hold attributes. Some attributes are -- affected by transformations and some are not. data Attribute v :: * Attribute :: a -> Attribute v TAttribute :: a -> Attribute v -- | Wrap up an attribute. mkAttr :: AttributeClass a => a -> Attribute v -- | Wrap up a transformable attribute. mkTAttr :: (AttributeClass a, Transformable a, V a ~ v) => a -> Attribute v -- | Unwrap an unknown Attribute type, performing a dynamic (but -- safe) check on the type of the result. If the required type matches -- the type of the attribute, the attribute value is returned wrapped in -- Just; if the types do not match, Nothing is -- returned. unwrapAttr :: AttributeClass a => Attribute v -> Maybe a -- | Apply an attribute to an instance of HasStyle (such as a -- diagram or a style). If the object already has an attribute of the -- same type, the new attribute is combined on the left with the existing -- attribute, according to their semigroup structure. applyAttr :: (AttributeClass a, HasStyle d) => a -> d -> d -- | Apply a transformable attribute to an instance of HasStyle -- (such as a diagram or a style). If the object already has an attribute -- of the same type, the new attribute is combined on the left with the -- existing attribute, according to their semigroup structure. applyTAttr :: (AttributeClass a, Transformable a, V a ~ V d, HasStyle d) => a -> d -> d -- | A Style is a heterogeneous collection of attributes, -- containing at most one attribute of any given type. newtype Style v Style :: (Map String (Attribute v)) -> Style v -- | Create a style from a single attribute. attrToStyle :: AttributeClass a => a -> Style v -- | Create a style from a single transformable attribute. tAttrToStyle :: (AttributeClass a, Transformable a, V a ~ v) => a -> Style v -- | Extract an attribute from a style of a particular type. If the style -- contains an attribute of the requested type, it will be returned -- wrapped in Just; otherwise, Nothing is returned. getAttr :: AttributeClass a => Style v -> Maybe a -- | Add a new attribute to a style, or replace the old attribute of the -- same type if one exists. setAttr :: AttributeClass a => a -> Style v -> Style v -- | Attempt to add a new attribute to a style, but if an attribute of the -- same type already exists, do not replace it. addAttr :: AttributeClass a => a -> Style v -> Style v -- | Add a new attribute to a style that does not already contain an -- attribute of this type, or combine it on the left with an existing -- attribute. combineAttr :: AttributeClass a => a -> Style v -> Style v -- | Type class for things which have a style. class HasStyle a applyStyle :: HasStyle a => Style (V a) -> a -> a instance (HasStyle a, Ord a) => HasStyle (Set a) instance HasStyle a => HasStyle (Map k a) instance HasStyle b => HasStyle (a -> b) instance HasStyle a => HasStyle [a] instance (HasStyle a, HasStyle b, V a ~ V b) => HasStyle (a, b) instance HasStyle (Style v) instance Action (Style v) m instance HasLinearMap v => Transformable (Style v) instance Monoid (Style v) instance Semigroup (Style v) instance HasLinearMap v => Transformable (Attribute v) instance Semigroup (Attribute v) -- | Diagrams defines the core library of primitives forming the -- basis of an embedded domain-specific language for describing and -- rendering diagrams. -- -- The Trace module defines a data type and type class for -- "traces", aka functional boundaries, essentially corresponding to -- embedding a raytracer with each diagram. module Diagrams.Core.Trace -- | Every diagram comes equipped with a *trace*. Intuitively, the trace -- for a diagram is like a raytracer: given a line (represented as a base -- point + direction), the trace computes the distance from the base -- point along the line to the first intersection with the diagram. The -- distance can be negative if the intersection is in the opposite -- direction from the base point, or infinite if the ray never intersects -- the diagram. Note: to obtain the distance to the *furthest* -- intersection instead of the *closest*, just negate the direction -- vector and then negate the result. -- -- Note that the output should actually be interpreted not as an absolute -- distance, but as a multiplier relative to the input vector. That is, -- if the input vector is v and the returned scalar is -- s, the distance from the base point to the intersection is -- given by s *^ magnitude v. newtype Trace v Trace :: (Point v -> v -> PosInf (Scalar v)) -> Trace v appTrace :: Trace v -> Point v -> v -> PosInf (Scalar v) inTrace :: ((Point v -> v -> PosInf (Scalar v)) -> (Point v -> v -> PosInf (Scalar v))) -> Trace v -> Trace v mkTrace :: (Point v -> v -> PosInf (Scalar v)) -> Trace v -- | Traced abstracts over things which have a trace. class (Ord (Scalar (V a)), VectorSpace (V a)) => Traced a getTrace :: Traced a => a -> Trace (V a) -- | Compute the vector from the given point to the boundary of the given -- object in the given direction, or Nothing if there is no -- intersection. traceV :: Traced a => Point (V a) -> V a -> a -> Maybe (V a) -- | Given a base point and direction, compute the closest point on the -- boundary of the given object, or Nothing if there is no -- intersection in the given direction. traceP :: Traced a => Point (V a) -> V a -> a -> Maybe (Point (V a)) -- | Like traceV, but computes a vector to the *furthest* point on -- the boundary instead of the closest. maxTraceV :: Traced a => Point (V a) -> V a -> a -> Maybe (V a) -- | Like traceP, but computes the *furthest* point on the boundary -- instead of the closest. maxTraceP :: Traced a => Point (V a) -> V a -> a -> Maybe (Point (V a)) instance Ord (Scalar v) => Monoid (Trace v) instance Ord (Scalar v) => Semigroup (Trace v) instance Traced b => Traced (Set b) instance Traced b => Traced (Map k b) instance Traced b => Traced [b] instance (Traced a, Traced b, V a ~ V b) => Traced (a, b) instance (Ord (Scalar v), VectorSpace v) => Traced (Point v) instance (Ord (Scalar v), VectorSpace v) => Traced (Trace v) instance HasLinearMap v => Transformable (Trace v) instance Show (Trace v) instance VectorSpace v => HasOrigin (Trace v) -- | Graphics.Rendering.Diagrams defines the core library of -- primitives forming the basis of an embedded domain-specific language -- for describing and rendering diagrams. -- -- The Envelope module defines a data type and type class for -- "envelopes", aka functional bounding regions. module Diagrams.Core.Envelope -- | Every diagram comes equipped with an envelope. What is an -- envelope? -- -- Consider first the idea of a bounding box. A bounding box -- expresses the distance to a bounding plane in every direction parallel -- to an axis. That is, a bounding box can be thought of as the -- intersection of a collection of half-planes, two perpendicular to each -- axis. -- -- More generally, the intersection of half-planes in every -- direction would give a tight "bounding region", or convex hull. -- However, representing such a thing intensionally would be impossible; -- hence bounding boxes are often used as an approximation. -- -- An envelope is an extensional representation of such a -- "bounding region". Instead of storing some sort of direct -- representation, we store a function which takes a direction as -- input and gives a distance to a bounding half-plane as output. The -- important point is that envelopes can be composed, and transformed by -- any affine transformation. -- -- Formally, given a vector v, the envelope computes a scalar -- s such that -- -- -- -- There is also a special "empty envelope". -- -- The idea for envelopes came from Sebastian Setzer; see -- http://byorgey.wordpress.com/2009/10/28/collecting-attributes/#comment-2030. -- See also Brent Yorgey, Monoids: Theme and Variations, published -- in the 2012 Haskell Symposium: -- http://www.cis.upenn.edu/~byorgey/pub/monoid-pearl.pdf; video: -- http://www.youtube.com/watch?v=X-8NCkD2vOw. newtype Envelope v Envelope :: Option (v -> Max (Scalar v)) -> Envelope v unEnvelope :: Envelope v -> Option (v -> Max (Scalar v)) inEnvelope :: (Option (v -> Max (Scalar v)) -> Option (v -> Max (Scalar v))) -> Envelope v -> Envelope v appEnvelope :: Envelope v -> Maybe (v -> Scalar v) onEnvelope :: ((v -> Scalar v) -> (v -> Scalar v)) -> Envelope v -> Envelope v mkEnvelope :: (v -> Scalar v) -> Envelope v -- | Create an envelope for the given point. pointEnvelope :: (Fractional (Scalar v), InnerSpace v) => Point v -> Envelope v -- | Enveloped abstracts over things which have an envelope. class (InnerSpace (V a), OrderedField (Scalar (V a))) => Enveloped a getEnvelope :: Enveloped a => a -> Envelope (V a) -- | Compute the diameter of a enveloped object along a particular vector. -- Returns zero for the empty envelope. diameter :: Enveloped a => V a -> a -> Scalar (V a) -- | Compute the "radius" (1/2 the diameter) of an enveloped object along a -- particular vector. radius :: Enveloped a => V a -> a -> Scalar (V a) -- | Compute the vector from the local origin to a separating hyperplane in -- the given direction, or Nothing for the empty envelope. envelopeVMay :: Enveloped a => V a -> a -> Maybe (V a) -- | Compute the vector from the local origin to a separating hyperplane in -- the given direction. Returns the zero vector for the empty envelope. envelopeV :: Enveloped a => V a -> a -> V a -- | Compute the point on a separating hyperplane in the given direction, -- or Nothing for the empty envelope. envelopePMay :: Enveloped a => V a -> a -> Maybe (Point (V a)) -- | Compute the point on a separating hyperplane in the given direction. -- Returns the origin for the empty envelope. envelopeP :: Enveloped a => V a -> a -> Point (V a) -- | Equivalent to the magnitude of envelopeVMay: -- --
--   envelopeSMay v x == fmap magnitude (envelopeVMay v x)
--   
-- -- (other than differences in rounding error) -- -- Note that the envelopeVMay / envelopePMay functions -- above should be preferred, as this requires a call to magnitude. -- However, it is more efficient than calling magnitude on the results of -- those functions. envelopeSMay :: Enveloped a => V a -> a -> Maybe (Scalar (V a)) -- | Equivalent to the magnitude of envelopeV: -- --
--   envelopeS v x == magnitude (envelopeV v x)
--   
-- -- (other than differences in rounding error) -- -- Note that the envelopeV / envelopeP functions above -- should be preferred, as this requires a call to magnitude. However, it -- is more efficient than calling magnitude on the results of those -- functions. envelopeS :: (Enveloped a, Num (Scalar (V a))) => V a -> a -> Scalar (V a) -- | When dealing with envelopes we often want scalars to be an ordered -- field (i.e. support all four arithmetic operations and be totally -- ordered) so we introduce this class as a convenient shorthand. class (Fractional s, Floating s, Ord s, AdditiveGroup s) => OrderedField s instance Ord (Scalar v) => Monoid (Envelope v) instance Ord (Scalar v) => Semigroup (Envelope v) instance Enveloped b => Enveloped (Set b) instance Enveloped b => Enveloped (Map k b) instance Enveloped b => Enveloped [b] instance (Enveloped a, Enveloped b, V a ~ V b) => Enveloped (a, b) instance (OrderedField (Scalar v), InnerSpace v) => Enveloped (Point v) instance (InnerSpace v, OrderedField (Scalar v)) => Enveloped (Envelope v) instance (Fractional s, Floating s, Ord s, AdditiveGroup s) => OrderedField s instance (HasLinearMap v, InnerSpace v, Floating (Scalar v)) => Transformable (Envelope v) instance Show (Envelope v) instance (InnerSpace v, Fractional (Scalar v)) => HasOrigin (Envelope v) -- | Things which can be placed "next to" other things, for some -- appropriate notion of "next to". module Diagrams.Core.Juxtapose -- | Class of things which can be placed "next to" other things, for some -- appropriate notion of "next to". class Juxtaposable a juxtapose :: Juxtaposable a => V a -> a -> a -> a -- | Default implementation of juxtapose for things which are -- instances of Enveloped and HasOrigin. If either envelope -- is empty, the second object is returned unchanged. juxtaposeDefault :: (Enveloped a, HasOrigin a) => V a -> a -> a -> a instance (Enveloped b, HasOrigin b, Ord b) => Juxtaposable (Set b) instance (Enveloped b, HasOrigin b) => Juxtaposable (Map k b) instance (Enveloped b, HasOrigin b) => Juxtaposable [b] instance (Enveloped a, HasOrigin a, Enveloped b, HasOrigin b, V a ~ V b) => Juxtaposable (a, b) instance (InnerSpace v, OrderedField (Scalar v)) => Juxtaposable (Envelope v) -- | The core library of primitives forming the basis of an embedded -- domain-specific language for describing and rendering diagrams. -- -- Diagrams.Core.Types defines types and classes for primitives, -- diagrams, and backends. module Diagrams.Core.Types -- | Monoidal annotations which travel up the diagram tree, i.e. -- which are aggregated from component diagrams to the whole: -- -- type UpAnnots b v m = Deletable (Envelope v) ::: (Deletable (Trace v) ::: (SubMap b v m ::: (Query v m ::: ()))) -- | Monoidal annotations which travel down the diagram tree, i.e. -- which accumulate along each path to a leaf (and which can act on the -- upwards-travelling annotations): -- -- type DownAnnots v = (Split (Transformation v) :+: Style v) ::: (Name ::: ()) -- | The fundamental diagram type is represented by trees of primitives -- with various monoidal annotations. The Q in QDiagram -- stands for "Queriable", as distinguished from Diagram, a -- synonym for QDiagram with the query type specialized to -- Any. newtype QDiagram b v m QD :: DUALTree (DownAnnots v) (UpAnnots b v m) () (Prim b v) -> QDiagram b v m unQD :: QDiagram b v m -> DUALTree (DownAnnots v) (UpAnnots b v m) () (Prim b v) -- | Create a diagram from a single primitive, along with an envelope, -- trace, subdiagram map, and query function. mkQD :: Prim b v -> Envelope v -> Trace v -> SubMap b v m -> Query v m -> QDiagram b v m -- | The default sort of diagram is one where querying at a point simply -- tells you whether the diagram contains that point or not. Transforming -- a default diagram into one with a more interesting query can be done -- via the Functor instance of QDiagram b or the -- value function. type Diagram b v = QDiagram b v Any -- | Extract a list of primitives from a diagram, together with their -- associated transformations and styles. prims :: HasLinearMap v => QDiagram b v m -> [(Prim b v, (Split (Transformation v), Style v))] -- | Get the envelope of a diagram. envelope :: Ord (Scalar v) => QDiagram b v m -> Envelope v -- | Get the trace of a diagram. trace :: (Ord (Scalar v), VectorSpace v, HasLinearMap v) => QDiagram b v m -> Trace v -- | Get the subdiagram map (i.e. an association from names to -- subdiagrams) of a diagram. subMap :: QDiagram b v m -> SubMap b v m -- | Get a list of names of subdiagrams and their locations. names :: HasLinearMap v => QDiagram b v m -> [(Name, [Point v])] -- | Get the query function associated with a diagram. query :: Monoid m => QDiagram b v m -> Query v m -- | Sample a diagram's query function at a given point. sample :: Monoid m => QDiagram b v m -> Point v -> m -- | Set the query value for True points in a diagram (i.e. -- points "inside" the diagram); False points will be set to -- mempty. value :: Monoid m => m -> QDiagram b v Any -> QDiagram b v m -- | Reset the query values of a diagram to True/False: -- any values equal to mempty are set to False; any other -- values are set to True. resetValue :: (Eq m, Monoid m) => QDiagram b v m -> QDiagram b v Any -- | Set all the query values of a diagram to False. clearValue :: QDiagram b v m -> QDiagram b v Any -- | A convenient synonym for mappend on diagrams, designed to be -- used infix (to help remember which diagram goes on top of which when -- combining them, namely, the first on top of the second). atop :: (HasLinearMap v, OrderedField (Scalar v), InnerSpace v, Semigroup m) => QDiagram b v m -> QDiagram b v m -> QDiagram b v m -- | Attach an atomic name to a diagram. named :: (IsName n, HasLinearMap v, InnerSpace v, OrderedField (Scalar v), Semigroup m) => n -> QDiagram b v m -> QDiagram b v m -- | Attach an atomic name to a certain subdiagram, computed from the given -- diagram. nameSub :: (IsName n, HasLinearMap v, InnerSpace v, OrderedField (Scalar v), Semigroup m) => (QDiagram b v m -> Subdiagram b v m) -> n -> QDiagram b v m -> QDiagram b v m -- | Attach an atomic name to a certain point (which may be computed from -- the given diagram), treated as a subdiagram with no content and a -- point envelope. namePoint :: (IsName n, HasLinearMap v, InnerSpace v, OrderedField (Scalar v), Semigroup m) => (QDiagram b v m -> Point v) -> n -> QDiagram b v m -> QDiagram b v m -- | Given a name and a diagram transformation indexed by a subdiagram, -- perform the transformation using the most recent subdiagram associated -- with (some qualification of) the name, or perform the identity -- transformation if the name does not exist. withName :: IsName n => n -> (Subdiagram b v m -> QDiagram b v m -> QDiagram b v m) -> QDiagram b v m -> QDiagram b v m -- | Given a name and a diagram transformation indexed by a list of -- subdiagrams, perform the transformation using the collection of all -- such subdiagrams associated with (some qualification of) the given -- name. withNameAll :: IsName n => n -> ([Subdiagram b v m] -> QDiagram b v m -> QDiagram b v m) -> QDiagram b v m -> QDiagram b v m -- | Given a list of names and a diagram transformation indexed by a list -- of subdiagrams, perform the transformation using the list of most -- recent subdiagrams associated with (some qualification of) each name. -- Do nothing (the identity transformation) if any of the names do not -- exist. withNames :: IsName n => [n] -> ([Subdiagram b v m] -> QDiagram b v m -> QDiagram b v m) -> QDiagram b v m -> QDiagram b v m -- | By default, diagram attributes are not affected by transformations. -- This means, for example, that lw 0.01 circle and scale 2 -- (lw 0.01 circle) will be drawn with lines of the same -- width, and scaleY 3 circle will be an ellipse drawn with a -- uniform line. Once a diagram is frozen, however, transformations do -- affect attributes, so, for example, scale 2 (freeze (lw 0.01 -- circle)) will be drawn with a line twice as thick as lw 0.01 -- circle, and scaleY 3 (freeze circle) will be drawn with -- a "stretched", variable-width line. -- -- Another way of thinking about it is that pre-freeze, we are -- transforming the "abstract idea" of a diagram, and the transformed -- version is then drawn; when doing a freeze, we produce a -- concrete drawing of the diagram, and it is this visual representation -- itself which is acted upon by subsequent transformations. freeze :: (HasLinearMap v, InnerSpace v, OrderedField (Scalar v), Semigroup m) => QDiagram b v m -> QDiagram b v m -- | Replace the envelope of a diagram. setEnvelope :: (OrderedField (Scalar v), InnerSpace v, HasLinearMap v, Monoid' m) => Envelope v -> QDiagram b v m -> QDiagram b v m -- | Replace the trace of a diagram. setTrace :: (OrderedField (Scalar v), InnerSpace v, HasLinearMap v, Semigroup m) => Trace v -> QDiagram b v m -> QDiagram b v m -- | A Subdiagram represents a diagram embedded within the context -- of a larger diagram. Essentially, it consists of a diagram paired with -- any accumulated information from the larger context (transformations, -- attributes, etc.). data Subdiagram b v m Subdiagram :: (QDiagram b v m) -> (DownAnnots v) -> Subdiagram b v m -- | Turn a diagram into a subdiagram with no accumulated context. mkSubdiagram :: QDiagram b v m -> Subdiagram b v m -- | Turn a subdiagram into a normal diagram, including the enclosing -- context. Concretely, a subdiagram is a pair of (1) a diagram and (2) a -- "context" consisting of an extra transformation and attributes. -- getSub simply applies the transformation and attributes to -- the diagram to get the corresponding "top-level" diagram. getSub :: (HasLinearMap v, InnerSpace v, Floating (Scalar v), Ord (Scalar v), Semigroup m) => Subdiagram b v m -> QDiagram b v m -- | Extract the "raw" content of a subdiagram, by throwing away the -- context. rawSub :: Subdiagram b v m -> QDiagram b v m -- | Get the location of a subdiagram; that is, the location of its local -- origin with respect to the vector space of its parent diagram. -- In other words, the point where its local origin "ended up". location :: HasLinearMap v => Subdiagram b v m -> Point v -- | Create a "point subdiagram", that is, a pointDiagram (with no -- content and a point envelope) treated as a subdiagram with local -- origin at the given point. Note this is not the same as -- mkSubdiagram . pointDiagram, which would result in a -- subdiagram with local origin at the parent origin, rather than at the -- given point. subPoint :: (HasLinearMap v, InnerSpace v, OrderedField (Scalar v), Semigroup m) => Point v -> Subdiagram b v m -- | A SubMap is a map associating names to subdiagrams. There can -- be multiple associations for any given name. newtype SubMap b v m SubMap :: (Map Name [Subdiagram b v m]) -> SubMap b v m -- | Construct a SubMap from a list of associations between names -- and subdiagrams. fromNames :: IsName a => [(a, Subdiagram b v m)] -> SubMap b v m -- | Add a name/diagram association to a submap. rememberAs :: IsName a => a -> QDiagram b v m -> SubMap b v m -> SubMap b v m -- | Look for the given name in a name map, returning a list of subdiagrams -- associated with that name. If no names match the given name exactly, -- return all the subdiagrams associated with names of which the given -- name is a suffix. lookupSub :: IsName n => n -> SubMap b v m -> Maybe [Subdiagram b v m] -- | A value of type Prim b v is an opaque (existentially -- quantified) primitive which backend b knows how to render in -- vector space v. data Prim b v Prim :: p -> Prim b (V p) -- | The null primitive, which every backend can render by doing nothing. nullPrim :: (HasLinearMap v, Monoid (Render b v)) => Prim b v -- | Abstract diagrams are rendered to particular formats by -- backends. Each backend/vector space combination must be an -- instance of the Backend class. A minimal complete definition -- consists of the three associated types and implementations for -- withStyle and doRender. class (HasLinearMap v, Monoid (Render b v)) => Backend b v where data family Render b v :: * type family Result b v :: * data family Options b v :: * adjustDia _ o d = (o, d) renderDia b opts d = doRender b opts' . mconcat . map renderOne . prims $ d' where (opts', d') = adjustDia b opts d renderOne :: (Prim b v, (Split (Transformation v), Style v)) -> Render b v renderOne (p, (M t, s)) = withStyle b s mempty (render b (transform t p)) renderOne (p, (t1 :| t2, s)) = withStyle b s t1 (render b (transform (t1 <> t2) p)) withStyle :: Backend b v => b -> Style v -> Transformation v -> Render b v -> Render b v doRender :: Backend b v => b -> Options b v -> Render b v -> Result b v adjustDia :: (Backend b v, Monoid' m) => b -> Options b v -> QDiagram b v m -> (Options b v, QDiagram b v m) renderDia :: (Backend b v, InnerSpace v, OrderedField (Scalar v), Monoid' m) => b -> Options b v -> QDiagram b v m -> Result b v -- | A class for backends which support rendering multiple diagrams, e.g. -- to a multi-page pdf or something similar. class Backend b v => MultiBackend b v renderDias :: (MultiBackend b v, InnerSpace v, OrderedField (Scalar v), Monoid' m) => b -> Options b v -> [QDiagram b v m] -> Result b v -- | A null backend which does no actual rendering. It is provided mainly -- for convenience in situations where you must give a diagram a -- concrete, monomorphic type, but don't actually care which one. See -- D for more explanation and examples. -- -- It is courteous, when defining a new primitive P, to make an -- instance -- --
--   instance Renderable P NullBackend where
--     render _ _ = mempty
--   
-- -- This ensures that the trick with D annotations can be used for -- diagrams containing your primitive. data NullBackend -- | The D type is provided for convenience in situations where -- you must give a diagram a concrete, monomorphic type, but don't care -- which one. Such situations arise when you pass a diagram to a function -- which is polymorphic in its input but monomorphic in its output, such -- as width, height, phantom, or names. -- Such functions compute some property of the diagram, or use it to -- accomplish some other purpose, but do not result in the diagram being -- rendered. If the diagram does not have a monomorphic type, GHC -- complains that it cannot determine the diagram's type. -- -- For example, here is the error we get if we try to compute the width -- of an image (this example requires diagrams-lib): -- --
--   ghci> width (image "foo.png" 200 200)
--   
--   <interactive>:8:8:
--       No instance for (Renderable Diagrams.TwoD.Image.Image b0)
--         arising from a use of `image'
--       Possible fix:
--         add an instance declaration for
--         (Renderable Diagrams.TwoD.Image.Image b0)
--       In the first argument of `width', namely
--         `(image "foo.png" 200 200)'
--       In the expression: width (image "foo.png" 200 200)
--       In an equation for `it': it = width (image "foo.png" 200 200)
--   
-- -- GHC complains that there is no instance for Renderable Image -- b0; what is really going on is that it does not have enough -- information to decide what backend to use (hence the uninstantiated -- b0). This is annoying because we know that the choice -- of backend cannot possibly affect the width of the image (it's 200! -- it's right there in the code!); but there is no way for GHC to -- know that. -- -- The solution is to annotate the call to image with the type -- D R2, like so: -- --
--   ghci> width (image "foo.png" 200 200 :: D R2)
--   200.00000000000006
--   
-- -- (It turns out the width wasn't 200 after all...) -- -- As another example, here is the error we get if we try to compute the -- width of a radius-1 circle: -- --
--   ghci> width (circle 1)
--   
--   <interactive>:4:1:
--       Couldn't match type `V a0' with `R2'
--       In the expression: width (circle 1)
--       In an equation for `it': it = width (circle 1)
--   
-- -- There's even more ambiguity here. Whereas image always -- returns a Diagram, the circle function can produce any -- PathLike type, and the width function can consume -- any Enveloped type, so GHC has no idea what type to pick to go -- in the middle. However, the solution is the same: -- --
--   ghci> width (circle 1 :: D R2)
--   1.9999999999999998
--   
type D v = Diagram NullBackend v -- | The Renderable type class connects backends to primitives which they -- know how to render. class Transformable t => Renderable t b render :: Renderable t b => b -> t -> Render b (V t) instance [overlap ok] Typeable3 QDiagram instance [overlap ok] HasLinearMap v => Backend NullBackend v instance [overlap ok] Monoid (Render NullBackend v) instance [overlap ok] (HasLinearMap v, Monoid (Render b v)) => Renderable (NullPrim v) b instance [overlap ok] HasLinearMap v => Transformable (NullPrim v) instance [overlap ok] HasLinearMap v => Renderable (Prim b v) b instance [overlap ok] HasLinearMap v => Transformable (Prim b v) instance [overlap ok] Action Name a instance [overlap ok] Action Name (SubMap b v m) instance [overlap ok] Qualifiable (SubMap b v m) instance [overlap ok] (InnerSpace v, Floating (Scalar v), HasLinearMap v) => Transformable (SubMap b v m) instance [overlap ok] (OrderedField (Scalar v), InnerSpace v, HasLinearMap v) => HasOrigin (SubMap b v m) instance [overlap ok] Monoid (SubMap b v m) instance [overlap ok] Semigroup (SubMap b v m) instance [overlap ok] Functor (SubMap b v) instance [overlap ok] Newtype (SubMap b v m) (Map Name [Subdiagram b v m]) instance [overlap ok] (HasLinearMap v, InnerSpace v, Floating (Scalar v)) => Transformable (Subdiagram b v m) instance [overlap ok] (HasLinearMap v, InnerSpace v, OrderedField (Scalar v)) => HasOrigin (Subdiagram b v m) instance [overlap ok] (Ord (Scalar v), VectorSpace v, HasLinearMap v) => Traced (Subdiagram b v m) instance [overlap ok] (OrderedField (Scalar v), InnerSpace v, HasLinearMap v) => Enveloped (Subdiagram b v m) instance [overlap ok] Functor (Subdiagram b v) instance [overlap ok] (HasLinearMap v, InnerSpace v, OrderedField (Scalar v), Semigroup m) => Qualifiable (QDiagram b v m) instance [overlap ok] (HasLinearMap v, OrderedField (Scalar v), InnerSpace v, Semigroup m) => Transformable (QDiagram b v m) instance [overlap ok] (HasLinearMap v, InnerSpace v, OrderedField (Scalar v), Semigroup m) => HasOrigin (QDiagram b v m) instance [overlap ok] (HasLinearMap v, VectorSpace v, Ord (Scalar v)) => Traced (QDiagram b v m) instance [overlap ok] (HasLinearMap v, InnerSpace v, OrderedField (Scalar v)) => Enveloped (QDiagram b v m) instance [overlap ok] (HasLinearMap v, InnerSpace v, OrderedField (Scalar v), Semigroup m) => Juxtaposable (QDiagram b v m) instance [overlap ok] (HasLinearMap v, InnerSpace v, OrderedField (Scalar v), Semigroup m) => HasStyle (QDiagram b v m) instance [overlap ok] Functor (QDiagram b v) instance [overlap ok] (HasLinearMap v, InnerSpace v, OrderedField (Scalar v), Semigroup m) => Semigroup (QDiagram b v m) instance [overlap ok] (HasLinearMap v, InnerSpace v, OrderedField (Scalar v), Semigroup m) => Monoid (QDiagram b v m) instance [overlap ok] Newtype (QDiagram b v m) (DUALTree (DownAnnots v) (UpAnnots b v m) () (Prim b v)) -- | The core library of primitives forming the basis of an embedded -- domain-specific language for describing and rendering diagrams. Normal -- users of the diagrams library should almost never need to import -- anything from this package directly; instead, import modules -- (especially Diagrams.Prelude) from the diagrams-lib package, -- which re-exports most things of value to users. -- -- For most library code needing access to core internals, it should be -- sufficient to import this module, which simply re-exports useful -- functionality from other modules in the core library. Library writers -- needing finer-grained access or functionality may occasionally find it -- useful to directly import one of the constituent core modules. module Diagrams.Core -- | Many sorts of objects have an associated vector space in which they -- "live". The type function V maps from object types to the -- associated vector space. -- | Point is a newtype wrapper around vectors used to represent -- points, so we don't get them mixed up. The distinction between vectors -- and points is important: translations affect points, but leave vectors -- unchanged. Points are instances of the AffineSpace class from -- Data.AffineSpace. data Point v :: * -> * -- | The origin of the vector space v. origin :: AdditiveGroup v => Point v -- | Scale a point by a scalar. (*.) :: VectorSpace v => Scalar v -> Point v -> Point v -- | (v1 :-: v2) is a linear map paired with its inverse. data (:-:) u v -- | Create an invertible linear map from two functions which are assumed -- to be linear inverses. (<->) :: (HasLinearMap u, HasLinearMap v) => (u -> v) -> (v -> u) -> (u :-: v) -- | Invert a linear map. linv :: (u :-: v) -> (v :-: u) -- | Apply a linear map to a vector. lapp :: (VectorSpace v, Scalar u ~ Scalar v, HasLinearMap u) => (u :-: v) -> u -> v -- | General (affine) transformations, represented by an invertible linear -- map, its transpose, and a vector representing a translation -- component. -- -- By the transpose of a linear map we mean simply the linear map -- corresponding to the transpose of the map's matrix representation. For -- example, any scale is its own transpose, since scales are represented -- by matrices with zeros everywhere except the diagonal. The transpose -- of a rotation is the same as its inverse. -- -- The reason we need to keep track of transposes is because it turns out -- that when transforming a shape according to some linear map L, the -- shape's normal vectors transform according to L's inverse -- transpose. This is exactly what we need when transforming bounding -- functions, which are defined in terms of perpendicular (i.e. -- normal) hyperplanes. data Transformation v -- | Invert a transformation. inv :: HasLinearMap v => Transformation v -> Transformation v -- | Get the transpose of a transformation (ignoring the translation -- component). transp :: Transformation v -> (v :-: v) -- | Get the translational component of a transformation. transl :: Transformation v -> v -- | Apply a transformation to a vector. Note that any translational -- component of the transformation will not affect the vector, since -- vectors are invariant under translation. apply :: HasLinearMap v => Transformation v -> v -> v -- | Apply a transformation to a point. papply :: HasLinearMap v => Transformation v -> Point v -> Point v -- | Create a general affine transformation from an invertible linear -- transformation and its transpose. The translational component is -- assumed to be zero. fromLinear :: AdditiveGroup v => (v :-: v) -> (v :-: v) -> Transformation v -- | Create a translation. translation :: HasLinearMap v => v -> Transformation v -- | Translate by a vector. translate :: (Transformable t, HasLinearMap (V t)) => V t -> t -> t -- | Translate the object by the translation that sends the origin to the -- given point. Note that this is dual to moveOriginTo, i.e. we -- should have -- --
--   moveTo (origin .^+ v) === moveOriginTo (origin .^- v)
--   
-- -- For types which are also Transformable, this is essentially -- the same as translate, i.e. -- --
--   moveTo (origin .^+ v) === translate v
--   
moveTo :: HasOrigin t => Point (V t) -> t -> t -- | A flipped variant of moveTo, provided for convenience. Useful -- when writing a function which takes a point as an argument, such as -- when using withName and friends. place :: HasOrigin t => t -> Point (V t) -> t -- | Create a uniform scaling transformation. scaling :: (HasLinearMap v, Fractional (Scalar v)) => Scalar v -> Transformation v -- | Scale uniformly in every dimension by the given scalar. scale :: (Transformable t, Fractional (Scalar (V t)), Eq (Scalar (V t))) => Scalar (V t) -> t -> t -- | Type class for things t which can be transformed. class HasLinearMap (V t) => Transformable t transform :: Transformable t => Transformation (V t) -> t -> t -- | TransInv is a wrapper which makes a transformable type -- translationally invariant; the translational component of -- transformations will no longer affect things wrapped in -- TransInv. newtype TransInv t TransInv :: t -> TransInv t unTransInv :: TransInv t -> t -- | Atomic names. AName is just an existential wrapper around -- things which are Typeable, Ord and Show. data AName -- | A (qualified) name is a (possibly empty) sequence of atomic names. data Name -- | Class for those types which can be used as names. They must support -- Typeable (to facilitate extracting them from existential -- wrappers), Ord (for comparison and efficient storage) and -- Show. class (Typeable a, Ord a, Show a) => IsName a where toName = Name . (: []) . AName toName :: IsName a => a -> Name -- | Instances of Qualifiable are things which can be qualified by -- prefixing them with a name. class Qualifiable q (|>) :: (Qualifiable q, IsName a) => a -> q -> q -- | Convenient operator for writing qualified names with atomic components -- of different types. Instead of writing toName a1 <> toName -- a2 <> toName a3 you can just write a1 .> a2 .> -- a3. (.>) :: (IsName a1, IsName a2) => a1 -> a2 -> Name -- | A SubMap is a map associating names to subdiagrams. There can -- be multiple associations for any given name. newtype SubMap b v m SubMap :: (Map Name [Subdiagram b v m]) -> SubMap b v m -- | Construct a SubMap from a list of associations between names -- and subdiagrams. fromNames :: IsName a => [(a, Subdiagram b v m)] -> SubMap b v m -- | Add a name/diagram association to a submap. rememberAs :: IsName a => a -> QDiagram b v m -> SubMap b v m -> SubMap b v m -- | Look for the given name in a name map, returning a list of subdiagrams -- associated with that name. If no names match the given name exactly, -- return all the subdiagrams associated with names of which the given -- name is a suffix. lookupSub :: IsName n => n -> SubMap b v m -> Maybe [Subdiagram b v m] -- | Every attribute must be an instance of AttributeClass, which -- simply guarantees Typeable and Semigroup constraints. -- The Semigroup instance for an attribute determines how it will -- combine with other attributes of the same type. class (Typeable a, Semigroup a) => AttributeClass a -- | An existential wrapper type to hold attributes. Some attributes are -- affected by transformations and some are not. data Attribute v :: * -- | Wrap up an attribute. mkAttr :: AttributeClass a => a -> Attribute v -- | Wrap up a transformable attribute. mkTAttr :: (AttributeClass a, Transformable a, V a ~ v) => a -> Attribute v -- | Unwrap an unknown Attribute type, performing a dynamic (but -- safe) check on the type of the result. If the required type matches -- the type of the attribute, the attribute value is returned wrapped in -- Just; if the types do not match, Nothing is -- returned. unwrapAttr :: AttributeClass a => Attribute v -> Maybe a -- | A Style is a heterogeneous collection of attributes, -- containing at most one attribute of any given type. data Style v -- | Type class for things which have a style. class HasStyle a applyStyle :: HasStyle a => Style (V a) -> a -> a -- | Extract an attribute from a style of a particular type. If the style -- contains an attribute of the requested type, it will be returned -- wrapped in Just; otherwise, Nothing is returned. getAttr :: AttributeClass a => Style v -> Maybe a -- | Add a new attribute to a style that does not already contain an -- attribute of this type, or combine it on the left with an existing -- attribute. combineAttr :: AttributeClass a => a -> Style v -> Style v -- | Apply an attribute to an instance of HasStyle (such as a -- diagram or a style). If the object already has an attribute of the -- same type, the new attribute is combined on the left with the existing -- attribute, according to their semigroup structure. applyAttr :: (AttributeClass a, HasStyle d) => a -> d -> d -- | Apply a transformable attribute to an instance of HasStyle -- (such as a diagram or a style). If the object already has an attribute -- of the same type, the new attribute is combined on the left with the -- existing attribute, according to their semigroup structure. applyTAttr :: (AttributeClass a, Transformable a, V a ~ V d, HasStyle d) => a -> d -> d -- | Every diagram comes equipped with an envelope. What is an -- envelope? -- -- Consider first the idea of a bounding box. A bounding box -- expresses the distance to a bounding plane in every direction parallel -- to an axis. That is, a bounding box can be thought of as the -- intersection of a collection of half-planes, two perpendicular to each -- axis. -- -- More generally, the intersection of half-planes in every -- direction would give a tight "bounding region", or convex hull. -- However, representing such a thing intensionally would be impossible; -- hence bounding boxes are often used as an approximation. -- -- An envelope is an extensional representation of such a -- "bounding region". Instead of storing some sort of direct -- representation, we store a function which takes a direction as -- input and gives a distance to a bounding half-plane as output. The -- important point is that envelopes can be composed, and transformed by -- any affine transformation. -- -- Formally, given a vector v, the envelope computes a scalar -- s such that -- -- -- -- There is also a special "empty envelope". -- -- The idea for envelopes came from Sebastian Setzer; see -- http://byorgey.wordpress.com/2009/10/28/collecting-attributes/#comment-2030. -- See also Brent Yorgey, Monoids: Theme and Variations, published -- in the 2012 Haskell Symposium: -- http://www.cis.upenn.edu/~byorgey/pub/monoid-pearl.pdf; video: -- http://www.youtube.com/watch?v=X-8NCkD2vOw. data Envelope v inEnvelope :: (Option (v -> Max (Scalar v)) -> Option (v -> Max (Scalar v))) -> Envelope v -> Envelope v appEnvelope :: Envelope v -> Maybe (v -> Scalar v) onEnvelope :: ((v -> Scalar v) -> (v -> Scalar v)) -> Envelope v -> Envelope v mkEnvelope :: (v -> Scalar v) -> Envelope v -- | Enveloped abstracts over things which have an envelope. class (InnerSpace (V a), OrderedField (Scalar (V a))) => Enveloped a getEnvelope :: Enveloped a => a -> Envelope (V a) -- | Compute the vector from the local origin to a separating hyperplane in -- the given direction, or Nothing for the empty envelope. envelopeVMay :: Enveloped a => V a -> a -> Maybe (V a) -- | Compute the vector from the local origin to a separating hyperplane in -- the given direction. Returns the zero vector for the empty envelope. envelopeV :: Enveloped a => V a -> a -> V a -- | Compute the point on a separating hyperplane in the given direction, -- or Nothing for the empty envelope. envelopePMay :: Enveloped a => V a -> a -> Maybe (Point (V a)) -- | Compute the point on a separating hyperplane in the given direction. -- Returns the origin for the empty envelope. envelopeP :: Enveloped a => V a -> a -> Point (V a) -- | Compute the diameter of a enveloped object along a particular vector. -- Returns zero for the empty envelope. diameter :: Enveloped a => V a -> a -> Scalar (V a) -- | Compute the "radius" (1/2 the diameter) of an enveloped object along a -- particular vector. radius :: Enveloped a => V a -> a -> Scalar (V a) -- | Every diagram comes equipped with a *trace*. Intuitively, the trace -- for a diagram is like a raytracer: given a line (represented as a base -- point + direction), the trace computes the distance from the base -- point along the line to the first intersection with the diagram. The -- distance can be negative if the intersection is in the opposite -- direction from the base point, or infinite if the ray never intersects -- the diagram. Note: to obtain the distance to the *furthest* -- intersection instead of the *closest*, just negate the direction -- vector and then negate the result. -- -- Note that the output should actually be interpreted not as an absolute -- distance, but as a multiplier relative to the input vector. That is, -- if the input vector is v and the returned scalar is -- s, the distance from the base point to the intersection is -- given by s *^ magnitude v. newtype Trace v Trace :: (Point v -> v -> PosInf (Scalar v)) -> Trace v appTrace :: Trace v -> Point v -> v -> PosInf (Scalar v) inTrace :: ((Point v -> v -> PosInf (Scalar v)) -> (Point v -> v -> PosInf (Scalar v))) -> Trace v -> Trace v mkTrace :: (Point v -> v -> PosInf (Scalar v)) -> Trace v -- | Traced abstracts over things which have a trace. class (Ord (Scalar (V a)), VectorSpace (V a)) => Traced a getTrace :: Traced a => a -> Trace (V a) -- | Compute the vector from the given point to the boundary of the given -- object in the given direction, or Nothing if there is no -- intersection. traceV :: Traced a => Point (V a) -> V a -> a -> Maybe (V a) -- | Given a base point and direction, compute the closest point on the -- boundary of the given object, or Nothing if there is no -- intersection in the given direction. traceP :: Traced a => Point (V a) -> V a -> a -> Maybe (Point (V a)) -- | Like traceV, but computes a vector to the *furthest* point on -- the boundary instead of the closest. maxTraceV :: Traced a => Point (V a) -> V a -> a -> Maybe (V a) -- | Like traceP, but computes the *furthest* point on the boundary -- instead of the closest. maxTraceP :: Traced a => Point (V a) -> V a -> a -> Maybe (Point (V a)) -- | Class of types which have an intrinsic notion of a "local origin", -- i.e. things which are not invariant under translation, and which allow -- the origin to be moved. -- -- One might wonder why not just use Transformable instead of -- having a separate class for HasOrigin; indeed, for types which -- are instances of both we should have the identity -- --
--   moveOriginTo (origin .^+ v) === translate (negateV v)
--   
-- -- The reason is that some things (e.g. vectors, Trails) are -- transformable but are translationally invariant, i.e. have no origin. class VectorSpace (V t) => HasOrigin t moveOriginTo :: HasOrigin t => Point (V t) -> t -> t -- | Move the local origin by a relative vector. moveOriginBy :: HasOrigin t => V t -> t -> t -- | Class of things which can be placed "next to" other things, for some -- appropriate notion of "next to". class Juxtaposable a juxtapose :: Juxtaposable a => V a -> a -> a -> a -- | Default implementation of juxtapose for things which are -- instances of Enveloped and HasOrigin. If either envelope -- is empty, the second object is returned unchanged. juxtaposeDefault :: (Enveloped a, HasOrigin a) => V a -> a -> a -> a -- | A query is a function that maps points in a vector space to values in -- some monoid. Queries naturally form a monoid, with two queries being -- combined pointwise. -- -- The idea for annotating diagrams with monoidal queries came from the -- graphics-drawingcombinators package, -- http://hackage.haskell.org/package/graphics-drawingcombinators. newtype Query v m Query :: (Point v -> m) -> Query v m runQuery :: Query v m -> Point v -> m -- | A value of type Prim b v is an opaque (existentially -- quantified) primitive which backend b knows how to render in -- vector space v. data Prim b v Prim :: p -> Prim b (V p) -- | The null primitive, which every backend can render by doing nothing. nullPrim :: (HasLinearMap v, Monoid (Render b v)) => Prim b v -- | The fundamental diagram type is represented by trees of primitives -- with various monoidal annotations. The Q in QDiagram -- stands for "Queriable", as distinguished from Diagram, a -- synonym for QDiagram with the query type specialized to -- Any. data QDiagram b v m -- | Create a diagram from a single primitive, along with an envelope, -- trace, subdiagram map, and query function. mkQD :: Prim b v -> Envelope v -> Trace v -> SubMap b v m -> Query v m -> QDiagram b v m -- | The default sort of diagram is one where querying at a point simply -- tells you whether the diagram contains that point or not. Transforming -- a default diagram into one with a more interesting query can be done -- via the Functor instance of QDiagram b or the -- value function. type Diagram b v = QDiagram b v Any -- | Extract a list of primitives from a diagram, together with their -- associated transformations and styles. prims :: HasLinearMap v => QDiagram b v m -> [(Prim b v, (Split (Transformation v), Style v))] -- | Get the envelope of a diagram. envelope :: Ord (Scalar v) => QDiagram b v m -> Envelope v -- | Get the trace of a diagram. trace :: (Ord (Scalar v), VectorSpace v, HasLinearMap v) => QDiagram b v m -> Trace v -- | Get the subdiagram map (i.e. an association from names to -- subdiagrams) of a diagram. subMap :: QDiagram b v m -> SubMap b v m -- | Get a list of names of subdiagrams and their locations. names :: HasLinearMap v => QDiagram b v m -> [(Name, [Point v])] -- | Get the query function associated with a diagram. query :: Monoid m => QDiagram b v m -> Query v m -- | Sample a diagram's query function at a given point. sample :: Monoid m => QDiagram b v m -> Point v -> m -- | Set the query value for True points in a diagram (i.e. -- points "inside" the diagram); False points will be set to -- mempty. value :: Monoid m => m -> QDiagram b v Any -> QDiagram b v m -- | Reset the query values of a diagram to True/False: -- any values equal to mempty are set to False; any other -- values are set to True. resetValue :: (Eq m, Monoid m) => QDiagram b v m -> QDiagram b v Any -- | Set all the query values of a diagram to False. clearValue :: QDiagram b v m -> QDiagram b v Any -- | Attach an atomic name to a diagram. named :: (IsName n, HasLinearMap v, InnerSpace v, OrderedField (Scalar v), Semigroup m) => n -> QDiagram b v m -> QDiagram b v m -- | Attach an atomic name to a certain subdiagram, computed from the given -- diagram. nameSub :: (IsName n, HasLinearMap v, InnerSpace v, OrderedField (Scalar v), Semigroup m) => (QDiagram b v m -> Subdiagram b v m) -> n -> QDiagram b v m -> QDiagram b v m -- | Attach an atomic name to a certain point (which may be computed from -- the given diagram), treated as a subdiagram with no content and a -- point envelope. namePoint :: (IsName n, HasLinearMap v, InnerSpace v, OrderedField (Scalar v), Semigroup m) => (QDiagram b v m -> Point v) -> n -> QDiagram b v m -> QDiagram b v m -- | Given a name and a diagram transformation indexed by a subdiagram, -- perform the transformation using the most recent subdiagram associated -- with (some qualification of) the name, or perform the identity -- transformation if the name does not exist. withName :: IsName n => n -> (Subdiagram b v m -> QDiagram b v m -> QDiagram b v m) -> QDiagram b v m -> QDiagram b v m -- | Given a name and a diagram transformation indexed by a list of -- subdiagrams, perform the transformation using the collection of all -- such subdiagrams associated with (some qualification of) the given -- name. withNameAll :: IsName n => n -> ([Subdiagram b v m] -> QDiagram b v m -> QDiagram b v m) -> QDiagram b v m -> QDiagram b v m -- | Given a list of names and a diagram transformation indexed by a list -- of subdiagrams, perform the transformation using the list of most -- recent subdiagrams associated with (some qualification of) each name. -- Do nothing (the identity transformation) if any of the names do not -- exist. withNames :: IsName n => [n] -> ([Subdiagram b v m] -> QDiagram b v m -> QDiagram b v m) -> QDiagram b v m -> QDiagram b v m -- | By default, diagram attributes are not affected by transformations. -- This means, for example, that lw 0.01 circle and scale 2 -- (lw 0.01 circle) will be drawn with lines of the same -- width, and scaleY 3 circle will be an ellipse drawn with a -- uniform line. Once a diagram is frozen, however, transformations do -- affect attributes, so, for example, scale 2 (freeze (lw 0.01 -- circle)) will be drawn with a line twice as thick as lw 0.01 -- circle, and scaleY 3 (freeze circle) will be drawn with -- a "stretched", variable-width line. -- -- Another way of thinking about it is that pre-freeze, we are -- transforming the "abstract idea" of a diagram, and the transformed -- version is then drawn; when doing a freeze, we produce a -- concrete drawing of the diagram, and it is this visual representation -- itself which is acted upon by subsequent transformations. freeze :: (HasLinearMap v, InnerSpace v, OrderedField (Scalar v), Semigroup m) => QDiagram b v m -> QDiagram b v m -- | Replace the envelope of a diagram. setEnvelope :: (OrderedField (Scalar v), InnerSpace v, HasLinearMap v, Monoid' m) => Envelope v -> QDiagram b v m -> QDiagram b v m -- | Replace the trace of a diagram. setTrace :: (OrderedField (Scalar v), InnerSpace v, HasLinearMap v, Semigroup m) => Trace v -> QDiagram b v m -> QDiagram b v m -- | A convenient synonym for mappend on diagrams, designed to be -- used infix (to help remember which diagram goes on top of which when -- combining them, namely, the first on top of the second). atop :: (HasLinearMap v, OrderedField (Scalar v), InnerSpace v, Semigroup m) => QDiagram b v m -> QDiagram b v m -> QDiagram b v m -- | A Subdiagram represents a diagram embedded within the context -- of a larger diagram. Essentially, it consists of a diagram paired with -- any accumulated information from the larger context (transformations, -- attributes, etc.). data Subdiagram b v m Subdiagram :: (QDiagram b v m) -> (DownAnnots v) -> Subdiagram b v m -- | Turn a diagram into a subdiagram with no accumulated context. mkSubdiagram :: QDiagram b v m -> Subdiagram b v m -- | Turn a subdiagram into a normal diagram, including the enclosing -- context. Concretely, a subdiagram is a pair of (1) a diagram and (2) a -- "context" consisting of an extra transformation and attributes. -- getSub simply applies the transformation and attributes to -- the diagram to get the corresponding "top-level" diagram. getSub :: (HasLinearMap v, InnerSpace v, Floating (Scalar v), Ord (Scalar v), Semigroup m) => Subdiagram b v m -> QDiagram b v m -- | Extract the "raw" content of a subdiagram, by throwing away the -- context. rawSub :: Subdiagram b v m -> QDiagram b v m -- | Get the location of a subdiagram; that is, the location of its local -- origin with respect to the vector space of its parent diagram. -- In other words, the point where its local origin "ended up". location :: HasLinearMap v => Subdiagram b v m -> Point v -- | Create a "point subdiagram", that is, a pointDiagram (with no -- content and a point envelope) treated as a subdiagram with local -- origin at the given point. Note this is not the same as -- mkSubdiagram . pointDiagram, which would result in a -- subdiagram with local origin at the parent origin, rather than at the -- given point. subPoint :: (HasLinearMap v, InnerSpace v, OrderedField (Scalar v), Semigroup m) => Point v -> Subdiagram b v m -- | Abstract diagrams are rendered to particular formats by -- backends. Each backend/vector space combination must be an -- instance of the Backend class. A minimal complete definition -- consists of the three associated types and implementations for -- withStyle and doRender. class (HasLinearMap v, Monoid (Render b v)) => Backend b v where data family Render b v :: * type family Result b v :: * data family Options b v :: * adjustDia _ o d = (o, d) renderDia b opts d = doRender b opts' . mconcat . map renderOne . prims $ d' where (opts', d') = adjustDia b opts d renderOne :: (Prim b v, (Split (Transformation v), Style v)) -> Render b v renderOne (p, (M t, s)) = withStyle b s mempty (render b (transform t p)) renderOne (p, (t1 :| t2, s)) = withStyle b s t1 (render b (transform (t1 <> t2) p)) withStyle :: Backend b v => b -> Style v -> Transformation v -> Render b v -> Render b v doRender :: Backend b v => b -> Options b v -> Render b v -> Result b v adjustDia :: (Backend b v, Monoid' m) => b -> Options b v -> QDiagram b v m -> (Options b v, QDiagram b v m) renderDia :: (Backend b v, InnerSpace v, OrderedField (Scalar v), Monoid' m) => b -> Options b v -> QDiagram b v m -> Result b v -- | A class for backends which support rendering multiple diagrams, e.g. -- to a multi-page pdf or something similar. class Backend b v => MultiBackend b v renderDias :: (MultiBackend b v, InnerSpace v, OrderedField (Scalar v), Monoid' m) => b -> Options b v -> [QDiagram b v m] -> Result b v -- | The Renderable type class connects backends to primitives which they -- know how to render. class Transformable t => Renderable t b render :: Renderable t b => b -> t -> Render b (V t) -- | A null backend which does no actual rendering. It is provided mainly -- for convenience in situations where you must give a diagram a -- concrete, monomorphic type, but don't actually care which one. See -- D for more explanation and examples. -- -- It is courteous, when defining a new primitive P, to make an -- instance -- --
--   instance Renderable P NullBackend where
--     render _ _ = mempty
--   
-- -- This ensures that the trick with D annotations can be used for -- diagrams containing your primitive. data NullBackend -- | The D type is provided for convenience in situations where -- you must give a diagram a concrete, monomorphic type, but don't care -- which one. Such situations arise when you pass a diagram to a function -- which is polymorphic in its input but monomorphic in its output, such -- as width, height, phantom, or names. -- Such functions compute some property of the diagram, or use it to -- accomplish some other purpose, but do not result in the diagram being -- rendered. If the diagram does not have a monomorphic type, GHC -- complains that it cannot determine the diagram's type. -- -- For example, here is the error we get if we try to compute the width -- of an image (this example requires diagrams-lib): -- --
--   ghci> width (image "foo.png" 200 200)
--   
--   <interactive>:8:8:
--       No instance for (Renderable Diagrams.TwoD.Image.Image b0)
--         arising from a use of `image'
--       Possible fix:
--         add an instance declaration for
--         (Renderable Diagrams.TwoD.Image.Image b0)
--       In the first argument of `width', namely
--         `(image "foo.png" 200 200)'
--       In the expression: width (image "foo.png" 200 200)
--       In an equation for `it': it = width (image "foo.png" 200 200)
--   
-- -- GHC complains that there is no instance for Renderable Image -- b0; what is really going on is that it does not have enough -- information to decide what backend to use (hence the uninstantiated -- b0). This is annoying because we know that the choice -- of backend cannot possibly affect the width of the image (it's 200! -- it's right there in the code!); but there is no way for GHC to -- know that. -- -- The solution is to annotate the call to image with the type -- D R2, like so: -- --
--   ghci> width (image "foo.png" 200 200 :: D R2)
--   200.00000000000006
--   
-- -- (It turns out the width wasn't 200 after all...) -- -- As another example, here is the error we get if we try to compute the -- width of a radius-1 circle: -- --
--   ghci> width (circle 1)
--   
--   <interactive>:4:1:
--       Couldn't match type `V a0' with `R2'
--       In the expression: width (circle 1)
--       In an equation for `it': it = width (circle 1)
--   
-- -- There's even more ambiguity here. Whereas image always -- returns a Diagram, the circle function can produce any -- PathLike type, and the width function can consume -- any Enveloped type, so GHC has no idea what type to pick to go -- in the middle. However, the solution is the same: -- --
--   ghci> width (circle 1 :: D R2)
--   1.9999999999999998
--   
type D v = Diagram NullBackend v -- | HasLinearMap is a poor man's class constraint synonym, just to -- help shorten some of the ridiculously long constraint sets. class (HasBasis v, HasTrie (Basis v), VectorSpace v) => HasLinearMap v -- | When dealing with envelopes we often want scalars to be an ordered -- field (i.e. support all four arithmetic operations and be totally -- ordered) so we introduce this class as a convenient shorthand. class (Fractional s, Floating s, Ord s, AdditiveGroup s) => OrderedField s -- | The Monoid' class is a synonym for things which are instances -- of both Semigroup and Monoid. Ideally, the Monoid -- class itself will eventually include a Semigroup superclass and -- we can get rid of this. class (Semigroup m, Monoid m) => Monoid' m