-- | Here I describe and define the class Visual and some example instances -- for the basic data structures in the GHC standard library, including -- Data.Map, Data.IntMap, Data.Set, and Lists. This gives a rich library -- of data structures that are Visual as a direct transformation from -- forall a, Visual b : a -> Visual b -- {-# LANGUAGE FlexibleInstances,IncoherentInstances #-} module Graphics.Rendering.Hieroglyph.Visual where import qualified Data.Map as M import qualified Data.IntMap as IM import qualified Data.Set as S -- import Data.Foldable import Data.List import Graphics.Rendering.Hieroglyph.Primitives type BaseVisual = [Primitive] -- | A Visual is an unstructured collection of primitives. Conceptually, the -- only requirement of a Visual is that it is Enumerable (or Foldable) in -- terms of Primitives. I initially wanted to implement this in terms of -- the Foldable typeclass from Data.Foldable, but very few things provide -- instances of Foldable that are conceptually so. A list is Foldable, -- and I have certain guarantees of efficiency by operating on lists, so -- this is the instance of Foldable that I choose to have people implement. class Visual t where primitives :: t -> BaseVisual -- | A Primitive by itself is a Visual. That is, a single piece of geometry -- standing alone is in fact Visual. instance Visual Primitive where primitives a = [a] -- | A any list of Visuals can be flattenend into a list of Primitives by -- a right fold, therefore a List of Visuals is a Visual instance Visual a => Visual [a] where primitives = Prelude.concat . Prelude.map primitives -- | A map to Visuals is Foldable over the elements in terms of Visuals, which -- are in turn Foldable in terms of Primitives, therefore a map of instance Visual b => Visual (M.Map a b) where primitives = Prelude.concat . Prelude.map primitives . M.elems -- | An intmap is merely a map, so once again if the elements are Visuals, the -- whole structure is a Visual. instance Visual b => Visual (IM.IntMap b) where primitives = Prelude.concat . Prelude.map primitives . IM.elems -- | A set of Visuals also comprises a Visual. instance Visual t => Visual (S.Set t) where primitives = Prelude.concat . Prelude.map primitives . S.toList -- | Declare that a Visual possibly occludes another Visual over :: (Visual t, Visual u) => t -> u -> BaseVisual over this that = (map (\p -> p{ attribs = (attribs p){ layer = maxlev+1 }}) . primitives $ this) ++ primitives that where maxlev = maximum . map (layer . attribs) . primitives $ that infixr 9 `over` infixr 9 `moreSpecific` -- | Declare that a Visual is more specific than another Visual. This way one drawing can have multiple levels of detail. moreSpecific :: (Visual t, Visual u) => t -> u -> BaseVisual moreSpecific this that = (map (\p -> p{ attribs = (attribs p){ lod = maxlev+1 }}) . primitives $ this) ++ primitives that where maxlev = minimum . map (lod . attribs) . primitives $ that -- | Get an ordering of two Visuals to see if one possibly occludes the other. The greater one is on top. isOverOrUnder :: (Visual t, Visual u) => t -> u -> Ordering isOverOrUnder a b = compare maxb maxa where maxa = maximum . map (layer . attribs) . primitives $ a maxb = maximum . map (layer . attribs) . primitives $ b -- | Get an ordering of two Visuals to see if one is more specific than another. Useful for filtering out detail for a higher level vis. isMoreSpecific :: (Visual t, Visual u) => t -> u -> Ordering isMoreSpecific a b = compare maxb maxa where maxa = maximum . map (lod . attribs) . primitives $ a maxb = maximum . map (lod . attribs) . primitives $ b