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.HexagonalInternal2

Description

A module containing private HexGrid2 internals. Most developers should use HexGrid2 instead. This module is subject to change without notice.

Synopsis

Documentation

data HexDirection Source #

Instances
Eq HexDirection Source # 
Instance details

Defined in Math.Geometry.Grid.HexagonalInternal2

Show HexDirection Source # 
Instance details

Defined in Math.Geometry.Grid.HexagonalInternal2

Generic HexDirection Source # 
Instance details

Defined in Math.Geometry.Grid.HexagonalInternal2

Associated Types

type Rep HexDirection :: Type -> Type #

type Rep HexDirection Source # 
Instance details

Defined in Math.Geometry.Grid.HexagonalInternal2

type Rep HexDirection = D1 (MetaData "HexDirection" "Math.Geometry.Grid.HexagonalInternal2" "grid-7.8.12-1ADrZUlWO0vHdPyzqP6MYM" False) ((C1 (MetaCons "Northwest" PrefixI False) (U1 :: Type -> Type) :+: (C1 (MetaCons "North" PrefixI False) (U1 :: Type -> Type) :+: C1 (MetaCons "Northeast" PrefixI False) (U1 :: Type -> Type))) :+: (C1 (MetaCons "Southeast" PrefixI False) (U1 :: Type -> Type) :+: (C1 (MetaCons "South" PrefixI False) (U1 :: Type -> Type) :+: C1 (MetaCons "Southwest" PrefixI False) (U1 :: Type -> Type))))

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.HexagonalInternal2

Show UnboundedHexGrid Source # 
Instance details

Defined in Math.Geometry.Grid.HexagonalInternal2

Generic UnboundedHexGrid Source # 
Instance details

Defined in Math.Geometry.Grid.HexagonalInternal2

Associated Types

type Rep UnboundedHexGrid :: Type -> Type #

Grid UnboundedHexGrid Source # 
Instance details

Defined in Math.Geometry.Grid.HexagonalInternal2

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.HexagonalInternal2

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

Defined in Math.Geometry.Grid.HexagonalInternal2

type Direction UnboundedHexGrid Source # 
Instance details

Defined in Math.Geometry.Grid.HexagonalInternal2

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.

Constructors

HexHexGrid Int [(Int, Int)] 
Instances
Eq HexHexGrid Source # 
Instance details

Defined in Math.Geometry.Grid.HexagonalInternal2

Show HexHexGrid Source # 
Instance details

Defined in Math.Geometry.Grid.HexagonalInternal2

Generic HexHexGrid Source # 
Instance details

Defined in Math.Geometry.Grid.HexagonalInternal2

Associated Types

type Rep HexHexGrid :: Type -> Type #

BoundedGrid HexHexGrid Source # 
Instance details

Defined in Math.Geometry.Grid.HexagonalInternal2

FiniteGrid HexHexGrid Source # 
Instance details

Defined in Math.Geometry.Grid.HexagonalInternal2

Associated Types

type Size HexHexGrid :: Type Source #

Grid HexHexGrid Source # 
Instance details

Defined in Math.Geometry.Grid.HexagonalInternal2

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.HexagonalInternal2

type Rep HexHexGrid = D1 (MetaData "HexHexGrid" "Math.Geometry.Grid.HexagonalInternal2" "grid-7.8.12-1ADrZUlWO0vHdPyzqP6MYM" 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.HexagonalInternal2

type Index HexHexGrid Source # 
Instance details

Defined in Math.Geometry.Grid.HexagonalInternal2

type Direction HexHexGrid Source # 
Instance details

Defined in Math.Geometry.Grid.HexagonalInternal2

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.

data RectHexGrid Source #

A rectangular 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

RectHexGrid (Int, Int) [(Int, Int)] 
Instances
Eq RectHexGrid Source # 
Instance details

Defined in Math.Geometry.Grid.HexagonalInternal2

Show RectHexGrid Source # 
Instance details

Defined in Math.Geometry.Grid.HexagonalInternal2

Generic RectHexGrid Source # 
Instance details

Defined in Math.Geometry.Grid.HexagonalInternal2

Associated Types

type Rep RectHexGrid :: Type -> Type #

BoundedGrid RectHexGrid Source # 
Instance details

Defined in Math.Geometry.Grid.HexagonalInternal2

FiniteGrid RectHexGrid Source # 
Instance details

Defined in Math.Geometry.Grid.HexagonalInternal2

Associated Types

type Size RectHexGrid :: Type Source #

Grid RectHexGrid Source # 
Instance details

Defined in Math.Geometry.Grid.HexagonalInternal2

Associated Types

type Index RectHexGrid :: Type Source #

type Direction RectHexGrid :: Type Source #

Methods

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

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

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

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

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

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

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

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

tileCount :: RectHexGrid -> Int Source #

null :: RectHexGrid -> Bool Source #

nonNull :: RectHexGrid -> Bool Source #

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

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

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

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

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

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

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

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

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

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

defaultTileCount :: RectHexGrid -> Int Source #

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

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

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

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

type Rep RectHexGrid Source # 
Instance details

Defined in Math.Geometry.Grid.HexagonalInternal2

type Rep RectHexGrid = D1 (MetaData "RectHexGrid" "Math.Geometry.Grid.HexagonalInternal2" "grid-7.8.12-1ADrZUlWO0vHdPyzqP6MYM" False) (C1 (MetaCons "RectHexGrid" 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 RectHexGrid Source # 
Instance details

Defined in Math.Geometry.Grid.HexagonalInternal2

type Index RectHexGrid Source # 
Instance details

Defined in Math.Geometry.Grid.HexagonalInternal2

type Direction RectHexGrid Source # 
Instance details

Defined in Math.Geometry.Grid.HexagonalInternal2

rectHexGrid :: Int -> Int -> RectHexGrid Source #

rectHexGrid 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.