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

Description

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

Synopsis

Documentation

data TriDirection Source #

Instances
Eq TriDirection Source # 
Instance details

Defined in Math.Geometry.Grid.TriangularInternal

Show TriDirection Source # 
Instance details

Defined in Math.Geometry.Grid.TriangularInternal

Generic TriDirection Source # 
Instance details

Defined in Math.Geometry.Grid.TriangularInternal

Associated Types

type Rep TriDirection :: Type -> Type #

type Rep TriDirection Source # 
Instance details

Defined in Math.Geometry.Grid.TriangularInternal

type Rep TriDirection = D1 (MetaData "TriDirection" "Math.Geometry.Grid.TriangularInternal" "grid-7.8.11-FsZ2zB5sbxUIH1WQmshk4x" False) ((C1 (MetaCons "South" PrefixI False) (U1 :: Type -> Type) :+: (C1 (MetaCons "Northwest" PrefixI False) (U1 :: Type -> Type) :+: C1 (MetaCons "Northeast" PrefixI False) (U1 :: Type -> Type))) :+: (C1 (MetaCons "North" PrefixI False) (U1 :: Type -> Type) :+: (C1 (MetaCons "Southeast" PrefixI False) (U1 :: Type -> Type) :+: C1 (MetaCons "Southwest" PrefixI False) (U1 :: Type -> Type))))

data UnboundedTriGrid Source #

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

Constructors

UnboundedTriGrid 
Instances
Eq UnboundedTriGrid Source # 
Instance details

Defined in Math.Geometry.Grid.TriangularInternal

Show UnboundedTriGrid Source # 
Instance details

Defined in Math.Geometry.Grid.TriangularInternal

Generic UnboundedTriGrid Source # 
Instance details

Defined in Math.Geometry.Grid.TriangularInternal

Associated Types

type Rep UnboundedTriGrid :: Type -> Type #

Grid UnboundedTriGrid Source # 
Instance details

Defined in Math.Geometry.Grid.TriangularInternal

Methods

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

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

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

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

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

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

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

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

tileCount :: UnboundedTriGrid -> Int Source #

null :: UnboundedTriGrid -> Bool Source #

nonNull :: UnboundedTriGrid -> Bool Source #

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

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

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

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

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

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

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

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

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

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

defaultTileCount :: UnboundedTriGrid -> Int Source #

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

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

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

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

type Rep UnboundedTriGrid Source # 
Instance details

Defined in Math.Geometry.Grid.TriangularInternal

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

Defined in Math.Geometry.Grid.TriangularInternal

type Direction UnboundedTriGrid Source # 
Instance details

Defined in Math.Geometry.Grid.TriangularInternal

triZ :: Int -> Int -> Int Source #

For triangular tiles, it is convenient to define a third component z.

data TriTriGrid Source #

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

Constructors

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

Defined in Math.Geometry.Grid.TriangularInternal

Show TriTriGrid Source # 
Instance details

Defined in Math.Geometry.Grid.TriangularInternal

Generic TriTriGrid Source # 
Instance details

Defined in Math.Geometry.Grid.TriangularInternal

Associated Types

type Rep TriTriGrid :: Type -> Type #

BoundedGrid TriTriGrid Source # 
Instance details

Defined in Math.Geometry.Grid.TriangularInternal

FiniteGrid TriTriGrid Source # 
Instance details

Defined in Math.Geometry.Grid.TriangularInternal

Associated Types

type Size TriTriGrid :: Type Source #

Grid TriTriGrid Source # 
Instance details

Defined in Math.Geometry.Grid.TriangularInternal

Associated Types

type Index TriTriGrid :: Type Source #

type Direction TriTriGrid :: Type Source #

Methods

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

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

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

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

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

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

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

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

tileCount :: TriTriGrid -> Int Source #

null :: TriTriGrid -> Bool Source #

nonNull :: TriTriGrid -> Bool Source #

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

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

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

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

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

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

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

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

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

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

defaultTileCount :: TriTriGrid -> Int Source #

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

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

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

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

type Rep TriTriGrid Source # 
Instance details

Defined in Math.Geometry.Grid.TriangularInternal

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

Defined in Math.Geometry.Grid.TriangularInternal

type Index TriTriGrid Source # 
Instance details

Defined in Math.Geometry.Grid.TriangularInternal

type Direction TriTriGrid Source # 
Instance details

Defined in Math.Geometry.Grid.TriangularInternal

triTriGrid :: Int -> TriTriGrid Source #

triTriGrid s returns a triangular grid with sides of length s, using triangular tiles. If s is nonnegative, the resulting grid will have s^2 tiles. Otherwise, the resulting grid will be null and the list of indices will be null.

data ParaTriGrid Source #

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

Constructors

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

Defined in Math.Geometry.Grid.TriangularInternal

Show ParaTriGrid Source # 
Instance details

Defined in Math.Geometry.Grid.TriangularInternal

Generic ParaTriGrid Source # 
Instance details

Defined in Math.Geometry.Grid.TriangularInternal

Associated Types

type Rep ParaTriGrid :: Type -> Type #

BoundedGrid ParaTriGrid Source # 
Instance details

Defined in Math.Geometry.Grid.TriangularInternal

FiniteGrid ParaTriGrid Source # 
Instance details

Defined in Math.Geometry.Grid.TriangularInternal

Associated Types

type Size ParaTriGrid :: Type Source #

Grid ParaTriGrid Source # 
Instance details

Defined in Math.Geometry.Grid.TriangularInternal

Associated Types

type Index ParaTriGrid :: Type Source #

type Direction ParaTriGrid :: Type Source #

Methods

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

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

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

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

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

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

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

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

tileCount :: ParaTriGrid -> Int Source #

null :: ParaTriGrid -> Bool Source #

nonNull :: ParaTriGrid -> Bool Source #

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

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

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

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

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

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

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

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

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

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

defaultTileCount :: ParaTriGrid -> Int Source #

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

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

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

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

type Rep ParaTriGrid Source # 
Instance details

Defined in Math.Geometry.Grid.TriangularInternal

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

Defined in Math.Geometry.Grid.TriangularInternal

type Index ParaTriGrid Source # 
Instance details

Defined in Math.Geometry.Grid.TriangularInternal

type Direction ParaTriGrid Source # 
Instance details

Defined in Math.Geometry.Grid.TriangularInternal

paraTriGrid :: Int -> Int -> ParaTriGrid Source #

paraTriGrid r c returns a grid in the shape of a parallelogram with r rows and c columns, using triangular tiles. If r and c are both nonnegative, the resulting grid will have 2*r*c tiles. Otherwise, the resulting grid will be null and the list of indices will be null.

data RectTriGrid Source #

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

Constructors

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

Defined in Math.Geometry.Grid.TriangularInternal

Show RectTriGrid Source # 
Instance details

Defined in Math.Geometry.Grid.TriangularInternal

Generic RectTriGrid Source # 
Instance details

Defined in Math.Geometry.Grid.TriangularInternal

Associated Types

type Rep RectTriGrid :: Type -> Type #

BoundedGrid RectTriGrid Source # 
Instance details

Defined in Math.Geometry.Grid.TriangularInternal

FiniteGrid RectTriGrid Source # 
Instance details

Defined in Math.Geometry.Grid.TriangularInternal

Associated Types

type Size RectTriGrid :: Type Source #

Grid RectTriGrid Source # 
Instance details

Defined in Math.Geometry.Grid.TriangularInternal

Associated Types

type Index RectTriGrid :: Type Source #

type Direction RectTriGrid :: Type Source #

Methods

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

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

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

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

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

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

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

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

tileCount :: RectTriGrid -> Int Source #

null :: RectTriGrid -> Bool Source #

nonNull :: RectTriGrid -> Bool Source #

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

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

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

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

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

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

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

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

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

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

defaultTileCount :: RectTriGrid -> Int Source #

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

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

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

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

type Rep RectTriGrid Source # 
Instance details

Defined in Math.Geometry.Grid.TriangularInternal

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

Defined in Math.Geometry.Grid.TriangularInternal

type Index RectTriGrid Source # 
Instance details

Defined in Math.Geometry.Grid.TriangularInternal

type Direction RectTriGrid Source # 
Instance details

Defined in Math.Geometry.Grid.TriangularInternal

rectTriGrid :: Int -> Int -> RectTriGrid Source #

rectTriGrid r c returns a grid in the shape of a rectangle (with jagged edges) that has r rows and c columns, using triangular tiles. If r and c are both nonnegative, the resulting grid will have 2*r*c tiles. Otherwise, the resulting grid will be null and the list of indices will be null.

data TorTriGrid Source #

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

Constructors

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

Defined in Math.Geometry.Grid.TriangularInternal

Show TorTriGrid Source # 
Instance details

Defined in Math.Geometry.Grid.TriangularInternal

Generic TorTriGrid Source # 
Instance details

Defined in Math.Geometry.Grid.TriangularInternal

Associated Types

type Rep TorTriGrid :: Type -> Type #

WrappedGrid TorTriGrid Source # 
Instance details

Defined in Math.Geometry.Grid.TriangularInternal

FiniteGrid TorTriGrid Source # 
Instance details

Defined in Math.Geometry.Grid.TriangularInternal

Associated Types

type Size TorTriGrid :: Type Source #

Grid TorTriGrid Source # 
Instance details

Defined in Math.Geometry.Grid.TriangularInternal

Associated Types

type Index TorTriGrid :: Type Source #

type Direction TorTriGrid :: Type Source #

Methods

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

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

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

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

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

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

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

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

tileCount :: TorTriGrid -> Int Source #

null :: TorTriGrid -> Bool Source #

nonNull :: TorTriGrid -> Bool Source #

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

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

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

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

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

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

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

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

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

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

defaultTileCount :: TorTriGrid -> Int Source #

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

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

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

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

type Rep TorTriGrid Source # 
Instance details

Defined in Math.Geometry.Grid.TriangularInternal

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

Defined in Math.Geometry.Grid.TriangularInternal

type Index TorTriGrid Source # 
Instance details

Defined in Math.Geometry.Grid.TriangularInternal

type Direction TorTriGrid Source # 
Instance details

Defined in Math.Geometry.Grid.TriangularInternal

torTriGrid :: Int -> Int -> TorTriGrid Source #

torTriGrid r c returns a toroidal grid with r rows and c columns, using triangular tiles. The indexing method is the same as for ParaTriGrid. If r and c are both nonnegative, the resulting grid will have 2*r*c tiles. Otherwise, the resulting grid will be null and the list of indices will be null.

data YCylTriGrid Source #

A cylindrical grid with triangular tiles, where the cylinder is along the y-axis. The grid and its indexing scheme are illustrated in the user guide, available at https://github.com/mhwombat/grid/wiki.

Constructors

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

Defined in Math.Geometry.Grid.TriangularInternal

Show YCylTriGrid Source # 
Instance details

Defined in Math.Geometry.Grid.TriangularInternal

Generic YCylTriGrid Source # 
Instance details

Defined in Math.Geometry.Grid.TriangularInternal

Associated Types

type Rep YCylTriGrid :: Type -> Type #

WrappedGrid YCylTriGrid Source # 
Instance details

Defined in Math.Geometry.Grid.TriangularInternal

FiniteGrid YCylTriGrid Source # 
Instance details

Defined in Math.Geometry.Grid.TriangularInternal

Associated Types

type Size YCylTriGrid :: Type Source #

Grid YCylTriGrid Source # 
Instance details

Defined in Math.Geometry.Grid.TriangularInternal

Associated Types

type Index YCylTriGrid :: Type Source #

type Direction YCylTriGrid :: Type Source #

Methods

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

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

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

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

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

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

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

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

tileCount :: YCylTriGrid -> Int Source #

null :: YCylTriGrid -> Bool Source #

nonNull :: YCylTriGrid -> Bool Source #

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

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

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

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

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

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

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

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

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

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

defaultTileCount :: YCylTriGrid -> Int Source #

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

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

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

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

type Rep YCylTriGrid Source # 
Instance details

Defined in Math.Geometry.Grid.TriangularInternal

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

Defined in Math.Geometry.Grid.TriangularInternal

type Index YCylTriGrid Source # 
Instance details

Defined in Math.Geometry.Grid.TriangularInternal

type Direction YCylTriGrid Source # 
Instance details

Defined in Math.Geometry.Grid.TriangularInternal

yCylTriGrid :: Int -> Int -> YCylTriGrid Source #

yCylTriGrid r c returns a cylindrical grid with r rows and c columns, using triangular tiles, where the cylinder is along the y-axis. The indexing method is the same as for ParaTriGrid. If r and c are both nonnegative, the resulting grid will have 2*r*c tiles. Otherwise, the resulting grid will be null and the list of indices will be null.

data XCylTriGrid Source #

A cylindrical grid with triangular tiles, where the cylinder is along the x-axis. The grid and its indexing scheme are illustrated in the user guide, available at https://github.com/mhwombat/grid/wiki.

Constructors

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

Defined in Math.Geometry.Grid.TriangularInternal

Show XCylTriGrid Source # 
Instance details

Defined in Math.Geometry.Grid.TriangularInternal

Generic XCylTriGrid Source # 
Instance details

Defined in Math.Geometry.Grid.TriangularInternal

Associated Types

type Rep XCylTriGrid :: Type -> Type #

WrappedGrid XCylTriGrid Source # 
Instance details

Defined in Math.Geometry.Grid.TriangularInternal

FiniteGrid XCylTriGrid Source # 
Instance details

Defined in Math.Geometry.Grid.TriangularInternal

Associated Types

type Size XCylTriGrid :: Type Source #

Grid XCylTriGrid Source # 
Instance details

Defined in Math.Geometry.Grid.TriangularInternal

Associated Types

type Index XCylTriGrid :: Type Source #

type Direction XCylTriGrid :: Type Source #

Methods

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

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

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

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

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

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

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

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

tileCount :: XCylTriGrid -> Int Source #

null :: XCylTriGrid -> Bool Source #

nonNull :: XCylTriGrid -> Bool Source #

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

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

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

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

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

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

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

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

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

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

defaultTileCount :: XCylTriGrid -> Int Source #

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

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

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

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

type Rep XCylTriGrid Source # 
Instance details

Defined in Math.Geometry.Grid.TriangularInternal

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

Defined in Math.Geometry.Grid.TriangularInternal

type Index XCylTriGrid Source # 
Instance details

Defined in Math.Geometry.Grid.TriangularInternal

type Direction XCylTriGrid Source # 
Instance details

Defined in Math.Geometry.Grid.TriangularInternal

xCylTriGrid :: Int -> Int -> XCylTriGrid Source #

xCylTriGrid r c returns a cylindrical grid with r rows and c columns, using triangular tiles, where the cylinder is along the y-axis. The indexing method is the same as for ParaTriGrid. If r and c are both nonnegative, the resulting grid will have 2*r*c tiles. Otherwise, the resulting grid will be null and the list of indices will be null.