chart-unit-0.6.2.0: Native haskell charts.

Safe HaskellNone
LanguageHaskell2010

Chart.Text

Description

textual chart elements

Synopsis

Documentation

data TextOptions Source #

text options

Constructors

TextOptions 

Fields

newtype TextPathOptions Source #

options specific to text as an SVG path

Constructors

TextPathOptions 

Fields

data TextSvgOptions Source #

options specific to text as SVG text

Constructors

TextSvgOptions 

Fields

Instances

Show TextSvgOptions Source # 
Generic TextSvgOptions Source # 

Associated Types

type Rep TextSvgOptions :: * -> * #

Default TextSvgOptions Source # 

Methods

def :: TextSvgOptions #

type Rep TextSvgOptions Source # 

data TextType Source #

text as a path or as svg text

data TextFont Source #

ADT of fonts

Constructors

Lin2 
FromFontFile Text 

textFont :: TextFont -> PreparedFont Double Source #

transform from chart-unit to SVGFonts rep of font

text_ :: TextOptions -> Text -> Chart b Source #

Create a textual chart element

text_ def "Welcome to chart-unit!"

Text can be either SVG text or text rendered as an SVG path. Text as SVG can be overridden by an opinionated browser. SVG Text not have a size, according to diagrams, and according to the svg standards for all I know. textSvg corrects for this by adding an approximately bounding rectangle so that size is forced.

text_SvgExample :: Chart b
text_SvgExample = text_
  (#textType .~ TextSvg (#textBox .~ def $ #svgFont .~ Just "Comic Sans MS" $ def) $
  #size .~ 0.2 $
  def)
  "abc & 0123 & POW!"

Text as an SVG path can use the fonts supplied in SVGFonts, follow the instructions there to make your own, or use the Hasklig font supplied in chart-unit.

text_PathExample :: Chart b
text_PathExample = text_
  (#textType .~ TextPath (#font .~ FromFontFile "other/Hasklig-Regular.svg" $ def) $
   #size .~ 0.2 $
   def)
   "0123 <*> <$> <| |> <> <- -> => ::"

texts :: R2 r => TextOptions -> [(Text, r Double)] -> Chart b Source #

Create positioned text from a list

textChart :: Traversable f => [TextOptions] -> Rect Double -> Rect Double -> [f (Text, Pair Double)] -> Chart b Source #

A chart of text

textChart_ :: [TextOptions] -> Rect Double -> [[(Text, Pair Double)]] -> Chart b Source #

A chart of text scaled to its own range

ts :: [(Text, Pair Double)]
ts = zip
  (map Text.singleton ['a' .. 'z'])
  [Pair (sin (x * 0.1)) x | x <- [0 .. 25]]

textChart_Example :: Chart b
textChart_Example =
  textChart_ [#size .~ 0.33 $ def] widescreen [ts]

data LabelOptions Source #

A label is a text element attached to a chart element

Constructors

LabelOptions 

Fields

labelled :: LabelOptions -> Text -> Chart b -> Chart b Source #

Label a chart element with some text

labelledExample :: Chart b
labelledExample = D.pad 1.1 $
  labelled (LabelOptions
    (#alignH .~ AlignLeft $ #rotation .~ 45 $ def) (Pair 1 1) 0.02)
  "a label"
  (glyph_ def)