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

Description

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

Synopsis

Documentation

data UnboundedSquareGrid Source #

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

Constructors

UnboundedSquareGrid 
Instances
Eq UnboundedSquareGrid Source # 
Instance details

Defined in Math.Geometry.Grid.SquareInternal

Show UnboundedSquareGrid Source # 
Instance details

Defined in Math.Geometry.Grid.SquareInternal

Generic UnboundedSquareGrid Source # 
Instance details

Defined in Math.Geometry.Grid.SquareInternal

Associated Types

type Rep UnboundedSquareGrid :: Type -> Type #

Grid UnboundedSquareGrid Source # 
Instance details

Defined in Math.Geometry.Grid.SquareInternal

Methods

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

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

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

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

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

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

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

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

tileCount :: UnboundedSquareGrid -> Int Source #

null :: UnboundedSquareGrid -> Bool Source #

nonNull :: UnboundedSquareGrid -> Bool Source #

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

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

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

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

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

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

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

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

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

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

defaultTileCount :: UnboundedSquareGrid -> Int Source #

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

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

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

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

type Rep UnboundedSquareGrid Source # 
Instance details

Defined in Math.Geometry.Grid.SquareInternal

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

Defined in Math.Geometry.Grid.SquareInternal

type Direction UnboundedSquareGrid Source # 
Instance details

Defined in Math.Geometry.Grid.SquareInternal

data RectSquareGrid Source #

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

Constructors

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

Defined in Math.Geometry.Grid.SquareInternal

Show RectSquareGrid Source # 
Instance details

Defined in Math.Geometry.Grid.SquareInternal

Generic RectSquareGrid Source # 
Instance details

Defined in Math.Geometry.Grid.SquareInternal

Associated Types

type Rep RectSquareGrid :: Type -> Type #

BoundedGrid RectSquareGrid Source # 
Instance details

Defined in Math.Geometry.Grid.SquareInternal

FiniteGrid RectSquareGrid Source # 
Instance details

Defined in Math.Geometry.Grid.SquareInternal

Associated Types

type Size RectSquareGrid :: Type Source #

Grid RectSquareGrid Source # 
Instance details

Defined in Math.Geometry.Grid.SquareInternal

Methods

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

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

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

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

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

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

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

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

tileCount :: RectSquareGrid -> Int Source #

null :: RectSquareGrid -> Bool Source #

nonNull :: RectSquareGrid -> Bool Source #

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

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

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

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

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

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

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

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

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

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

defaultTileCount :: RectSquareGrid -> Int Source #

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

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

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

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

type Rep RectSquareGrid Source # 
Instance details

Defined in Math.Geometry.Grid.SquareInternal

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

Defined in Math.Geometry.Grid.SquareInternal

type Index RectSquareGrid Source # 
Instance details

Defined in Math.Geometry.Grid.SquareInternal

type Direction RectSquareGrid Source # 
Instance details

Defined in Math.Geometry.Grid.SquareInternal

rectSquareGrid :: Int -> Int -> RectSquareGrid Source #

rectSquareGrid r c produces a rectangular grid with r rows and c columns, using square 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.

data TorSquareGrid Source #

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

Constructors

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

Defined in Math.Geometry.Grid.SquareInternal

Show TorSquareGrid Source # 
Instance details

Defined in Math.Geometry.Grid.SquareInternal

Generic TorSquareGrid Source # 
Instance details

Defined in Math.Geometry.Grid.SquareInternal

Associated Types

type Rep TorSquareGrid :: Type -> Type #

WrappedGrid TorSquareGrid Source # 
Instance details

Defined in Math.Geometry.Grid.SquareInternal

FiniteGrid TorSquareGrid Source # 
Instance details

Defined in Math.Geometry.Grid.SquareInternal

Associated Types

type Size TorSquareGrid :: Type Source #

Grid TorSquareGrid Source # 
Instance details

Defined in Math.Geometry.Grid.SquareInternal

Methods

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

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

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

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

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

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

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

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

tileCount :: TorSquareGrid -> Int Source #

null :: TorSquareGrid -> Bool Source #

nonNull :: TorSquareGrid -> Bool Source #

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

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

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

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

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

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

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

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

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

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

defaultTileCount :: TorSquareGrid -> Int Source #

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

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

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

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

type Rep TorSquareGrid Source # 
Instance details

Defined in Math.Geometry.Grid.SquareInternal

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

Defined in Math.Geometry.Grid.SquareInternal

type Index TorSquareGrid Source # 
Instance details

Defined in Math.Geometry.Grid.SquareInternal

type Direction TorSquareGrid Source # 
Instance details

Defined in Math.Geometry.Grid.SquareInternal

torSquareGrid :: Int -> Int -> TorSquareGrid Source #

torSquareGrid r c returns a toroidal grid with r rows and c columns, using square 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.