diagrams-contrib-1.4.1: 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

Contents

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 Double) b, Renderable (Path V2 Double) b) =>
           Int -> Int -> QDiagram b V2 Double Any
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 (Path V2 n) b, TypeableFloat n) => Int -> Int -> QDiagram b V2 n Any Source #

gridWithHalves' with default opts.

gridWithHalves' :: (Renderable (Path V2 n) b, TypeableFloat n) => GridOpts n -> Int -> Int -> QDiagram b V2 n Any 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.

annotate :: (Floating n, Ord n, Typeable n) => String -> (String -> QDiagram b V2 n Any) -> Colour Double -> Int -> Int -> QDiagram b V2 n Any -> QDiagram b V2 n Any Source #

gridLine :: (IsName a, IsName b, Renderable (Path V2 n) c, TypeableFloat n) => a -> b -> QDiagram c V2 n Any -> QDiagram c V2 n Any Source #

Draw a line between two named points on the grid.

gridLine' :: (IsName a, IsName b, Renderable (Path V2 n) c, TypeableFloat n) => HighlightLineOpts n -> a -> b -> QDiagram c V2 n Any -> QDiagram c V2 n Any Source #

Draw a line between two named points on the grid.

gridLines :: (Renderable (Path V2 n) c, TypeableFloat n, IsName a, IsName b) => [(a, b)] -> QDiagram c V2 n Any -> QDiagram c V2 n Any Source #

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

placeDiagramOnGrid :: (IsName nm, Floating n, Ord n) => QDiagram b V2 n Any -> [nm] -> QDiagram b V2 n Any -> QDiagram b V2 n Any Source #

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

Options

data GridOpts n Source #

Instances

(Floating n, Ord n) => Default (GridOpts n) Source # 

Methods

def :: GridOpts n #

gridLL :: forall n. Lens' (GridOpts n) (V2 n) Source #

gridLR :: forall n. Lens' (GridOpts n) (V2 n) Source #

gridUL :: forall n. Lens' (GridOpts n) (V2 n) Source #