chart-unit-0.6.3.0: Native haskell charts.

Safe HaskellNone
LanguageHaskell2010

Chart.Arrow

Description

Charts that depict gradients and similar data, using arrows in positions

Synopsis

Documentation

data Arrow Source #

An arrow structure contains position, direction and size information

Constructors

Arrow 

Instances

Eq Arrow Source # 

Methods

(==) :: Arrow -> Arrow -> Bool #

(/=) :: Arrow -> Arrow -> Bool #

Show Arrow Source # 

Methods

showsPrec :: Int -> Arrow -> ShowS #

show :: Arrow -> String #

showList :: [Arrow] -> ShowS #

data ArrowHTStyle a Source #

ArrowStyles based on diagrams

Instances

data ArrowOptions Source #

todo: quite a clunky specification of what an arrow is (or could be)

Instances

Show ArrowOptions Source # 
Generic ArrowOptions Source # 

Associated Types

type Rep ArrowOptions :: * -> * #

Default ArrowOptions Source # 

Methods

def :: ArrowOptions #

type Rep ArrowOptions Source # 

normArrows :: [Arrow] -> [Arrow] Source #

Equalize the arrow space width with the data space one. this creates the right arrow sizing in physical chart space

arrows :: Traversable f => ArrowOptions -> f Arrow -> Chart b Source #

Rescale data across position, and between position and arrow direction.

note that, due to this auto-scaling, there is no such thing as a single arrow_ chart

arrowsExample :: Chart b
arrowsExample =
  arrows
    ( #maxLength .~ 0.5 $
      #maxHeadLength .~ 0.2 $
      #maxStaffWidth .~ 0.01 $ def)
    [ Arrow (Pair x (sin (5 * x))) (Pair x (cos x))
    | x <- grid MidPos (one :: Range Double) 100
    ]

arrowChart :: Traversable f => [ArrowOptions] -> Rect Double -> Rect Double -> [f Arrow] -> Chart b Source #

A chart of arrows

arrowChart_ :: Traversable f => [ArrowOptions] -> Rect Double -> [f Arrow] -> Chart b Source #

An arrow chart scaled to its own range

arrowChart_Example :: Chart b
arrowChart_Example = arrowChart_ [def] asquare [as]
  where
    as =
      normArrows
        [ Arrow (Pair x y) (Pair (sin 1 / x + 0.0001) (cos 1 / y + 0.0001))
        | x <- grid MidPos (one :: Range Double) 20
        , y <- grid MidPos (one :: Range Double) 20
        ]