grid-7.8.11: 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.Hexagonal

Contents

Description

A regular arrangement of hexagonal tiles. 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 hexagonal tiles

data UnboundedHexGrid Source #

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

Constructors

UnboundedHexGrid 
Instances
Eq UnboundedHexGrid Source # 
Instance details

Defined in Math.Geometry.Grid.HexagonalInternal

Show UnboundedHexGrid Source # 
Instance details

Defined in Math.Geometry.Grid.HexagonalInternal

Generic UnboundedHexGrid Source # 
Instance details

Defined in Math.Geometry.Grid.HexagonalInternal

Associated Types

type Rep UnboundedHexGrid :: Type -> Type #

Grid UnboundedHexGrid Source # 
Instance details

Defined in Math.Geometry.Grid.HexagonalInternal

Methods

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

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

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

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

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

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

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

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

tileCount :: UnboundedHexGrid -> Int Source #

null :: UnboundedHexGrid -> Bool Source #

nonNull :: UnboundedHexGrid -> Bool Source #

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

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

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

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

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

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

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

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

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

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

defaultTileCount :: UnboundedHexGrid -> Int Source #

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

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

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

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

type Rep UnboundedHexGrid Source # 
Instance details

Defined in Math.Geometry.Grid.HexagonalInternal

type Rep UnboundedHexGrid = D1 (MetaData "UnboundedHexGrid" "Math.Geometry.Grid.HexagonalInternal" "grid-7.8.11-FsZ2zB5sbxUIH1WQmshk4x" False) (C1 (MetaCons "UnboundedHexGrid" PrefixI False) (U1 :: Type -> Type))
type Index UnboundedHexGrid Source # 
Instance details

Defined in Math.Geometry.Grid.HexagonalInternal

type Direction UnboundedHexGrid Source # 
Instance details

Defined in Math.Geometry.Grid.HexagonalInternal

Hexagonal grid with hexagonal tiles

data HexHexGrid Source #

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

Instances
Eq HexHexGrid Source # 
Instance details

Defined in Math.Geometry.Grid.HexagonalInternal

Show HexHexGrid Source # 
Instance details

Defined in Math.Geometry.Grid.HexagonalInternal

Generic HexHexGrid Source # 
Instance details

Defined in Math.Geometry.Grid.HexagonalInternal

Associated Types

type Rep HexHexGrid :: Type -> Type #

BoundedGrid HexHexGrid Source # 
Instance details

Defined in Math.Geometry.Grid.HexagonalInternal

FiniteGrid HexHexGrid Source # 
Instance details

Defined in Math.Geometry.Grid.HexagonalInternal

Associated Types

type Size HexHexGrid :: Type Source #

Grid HexHexGrid Source # 
Instance details

Defined in Math.Geometry.Grid.HexagonalInternal

Associated Types

type Index HexHexGrid :: Type Source #

type Direction HexHexGrid :: Type Source #

Methods

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

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

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

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

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

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

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

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

tileCount :: HexHexGrid -> Int Source #

null :: HexHexGrid -> Bool Source #

nonNull :: HexHexGrid -> Bool Source #

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

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

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

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

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

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

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

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

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

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

defaultTileCount :: HexHexGrid -> Int Source #

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

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

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

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

type Rep HexHexGrid Source # 
Instance details

Defined in Math.Geometry.Grid.HexagonalInternal

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

Defined in Math.Geometry.Grid.HexagonalInternal

type Index HexHexGrid Source # 
Instance details

Defined in Math.Geometry.Grid.HexagonalInternal

type Direction HexHexGrid Source # 
Instance details

Defined in Math.Geometry.Grid.HexagonalInternal

hexHexGrid :: Int -> HexHexGrid Source #

hexHexGrid s returns a grid of hexagonal shape, with sides of length s, using hexagonal tiles. If s is nonnegative, the resulting grid will have 3*s*(s-1) + 1 tiles. Otherwise, the resulting grid will be null and the list of indices will be null.

Parallelogram-shaped grid with hexagonal tiles

data ParaHexGrid Source #

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

Instances
Eq ParaHexGrid Source # 
Instance details

Defined in Math.Geometry.Grid.HexagonalInternal

Show ParaHexGrid Source # 
Instance details

Defined in Math.Geometry.Grid.HexagonalInternal

Generic ParaHexGrid Source # 
Instance details

Defined in Math.Geometry.Grid.HexagonalInternal

Associated Types

type Rep ParaHexGrid :: Type -> Type #

BoundedGrid ParaHexGrid Source # 
Instance details

Defined in Math.Geometry.Grid.HexagonalInternal

FiniteGrid ParaHexGrid Source # 
Instance details

Defined in Math.Geometry.Grid.HexagonalInternal

Associated Types

type Size ParaHexGrid :: Type Source #

Grid ParaHexGrid Source # 
Instance details

Defined in Math.Geometry.Grid.HexagonalInternal

Associated Types

type Index ParaHexGrid :: Type Source #

type Direction ParaHexGrid :: Type Source #

Methods

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

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

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

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

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

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

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

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

tileCount :: ParaHexGrid -> Int Source #

null :: ParaHexGrid -> Bool Source #

nonNull :: ParaHexGrid -> Bool Source #

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

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

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

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

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

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

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

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

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

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

defaultTileCount :: ParaHexGrid -> Int Source #

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

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

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

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

type Rep ParaHexGrid Source # 
Instance details

Defined in Math.Geometry.Grid.HexagonalInternal

type Rep ParaHexGrid = D1 (MetaData "ParaHexGrid" "Math.Geometry.Grid.HexagonalInternal" "grid-7.8.11-FsZ2zB5sbxUIH1WQmshk4x" False) (C1 (MetaCons "ParaHexGrid" 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 ParaHexGrid Source # 
Instance details

Defined in Math.Geometry.Grid.HexagonalInternal

type Index ParaHexGrid Source # 
Instance details

Defined in Math.Geometry.Grid.HexagonalInternal

type Direction ParaHexGrid Source # 
Instance details

Defined in Math.Geometry.Grid.HexagonalInternal

paraHexGrid :: Int -> Int -> ParaHexGrid Source #

paraHexGrid r c returns a grid in the shape of a parallelogram with r rows and c columns, using hexagonal 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.