module Graphics.Rendering.Chart.Drawing
(
PointShape(..)
, PointStyle(..)
, drawPoint
, defaultPointStyle
, alignPath
, alignFillPath
, alignStrokePath
, alignFillPoints
, alignStrokePoints
, alignFillPoint
, alignStrokePoint
, strokePointPath
, fillPointPath
, withRotation
, withTranslation
, withScale
, withScaleX, withScaleY
, withPointStyle
, withDefaultStyle
, drawTextA
, drawTextR
, drawTextsR
, textDrawRect
, textDimension
, defaultColorSeq
, solidLine
, dashedLine
, filledCircles
, hollowCircles
, filledPolygon
, hollowPolygon
, plusses
, exes
, stars
, solidFillStyle
, module Graphics.Rendering.Chart.Backend
, point_color
, point_border_color
, point_border_width
, point_radius
, point_shape
) where
import Data.Default.Class
import Control.Lens hiding (moveTo)
import Data.Colour
import Data.Colour.SRGB
import Data.Colour.Names
import Data.List (unfoldr)
import Data.Monoid
import Control.Monad.Reader
import Graphics.Rendering.Chart.Backend
import Graphics.Rendering.Chart.Geometry
withRotation :: Double -> ChartBackend a -> ChartBackend a
withRotation angle = withTransform (rotate angle 1)
withTranslation :: Point -> ChartBackend a -> ChartBackend a
withTranslation p = withTransform (translate (pointToVec p) 1)
withScale :: Vector -> ChartBackend a -> ChartBackend a
withScale v = withTransform (scale v 1)
withScaleX :: Double -> ChartBackend a -> ChartBackend a
withScaleX x = withScale (Vector x 1)
withScaleY :: Double -> ChartBackend a -> ChartBackend a
withScaleY y = withScale (Vector 1 y)
withPointStyle :: PointStyle -> ChartBackend a -> ChartBackend a
withPointStyle (PointStyle cl bcl bw _ _) m = do
withLineStyle (def { _line_color = bcl, _line_width = bw }) $ do
withFillStyle (solidFillStyle cl) m
withDefaultStyle :: ChartBackend a -> ChartBackend a
withDefaultStyle = withLineStyle def . withFillStyle def . withFontStyle def
alignPath :: (Point -> Point) -> Path -> Path
alignPath f = foldPath (\p -> moveTo $ f p)
(\p -> lineTo $ f p)
(\p -> arc $ f p)
(\p -> arcNeg $ f p)
(close)
alignStrokePath :: Path -> ChartBackend Path
alignStrokePath p = do
f <- getPointAlignFn
return $ alignPath f p
alignFillPath :: Path -> ChartBackend Path
alignFillPath p = do
f <- getCoordAlignFn
return $ alignPath f p
alignStrokePoints :: [Point] -> ChartBackend [Point]
alignStrokePoints p = do
f <- getPointAlignFn
return $ fmap f p
alignFillPoints :: [Point] -> ChartBackend [Point]
alignFillPoints p = do
f <- getCoordAlignFn
return $ fmap f p
alignStrokePoint :: Point -> ChartBackend Point
alignStrokePoint p = do
alignfn <- getPointAlignFn
return (alignfn p)
alignFillPoint :: Point -> ChartBackend Point
alignFillPoint p = do
alignfn <- getCoordAlignFn
return (alignfn p)
stepPath :: [Point] -> Path
stepPath (p:ps) = moveTo p
<> mconcat (map lineTo ps)
stepPath [] = mempty
strokePointPath :: [Point] -> ChartBackend ()
strokePointPath pts = strokePath $ stepPath pts
fillPointPath :: [Point] -> ChartBackend ()
fillPointPath pts = fillPath $ stepPath pts
drawTextA :: HTextAnchor -> VTextAnchor -> Point -> String -> ChartBackend ()
drawTextA hta vta p s = drawTextR hta vta 0 p s
drawTextR :: HTextAnchor -> VTextAnchor -> Double -> Point -> String -> ChartBackend ()
drawTextR hta vta angle p s =
withTranslation p $
withRotation theta $ do
ts <- textSize s
drawText (adjustText hta vta ts) s
where
theta = angle*pi/180.0
drawTextsR :: HTextAnchor -> VTextAnchor -> Double -> Point -> String -> ChartBackend ()
drawTextsR hta vta angle p s = case num of
0 -> return ()
1 -> drawTextR hta vta angle p s
_ -> do
withTranslation p $
withRotation theta $ do
tss <- mapM textSize ss
let ts = head tss
let widths = map textSizeWidth tss
maxw = maximum widths
maxh = maximum (map textSizeYBearing tss)
gap = maxh / 2
totalHeight = fromIntegral num*maxh +
(fromIntegral num1)*gap
ys = take num (unfoldr (\y-> Just (y, ygapmaxh))
(yinit vta ts totalHeight))
xs = map (adjustTextX hta) tss
sequence_ (zipWith3 drawT xs ys ss)
where
ss = lines s
num = length ss
drawT x y s = drawText (Point x y) s
theta = angle*pi/180.0
yinit VTA_Top ts height = textSizeAscent ts
yinit VTA_BaseLine ts height = 0
yinit VTA_Centre ts height = height / 2 + textSizeAscent ts
yinit VTA_Bottom ts height = height + textSizeAscent ts
adjustText :: HTextAnchor -> VTextAnchor -> TextSize -> Point
adjustText hta vta ts = Point (adjustTextX hta ts) (adjustTextY vta ts)
adjustTextX :: HTextAnchor -> TextSize -> Double
adjustTextX HTA_Left _ = 0
adjustTextX HTA_Centre ts = ( (textSizeWidth ts / 2))
adjustTextX HTA_Right ts = ( textSizeWidth ts)
adjustTextY :: VTextAnchor -> TextSize -> Double
adjustTextY VTA_Top ts = textSizeAscent ts
adjustTextY VTA_Centre ts = (textSizeYBearing ts) / 2
adjustTextY VTA_BaseLine _ = 0
adjustTextY VTA_Bottom ts = (textSizeDescent ts)
textDrawRect :: HTextAnchor -> VTextAnchor -> Point -> String -> ChartBackend Rect
textDrawRect hta vta (Point x y) s = do
ts <- textSize s
let (w,h) = (textSizeWidth ts, textSizeHeight ts)
let lx = adjustTextX hta ts
let ly = adjustTextY vta ts
let (x',y') = (x + lx, y + ly)
let p1 = Point x' y'
let p2 = Point (x' + w) (y' + h)
return $ Rect p1 p2
textDimension :: String -> ChartBackend RectSize
textDimension s = do
ts <- textSize s
return (textSizeWidth ts, textSizeHeight ts)
data PointShape = PointShapeCircle
| PointShapePolygon Int Bool
| PointShapePlus
| PointShapeCross
| PointShapeStar
data PointStyle = PointStyle
{ _point_color :: AlphaColour Double
, _point_border_color :: AlphaColour Double
, _point_border_width :: Double
, _point_radius :: Double
, _point_shape :: PointShape
}
instance Default PointStyle where
def = PointStyle
{ _point_color = opaque black
, _point_border_color = transparent
, _point_border_width = 0
, _point_radius = 1
, _point_shape = PointShapeCircle
}
defaultPointStyle :: PointStyle
defaultPointStyle = def
drawPoint :: PointStyle
-> Point
-> ChartBackend ()
drawPoint ps@(PointStyle cl bcl bw r shape) p = withPointStyle ps $ do
p'@(Point x y) <- alignStrokePoint p
case shape of
PointShapeCircle -> do
let path = arc p' r 0 (2*pi)
fillPath path
strokePath path
PointShapePolygon sides isrot -> do
let intToAngle n =
if isrot
then fromIntegral n * 2*pi/fromIntegral sides
else (0.5 + fromIntegral n)*2*pi/fromIntegral sides
angles = map intToAngle [0 .. sides1]
(p:ps) = map (\a -> Point (x + r * sin a)
(y + r * cos a)) angles
let path = moveTo p <> mconcat (map lineTo ps) <> lineTo p
fillPath path
strokePath path
PointShapePlus -> do
strokePath $ moveTo' (x+r) y
<> lineTo' (xr) y
<> moveTo' x (yr)
<> lineTo' x (y+r)
PointShapeCross -> do
let rad = r / sqrt 2
strokePath $ moveTo' (x+rad) (y+rad)
<> lineTo' (xrad) (yrad)
<> moveTo' (x+rad) (yrad)
<> lineTo' (xrad) (y+rad)
PointShapeStar -> do
let rad = r / sqrt 2
strokePath $ moveTo' (x+r) y
<> lineTo' (xr) y
<> moveTo' x (yr)
<> lineTo' x (y+r)
<> moveTo' (x+rad) (y+rad)
<> lineTo' (xrad) (yrad)
<> moveTo' (x+rad) (yrad)
<> lineTo' (xrad) (y+rad)
defaultColorSeq :: [AlphaColour Double]
defaultColorSeq = cycle $ map opaque [blue, red, green, yellow, cyan, magenta]
solidLine :: Double
-> AlphaColour Double
-> LineStyle
solidLine w cl = LineStyle w cl [] LineCapButt LineJoinMiter
dashedLine :: Double
-> [Double]
-> AlphaColour Double
-> LineStyle
dashedLine w ds cl = LineStyle w cl ds LineCapButt LineJoinMiter
filledCircles :: Double
-> AlphaColour Double
-> PointStyle
filledCircles radius cl =
PointStyle cl transparent 0 radius PointShapeCircle
hollowCircles :: Double
-> Double
-> AlphaColour Double
-> PointStyle
hollowCircles radius w cl =
PointStyle transparent cl w radius PointShapeCircle
hollowPolygon :: Double
-> Double
-> Int
-> Bool
-> AlphaColour Double
-> PointStyle
hollowPolygon radius w sides isrot cl =
PointStyle transparent cl w radius (PointShapePolygon sides isrot)
filledPolygon :: Double
-> Int
-> Bool
-> AlphaColour Double
-> PointStyle
filledPolygon radius sides isrot cl =
PointStyle cl transparent 0 radius (PointShapePolygon sides isrot)
plusses :: Double
-> Double
-> AlphaColour Double
-> PointStyle
plusses radius w cl =
PointStyle transparent cl w radius PointShapePlus
exes :: Double
-> Double
-> AlphaColour Double
-> PointStyle
exes radius w cl =
PointStyle transparent cl w radius PointShapeCross
stars :: Double
-> Double
-> AlphaColour Double
-> PointStyle
stars radius w cl =
PointStyle transparent cl w radius PointShapeStar
solidFillStyle :: AlphaColour Double -> FillStyle
solidFillStyle cl = FillStyleSolid cl
$( makeLenses ''PointStyle )