grid-7.8.12: Tools for working with regular grids (graphs, lattices).

Copyright(c) Amy de Buitléir 2012-2017
LicenseBSD-style
Maintaineramy@nualeargais.ie
Stabilityexperimental
Portabilityportable
Safe HaskellSafe
LanguageHaskell2010

Math.Geometry.Grid.Octagonal

Contents

Description

A regular arrangement of octagonal tiles. Octagons won't tile a regular plane (there will be diamond-shaped gaps between the tiles), but they will tile a hyperbolic plane. (Alternatively, you can think of these as squares on a board game where diagonal moves are allowed.) The userguide, with illustrations, is available at https://github.com/mhwombat/grid/wiki. Also see Math.Geometry.Grid for examples of how to use this class.

Synopsis

Unbounded grid with octagonal tiles

data UnboundedOctGrid Source #

An unbounded grid with octagonal tiles. The grid and its indexing scheme are illustrated in the user guide, available at https://github.com/mhwombat/grid/wiki.

Constructors

UnboundedOctGrid 
Instances
Eq UnboundedOctGrid Source # 
Instance details

Defined in Math.Geometry.Grid.OctagonalInternal

Show UnboundedOctGrid Source # 
Instance details

Defined in Math.Geometry.Grid.OctagonalInternal

Generic UnboundedOctGrid Source # 
Instance details

Defined in Math.Geometry.Grid.OctagonalInternal

Associated Types

type Rep UnboundedOctGrid :: Type -> Type #

Grid UnboundedOctGrid Source # 
Instance details

Defined in Math.Geometry.Grid.OctagonalInternal

Methods

indices :: UnboundedOctGrid -> [Index UnboundedOctGrid] Source #

distance :: UnboundedOctGrid -> Index UnboundedOctGrid -> Index UnboundedOctGrid -> Int Source #

minDistance :: UnboundedOctGrid -> [Index UnboundedOctGrid] -> Index UnboundedOctGrid -> Int Source #

neighbours :: UnboundedOctGrid -> Index UnboundedOctGrid -> [Index UnboundedOctGrid] Source #

neighboursOfSet :: UnboundedOctGrid -> [Index UnboundedOctGrid] -> [Index UnboundedOctGrid] Source #

neighbour :: UnboundedOctGrid -> Index UnboundedOctGrid -> Direction UnboundedOctGrid -> Maybe (Index UnboundedOctGrid) Source #

numNeighbours :: UnboundedOctGrid -> Index UnboundedOctGrid -> Int Source #

contains :: UnboundedOctGrid -> Index UnboundedOctGrid -> Bool Source #

tileCount :: UnboundedOctGrid -> Int Source #

null :: UnboundedOctGrid -> Bool Source #

nonNull :: UnboundedOctGrid -> Bool Source #

edges :: UnboundedOctGrid -> [(Index UnboundedOctGrid, Index UnboundedOctGrid)] Source #

viewpoint :: UnboundedOctGrid -> Index UnboundedOctGrid -> [(Index UnboundedOctGrid, Int)] Source #

isAdjacent :: UnboundedOctGrid -> Index UnboundedOctGrid -> Index UnboundedOctGrid -> Bool Source #

adjacentTilesToward :: UnboundedOctGrid -> Index UnboundedOctGrid -> Index UnboundedOctGrid -> [Index UnboundedOctGrid] Source #

minimalPaths :: UnboundedOctGrid -> Index UnboundedOctGrid -> Index UnboundedOctGrid -> [[Index UnboundedOctGrid]] Source #

directionTo :: UnboundedOctGrid -> Index UnboundedOctGrid -> Index UnboundedOctGrid -> [Direction UnboundedOctGrid] Source #

defaultMinDistance :: UnboundedOctGrid -> [Index UnboundedOctGrid] -> Index UnboundedOctGrid -> Int Source #

defaultNeighbours :: UnboundedOctGrid -> Index UnboundedOctGrid -> [Index UnboundedOctGrid] Source #

defaultNeighboursOfSet :: UnboundedOctGrid -> [Index UnboundedOctGrid] -> [Index UnboundedOctGrid] Source #

defaultNeighbour :: UnboundedOctGrid -> Index UnboundedOctGrid -> Direction UnboundedOctGrid -> Maybe (Index UnboundedOctGrid) Source #

defaultTileCount :: UnboundedOctGrid -> Int Source #

defaultEdges :: UnboundedOctGrid -> [(Index UnboundedOctGrid, Index UnboundedOctGrid)] Source #

defaultIsAdjacent :: UnboundedOctGrid -> Index UnboundedOctGrid -> Index UnboundedOctGrid -> Bool Source #

defaultAdjacentTilesToward :: UnboundedOctGrid -> Index UnboundedOctGrid -> Index UnboundedOctGrid -> [Index UnboundedOctGrid] Source #

defaultMinimalPaths :: UnboundedOctGrid -> Index UnboundedOctGrid -> Index UnboundedOctGrid -> [[Index UnboundedOctGrid]] Source #

type Rep UnboundedOctGrid Source # 
Instance details

Defined in Math.Geometry.Grid.OctagonalInternal

type Rep UnboundedOctGrid = D1 (MetaData "UnboundedOctGrid" "Math.Geometry.Grid.OctagonalInternal" "grid-7.8.12-1ADrZUlWO0vHdPyzqP6MYM" False) (C1 (MetaCons "UnboundedOctGrid" PrefixI False) (U1 :: Type -> Type))
type Index UnboundedOctGrid Source # 
Instance details

Defined in Math.Geometry.Grid.OctagonalInternal

type Direction UnboundedOctGrid Source # 
Instance details

Defined in Math.Geometry.Grid.OctagonalInternal

Rectangular grid with octagonal tiles

data RectOctGrid Source #

A rectangular grid with octagonal tiles. The grid and its indexing scheme are illustrated in the user guide, available at https://github.com/mhwombat/grid/wiki.

Instances
Eq RectOctGrid Source # 
Instance details

Defined in Math.Geometry.Grid.OctagonalInternal

Show RectOctGrid Source # 
Instance details

Defined in Math.Geometry.Grid.OctagonalInternal

Generic RectOctGrid Source # 
Instance details

Defined in Math.Geometry.Grid.OctagonalInternal

Associated Types

type Rep RectOctGrid :: Type -> Type #

BoundedGrid RectOctGrid Source # 
Instance details

Defined in Math.Geometry.Grid.OctagonalInternal

FiniteGrid RectOctGrid Source # 
Instance details

Defined in Math.Geometry.Grid.OctagonalInternal

Associated Types

type Size RectOctGrid :: Type Source #

Grid RectOctGrid Source # 
Instance details

Defined in Math.Geometry.Grid.OctagonalInternal

Associated Types

type Index RectOctGrid :: Type Source #

type Direction RectOctGrid :: Type Source #

Methods

indices :: RectOctGrid -> [Index RectOctGrid] Source #

distance :: RectOctGrid -> Index RectOctGrid -> Index RectOctGrid -> Int Source #

minDistance :: RectOctGrid -> [Index RectOctGrid] -> Index RectOctGrid -> Int Source #

neighbours :: RectOctGrid -> Index RectOctGrid -> [Index RectOctGrid] Source #

neighboursOfSet :: RectOctGrid -> [Index RectOctGrid] -> [Index RectOctGrid] Source #

neighbour :: RectOctGrid -> Index RectOctGrid -> Direction RectOctGrid -> Maybe (Index RectOctGrid) Source #

numNeighbours :: RectOctGrid -> Index RectOctGrid -> Int Source #

contains :: RectOctGrid -> Index RectOctGrid -> Bool Source #

tileCount :: RectOctGrid -> Int Source #

null :: RectOctGrid -> Bool Source #

nonNull :: RectOctGrid -> Bool Source #

edges :: RectOctGrid -> [(Index RectOctGrid, Index RectOctGrid)] Source #

viewpoint :: RectOctGrid -> Index RectOctGrid -> [(Index RectOctGrid, Int)] Source #

isAdjacent :: RectOctGrid -> Index RectOctGrid -> Index RectOctGrid -> Bool Source #

adjacentTilesToward :: RectOctGrid -> Index RectOctGrid -> Index RectOctGrid -> [Index RectOctGrid] Source #

minimalPaths :: RectOctGrid -> Index RectOctGrid -> Index RectOctGrid -> [[Index RectOctGrid]] Source #

directionTo :: RectOctGrid -> Index RectOctGrid -> Index RectOctGrid -> [Direction RectOctGrid] Source #

defaultMinDistance :: RectOctGrid -> [Index RectOctGrid] -> Index RectOctGrid -> Int Source #

defaultNeighbours :: RectOctGrid -> Index RectOctGrid -> [Index RectOctGrid] Source #

defaultNeighboursOfSet :: RectOctGrid -> [Index RectOctGrid] -> [Index RectOctGrid] Source #

defaultNeighbour :: RectOctGrid -> Index RectOctGrid -> Direction RectOctGrid -> Maybe (Index RectOctGrid) Source #

defaultTileCount :: RectOctGrid -> Int Source #

defaultEdges :: RectOctGrid -> [(Index RectOctGrid, Index RectOctGrid)] Source #

defaultIsAdjacent :: RectOctGrid -> Index RectOctGrid -> Index RectOctGrid -> Bool Source #

defaultAdjacentTilesToward :: RectOctGrid -> Index RectOctGrid -> Index RectOctGrid -> [Index RectOctGrid] Source #

defaultMinimalPaths :: RectOctGrid -> Index RectOctGrid -> Index RectOctGrid -> [[Index RectOctGrid]] Source #

type Rep RectOctGrid Source # 
Instance details

Defined in Math.Geometry.Grid.OctagonalInternal

type Rep RectOctGrid = D1 (MetaData "RectOctGrid" "Math.Geometry.Grid.OctagonalInternal" "grid-7.8.12-1ADrZUlWO0vHdPyzqP6MYM" False) (C1 (MetaCons "RectOctGrid" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Int, Int)) :*: S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 [(Int, Int)])))
type Size RectOctGrid Source # 
Instance details

Defined in Math.Geometry.Grid.OctagonalInternal

type Index RectOctGrid Source # 
Instance details

Defined in Math.Geometry.Grid.OctagonalInternal

type Direction RectOctGrid Source # 
Instance details

Defined in Math.Geometry.Grid.OctagonalInternal

rectOctGrid :: Int -> Int -> RectOctGrid Source #

rectOctGrid r c produces a rectangular grid with r rows and c columns, using octagonal tiles. If r and c are both nonnegative, the resulting grid will have r*c tiles. Otherwise, the resulting grid will be null and the list of indices will be null.

Toroidal grid with octagonal tiles

data TorOctGrid Source #

A toroidal grid with octagonal tiles. The grid and its indexing scheme are illustrated in the user guide, available at https://github.com/mhwombat/grid/wiki.

Instances
Eq TorOctGrid Source # 
Instance details

Defined in Math.Geometry.Grid.OctagonalInternal

Show TorOctGrid Source # 
Instance details

Defined in Math.Geometry.Grid.OctagonalInternal

Generic TorOctGrid Source # 
Instance details

Defined in Math.Geometry.Grid.OctagonalInternal

Associated Types

type Rep TorOctGrid :: Type -> Type #

WrappedGrid TorOctGrid Source # 
Instance details

Defined in Math.Geometry.Grid.OctagonalInternal

FiniteGrid TorOctGrid Source # 
Instance details

Defined in Math.Geometry.Grid.OctagonalInternal

Associated Types

type Size TorOctGrid :: Type Source #

Grid TorOctGrid Source # 
Instance details

Defined in Math.Geometry.Grid.OctagonalInternal

Associated Types

type Index TorOctGrid :: Type Source #

type Direction TorOctGrid :: Type Source #

Methods

indices :: TorOctGrid -> [Index TorOctGrid] Source #

distance :: TorOctGrid -> Index TorOctGrid -> Index TorOctGrid -> Int Source #

minDistance :: TorOctGrid -> [Index TorOctGrid] -> Index TorOctGrid -> Int Source #

neighbours :: TorOctGrid -> Index TorOctGrid -> [Index TorOctGrid] Source #

neighboursOfSet :: TorOctGrid -> [Index TorOctGrid] -> [Index TorOctGrid] Source #

neighbour :: TorOctGrid -> Index TorOctGrid -> Direction TorOctGrid -> Maybe (Index TorOctGrid) Source #

numNeighbours :: TorOctGrid -> Index TorOctGrid -> Int Source #

contains :: TorOctGrid -> Index TorOctGrid -> Bool Source #

tileCount :: TorOctGrid -> Int Source #

null :: TorOctGrid -> Bool Source #

nonNull :: TorOctGrid -> Bool Source #

edges :: TorOctGrid -> [(Index TorOctGrid, Index TorOctGrid)] Source #

viewpoint :: TorOctGrid -> Index TorOctGrid -> [(Index TorOctGrid, Int)] Source #

isAdjacent :: TorOctGrid -> Index TorOctGrid -> Index TorOctGrid -> Bool Source #

adjacentTilesToward :: TorOctGrid -> Index TorOctGrid -> Index TorOctGrid -> [Index TorOctGrid] Source #

minimalPaths :: TorOctGrid -> Index TorOctGrid -> Index TorOctGrid -> [[Index TorOctGrid]] Source #

directionTo :: TorOctGrid -> Index TorOctGrid -> Index TorOctGrid -> [Direction TorOctGrid] Source #

defaultMinDistance :: TorOctGrid -> [Index TorOctGrid] -> Index TorOctGrid -> Int Source #

defaultNeighbours :: TorOctGrid -> Index TorOctGrid -> [Index TorOctGrid] Source #

defaultNeighboursOfSet :: TorOctGrid -> [Index TorOctGrid] -> [Index TorOctGrid] Source #

defaultNeighbour :: TorOctGrid -> Index TorOctGrid -> Direction TorOctGrid -> Maybe (Index TorOctGrid) Source #

defaultTileCount :: TorOctGrid -> Int Source #

defaultEdges :: TorOctGrid -> [(Index TorOctGrid, Index TorOctGrid)] Source #

defaultIsAdjacent :: TorOctGrid -> Index TorOctGrid -> Index TorOctGrid -> Bool Source #

defaultAdjacentTilesToward :: TorOctGrid -> Index TorOctGrid -> Index TorOctGrid -> [Index TorOctGrid] Source #

defaultMinimalPaths :: TorOctGrid -> Index TorOctGrid -> Index TorOctGrid -> [[Index TorOctGrid]] Source #

type Rep TorOctGrid Source # 
Instance details

Defined in Math.Geometry.Grid.OctagonalInternal

type Rep TorOctGrid = D1 (MetaData "TorOctGrid" "Math.Geometry.Grid.OctagonalInternal" "grid-7.8.12-1ADrZUlWO0vHdPyzqP6MYM" False) (C1 (MetaCons "TorOctGrid" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Int, Int)) :*: S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 [(Int, Int)])))
type Size TorOctGrid Source # 
Instance details

Defined in Math.Geometry.Grid.OctagonalInternal

type Index TorOctGrid Source # 
Instance details

Defined in Math.Geometry.Grid.OctagonalInternal

type Direction TorOctGrid Source # 
Instance details

Defined in Math.Geometry.Grid.OctagonalInternal

torOctGrid :: Int -> Int -> TorOctGrid Source #

torOctGrid r c returns a toroidal grid with r rows and c columns, using octagonal tiles. If r and c are both nonnegative, the resulting grid will have r*c tiles. Otherwise, the resulting grid will be null and the list of indices will be null.