[Chart] Example diagrams code for pentagonal area diagram

Jorden M jrm3000 at gmx.com
Wed Apr 9 19:37:12 BST 2014


I just started out with haskell-diagrams. Here's some off-the-cuff diagrams code that could be worked into a chart to display five variables. It's roughly the same thing as a polar area diagram. I created it in the context of displaying correlations in the Big Five Personality Traits or OCEAN model. It obviously needs much work to make it into an actual chart, but I thought I'd post the code in case anyone wanted to run with it. The obvious problems are that the labels, colors, and opacity need to be configurable, sizing needs to be calculated and adjustable, and the lengths should be proportional to the square root of the parameter so that the areas are proportional to the parameters. Also, the number of parameters could be variable and the type of polygon and dispositions of the sectors calculated from that dynamically.

Cheers
-j

---
{-# LANGUAGE NoMonomorphismRestriction #-}

import Data.Default (def)
import Data.Colour.Names (black)
import Diagrams.Prelude
import Diagrams.Backend.SVG.CmdLine
import Diagrams.Core.Transform
import Diagrams.TwoD

main = mainWith pentPlot

labels = decorateLocatedTrail (pentagon 3.8 # rotateBy (1/10)) ls

ls = [ text "Openness" # scale 0.4 # rotate (2/5 * pi :: Rad)
     , text "Conscientiousness" # scale 0.4 # rotate (-2/10 * pi :: Rad)
     , text "Extroversion" # scale 0.4 # rotate (2/10 * pi :: Rad)
     , text "Aggreeableness" # scale 0.4 # rotate (3/5 * pi :: Rad)
     , text "Neuroticism" # scale 0.4 ]

pentPlot :: Diagram B R2
pentPlot = labels `atop` redTri 1 `atop` blueTri 2.4 `atop` orangeTri 2.13 
           `atop` greenTri 1.23 `atop` yellowTri 2.8
           `atop` backGround # opacity 0.4 `atop` backBackGround `atop` web

-- Nasty hack
backBackGround = pentagon 5 # opacity 0

-- Also nasty hacks
web = someTri (1/5) `atop` someTri (2/5) `atop` someTri (3/5)
      `atop` someTri (4/5) `atop` someTri 0

someTri r = polygon (with & polyType .~ PolySides [Rad pi*6/10, 
           Rad pi*2/5] [3.4,3.4]) 
           # opacity 0.4 # alignT # rotateBy r

backGround :: Diagram B R2
backGround = pentagon 4 <> pentagon 3.5 <> pentagon 3 <> pentagon 2.5 
             <> pentagon 2 <> pentagon 1.5 <> pentagon 1 
             <> pentagon 0.5 # showOrigin' def{_oColor = black}
 
redTri :: Double -> Diagram B R2
redTri l = polygon (with & polyType .~ PolySides [Rad pi*6/10, 
           Rad pi*2/5] [l,l]) 
           # fc red # opacity 0.55 # alignT # rotateBy (1/5)

blueTri :: Double -> Diagram B R2
blueTri l = polygon (with & polyType .~ PolySides [Rad pi*6/10, 
            Rad pi*2/5] [l,l]) 
            # fc blue # opacity 0.55 # alignT # rotateBy (2/5)

orangeTri :: Double -> Diagram B R2
orangeTri l = polygon (with & polyType .~ PolySides [Rad pi*6/10, 
              Rad pi*2/5] [l,l]) 
              # fc orange # opacity 0.55 # alignT # rotateBy (3/5)

greenTri :: Double -> Diagram B R2
greenTri l = polygon (with & polyType .~ PolySides [Rad pi*6/10, 
             Rad pi*2/5] [l,l]) 
             # fc green # opacity 0.55 # alignT # rotateBy (4/5)

yellowTri :: Double -> Diagram B R2
yellowTri l = polygon (with & polyType .~ PolySides [Rad pi*6/10, 
              Rad pi*2/5] [l,l]) 
              # fc yellow # opacity 0.55 # alignT



More information about the Chart mailing list