diagrams-contrib-1.1.2.4: Collection of user contributions to diagrams EDSL

Copyright(c) 2014 Dominic Steinitz
LicenseBSD-style (see LICENSE)
Maintainerdominic@steinitz.org
Safe HaskellNone
LanguageHaskell2010

Diagrams.TwoD.Grid

Description

The example above is created by the code below which generates a grid, puts points on the interior and the boundary, draws dashed lines around the points to which we wish to draw attention and annotates the points of interest with some text.

{-# LANGUAGE FlexibleContexts      #-}
{-# LANGUAGE MultiParamTypeClasses #-}

import Diagrams.TwoD.Grid
import Diagrams.TwoD.Text

example :: (Renderable Text b, Renderable (Path R2) b, Backend b R2) =>
           Int -> Int -> Diagram b R2
example n m =

  (gridWithHalves n m) #

  -- Put points on the boundary
  bndPts [ (1 :: Int,  m + 1     ) | m <- [0,2..2 * m] ] #
  bndPts [ (n + 1,     1 :: Int  ) | n <- [0,2..2 * n] ] #
  bndPts [ (2 * n + 1, m + 1     ) | m <- [0,2..2 * m] ] #
  bndPts [ (n + 1,     2 * m + 1 ) | n <- [0,2..2 * n] ] #

  intPts [ (n + 1,          m + 1) | n <- [2,4..2 * n - 1] :: [Int]
                                   , m <- [2,4..2 * m - 1] :: [Int] ] #

  selectedLines (2 * n - 3) (3 :: Int) #

  ann (2 * n - 1) (1 :: Int) red  #
  ann (2 * n + 1) (3 :: Int) red  #
  ann (2 * n - 1) (3 :: Int) blue #
  ann (2 * n - 3) (3 :: Int) blue #
  ann (2 * n - 1) (5 :: Int) blue

  where

    ann n m c = annotate ("u_" ++ show (n `div` 2) ++ show (m `div` 2)) txtPt c n m

    selectedLines n m = gridLines $ selectedPairs n m

    selectedPairs n m = let pts = selectedList n m
                        in zip pts (tail pts)

    selectedList n m = [ (n - 1, m - 1)
                       , (n - 1, m + 1)
                       , (n + 1, m + 1)
                       , (n + 1, m + 3)
                       , (n + 3, m + 3)
                       , (n + 3, m + 1)
                       , (n + 5, m + 1)
                       , (n + 5, m - 1)
                       , (n + 3, m - 1)
                       , (n + 3, m - 3)
                       , (n + 1, m - 3)
                       , (n + 1, m - 1)
                       , (n - 1, m - 1)
                       ]

    txtPt t = circle cSize # opacity 0.0 # lw none
              ===
              text t # fontSize (Local 0.06)

    intPts = placeDiagramOnGrid (circle (cSize / 2) # fc blue # opacity 0.5 # lw none)
    bndPts = placeDiagramOnGrid (circle (cSize / 2) # fc red  # opacity 0.5 # lw none)

    cSize :: Double
    cSize = 0.03

example1 = example 5 5

Synopsis

Documentation

gridWithHalves :: (Renderable Text b, Renderable (Path R2) b, Backend b R2) => Int -> Int -> Diagram b R2 Source

gridWithHalves with default opts.

gridWithHalves' :: (Renderable Text b, Renderable (Path R2) b, Backend b R2) => GridOpts -> Int -> Int -> Diagram b R2 Source

Create a n by m grid. Diagrams can be placed on either the grid points themselves or on points half way between grid points. The latter includes points a half grid length outside of the grid itself.

gridLine :: (IsName a, IsName b, Renderable Text c, Renderable (Path R2) c) => a -> b -> Diagram c R2 -> Diagram c R2 Source

Draw a line between two named points on the grid.

gridLines :: (Renderable Text c, Renderable (Path R2) c, IsName a, IsName b) => [(a, b)] -> Diagram c R2 -> Diagram c R2 Source

Draw lines between a list of pairs of named points on the grid.

placeDiagramOnGrid :: (IsName n, Renderable Text b, Renderable (Path R2) b) => Diagram b R2 -> [n] -> Diagram b R2 -> Diagram b R2 Source

Place a diagram on a grid (which is itself a diagram) at all the co-ordinates specified.