Copyright | (c) 2011-2015 diagrams-lib team (see LICENSE) |
---|---|
License | BSD-style (see LICENSE) |
Maintainer | diagrams-discuss@googlegroups.com |
Safe Haskell | None |
Language | Haskell2010 |
This module defines the two-dimensional vector space R^2, two-dimensional transformations, and various predefined two-dimensional shapes. This module re-exports useful functionality from a group of more specific modules:
- Diagrams.TwoD.Types defines basic types for two-dimensional diagrams, including types representing the 2D Euclidean vector space and various systems of angle measurement.
- Diagrams.TwoD.Align defines alignment combinators specialized to two dimensions (see Diagrams.Align for more general alignment).
- Diagrams.TwoD.Combinators defines ways of combining diagrams specialized to two dimensions (see also Diagrams.Combinators for more general combining).
- Diagrams.TwoD.Attributes defines attributes specific to two dimensions, *e.g.* fill color, line color, and gradients.
- Diagrams.TwoD.Transform defines R^2-specific transformations such as rotation by an angle, and scaling, translation, and reflection in the X and Y directions.
- Diagrams.TwoD.Deform defines some non-affine transformations specific to two dimensions, *e.g.* parallel and perspective projections.
- Diagrams.TwoD.Ellipse defines circles and ellipses.
- Diagrams.TwoD.Arc defines circular arcs.
- Diagrams.TwoD.Path exports various operations on two-dimensional paths when viewed as regions of the plane.
- Diagrams.TwoD.Polygons defines general algorithms for drawing various types of polygons.
- Diagrams.TwoD.Shapes defines other two-dimensional shapes, e.g. various polygons.
- Diagrams.TwoD.Arrow contains tools for drawing arrows between things, and Diagrams.TwoD.Arrowheads defines a collection of arrowheads.
- Diagrams.TwoD.Text defines primitive text diagrams.
- Diagrams.TwoD.Image allows importing external images into diagrams.
- Diagrams.TwoD.Vector defines some special 2D vectors and functions for converting between vectors and angles.
- Diagrams.TwoD.Size defines functions for working with the size of 2D objects.
- Diagrams.TwoD.Model defines some aids for visualizing diagrams' internal model (local origins, envelopes, etc.)
- data V2 a :: * -> * = V2 !a !a
- class R1 t where
- class R1 t => R2 t where
- type P2 = Point V2
- type T2 = Transformation V2
- r2 :: (n, n) -> V2 n
- unr2 :: V2 n -> (n, n)
- mkR2 :: n -> n -> V2 n
- p2 :: (n, n) -> P2 n
- unp2 :: P2 n -> (n, n)
- mkP2 :: n -> n -> P2 n
- unitX :: (R1 v, Additive v, Num n) => v n
- unitY :: (R2 v, Additive v, Num n) => v n
- unit_X :: (R1 v, Additive v, Num n) => v n
- unit_Y :: (R2 v, Additive v, Num n) => v n
- perp :: Num a => V2 a -> V2 a
- leftTurn :: (Num n, Ord n) => V2 n -> V2 n -> Bool
- xDir :: (R1 v, Additive v, Num n) => Direction v n
- yDir :: (R2 v, Additive v, Num n) => Direction v n
- tau :: Floating a => a
- angleV :: Floating n => Angle n -> V2 n
- angleDir :: Floating n => Angle n -> Direction V2 n
- signedAngleBetween :: RealFloat n => V2 n -> V2 n -> Angle n
- signedAngleBetweenDirs :: RealFloat n => Direction V2 n -> Direction V2 n -> Angle n
- class HasR t where
- r2PolarIso :: RealFloat n => Iso' (V2 n) (n, Angle n)
- stroke :: (InSpace V2 n t, ToPath t, TypeableFloat n, Renderable (Path V2 n) b) => t -> QDiagram b V2 n Any
- stroke' :: (InSpace V2 n t, ToPath t, TypeableFloat n, Renderable (Path V2 n) b, IsName a) => StrokeOpts a -> t -> QDiagram b V2 n Any
- strokePath :: (TypeableFloat n, Renderable (Path V2 n) b) => Path V2 n -> QDiagram b V2 n Any
- strokeP :: (TypeableFloat n, Renderable (Path V2 n) b) => Path V2 n -> QDiagram b V2 n Any
- strokePath' :: (TypeableFloat n, Renderable (Path V2 n) b, IsName a) => StrokeOpts a -> Path V2 n -> QDiagram b V2 n Any
- strokeP' :: (TypeableFloat n, Renderable (Path V2 n) b, IsName a) => StrokeOpts a -> Path V2 n -> QDiagram b V2 n Any
- strokeTrail :: (TypeableFloat n, Renderable (Path V2 n) b) => Trail V2 n -> QDiagram b V2 n Any
- strokeT :: (TypeableFloat n, Renderable (Path V2 n) b) => Trail V2 n -> QDiagram b V2 n Any
- strokeTrail' :: (TypeableFloat n, Renderable (Path V2 n) b, IsName a) => StrokeOpts a -> Trail V2 n -> QDiagram b V2 n Any
- strokeT' :: (TypeableFloat n, Renderable (Path V2 n) b, IsName a) => StrokeOpts a -> Trail V2 n -> QDiagram b V2 n Any
- strokeLine :: (TypeableFloat n, Renderable (Path V2 n) b) => Trail' Line V2 n -> QDiagram b V2 n Any
- strokeLoop :: (TypeableFloat n, Renderable (Path V2 n) b) => Trail' Loop V2 n -> QDiagram b V2 n Any
- strokeLocTrail :: (TypeableFloat n, Renderable (Path V2 n) b) => Located (Trail V2 n) -> QDiagram b V2 n Any
- strokeLocT :: (TypeableFloat n, Renderable (Path V2 n) b) => Located (Trail V2 n) -> QDiagram b V2 n Any
- strokeLocLine :: (TypeableFloat n, Renderable (Path V2 n) b) => Located (Trail' Line V2 n) -> QDiagram b V2 n Any
- strokeLocLoop :: (TypeableFloat n, Renderable (Path V2 n) b) => Located (Trail' Loop V2 n) -> QDiagram b V2 n Any
- data FillRule
- fillRule :: HasStyle a => FillRule -> a -> a
- _fillRule :: Lens' (Style V2 n) FillRule
- data StrokeOpts a = StrokeOpts {
- _vertexNames :: [[a]]
- _queryFillRule :: FillRule
- vertexNames :: forall a a'. Lens (StrokeOpts a) (StrokeOpts a') [[a]] [[a']]
- queryFillRule :: forall a. Lens' (StrokeOpts a) FillRule
- intersectPoints :: (InSpace V2 n t, SameSpace t s, ToPath t, ToPath s, OrderedField n) => t -> s -> [P2 n]
- intersectPoints' :: (InSpace V2 n t, SameSpace t s, ToPath t, ToPath s, OrderedField n) => n -> t -> s -> [P2 n]
- intersectPointsP :: OrderedField n => Path V2 n -> Path V2 n -> [P2 n]
- intersectPointsP' :: OrderedField n => n -> Path V2 n -> Path V2 n -> [P2 n]
- intersectPointsT :: OrderedField n => Located (Trail V2 n) -> Located (Trail V2 n) -> [P2 n]
- intersectPointsT' :: OrderedField n => n -> Located (Trail V2 n) -> Located (Trail V2 n) -> [P2 n]
- clipBy :: (HasStyle a, V a ~ V2, N a ~ n, TypeableFloat n) => Path V2 n -> a -> a
- clipTo :: (TypeableFloat n, Renderable (Path V2 n) b) => Path V2 n -> QDiagram b V2 n Any -> QDiagram b V2 n Any
- clipped :: (TypeableFloat n, Renderable (Path V2 n) b) => Path V2 n -> QDiagram b V2 n Any -> QDiagram b V2 n Any
- _Clip :: Iso (Clip n) (Clip n') [Path V2 n] [Path V2 n']
- _clip :: (Typeable n, OrderedField n) => Lens' (Style V2 n) [Path V2 n]
- hrule :: (InSpace V2 n t, TrailLike t) => n -> t
- vrule :: (InSpace V2 n t, TrailLike t) => n -> t
- unitCircle :: (TrailLike t, V t ~ V2, N t ~ n, RealFloat n) => t
- circle :: (TrailLike t, V t ~ V2, N t ~ n, RealFloat n, Transformable t) => n -> t
- ellipse :: (TrailLike t, V t ~ V2, N t ~ n, RealFloat n, Transformable t) => n -> t
- ellipseXY :: (TrailLike t, V t ~ V2, N t ~ n, RealFloat n, Transformable t) => n -> n -> t
- arc :: (InSpace V2 n t, OrderedField n, TrailLike t) => Direction V2 n -> Angle n -> t
- arc' :: (InSpace V2 n t, OrderedField n, TrailLike t) => n -> Direction V2 n -> Angle n -> t
- arcCW :: (InSpace V2 n t, RealFloat n, TrailLike t) => Direction V2 n -> Direction V2 n -> t
- arcCCW :: (InSpace V2 n t, RealFloat n, TrailLike t) => Direction V2 n -> Direction V2 n -> t
- wedge :: (InSpace V2 n t, OrderedField n, TrailLike t) => n -> Direction V2 n -> Angle n -> t
- arcBetween :: (TrailLike t, V t ~ V2, N t ~ n, RealFloat n) => Point V2 n -> Point V2 n -> n -> t
- annularWedge :: (TrailLike t, V t ~ V2, N t ~ n, RealFloat n) => n -> n -> Direction V2 n -> Angle n -> t
- polygon :: (InSpace V2 n t, TrailLike t, OrderedField n) => PolygonOpts n -> t
- polyTrail :: OrderedField n => PolygonOpts n -> Located (Trail V2 n)
- data PolygonOpts n = PolygonOpts {
- _polyType :: PolyType n
- _polyOrient :: PolyOrientation n
- _polyCenter :: Point V2 n
- polyType :: Lens' (PolygonOpts n) (PolyType n)
- polyOrient :: Lens' (PolygonOpts n) (PolyOrientation n)
- polyCenter :: Lens' (PolygonOpts n) (Point V2 n)
- data PolyType n
- data PolyOrientation n
- data StarOpts
- star :: OrderedField n => StarOpts -> [Point V2 n] -> Path V2 n
- regPoly :: (InSpace V2 n t, TrailLike t, OrderedField n) => Int -> n -> t
- triangle :: (InSpace V2 n t, TrailLike t, OrderedField n) => n -> t
- eqTriangle :: (InSpace V2 n t, TrailLike t, OrderedField n) => n -> t
- square :: (InSpace V2 n t, TrailLike t, OrderedField n) => n -> t
- pentagon :: (InSpace V2 n t, TrailLike t, OrderedField n) => n -> t
- hexagon :: (InSpace V2 n t, TrailLike t, OrderedField n) => n -> t
- heptagon :: (InSpace V2 n t, TrailLike t, OrderedField n) => n -> t
- septagon :: (InSpace V2 n t, TrailLike t, OrderedField n) => n -> t
- octagon :: (InSpace V2 n t, TrailLike t, OrderedField n) => n -> t
- nonagon :: (InSpace V2 n t, TrailLike t, OrderedField n) => n -> t
- decagon :: (InSpace V2 n t, TrailLike t, OrderedField n) => n -> t
- hendecagon :: (InSpace V2 n t, TrailLike t, OrderedField n) => n -> t
- dodecagon :: (InSpace V2 n t, TrailLike t, OrderedField n) => n -> t
- unitSquare :: (InSpace V2 n t, TrailLike t, OrderedField n) => t
- rect :: (InSpace V2 n t, TrailLike t, OrderedField n) => n -> n -> t
- roundedRect :: (InSpace V2 n t, TrailLike t, RealFloat n) => n -> n -> n -> t
- roundedRect' :: (InSpace V2 n t, TrailLike t, RealFloat n) => n -> n -> RoundedRectOpts n -> t
- data RoundedRectOpts d = RoundedRectOpts {}
- radiusTL :: forall d. Lens' (RoundedRectOpts d) d
- radiusTR :: forall d. Lens' (RoundedRectOpts d) d
- radiusBL :: forall d. Lens' (RoundedRectOpts d) d
- radiusBR :: forall d. Lens' (RoundedRectOpts d) d
- arrowV :: (TypeableFloat n, Renderable (Path V2 n) b) => V2 n -> QDiagram b V2 n Any
- arrowV' :: (TypeableFloat n, Renderable (Path V2 n) b) => ArrowOpts n -> V2 n -> QDiagram b V2 n Any
- arrowAt :: (TypeableFloat n, Renderable (Path V2 n) b) => Point V2 n -> V2 n -> QDiagram b V2 n Any
- arrowAt' :: (TypeableFloat n, Renderable (Path V2 n) b) => ArrowOpts n -> Point V2 n -> V2 n -> QDiagram b V2 n Any
- arrowBetween :: (TypeableFloat n, Renderable (Path V2 n) b) => Point V2 n -> Point V2 n -> QDiagram b V2 n Any
- arrowBetween' :: (TypeableFloat n, Renderable (Path V2 n) b) => ArrowOpts n -> Point V2 n -> Point V2 n -> QDiagram b V2 n Any
- connect :: (TypeableFloat n, Renderable (Path V2 n) b, IsName n1, IsName n2) => n1 -> n2 -> QDiagram b V2 n Any -> QDiagram b V2 n Any
- connect' :: (TypeableFloat n, Renderable (Path V2 n) b, IsName n1, IsName n2) => ArrowOpts n -> n1 -> n2 -> QDiagram b V2 n Any -> QDiagram b V2 n Any
- connectPerim :: (TypeableFloat n, Renderable (Path V2 n) b, IsName n1, IsName n2) => n1 -> n2 -> Angle n -> Angle n -> QDiagram b V2 n Any -> QDiagram b V2 n Any
- connectPerim' :: (TypeableFloat n, Renderable (Path V2 n) b, IsName n1, IsName n2) => ArrowOpts n -> n1 -> n2 -> Angle n -> Angle n -> QDiagram b V2 n Any -> QDiagram b V2 n Any
- connectOutside :: (TypeableFloat n, Renderable (Path V2 n) b, IsName n1, IsName n2) => n1 -> n2 -> QDiagram b V2 n Any -> QDiagram b V2 n Any
- connectOutside' :: (TypeableFloat n, Renderable (Path V2 n) b, IsName n1, IsName n2) => ArrowOpts n -> n1 -> n2 -> QDiagram b V2 n Any -> QDiagram b V2 n Any
- arrow :: (TypeableFloat n, Renderable (Path V2 n) b) => n -> QDiagram b V2 n Any
- arrow' :: (TypeableFloat n, Renderable (Path V2 n) b) => ArrowOpts n -> n -> QDiagram b V2 n Any
- straightShaft :: OrderedField n => Trail V2 n
- module Diagrams.TwoD.Arrowheads
- data ArrowOpts n = ArrowOpts {
- _arrowHead :: ArrowHT n
- _arrowTail :: ArrowHT n
- _arrowShaft :: Trail V2 n
- _headGap :: Measure n
- _tailGap :: Measure n
- _headStyle :: Style V2 n
- _headLength :: Measure n
- _tailStyle :: Style V2 n
- _tailLength :: Measure n
- _shaftStyle :: Style V2 n
- arrowHead :: Lens' (ArrowOpts n) (ArrowHT n)
- arrowTail :: Lens' (ArrowOpts n) (ArrowHT n)
- arrowShaft :: Lens' (ArrowOpts n) (Trail V2 n)
- headGap :: Lens' (ArrowOpts n) (Measure n)
- tailGap :: Lens' (ArrowOpts n) (Measure n)
- gaps :: Traversal' (ArrowOpts n) (Measure n)
- gap :: Traversal' (ArrowOpts n) (Measure n)
- headTexture :: TypeableFloat n => Lens' (ArrowOpts n) (Texture n)
- headStyle :: Lens' (ArrowOpts n) (Style V2 n)
- tailTexture :: TypeableFloat n => Lens' (ArrowOpts n) (Texture n)
- tailStyle :: Lens' (ArrowOpts n) (Style V2 n)
- shaftTexture :: TypeableFloat n => Lens' (ArrowOpts n) (Texture n)
- shaftStyle :: Lens' (ArrowOpts n) (Style V2 n)
- headLength :: Lens' (ArrowOpts n) (Measure n)
- tailLength :: Lens' (ArrowOpts n) (Measure n)
- lengths :: Traversal' (ArrowOpts n) (Measure n)
- text :: (TypeableFloat n, Renderable (Text n) b) => String -> QDiagram b V2 n Any
- topLeftText :: (TypeableFloat n, Renderable (Text n) b) => String -> QDiagram b V2 n Any
- alignedText :: (TypeableFloat n, Renderable (Text n) b) => n -> n -> String -> QDiagram b V2 n Any
- baselineText :: (TypeableFloat n, Renderable (Text n) b) => String -> QDiagram b V2 n Any
- font :: HasStyle a => String -> a -> a
- italic :: HasStyle a => a -> a
- oblique :: HasStyle a => a -> a
- bold :: HasStyle a => a -> a
- fontSize :: (N a ~ n, Typeable n, HasStyle a) => Measure n -> a -> a
- _font :: (Typeable n, OrderedField n) => Lens' (Style v n) (Maybe String)
- _fontSizeR :: (Typeable n, OrderedField n) => Lens' (Style v n) (Measured n (Recommend n))
- _fontSize :: (Typeable n, OrderedField n) => Lens' (Style v n) (Measure n)
- fontSizeO :: (N a ~ n, Typeable n, Num n, HasStyle a) => n -> a -> a
- fontSizeL :: (N a ~ n, Typeable n, Num n, HasStyle a) => n -> a -> a
- fontSizeN :: (N a ~ n, Typeable n, Num n, HasStyle a) => n -> a -> a
- fontSizeG :: (N a ~ n, Typeable n, Num n, HasStyle a) => n -> a -> a
- data DImage :: * -> * -> * where
- data ImageData :: * -> * where
- ImageRaster :: DynamicImage -> ImageData Embedded
- ImageRef :: FilePath -> ImageData External
- ImageNative :: t -> ImageData (Native t)
- data Embedded
- data External
- data Native t
- image :: (TypeableFloat n, Typeable a, Renderable (DImage n a) b) => DImage n a -> QDiagram b V2 n Any
- loadImageEmb :: Num n => FilePath -> IO (Either String (DImage n Embedded))
- loadImageExt :: Num n => FilePath -> IO (Either String (DImage n External))
- uncheckedImageRef :: Num n => FilePath -> Int -> Int -> DImage n External
- raster :: Num n => (Int -> Int -> AlphaColour Double) -> Int -> Int -> DImage n Embedded
- rasterDia :: (TypeableFloat n, Renderable (DImage n Embedded) b) => (Int -> Int -> AlphaColour Double) -> Int -> Int -> QDiagram b V2 n Any
- rotation :: Floating n => Angle n -> T2 n
- rotate :: (InSpace V2 n t, Transformable t, Floating n) => Angle n -> t -> t
- rotateBy :: (InSpace V2 n t, Transformable t, Floating n) => n -> t -> t
- rotated :: (InSpace V2 n a, Floating n, SameSpace a b, Transformable a, Transformable b) => Angle n -> Iso a b a b
- rotationAround :: Floating n => P2 n -> Angle n -> T2 n
- rotateAround :: (InSpace V2 n t, Transformable t, Floating n) => P2 n -> Angle n -> t -> t
- rotationTo :: OrderedField n => Direction V2 n -> T2 n
- rotateTo :: (InSpace V2 n t, OrderedField n, Transformable t) => Direction V2 n -> t -> t
- scalingX :: (Additive v, R1 v, Fractional n) => n -> Transformation v n
- scaleX :: (InSpace v n t, R2 v, Fractional n, Transformable t) => n -> t -> t
- scalingY :: (Additive v, R2 v, Fractional n) => n -> Transformation v n
- scaleY :: (InSpace v n t, R2 v, Fractional n, Transformable t) => n -> t -> t
- scaling :: (Additive v, Fractional n) => n -> Transformation v n
- scale :: (InSpace v n a, Eq n, Fractional n, Transformable a) => n -> a -> a
- scaleToX :: (InSpace v n t, R2 v, Enveloped t, Transformable t) => n -> t -> t
- scaleToY :: (InSpace v n t, R2 v, Enveloped t, Transformable t) => n -> t -> t
- scaleUToX :: (InSpace v n t, R1 v, Enveloped t, Transformable t) => n -> t -> t
- scaleUToY :: (InSpace v n t, R2 v, Enveloped t, Transformable t) => n -> t -> t
- translationX :: (Additive v, R1 v, Num n) => n -> Transformation v n
- translateX :: (InSpace v n t, R1 v, Transformable t) => n -> t -> t
- translationY :: (Additive v, R2 v, Num n) => n -> Transformation v n
- translateY :: (InSpace v n t, R2 v, Transformable t) => n -> t -> t
- translation :: v n -> Transformation v n
- translate :: (Num (N t), Transformable t) => Vn t -> t -> t
- reflectionX :: (Additive v, R1 v, Num n) => Transformation v n
- reflectX :: (InSpace v n t, R1 v, Transformable t) => t -> t
- reflectionY :: (Additive v, R2 v, Num n) => Transformation v n
- reflectY :: (InSpace v n t, R2 v, Transformable t) => t -> t
- reflectionAbout :: OrderedField n => P2 n -> Direction V2 n -> T2 n
- reflectAbout :: (InSpace V2 n t, OrderedField n, Transformable t) => P2 n -> Direction V2 n -> t -> t
- shearingX :: Num n => n -> T2 n
- shearX :: (InSpace V2 n t, Transformable t) => n -> t -> t
- shearingY :: Num n => n -> T2 n
- shearY :: (InSpace V2 n t, Transformable t) => n -> t -> t
- parallelX0 :: (R1 v, Num n) => Deformation v v n
- perspectiveX1 :: (R1 v, Functor v, Fractional n) => Deformation v v n
- parallelY0 :: (R2 v, Num n) => Deformation v v n
- perspectiveY1 :: (R2 v, Functor v, Floating n) => Deformation v v n
- facingX :: (R1 v, Functor v, Fractional n) => Deformation v v n
- facingY :: (R2 v, Functor v, Fractional n) => Deformation v v n
- (===) :: (InSpace V2 n a, Num n, Juxtaposable a, Semigroup a) => a -> a -> a
- (|||) :: (InSpace V2 n a, Num n, Juxtaposable a, Semigroup a) => a -> a -> a
- hcat :: (InSpace V2 n a, Floating n, Juxtaposable a, HasOrigin a, Monoid' a) => [a] -> a
- hcat' :: (InSpace V2 n a, Floating n, Juxtaposable a, HasOrigin a, Monoid' a) => CatOpts n -> [a] -> a
- hsep :: (InSpace V2 n a, Floating n, Juxtaposable a, HasOrigin a, Monoid' a) => n -> [a] -> a
- vcat :: (InSpace V2 n a, Floating n, Juxtaposable a, HasOrigin a, Monoid' a) => [a] -> a
- vcat' :: (InSpace V2 n a, Floating n, Juxtaposable a, HasOrigin a, Monoid' a) => CatOpts n -> [a] -> a
- vsep :: (InSpace V2 n a, Floating n, Juxtaposable a, HasOrigin a, Monoid' a) => n -> [a] -> a
- strutX :: (Metric v, R1 v, OrderedField n, Monoid' m) => n -> QDiagram b v n m
- strutY :: (Metric v, R2 v, OrderedField n, Monoid' m) => n -> QDiagram b v n m
- padX :: (Metric v, R2 v, OrderedField n, Monoid' m) => n -> QDiagram b v n m -> QDiagram b v n m
- padY :: (Metric v, R2 v, Monoid' m, OrderedField n) => n -> QDiagram b v n m -> QDiagram b v n m
- extrudeLeft :: (OrderedField n, Monoid' m) => n -> QDiagram b V2 n m -> QDiagram b V2 n m
- extrudeRight :: (OrderedField n, Monoid' m) => n -> QDiagram b V2 n m -> QDiagram b V2 n m
- extrudeBottom :: (OrderedField n, Monoid' m) => n -> QDiagram b V2 n m -> QDiagram b V2 n m
- extrudeTop :: (OrderedField n, Monoid' m) => n -> QDiagram b V2 n m -> QDiagram b V2 n m
- rectEnvelope :: forall b n m. (OrderedField n, Monoid' m) => Point V2 n -> V2 n -> QDiagram b V2 n m -> QDiagram b V2 n m
- boundingRect :: (InSpace V2 n a, SameSpace a t, Enveloped t, Transformable t, TrailLike t, Monoid t, Enveloped a) => a -> t
- bg :: (TypeableFloat n, Renderable (Path V2 n) b) => Colour Double -> QDiagram b V2 n Any -> QDiagram b V2 n Any
- bgFrame :: (TypeableFloat n, Renderable (Path V2 n) b) => n -> Colour Double -> QDiagram b V2 n Any -> QDiagram b V2 n Any
- alignL :: (InSpace V2 n a, Fractional n, Alignable a, HasOrigin a) => a -> a
- alignR :: (InSpace V2 n a, Fractional n, Alignable a, HasOrigin a) => a -> a
- alignT :: (InSpace V2 n a, Fractional n, Alignable a, HasOrigin a) => a -> a
- alignB :: (InSpace V2 n a, Fractional n, Alignable a, HasOrigin a) => a -> a
- alignTL :: (InSpace V2 n a, Fractional n, Alignable a, HasOrigin a) => a -> a
- alignTR :: (InSpace V2 n a, Fractional n, Alignable a, HasOrigin a) => a -> a
- alignBL :: (InSpace V2 n a, Fractional n, Alignable a, HasOrigin a) => a -> a
- alignBR :: (InSpace V2 n a, Fractional n, Alignable a, HasOrigin a) => a -> a
- alignX :: (InSpace v n a, R1 v, Fractional n, Alignable a, HasOrigin a) => n -> a -> a
- alignY :: (InSpace v n a, R2 v, Fractional n, Alignable a, HasOrigin a) => n -> a -> a
- centerX :: (InSpace v n a, R1 v, Fractional n, Alignable a, HasOrigin a) => a -> a
- centerY :: (InSpace v n a, R2 v, Fractional n, Alignable a, HasOrigin a) => a -> a
- centerXY :: (InSpace v n a, R2 v, Fractional n, Alignable a, HasOrigin a) => a -> a
- snugL :: (InSpace V2 n a, Fractional n, Alignable a, Traced a, HasOrigin a) => a -> a
- snugR :: (InSpace V2 n a, Fractional n, Alignable a, Traced a, HasOrigin a) => a -> a
- snugT :: (InSpace V2 n a, Fractional n, Alignable a, Traced a, HasOrigin a) => a -> a
- snugB :: (InSpace V2 n a, Fractional n, Alignable a, Traced a, HasOrigin a) => a -> a
- snugTL :: (InSpace V2 n a, Fractional n, Alignable a, Traced a, HasOrigin a) => a -> a
- snugTR :: (InSpace V2 n a, Fractional n, Alignable a, Traced a, HasOrigin a) => a -> a
- snugBL :: (InSpace V2 n a, Fractional n, Alignable a, Traced a, HasOrigin a) => a -> a
- snugBR :: (InSpace V2 n a, Fractional n, Alignable a, Traced a, HasOrigin a) => a -> a
- snugX :: (InSpace v n a, R1 v, Fractional n, Alignable a, Traced a, HasOrigin a) => n -> a -> a
- snugY :: (InSpace v n a, R2 v, Fractional n, Alignable a, Traced a, HasOrigin a) => n -> a -> a
- snugCenterX :: (InSpace v n a, R1 v, Fractional n, Alignable a, Traced a, HasOrigin a) => a -> a
- snugCenterY :: (InSpace v n a, R2 v, Fractional n, Alignable a, Traced a, HasOrigin a) => a -> a
- snugCenterXY :: (InSpace v n a, R2 v, Fractional n, Alignable a, Traced a, HasOrigin a) => a -> a
- width :: (InSpace V2 n a, Enveloped a) => a -> n
- height :: (InSpace V2 n a, Enveloped a) => a -> n
- extentX :: (InSpace v n a, R1 v, Enveloped a) => a -> Maybe (n, n)
- extentY :: (InSpace v n a, R2 v, Enveloped a) => a -> Maybe (n, n)
- mkSizeSpec2D :: Num n => Maybe n -> Maybe n -> SizeSpec V2 n
- mkWidth :: Num n => n -> SizeSpec V2 n
- mkHeight :: Num n => n -> SizeSpec V2 n
- dims2D :: n -> n -> SizeSpec V2 n
- data Texture n
- solid :: Color a => a -> Texture n
- data SpreadMethod
- data GradientStop d = GradientStop {
- _stopColor :: SomeColor
- _stopFraction :: d
- _FillTexture :: Iso' (FillTexture n) (Recommend (Texture n))
- fillTexture :: (InSpace V2 n a, Typeable n, Floating n, HasStyle a) => Texture n -> a -> a
- _fillTexture :: (Typeable n, Floating n) => Lens' (Style V2 n) (Texture n)
- getFillTexture :: FillTexture n -> Texture n
- _LineTexture :: Iso (LineTexture n) (LineTexture n') (Texture n) (Texture n')
- lineTexture :: (InSpace V2 n a, Typeable n, Floating n, HasStyle a) => Texture n -> a -> a
- _lineTexture :: (Floating n, Typeable n) => Lens' (Style V2 n) (Texture n)
- lineTextureA :: (InSpace V2 n a, Typeable n, Floating n, HasStyle a) => LineTexture n -> a -> a
- getLineTexture :: LineTexture n -> Texture n
- stopFraction :: Lens' (GradientStop n) n
- stopColor :: Lens' (GradientStop n) SomeColor
- mkStops :: [(Colour Double, d, Double)] -> [GradientStop d]
- data LGradient n = LGradient {
- _lGradStops :: [GradientStop n]
- _lGradStart :: Point V2 n
- _lGradEnd :: Point V2 n
- _lGradTrans :: Transformation V2 n
- _lGradSpreadMethod :: SpreadMethod
- _LG :: forall n. Prism' (Texture n) (LGradient n)
- lGradStops :: Lens' (LGradient n) [GradientStop n]
- lGradTrans :: Lens' (LGradient n) (Transformation V2 n)
- lGradStart :: Lens' (LGradient n) (Point V2 n)
- lGradEnd :: Lens' (LGradient n) (Point V2 n)
- lGradSpreadMethod :: Lens' (LGradient n) SpreadMethod
- defaultLG :: Fractional n => Texture n
- mkLinearGradient :: Num n => [GradientStop n] -> Point V2 n -> Point V2 n -> SpreadMethod -> Texture n
- data RGradient n = RGradient {
- _rGradStops :: [GradientStop n]
- _rGradCenter0 :: Point V2 n
- _rGradRadius0 :: n
- _rGradCenter1 :: Point V2 n
- _rGradRadius1 :: n
- _rGradTrans :: Transformation V2 n
- _rGradSpreadMethod :: SpreadMethod
- rGradStops :: Lens' (RGradient n) [GradientStop n]
- rGradCenter0 :: Lens' (RGradient n) (Point V2 n)
- rGradRadius0 :: Lens' (RGradient n) n
- rGradCenter1 :: Lens' (RGradient n) (Point V2 n)
- rGradRadius1 :: Lens' (RGradient n) n
- rGradTrans :: Lens' (RGradient n) (Transformation V2 n)
- rGradSpreadMethod :: Lens' (RGradient n) SpreadMethod
- defaultRG :: Fractional n => Texture n
- _RG :: forall n. Prism' (Texture n) (RGradient n)
- mkRadialGradient :: Num n => [GradientStop n] -> Point V2 n -> n -> Point V2 n -> n -> SpreadMethod -> Texture n
- fillColor :: (InSpace V2 n a, Color c, Typeable n, Floating n, HasStyle a) => c -> a -> a
- _SC :: forall n. Prism' (Texture n) SomeColor
- _AC :: Prism' (Texture n) (AlphaColour Double)
- fc :: (InSpace V2 n a, Floating n, Typeable n, HasStyle a) => Colour Double -> a -> a
- fcA :: (InSpace V2 n a, Floating n, Typeable n, HasStyle a) => AlphaColour Double -> a -> a
- recommendFillColor :: (InSpace V2 n a, Color c, Typeable n, Floating n, HasStyle a) => c -> a -> a
- lineColor :: (InSpace V2 n a, Color c, Typeable n, Floating n, HasStyle a) => c -> a -> a
- lc :: (InSpace V2 n a, Typeable n, Floating n, HasStyle a) => Colour Double -> a -> a
- lcA :: (InSpace V2 n a, Typeable n, Floating n, HasStyle a) => AlphaColour Double -> a -> a
- showOrigin :: (TypeableFloat n, Renderable (Path V2 n) b, Monoid' m) => QDiagram b V2 n m -> QDiagram b V2 n m
- showOrigin' :: (TypeableFloat n, Renderable (Path V2 n) b, Monoid' m) => OriginOpts n -> QDiagram b V2 n m -> QDiagram b V2 n m
- data OriginOpts n = OriginOpts {}
- oColor :: forall n. Lens' (OriginOpts n) (Colour Double)
- oScale :: forall n. Lens' (OriginOpts n) n
- oMinSize :: forall n. Lens' (OriginOpts n) n
- showEnvelope :: (Enum n, TypeableFloat n, Renderable (Path V2 n) b) => QDiagram b V2 n Any -> QDiagram b V2 n Any
- showEnvelope' :: (Enum n, TypeableFloat n, Renderable (Path V2 n) b) => EnvelopeOpts n -> QDiagram b V2 n Any -> QDiagram b V2 n Any
- data EnvelopeOpts n = EnvelopeOpts {}
- eColor :: forall n. Lens' (EnvelopeOpts n) (Colour Double)
- eLineWidth :: forall n n. Lens (EnvelopeOpts n) (EnvelopeOpts n) (Measure n) (Measure n)
- ePoints :: forall n. Lens' (EnvelopeOpts n) Int
- showTrace :: (Enum n, TypeableFloat n, Renderable (Path V2 n) b) => QDiagram b V2 n Any -> QDiagram b V2 n Any
- showTrace' :: (Enum n, TypeableFloat n, Renderable (Path V2 n) b) => TraceOpts n -> QDiagram b V2 n Any -> QDiagram b V2 n Any
- data TraceOpts n = TraceOpts {}
- tColor :: forall n. Lens' (TraceOpts n) (Colour Double)
- tScale :: forall n. Lens' (TraceOpts n) n
- tMinSize :: forall n. Lens' (TraceOpts n) n
- tPoints :: forall n. Lens' (TraceOpts n) Int
- showLabels :: (TypeableFloat n, Renderable (Text n) b, Semigroup m) => QDiagram b V2 n m -> QDiagram b V2 n Any
R^2
data V2 a :: * -> *
A 2-dimensional vector
>>>
pure 1 :: V2 Int
V2 1 1
>>>
V2 1 2 + V2 3 4
V2 4 6
>>>
V2 1 2 * V2 3 4
V2 3 8
>>>
sum (V2 1 2)
3
V2 !a !a |
type T2 = Transformation V2 Source
the counter-clockwise perpendicular vector
>>>
perp $ V2 10 20
V2 (-20) 10
leftTurn :: (Num n, Ord n) => V2 n -> V2 n -> Bool Source
leftTurn v1 v2
tests whether the direction of v2
is a left
turn from v1
(that is, if the direction of v2
can be obtained
from that of v1
by adding an angle 0 <= theta <= tau/2).
Angles
The circle constant, the ratio of a circle's circumference to its
radius. Note that pi = tau/2
.
For more information and a well-reasoned argument why we should all be using tau instead of pi, see The Tau Manifesto, http://tauday.com/.
To hear what it sounds like (and to easily memorize the first 30 digits or so), try http://youtu.be/3174T-3-59Q.
angleV :: Floating n => Angle n -> V2 n Source
A unit vector at a specified angle counter-clockwise from the positive x-axis
angleDir :: Floating n => Angle n -> Direction V2 n Source
A direction at a specified angle counter-clockwise from the xDir
.
Polar Coördinates
A space which has magnitude _r
that can be calculated numerically.
Nothing
Paths
Stroking
stroke :: (InSpace V2 n t, ToPath t, TypeableFloat n, Renderable (Path V2 n) b) => t -> QDiagram b V2 n Any Source
stroke' :: (InSpace V2 n t, ToPath t, TypeableFloat n, Renderable (Path V2 n) b, IsName a) => StrokeOpts a -> t -> QDiagram b V2 n Any Source
A variant of stroke
that takes an extra record of options to
customize its behaviour. In particular:
- Names can be assigned to the path's vertices
StrokeOpts
is an instance of Default
, so stroke' (
syntax may be used.with
&
... )
strokePath :: (TypeableFloat n, Renderable (Path V2 n) b) => Path V2 n -> QDiagram b V2 n Any Source
strokePath' :: (TypeableFloat n, Renderable (Path V2 n) b, IsName a) => StrokeOpts a -> Path V2 n -> QDiagram b V2 n Any Source
strokeP' :: (TypeableFloat n, Renderable (Path V2 n) b, IsName a) => StrokeOpts a -> Path V2 n -> QDiagram b V2 n Any Source
strokeTrail :: (TypeableFloat n, Renderable (Path V2 n) b) => Trail V2 n -> QDiagram b V2 n Any Source
strokeTrail' :: (TypeableFloat n, Renderable (Path V2 n) b, IsName a) => StrokeOpts a -> Trail V2 n -> QDiagram b V2 n Any Source
A composition of stroke'
and pathFromTrail
for conveniently
converting a trail directly into a diagram.
strokeT' :: (TypeableFloat n, Renderable (Path V2 n) b, IsName a) => StrokeOpts a -> Trail V2 n -> QDiagram b V2 n Any Source
Deprecated synonym for strokeTrail'
.
strokeLine :: (TypeableFloat n, Renderable (Path V2 n) b) => Trail' Line V2 n -> QDiagram b V2 n Any Source
strokeLoop :: (TypeableFloat n, Renderable (Path V2 n) b) => Trail' Loop V2 n -> QDiagram b V2 n Any Source
strokeLocTrail :: (TypeableFloat n, Renderable (Path V2 n) b) => Located (Trail V2 n) -> QDiagram b V2 n Any Source
A convenience function for converting a Located Trail
directly
into a diagram; strokeLocTrail = stroke . trailLike
.
strokeLocT :: (TypeableFloat n, Renderable (Path V2 n) b) => Located (Trail V2 n) -> QDiagram b V2 n Any Source
Deprecated synonym for strokeLocTrail
.
strokeLocLine :: (TypeableFloat n, Renderable (Path V2 n) b) => Located (Trail' Line V2 n) -> QDiagram b V2 n Any Source
A convenience function for converting a Located
line directly
into a diagram; strokeLocLine = stroke . trailLike . mapLoc wrapLine
.
strokeLocLoop :: (TypeableFloat n, Renderable (Path V2 n) b) => Located (Trail' Loop V2 n) -> QDiagram b V2 n Any Source
A convenience function for converting a Located
loop directly
into a diagram; strokeLocLoop = stroke . trailLike . mapLoc wrapLoop
.
Enumeration of algorithms or "rules" for determining which points lie in the interior of a (possibly self-intersecting) path.
Winding | Interior points are those with a nonzero winding number. See http://en.wikipedia.org/wiki/Nonzero-rule. |
EvenOdd | Interior points are those where a ray extended infinitely in a particular direction crosses the path an odd number of times. See http://en.wikipedia.org/wiki/Even-odd_rule. |
fillRule :: HasStyle a => FillRule -> a -> a Source
Specify the fill rule that should be used for determining which points are inside a path.
data StrokeOpts a Source
A record of options that control how a path is stroked.
StrokeOpts
is an instance of Default
, so a StrokeOpts
records can be created using
notation.with
{ ... }
StrokeOpts | |
|
Default (StrokeOpts a) Source |
vertexNames :: forall a a'. Lens (StrokeOpts a) (StrokeOpts a') [[a]] [[a']] Source
Atomic names that should be assigned to the vertices of the path so that they can be referenced later. If there are not enough names, the extra vertices are not assigned names; if there are too many, the extra names are ignored. Note that this is a list of lists of names, since paths can consist of multiple trails. The first list of names are assigned to the vertices of the first trail, the second list to the second trail, and so on.
The default value is the empty list.
queryFillRule :: forall a. Lens' (StrokeOpts a) FillRule Source
intersectPoints :: (InSpace V2 n t, SameSpace t s, ToPath t, ToPath s, OrderedField n) => t -> s -> [P2 n] Source
Find the intersect points of two objects that can be converted to a path.
intersectPoints' :: (InSpace V2 n t, SameSpace t s, ToPath t, ToPath s, OrderedField n) => n -> t -> s -> [P2 n] Source
Find the intersect points of two objects that can be converted to a path within the given tolerance.
intersectPointsP :: OrderedField n => Path V2 n -> Path V2 n -> [P2 n] Source
Compute the intersect points between two paths.
intersectPointsP' :: OrderedField n => n -> Path V2 n -> Path V2 n -> [P2 n] Source
Compute the intersect points between two paths within given tolerance.
intersectPointsT :: OrderedField n => Located (Trail V2 n) -> Located (Trail V2 n) -> [P2 n] Source
Compute the intersect points between two located trails.
intersectPointsT' :: OrderedField n => n -> Located (Trail V2 n) -> Located (Trail V2 n) -> [P2 n] Source
Compute the intersect points between two located trails within the given tolerance.
Clipping
clipBy :: (HasStyle a, V a ~ V2, N a ~ n, TypeableFloat n) => Path V2 n -> a -> a Source
Clip a diagram by the given path:
- Only the parts of the diagram which lie in the interior of the path will be drawn.
- The envelope of the diagram is unaffected.
clipTo :: (TypeableFloat n, Renderable (Path V2 n) b) => Path V2 n -> QDiagram b V2 n Any -> QDiagram b V2 n Any Source
Clip a diagram to the given path setting its envelope to the pointwise minimum of the envelopes of the diagram and path. The trace consists of those parts of the original diagram's trace which fall within the clipping path, or parts of the path's trace within the original diagram.
clipped :: (TypeableFloat n, Renderable (Path V2 n) b) => Path V2 n -> QDiagram b V2 n Any -> QDiagram b V2 n Any Source
Clip a diagram to the clip path taking the envelope and trace of the clip path.
_clip :: (Typeable n, OrderedField n) => Lens' (Style V2 n) [Path V2 n] Source
Lens onto the Clip in a style. An empty list means no clipping.
Shapes
Rules
hrule :: (InSpace V2 n t, TrailLike t) => n -> t Source
Create a centered horizontal (L-R) line of the given length.
hruleEx = vcat' (with & sep .~ 0.2) (map hrule [1..5]) # centerXY # pad 1.1
vrule :: (InSpace V2 n t, TrailLike t) => n -> t Source
Create a centered vertical (T-B) line of the given length.
vruleEx = hcat' (with & sep .~ 0.2) (map vrule [1, 1.2 .. 2]) # centerXY # pad 1.1
Circle-ish things
unitCircle :: (TrailLike t, V t ~ V2, N t ~ n, RealFloat n) => t Source
A circle of radius 1, with center at the origin.
circle :: (TrailLike t, V t ~ V2, N t ~ n, RealFloat n, Transformable t) => n -> t Source
A circle of the given radius, centered at the origin. As a path, it begins at (r,0).
ellipse :: (TrailLike t, V t ~ V2, N t ~ n, RealFloat n, Transformable t) => n -> t Source
ellipse e
constructs an ellipse with eccentricity e
by
scaling the unit circle in the X direction. The eccentricity must
be within the interval [0,1).
ellipseXY :: (TrailLike t, V t ~ V2, N t ~ n, RealFloat n, Transformable t) => n -> n -> t Source
ellipseXY x y
creates an axis-aligned ellipse, centered at the
origin, with radius x
along the x-axis and radius y
along the
y-axis.
arc :: (InSpace V2 n t, OrderedField n, TrailLike t) => Direction V2 n -> Angle n -> t Source
Given a start direction d
and a sweep angle s
,
is the
path of a radius one arc starting at arc
d sd
and sweeping out the angle
s
counterclockwise (for positive s). The resulting
Trail
is allowed to wrap around and overlap itself.
arc' :: (InSpace V2 n t, OrderedField n, TrailLike t) => n -> Direction V2 n -> Angle n -> t Source
Given a radus r
, a start direction d
and an angle s
,
is the path of a radius arc'
r d s(abs r)
arc starting at
d
and sweeping out the angle s
counterclockwise (for positive
s). The origin of the arc is its center.
arc'Ex = mconcat [ arc' r xDir (1/4 @@ turn) | r <- [0.5,-1,1.5] ] # centerXY # pad 1.1
arcCW :: (InSpace V2 n t, RealFloat n, TrailLike t) => Direction V2 n -> Direction V2 n -> t Source
Like arcAngleCCW
but clockwise.
arcCCW :: (InSpace V2 n t, RealFloat n, TrailLike t) => Direction V2 n -> Direction V2 n -> t Source
Given a start direction s
and end direction e
, arcCCW s e
is the
path of a radius one arc counterclockwise between the two directions.
The origin of the arc is its center.
wedge :: (InSpace V2 n t, OrderedField n, TrailLike t) => n -> Direction V2 n -> Angle n -> t Source
Create a circular wedge of the given radius, beginning at the given direction and extending through the given angle.
wedgeEx = hcat' (with & sep .~ 0.5) [ wedge 1 xDir (1/4 @@ turn) , wedge 1 (rotate (7/30 @@ turn) xDir) (4/30 @@ turn) , wedge 1 (rotate (1/8 @@ turn) xDir) (3/4 @@ turn) ] # fc blue # centerXY # pad 1.1
arcBetween :: (TrailLike t, V t ~ V2, N t ~ n, RealFloat n) => Point V2 n -> Point V2 n -> n -> t Source
arcBetween p q height
creates an arc beginning at p
and
ending at q
, with its midpoint at a distance of abs height
away from the straight line from p
to q
. A positive value of
height
results in an arc to the left of the line from p
to
q
; a negative value yields one to the right.
arcBetweenEx = mconcat [ arcBetween origin (p2 (2,1)) ht | ht <- [-0.2, -0.1 .. 0.2] ] # centerXY # pad 1.1
annularWedge :: (TrailLike t, V t ~ V2, N t ~ n, RealFloat n) => n -> n -> Direction V2 n -> Angle n -> t Source
Create an annular wedge of the given radii, beginning at the first direction and extending through the given sweep angle. The radius of the outer circle is given first.
annularWedgeEx = hsep 0.50 [ annularWedge 1 0.5 xDir (1/4 @@ turn) , annularWedge 1 0.3 (rotate (7/30 @@ turn) xDir) (4/30 @@ turn) , annularWedge 1 0.7 (rotate (1/8 @@ turn) xDir) (3/4 @@ turn) ] # fc blue # centerXY # pad 1.1
General polygons
polygon :: (InSpace V2 n t, TrailLike t, OrderedField n) => PolygonOpts n -> t Source
Generate the polygon described by the given options.
polyTrail :: OrderedField n => PolygonOpts n -> Located (Trail V2 n) Source
Generate a polygon. See PolygonOpts
for more information.
data PolygonOpts n Source
Options for specifying a polygon.
PolygonOpts | |
|
Num n => Default (PolygonOpts n) Source | The default polygon is a regular pentagon of radius 1, centered at the origin, aligned to the x-axis. |
polyType :: Lens' (PolygonOpts n) (PolyType n) Source
Specification for the polygon's vertices.
polyOrient :: Lens' (PolygonOpts n) (PolyOrientation n) Source
Should a rotation be applied to the polygon in order to orient it in a particular way?
polyCenter :: Lens' (PolygonOpts n) (Point V2 n) Source
Should a translation be applied to the polygon in order to place the center at a particular location?
Method used to determine the vertices of a polygon.
PolyPolar [Angle n] [n] | A "polar" polygon.
To construct an n-gon, use a list of n-1 angles and n radii. Extra angles or radii are ignored. Cyclic polygons (with all vertices lying on a
circle) can be constructed using a second
argument of |
PolySides [Angle n] [n] | A polygon determined by the distance between successive vertices and the external angles formed by each three successive vertices. In other words, a polygon specified by "turtle graphics": go straight ahead x1 units; turn by external angle a1; go straight ahead x2 units; turn by external angle a2; etc. The polygon will be centered at the centroid of its vertices.
To construct an n-gon, use a list of n-2 angles and n-1 edge lengths. Extra angles or lengths are ignored. |
PolyRegular Int n | A regular polygon with the given number of sides (first argument) and the given radius (second argument). |
data PolyOrientation n Source
Determine how a polygon should be oriented.
NoOrient | No special orientation; the first vertex will be at (1,0). This is the default. |
OrientH | Orient horizontally, so the bottommost edge is parallel to the x-axis. |
OrientV | Orient vertically, so the leftmost edge is parallel to the y-axis. |
OrientTo (V2 n) | Orient so some edge is facing in the direction of, that is, perpendicular to, the given vector. |
Eq n => Eq (PolyOrientation n) Source | |
Ord n => Ord (PolyOrientation n) Source | |
Read n => Read (PolyOrientation n) Source | |
Show n => Show (PolyOrientation n) Source |
Star polygons
Options for creating "star" polygons, where the edges connect possibly non-adjacent vertices.
StarFun (Int -> Int) | Specify the order in which the vertices should be connected by a function that maps each vertex index to the index of the vertex that should come next. Indexing of vertices begins at 0. |
StarSkip Int | Specify a star polygon by a "skip". A skip of 1 indicates a normal polygon, where edges go between successive vertices. A skip of 2 means that edges will connect every second vertex, skipping one in between. Generally, a skip of n means that edges will connect every nth vertex. |
star :: OrderedField n => StarOpts -> [Point V2 n] -> Path V2 n Source
Create a generalized star polygon. The StarOpts
are used
to determine in which order the given vertices should be
connected. The intention is that the second argument of type
[Point v]
could be generated by a call to polygon
, regPoly
, or
the like, since a list of vertices is TrailLike
. But of course
the list can be generated any way you like. A
is
returned (instead of any Path
v
TrailLike
) because the resulting path
may have more than one component, for example if the vertices are
to be connected in several disjoint cycles.
Regular polygons
regPoly :: (InSpace V2 n t, TrailLike t, OrderedField n) => Int -> n -> t Source
Create a regular polygon. The first argument is the number of
sides, and the second is the length of the sides. (Compare to the
polygon
function with a PolyRegular
option, which produces
polygons of a given radius).
The polygon will be oriented with one edge parallel to the x-axis.
triangle :: (InSpace V2 n t, TrailLike t, OrderedField n) => n -> t Source
An equilateral triangle, with sides of the given length and base parallel to the x-axis.
eqTriangle :: (InSpace V2 n t, TrailLike t, OrderedField n) => n -> t Source
A synonym for triangle
, provided for backwards compatibility.
square :: (InSpace V2 n t, TrailLike t, OrderedField n) => n -> t Source
A square with its center at the origin and sides of the given length, oriented parallel to the axes.
pentagon :: (InSpace V2 n t, TrailLike t, OrderedField n) => n -> t Source
A regular pentagon, with sides of the given length and base parallel to the x-axis.
hexagon :: (InSpace V2 n t, TrailLike t, OrderedField n) => n -> t Source
A regular hexagon, with sides of the given length and base parallel to the x-axis.
heptagon :: (InSpace V2 n t, TrailLike t, OrderedField n) => n -> t Source
A regular heptagon, with sides of the given length and base parallel to the x-axis.
septagon :: (InSpace V2 n t, TrailLike t, OrderedField n) => n -> t Source
A synonym for heptagon
. It is, however, completely inferior,
being a base admixture of the Latin septum (seven) and the
Greek γωνία (angle).
octagon :: (InSpace V2 n t, TrailLike t, OrderedField n) => n -> t Source
A regular octagon, with sides of the given length and base parallel to the x-axis.
nonagon :: (InSpace V2 n t, TrailLike t, OrderedField n) => n -> t Source
A regular nonagon, with sides of the given length and base parallel to the x-axis.
decagon :: (InSpace V2 n t, TrailLike t, OrderedField n) => n -> t Source
A regular decagon, with sides of the given length and base parallel to the x-axis.
hendecagon :: (InSpace V2 n t, TrailLike t, OrderedField n) => n -> t Source
A regular hendecagon, with sides of the given length and base parallel to the x-axis.
dodecagon :: (InSpace V2 n t, TrailLike t, OrderedField n) => n -> t Source
A regular dodecagon, with sides of the given length and base parallel to the x-axis.
Other special polygons
unitSquare :: (InSpace V2 n t, TrailLike t, OrderedField n) => t Source
A square with its center at the origin and sides of length 1, oriented parallel to the axes.
rect :: (InSpace V2 n t, TrailLike t, OrderedField n) => n -> n -> t Source
rect w h
is an axis-aligned rectangle of width w
and height
h
, centered at the origin.
Other shapes
roundedRect :: (InSpace V2 n t, TrailLike t, RealFloat n) => n -> n -> n -> t Source
roundedRect w h r
generates a closed trail, or closed path
centered at the origin, of an axis-aligned rectangle with width
w
, height h
, and circular rounded corners of radius r
. If
r
is negative the corner will be cut out in a reverse arc. If
the size of r
is larger than half the smaller dimension of w
and h
, then it will be reduced to fit in that range, to prevent
the corners from overlapping. The trail or path begins with the
right edge and proceeds counterclockwise. If you need to specify
a different radius for each corner individually, use
roundedRect'
instead.
roundedRectEx = pad 1.1 . centerXY $ hcat' (with & sep .~ 0.2) [ roundedRect 0.5 0.4 0.1 , roundedRect 0.5 0.4 (-0.1) , roundedRect' 0.7 0.4 (with & radiusTL .~ 0.2 & radiusTR .~ -0.2 & radiusBR .~ 0.1) ]
roundedRect' :: (InSpace V2 n t, TrailLike t, RealFloat n) => n -> n -> RoundedRectOpts n -> t Source
roundedRect'
works like roundedRect
but allows you to set the radius of
each corner indivually, using RoundedRectOpts
. The default corner radius is 0.
Each radius can also be negative, which results in the curves being reversed
to be inward instead of outward.
radiusTL :: forall d. Lens' (RoundedRectOpts d) d Source
radiusTR :: forall d. Lens' (RoundedRectOpts d) d Source
radiusBL :: forall d. Lens' (RoundedRectOpts d) d Source
radiusBR :: forall d. Lens' (RoundedRectOpts d) d Source
Arrows
arrowV :: (TypeableFloat n, Renderable (Path V2 n) b) => V2 n -> QDiagram b V2 n Any Source
arrowV v
creates an arrow with the direction and norm of
the vector v
(with its tail at the origin), using default
parameters.
arrowV' :: (TypeableFloat n, Renderable (Path V2 n) b) => ArrowOpts n -> V2 n -> QDiagram b V2 n Any Source
arrowV' v
creates an arrow with the direction and norm of
the vector v
(with its tail at the origin).
arrowAt :: (TypeableFloat n, Renderable (Path V2 n) b) => Point V2 n -> V2 n -> QDiagram b V2 n Any Source
Create an arrow starting at s with length and direction determined by the vector v.
arrowAt' :: (TypeableFloat n, Renderable (Path V2 n) b) => ArrowOpts n -> Point V2 n -> V2 n -> QDiagram b V2 n Any Source
arrowBetween :: (TypeableFloat n, Renderable (Path V2 n) b) => Point V2 n -> Point V2 n -> QDiagram b V2 n Any Source
arrowBetween s e
creates an arrow pointing from s
to e
with default parameters.
arrowBetween' :: (TypeableFloat n, Renderable (Path V2 n) b) => ArrowOpts n -> Point V2 n -> Point V2 n -> QDiagram b V2 n Any Source
arrowBetween' opts s e
creates an arrow pointing from s
to
e
using the given options. In particular, it scales and
rotates arrowShaft
to go between s
and e
, taking head,
tail, and gaps into account.
connect :: (TypeableFloat n, Renderable (Path V2 n) b, IsName n1, IsName n2) => n1 -> n2 -> QDiagram b V2 n Any -> QDiagram b V2 n Any Source
Connect two diagrams with a straight arrow.
connect' :: (TypeableFloat n, Renderable (Path V2 n) b, IsName n1, IsName n2) => ArrowOpts n -> n1 -> n2 -> QDiagram b V2 n Any -> QDiagram b V2 n Any Source
Connect two diagrams with an arbitrary arrow.
connectPerim :: (TypeableFloat n, Renderable (Path V2 n) b, IsName n1, IsName n2) => n1 -> n2 -> Angle n -> Angle n -> QDiagram b V2 n Any -> QDiagram b V2 n Any Source
Connect two diagrams at point on the perimeter of the diagrams, choosen by angle.
connectPerim' :: (TypeableFloat n, Renderable (Path V2 n) b, IsName n1, IsName n2) => ArrowOpts n -> n1 -> n2 -> Angle n -> Angle n -> QDiagram b V2 n Any -> QDiagram b V2 n Any Source
connectOutside :: (TypeableFloat n, Renderable (Path V2 n) b, IsName n1, IsName n2) => n1 -> n2 -> QDiagram b V2 n Any -> QDiagram b V2 n Any Source
Draw an arrow from diagram named "n1" to diagram named "n2". The arrow lies on the line between the centres of the diagrams, but is drawn so that it stops at the boundaries of the diagrams, using traces to find the intersection points.
connectOutside' :: (TypeableFloat n, Renderable (Path V2 n) b, IsName n1, IsName n2) => ArrowOpts n -> n1 -> n2 -> QDiagram b V2 n Any -> QDiagram b V2 n Any Source
arrow :: (TypeableFloat n, Renderable (Path V2 n) b) => n -> QDiagram b V2 n Any Source
arrow len
creates an arrow of length len
with default
parameters, starting at the origin and ending at the point
(len,0)
.
arrow' :: (TypeableFloat n, Renderable (Path V2 n) b) => ArrowOpts n -> n -> QDiagram b V2 n Any Source
arrow' opts len
creates an arrow of length len
using the
given options, starting at the origin and ending at the point
(len,0)
. In particular, it scales the given arrowShaft
so
that the entire arrow has length len
.
straightShaft :: OrderedField n => Trail V2 n Source
Straight line arrow shaft.
module Diagrams.TwoD.Arrowheads
ArrowOpts | |
|
TypeableFloat n => Default (ArrowOpts n) Source |
headGap :: Lens' (ArrowOpts n) (Measure n) Source
Distance to leave between the head and the target point.
tailGap :: Lens' (ArrowOpts n) (Measure n) Source
Distance to leave between the starting point and the tail.
gaps :: Traversal' (ArrowOpts n) (Measure n) Source
Set both the headGap
and tailGap
simultaneously.
gap :: Traversal' (ArrowOpts n) (Measure n) Source
Same as gaps, provided for backward compatiiblity.
headTexture :: TypeableFloat n => Lens' (ArrowOpts n) (Texture n) Source
A lens for setting or modifying the texture of an arrowhead. For
example, one may write ... (with & headTexture .~ grad)
to get an
arrow with a head filled with a gradient, assuming grad has been
defined. Or ... (with & headTexture .~ solid blue
to set the head
color to blue. For more general control over the style of arrowheads,
see headStyle
.
headStyle :: Lens' (ArrowOpts n) (Style V2 n) Source
Style to apply to the head. headStyle
is modified by using the lens
combinator %~
to change the current style. For example, to change
an opaque black arrowhead to translucent orange:
(with & headStyle %~ fc orange . opacity 0.75)
.
tailTexture :: TypeableFloat n => Lens' (ArrowOpts n) (Texture n) Source
A lens for setting or modifying the texture of an arrow
tail. This is *not* a valid lens (see committed
).
shaftTexture :: TypeableFloat n => Lens' (ArrowOpts n) (Texture n) Source
A lens for setting or modifying the texture of an arrow shaft.
headLength :: Lens' (ArrowOpts n) (Measure n) Source
The length from the start of the joint to the tip of the head.
tailLength :: Lens' (ArrowOpts n) (Measure n) Source
The length of the tail plus its joint.
lengths :: Traversal' (ArrowOpts n) (Measure n) Source
Set both the headLength
and tailLength
simultaneously.
Text
text :: (TypeableFloat n, Renderable (Text n) b) => String -> QDiagram b V2 n Any Source
Create a primitive text diagram from the given string, with center
alignment, equivalent to
.alignedText
0.5 0.5
Note that it takes up no space, as text size information is not available.
topLeftText :: (TypeableFloat n, Renderable (Text n) b) => String -> QDiagram b V2 n Any Source
Create a primitive text diagram from the given string, origin at
the top left corner of the text's bounding box, equivalent to
.alignedText
0 1
Note that it takes up no space.
alignedText :: (TypeableFloat n, Renderable (Text n) b) => n -> n -> String -> QDiagram b V2 n Any Source
Create a primitive text diagram from the given string, with the origin set to a point interpolated within the bounding box. The first parameter varies from 0 (left) to 1 (right), and the second parameter from 0 (bottom) to 1 (top). Some backends do not implement this and instead snap to closest corner or the center.
The height of this box is determined by the font's potential ascent and descent, rather than the height of the particular string.
Note that it takes up no space.
baselineText :: (TypeableFloat n, Renderable (Text n) b) => String -> QDiagram b V2 n Any Source
Create a primitive text diagram from the given string, with the origin set to be on the baseline, at the beginning (although not bounding). This is the reference point of showText in the Cairo graphics library.
Note that it takes up no space.
font :: HasStyle a => String -> a -> a Source
Specify a font family to be used for all text within a diagram.
fontSize :: (N a ~ n, Typeable n, HasStyle a) => Measure n -> a -> a Source
Set the font size, that is, the size of the font's em-square as
measured within the current local vector space. The default size
is 1
.
_font :: (Typeable n, OrderedField n) => Lens' (Style v n) (Maybe String) Source
Lens onto the font name of a style.
_fontSizeR :: (Typeable n, OrderedField n) => Lens' (Style v n) (Measured n (Recommend n)) Source
_fontSize :: (Typeable n, OrderedField n) => Lens' (Style v n) (Measure n) Source
Lens to commit a font size. This is *not* a valid lens (see
commited
.
fontSizeO :: (N a ~ n, Typeable n, Num n, HasStyle a) => n -> a -> a Source
A convenient synonym for 'fontSize (Output w)'.
fontSizeL :: (N a ~ n, Typeable n, Num n, HasStyle a) => n -> a -> a Source
A convenient sysnonym for 'fontSize (Local w)'.
fontSizeN :: (N a ~ n, Typeable n, Num n, HasStyle a) => n -> a -> a Source
A convenient synonym for 'fontSize (Normalized w)'.
fontSizeG :: (N a ~ n, Typeable n, Num n, HasStyle a) => n -> a -> a Source
A convenient synonym for 'fontSize (Global w)'.
Images
data DImage :: * -> * -> * where Source
An image primitive, the two ints are width followed by height.
Will typically be created by loadImageEmb
or loadImageExt
which,
will handle setting the width and height to the actual width and height
of the image.
Fractional n => Transformable (DImage n a) Source | |
Fractional n => HasOrigin (DImage n a) Source | |
Fractional n => Renderable (DImage n a) NullBackend Source | |
type V (DImage n a) = V2 Source | |
type N (DImage n a) = n Source |
data ImageData :: * -> * where Source
ImageData
is either a JuicyPixels DynamicImage
tagged as Embedded
or
a reference tagged as External
. Additionally Native
is provided for
external libraries to hook into.
ImageRaster :: DynamicImage -> ImageData Embedded | |
ImageRef :: FilePath -> ImageData External | |
ImageNative :: t -> ImageData (Native t) |
image :: (TypeableFloat n, Typeable a, Renderable (DImage n a) b) => DImage n a -> QDiagram b V2 n Any Source
loadImageEmb :: Num n => FilePath -> IO (Either String (DImage n Embedded)) Source
Use JuicyPixels to read an image in any format and wrap it in a DImage
.
The width and height of the image are set to their actual values.
loadImageExt :: Num n => FilePath -> IO (Either String (DImage n External)) Source
Check that a file exists, and use JuicyPixels to figure out the right size, but save a reference to the image instead of the raster data
uncheckedImageRef :: Num n => FilePath -> Int -> Int -> DImage n External Source
Make an "unchecked" image reference; have to specify a width and height. Unless the aspect ratio of the external image is the w :: h, then the image will be distorted.
raster :: Num n => (Int -> Int -> AlphaColour Double) -> Int -> Int -> DImage n Embedded Source
Create an image "from scratch" by specifying the pixel data
rasterDia :: (TypeableFloat n, Renderable (DImage n Embedded) b) => (Int -> Int -> AlphaColour Double) -> Int -> Int -> QDiagram b V2 n Any Source
Crate a diagram from raw raster data.
Transformations
Rotation
rotation :: Floating n => Angle n -> T2 n Source
Create a transformation which performs a rotation about the local
origin by the given angle. See also rotate
.
rotate :: (InSpace V2 n t, Transformable t, Floating n) => Angle n -> t -> t Source
Rotate about the local origin by the given angle. Positive angles
correspond to counterclockwise rotation, negative to
clockwise. The angle can be expressed using any of the Iso
s on
Angle
. For example, rotate (1/4 @@
, turn
)rotate
(tau/4 @@ rad)
, and rotate (90 @@ deg)
all
represent the same transformation, namely, a counterclockwise
rotation by a right angle. To rotate about some point other than
the local origin, see rotateAbout
.
Note that writing rotate (1/4)
, with no Angle
constructor,
will yield an error since GHC cannot figure out which sort of
angle you want to use. In this common situation you can use
rotateBy
, which interprets its argument as a number of turns.
rotated :: (InSpace V2 n a, Floating n, SameSpace a b, Transformable a, Transformable b) => Angle n -> Iso a b a b Source
rotationAround :: Floating n => P2 n -> Angle n -> T2 n Source
rotationAbout p
is a rotation about the point p
(instead of
around the local origin).
rotateAround :: (InSpace V2 n t, Transformable t, Floating n) => P2 n -> Angle n -> t -> t Source
rotateAbout p
is like rotate
, except it rotates around the
point p
instead of around the local origin.
rotationTo :: OrderedField n => Direction V2 n -> T2 n Source
The rotation that aligns the x-axis with the given direction.
rotateTo :: (InSpace V2 n t, OrderedField n, Transformable t) => Direction V2 n -> t -> t Source
Rotate around the local origin such that the x axis aligns with the given direction.
Scaling
scalingX :: (Additive v, R1 v, Fractional n) => n -> Transformation v n Source
Construct a transformation which scales by the given factor in the x (horizontal) direction.
scaleX :: (InSpace v n t, R2 v, Fractional n, Transformable t) => n -> t -> t Source
Scale a diagram by the given factor in the x (horizontal)
direction. To scale uniformly, use scale
.
scalingY :: (Additive v, R2 v, Fractional n) => n -> Transformation v n Source
Construct a transformation which scales by the given factor in the y (vertical) direction.
scaleY :: (InSpace v n t, R2 v, Fractional n, Transformable t) => n -> t -> t Source
Scale a diagram by the given factor in the y (vertical)
direction. To scale uniformly, use scale
.
scaling :: (Additive v, Fractional n) => n -> Transformation v n
Create a uniform scaling transformation.
scale :: (InSpace v n a, Eq n, Fractional n, Transformable a) => n -> a -> a
Scale uniformly in every dimension by the given scalar.
scaleToX :: (InSpace v n t, R2 v, Enveloped t, Transformable t) => n -> t -> t Source
scaleToX w
scales a diagram in the x (horizontal) direction by
whatever factor required to make its width w
. scaleToX
should not be applied to diagrams with a width of 0, such as
vrule
.
scaleToY :: (InSpace v n t, R2 v, Enveloped t, Transformable t) => n -> t -> t Source
scaleToY h
scales a diagram in the y (vertical) direction by
whatever factor required to make its height h
. scaleToY
should not be applied to diagrams with a height of 0, such as
hrule
.
scaleUToX :: (InSpace v n t, R1 v, Enveloped t, Transformable t) => n -> t -> t Source
scaleUToX w
scales a diagram uniformly by whatever factor
required to make its width w
. scaleUToX
should not be
applied to diagrams with a width of 0, such as vrule
.
scaleUToY :: (InSpace v n t, R2 v, Enveloped t, Transformable t) => n -> t -> t Source
scaleUToY h
scales a diagram uniformly by whatever factor
required to make its height h
. scaleUToY
should not be applied
to diagrams with a height of 0, such as hrule
.
Translation
translationX :: (Additive v, R1 v, Num n) => n -> Transformation v n Source
Construct a transformation which translates by the given distance in the x (horizontal) direction.
translateX :: (InSpace v n t, R1 v, Transformable t) => n -> t -> t Source
Translate a diagram by the given distance in the x (horizontal) direction.
translationY :: (Additive v, R2 v, Num n) => n -> Transformation v n Source
Construct a transformation which translates by the given distance in the y (vertical) direction.
translateY :: (InSpace v n t, R2 v, Transformable t) => n -> t -> t Source
Translate a diagram by the given distance in the y (vertical) direction.
translation :: v n -> Transformation v n
Create a translation.
translate :: (Num (N t), Transformable t) => Vn t -> t -> t
Translate by a vector.
Reflection
reflectionX :: (Additive v, R1 v, Num n) => Transformation v n Source
Construct a transformation which flips a diagram from left to right, i.e. sends the point (x,y) to (-x,y).
reflectX :: (InSpace v n t, R1 v, Transformable t) => t -> t Source
Flip a diagram from left to right, i.e. send the point (x,y) to (-x,y).
reflectionY :: (Additive v, R2 v, Num n) => Transformation v n Source
Construct a transformation which flips a diagram from top to bottom, i.e. sends the point (x,y) to (x,-y).
reflectY :: (InSpace v n t, R2 v, Transformable t) => t -> t Source
Flip a diagram from top to bottom, i.e. send the point (x,y) to (x,-y).
reflectionAbout :: OrderedField n => P2 n -> Direction V2 n -> T2 n Source
reflectionAbout p d
is a reflection in the line determined by
the point p
and direction d
.
reflectAbout :: (InSpace V2 n t, OrderedField n, Transformable t) => P2 n -> Direction V2 n -> t -> t Source
reflectAbout p d
reflects a diagram in the line determined by
the point p
and direction d
.
Shears
shearingX :: Num n => n -> T2 n Source
shearingX d
is the linear transformation which is the identity on
y coordinates and sends (0,1)
to (d,1)
.
shearX :: (InSpace V2 n t, Transformable t) => n -> t -> t Source
shearX d
performs a shear in the x-direction which sends
(0,1)
to (d,1)
.
shearingY :: Num n => n -> T2 n Source
shearingY d
is the linear transformation which is the identity on
x coordinates and sends (1,0)
to (1,d)
.
shearY :: (InSpace V2 n t, Transformable t) => n -> t -> t Source
shearY d
performs a shear in the y-direction which sends
(1,0)
to (1,d)
.
Deformations - non-affine transforms
parallelX0 :: (R1 v, Num n) => Deformation v v n Source
The parallel projection onto the plane x=0
perspectiveX1 :: (R1 v, Functor v, Fractional n) => Deformation v v n Source
The perspective division onto the plane x=1 along lines going through the origin.
parallelY0 :: (R2 v, Num n) => Deformation v v n Source
The parallel projection onto the plane y=0
perspectiveY1 :: (R2 v, Functor v, Floating n) => Deformation v v n Source
The perspective division onto the plane y=1 along lines going through the origin.
facingX :: (R1 v, Functor v, Fractional n) => Deformation v v n Source
The viewing transform for a viewer facing along the positive X
axis. X coördinates stay fixed, while Y coördinates are compressed
with increasing distance. asDeformation (translation unitX) <>
parallelX0 <> frustrumX = perspectiveX1
facingY :: (R2 v, Functor v, Fractional n) => Deformation v v n Source
Combinators
Combining multiple diagrams
(===) :: (InSpace V2 n a, Num n, Juxtaposable a, Semigroup a) => a -> a -> a infixl 6 Source
Place two diagrams (or other objects) vertically adjacent to one another, with the first diagram above the second. Since Haskell ignores whitespace in expressions, one can thus write
c === d
to place c
above d
. The local origin of the resulting
combined diagram is the same as the local origin of the first.
(===)
is associative and has mempty
as an identity. See the
documentation of beside
for more information.
(|||) :: (InSpace V2 n a, Num n, Juxtaposable a, Semigroup a) => a -> a -> a infixl 6 Source
Place two diagrams (or other juxtaposable objects) horizontally
adjacent to one another, with the first diagram to the left of
the second. The local origin of the resulting combined diagram
is the same as the local origin of the first. (|||)
is
associative and has mempty
as an identity. See the
documentation of beside
for more information.
hcat :: (InSpace V2 n a, Floating n, Juxtaposable a, HasOrigin a, Monoid' a) => [a] -> a Source
Lay out a list of juxtaposable objects in a row from left to right, so that their local origins lie along a single horizontal line, with successive envelopes tangent to one another.
hcat' :: (InSpace V2 n a, Floating n, Juxtaposable a, HasOrigin a, Monoid' a) => CatOpts n -> [a] -> a Source
hsep :: (InSpace V2 n a, Floating n, Juxtaposable a, HasOrigin a, Monoid' a) => n -> [a] -> a Source
A convenient synonym for horizontal concatenation with
separation: hsep s === hcat' (with & sep .~ s)
.
vcat :: (InSpace V2 n a, Floating n, Juxtaposable a, HasOrigin a, Monoid' a) => [a] -> a Source
Lay out a list of juxtaposable objects in a column from top to bottom, so that their local origins lie along a single vertical line, with successive envelopes tangent to one another.
vcat' :: (InSpace V2 n a, Floating n, Juxtaposable a, HasOrigin a, Monoid' a) => CatOpts n -> [a] -> a Source
vsep :: (InSpace V2 n a, Floating n, Juxtaposable a, HasOrigin a, Monoid' a) => n -> [a] -> a Source
A convenient synonym for vertical concatenation with
separation: vsep s === vcat' (with & sep .~ s)
.
Spacing and envelopes
strutX :: (Metric v, R1 v, OrderedField n, Monoid' m) => n -> QDiagram b v n m Source
strutX w
is an empty diagram with width w
, height 0, and a
centered local origin. Note that strutX (-w)
behaves the same as
strutX w
.
strutY :: (Metric v, R2 v, OrderedField n, Monoid' m) => n -> QDiagram b v n m Source
strutY h
is an empty diagram with height h
, width 0, and a
centered local origin. Note that strutY (-h)
behaves the same as
strutY h
.
padX :: (Metric v, R2 v, OrderedField n, Monoid' m) => n -> QDiagram b v n m -> QDiagram b v n m Source
padX s
"pads" a diagram in the x-direction, expanding its
envelope horizontally by a factor of s
(factors between 0 and 1
can be used to shrink the envelope). Note that the envelope will
expand with respect to the local origin, so if the origin is not
centered horizontally the padding may appear "uneven". If this
is not desired, the origin can be centered (using centerX
)
before applying padX
.
padY :: (Metric v, R2 v, Monoid' m, OrderedField n) => n -> QDiagram b v n m -> QDiagram b v n m Source
padY s
"pads" a diagram in the y-direction, expanding its
envelope vertically by a factor of s
(factors between
0 and 1 can be used to shrink the envelope). Note that
the envelope will expand with respect to the local origin,
so if the origin is not centered vertically the padding may appear
"uneven". If this is not desired, the origin can be centered
(using centerY
) before applying padY
.
extrudeLeft :: (OrderedField n, Monoid' m) => n -> QDiagram b V2 n m -> QDiagram b V2 n m Source
extrudeLeft s
"extrudes" a diagram in the negative x-direction,
offsetting its envelope by the provided distance. When s < 0
,
the envelope is inset instead.
See the documentation for extrudeEnvelope
for more information.
extrudeRight :: (OrderedField n, Monoid' m) => n -> QDiagram b V2 n m -> QDiagram b V2 n m Source
extrudeRight s
"extrudes" a diagram in the positive x-direction,
offsetting its envelope by the provided distance. When s < 0
,
the envelope is inset instead.
See the documentation for extrudeEnvelope
for more information.
extrudeBottom :: (OrderedField n, Monoid' m) => n -> QDiagram b V2 n m -> QDiagram b V2 n m Source
extrudeBottom s
"extrudes" a diagram in the negative y-direction,
offsetting its envelope by the provided distance. When s < 0
,
the envelope is inset instead.
See the documentation for extrudeEnvelope
for more information.
extrudeTop :: (OrderedField n, Monoid' m) => n -> QDiagram b V2 n m -> QDiagram b V2 n m Source
extrudeTop s
"extrudes" a diagram in the positive y-direction,
offsetting its envelope by the provided distance. When s < 0
,
the envelope is inset instead.
See the documentation for extrudeEnvelope
for more information.
rectEnvelope :: forall b n m. (OrderedField n, Monoid' m) => Point V2 n -> V2 n -> QDiagram b V2 n m -> QDiagram b V2 n m Source
rectEnvelope p v
sets the envelope of a diagram to a rectangle whose
lower-left corner is at p
and whose upper-right corner is at p
.+^ v
. Useful for selecting the rectangular portion of a
diagram which should actually be "viewed" in the final render,
if you don't want to see the entire diagram.
Background
boundingRect :: (InSpace V2 n a, SameSpace a t, Enveloped t, Transformable t, TrailLike t, Monoid t, Enveloped a) => a -> t Source
Construct a bounding rectangle for an enveloped object, that is, the smallest axis-aligned rectangle which encloses the object.
bg :: (TypeableFloat n, Renderable (Path V2 n) b) => Colour Double -> QDiagram b V2 n Any -> QDiagram b V2 n Any Source
"Set the background color" of a diagram. That is, place a diagram atop a bounding rectangle of the given color.
bgFrame :: (TypeableFloat n, Renderable (Path V2 n) b) => n -> Colour Double -> QDiagram b V2 n Any -> QDiagram b V2 n Any Source
Similar to bg
but makes the colored background rectangle larger than
the diagram. The first parameter is used to set how far the background
extends beyond the diagram.
Alignment
alignL :: (InSpace V2 n a, Fractional n, Alignable a, HasOrigin a) => a -> a Source
Align along the left edge, i.e. translate the diagram in a horizontal direction so that the local origin is on the left edge of the envelope.
alignR :: (InSpace V2 n a, Fractional n, Alignable a, HasOrigin a) => a -> a Source
Align along the right edge.
alignT :: (InSpace V2 n a, Fractional n, Alignable a, HasOrigin a) => a -> a Source
Align along the top edge.
alignB :: (InSpace V2 n a, Fractional n, Alignable a, HasOrigin a) => a -> a Source
Align along the bottom edge.
alignX :: (InSpace v n a, R1 v, Fractional n, Alignable a, HasOrigin a) => n -> a -> a Source
alignX
and snugX
move the local origin horizontally as follows:
alignX (-1)
moves the local origin to the left edge of the boundary;align 1
moves the local origin to the right edge;- any other argument interpolates linearly between these. For
example,
alignX 0
centers,alignX 2
moves the origin one "radius" to the right of the right edge, and so on. snugX
works the same way.
alignY :: (InSpace v n a, R2 v, Fractional n, Alignable a, HasOrigin a) => n -> a -> a Source
Like alignX
, but moving the local origin vertically, with an
argument of 1
corresponding to the top edge and (-1)
corresponding
to the bottom edge.
centerX :: (InSpace v n a, R1 v, Fractional n, Alignable a, HasOrigin a) => a -> a Source
Center the local origin along the X-axis.
centerY :: (InSpace v n a, R2 v, Fractional n, Alignable a, HasOrigin a) => a -> a Source
Center the local origin along the Y-axis.
centerXY :: (InSpace v n a, R2 v, Fractional n, Alignable a, HasOrigin a) => a -> a Source
Center along both the X- and Y-axes.
Snugging
snugX :: (InSpace v n a, R1 v, Fractional n, Alignable a, Traced a, HasOrigin a) => n -> a -> a Source
See the documentation for alignX
.
snugY :: (InSpace v n a, R2 v, Fractional n, Alignable a, Traced a, HasOrigin a) => n -> a -> a Source
See the documentation for alignY
.
snugCenterX :: (InSpace v n a, R1 v, Fractional n, Alignable a, Traced a, HasOrigin a) => a -> a Source
snugCenterY :: (InSpace v n a, R2 v, Fractional n, Alignable a, Traced a, HasOrigin a) => a -> a Source
snugCenterXY :: (InSpace v n a, R2 v, Fractional n, Alignable a, Traced a, HasOrigin a) => a -> a Source
Size
Computing size
width :: (InSpace V2 n a, Enveloped a) => a -> n Source
Compute the width of an enveloped object.
Note this is just diameter unitX
.
extentX :: (InSpace v n a, R1 v, Enveloped a) => a -> Maybe (n, n) Source
Compute the absolute x-coordinate range of an enveloped object in
the form (lo,hi)
. Return Nothing
for objects with an empty
envelope.
Note this is just extent unitX
.
extentY :: (InSpace v n a, R2 v, Enveloped a) => a -> Maybe (n, n) Source
Compute the absolute y-coordinate range of an enveloped object in
the form (lo,hi)
. Return Nothing
for objects with an empty
envelope.
Specifying size
mkSizeSpec2D :: Num n => Maybe n -> Maybe n -> SizeSpec V2 n Source
Make a SizeSpec
from possibly-specified width and height.
Textures
data SpreadMethod Source
The SpreadMethod
determines what happens before lGradStart
and after
lGradEnd
. GradPad
fills the space before the start of the gradient
with the color of the first stop and the color after end of the gradient
with the color of the last stop. GradRepeat
restarts the gradient and
GradReflect
restarts the gradient with the stops in reverse order.
data GradientStop d Source
A gradient stop contains a color and fraction (usually between 0 and 1)
GradientStop | |
|
_FillTexture :: Iso' (FillTexture n) (Recommend (Texture n)) Source
_fillTexture :: (Typeable n, Floating n) => Lens' (Style V2 n) (Texture n) Source
Commit a fill texture in a style. This is not a valid setter
because it doesn't abide the functor law (see committed
).
getFillTexture :: FillTexture n -> Texture n Source
_LineTexture :: Iso (LineTexture n) (LineTexture n') (Texture n) (Texture n') Source
lineTextureA :: (InSpace V2 n a, Typeable n, Floating n, HasStyle a) => LineTexture n -> a -> a Source
getLineTexture :: LineTexture n -> Texture n Source
stopFraction :: Lens' (GradientStop n) n Source
The fraction for stop.
stopColor :: Lens' (GradientStop n) SomeColor Source
A color for the stop.
mkStops :: [(Colour Double, d, Double)] -> [GradientStop d] Source
A convenient function for making gradient stops from a list of triples. (An opaque color, a stop fraction, an opacity).
Linear Gradient
LGradient | |
|
lGradStops :: Lens' (LGradient n) [GradientStop n] Source
A list of stops (colors and fractions).
lGradTrans :: Lens' (LGradient n) (Transformation V2 n) Source
A transformation to be applied to the gradient. Usually this field will start as the identity transform and capture the transforms that are applied to the gradient.
lGradStart :: Lens' (LGradient n) (Point V2 n) Source
The starting point for the first gradient stop. The coordinates are in
local
units and the default is (-0.5, 0).
lGradEnd :: Lens' (LGradient n) (Point V2 n) Source
The ending point for the last gradient stop.The coordinates are in
local
units and the default is (0.5, 0).
lGradSpreadMethod :: Lens' (LGradient n) SpreadMethod Source
For setting the spread method.
defaultLG :: Fractional n => Texture n Source
A default is provided so that linear gradients can easily be created using
lenses. For example, lg = defaultLG & lGradStart .~ (0.25 ^& 0.33)
. Note that
no default value is provided for lGradStops
, this must be set before
the gradient value is used, otherwise the object will appear transparent.
mkLinearGradient :: Num n => [GradientStop n] -> Point V2 n -> Point V2 n -> SpreadMethod -> Texture n Source
Make a linear gradient texture from a stop list, start point, end point,
and SpreadMethod
. The lGradTrans
field is set to the identity
transfrom, to change it use the lGradTrans
lens.
Radial Gradient
RGradient | |
|
rGradStops :: Lens' (RGradient n) [GradientStop n] Source
A list of stops (colors and fractions).
rGradRadius0 :: Lens' (RGradient n) n Source
The radius of the inner cirlce in local
coordinates.
rGradRadius1 :: Lens' (RGradient n) n Source
The radius of the outer circle in local
coordinates.
rGradTrans :: Lens' (RGradient n) (Transformation V2 n) Source
A transformation to be applied to the gradient. Usually this field will start as the identity transform and capture the transforms that are applied to the gradient.
rGradSpreadMethod :: Lens' (RGradient n) SpreadMethod Source
For setting the spread method.
defaultRG :: Fractional n => Texture n Source
A default is provided so that radial gradients can easily be created using
lenses. For example, rg = defaultRG & rGradRadius1 .~ 0.25
. Note that
no default value is provided for rGradStops
, this must be set before
the gradient value is used, otherwise the object will appear transparent.
mkRadialGradient :: Num n => [GradientStop n] -> Point V2 n -> n -> Point V2 n -> n -> SpreadMethod -> Texture n Source
Make a radial gradient texture from a stop list, radius, start point,
end point, and SpreadMethod
. The rGradTrans
field is set to the identity
transfrom, to change it use the rGradTrans
lens.
Colors
fillColor :: (InSpace V2 n a, Color c, Typeable n, Floating n, HasStyle a) => c -> a -> a Source
Set the fill color. This function is polymorphic in the color
type (so it can be used with either Colour
or AlphaColour
),
but this can sometimes create problems for type inference, so the
fc
and fcA
variants are provided with more concrete types.
_AC :: Prism' (Texture n) (AlphaColour Double) Source
Prism onto an AlphaColour
Double
of a SC
texture.
fcA :: (InSpace V2 n a, Floating n, Typeable n, HasStyle a) => AlphaColour Double -> a -> a Source
A synonym for fillColor
, specialized to
(i.e. colors with transparency). See comment after AlphaColour
DoublefillColor
about backends.
recommendFillColor :: (InSpace V2 n a, Color c, Typeable n, Floating n, HasStyle a) => c -> a -> a Source
lineColor :: (InSpace V2 n a, Color c, Typeable n, Floating n, HasStyle a) => c -> a -> a Source
Set the line (stroke) color. This function is polymorphic in the
color type (so it can be used with either Colour
or
AlphaColour
), but this can sometimes create problems for type
inference, so the lc
and lcA
variants are provided with more
concrete types.
lcA :: (InSpace V2 n a, Typeable n, Floating n, HasStyle a) => AlphaColour Double -> a -> a Source
A synonym for lineColor
, specialized to
(i.e. colors with transparency). See comment in AlphaColour
DoublelineColor
about backends.
Visual aids for understanding the internal model
showOrigin :: (TypeableFloat n, Renderable (Path V2 n) b, Monoid' m) => QDiagram b V2 n m -> QDiagram b V2 n m Source
Mark the origin of a diagram by placing a red dot 1/50th its size.
showOrigin' :: (TypeableFloat n, Renderable (Path V2 n) b, Monoid' m) => OriginOpts n -> QDiagram b V2 n m -> QDiagram b V2 n m Source
Mark the origin of a diagram, with control over colour and scale of marker dot.
data OriginOpts n Source
Fractional n => Default (OriginOpts n) Source |
oScale :: forall n. Lens' (OriginOpts n) n Source
oMinSize :: forall n. Lens' (OriginOpts n) n Source
showEnvelope :: (Enum n, TypeableFloat n, Renderable (Path V2 n) b) => QDiagram b V2 n Any -> QDiagram b V2 n Any Source
Mark the envelope with an approximating cubic spline using 32 points, medium line width and red line color.
showEnvelope' :: (Enum n, TypeableFloat n, Renderable (Path V2 n) b) => EnvelopeOpts n -> QDiagram b V2 n Any -> QDiagram b V2 n Any Source
Mark the envelope with an approximating cubic spline with control over the color, line width and number of points.
eLineWidth :: forall n n. Lens (EnvelopeOpts n) (EnvelopeOpts n) (Measure n) (Measure n) Source
ePoints :: forall n. Lens' (EnvelopeOpts n) Int Source
showTrace :: (Enum n, TypeableFloat n, Renderable (Path V2 n) b) => QDiagram b V2 n Any -> QDiagram b V2 n Any Source
Mark the trace of a diagram by placing 64 red dots 1/100th its size along the trace.
showTrace' :: (Enum n, TypeableFloat n, Renderable (Path V2 n) b) => TraceOpts n -> QDiagram b V2 n Any -> QDiagram b V2 n Any Source
Mark the trace of a diagram, with control over colour and scale of marker dot and the number of points on the trace.
showLabels :: (TypeableFloat n, Renderable (Text n) b, Semigroup m) => QDiagram b V2 n m -> QDiagram b V2 n Any Source