sized-grid: Multidimensional grids with sized specified at compile time

[ data, library, mit ] [ Propose Tags ]

`size-grid` allows you to make finite sized grids and have their size and shape confirmed at compile time

Consult the readme for a short tutorial and explanation.


[Skip to Readme]

Downloads

Maintainer's Corner

Package maintainers

For package maintainers and hackage trustees

Candidates

Versions [RSS] 0.1.0.0, 0.1.1.0, 0.1.1.1, 0.1.1.4, 0.1.1.5, 0.1.1.6, 0.2.0.1
Change log ChangeLog.md
Dependencies adjunctions (>=4.3 && <4.5), aeson (>=1.2 && <1.5), base (>=4.9 && <4.13), comonad (>=5.0 && <5.1), constraints (>=0.9 && <0.11), distributive (>=0.5 && <1), generics-sop (>=0.3 && <0.6), lens (>=4.15 && <5), mtl (>=2.2.2 && <2.3), random (>=1.1 && <1.2), vector (>=0.12 && <0.13), vector-space (>=0.10 && <2) [details]
License MIT
Author edwardwas
Maintainer ed@wastell.co.uk
Category Data
Home page https://github.com/edwardwas/sized-grid
Bug tracker https://github.com/edwardwas/sized-grid/issues
Source repo head: git clone https://github.com/edwardwas/sized-grid
Uploaded by edwardwas at 2019-09-13T10:14:52Z
Distributions
Reverse Dependencies 1 direct, 0 indirect [details]
Downloads 3379 total (19 in the last 30 days)
Rating 2.0 (votes: 1) [estimated by Bayesian average]
Your Rating
  • λ
  • λ
  • λ
Status Docs available [build log]
Last success reported on 2019-09-13 [all 1 reports]

Readme for sized-grid-0.2.0.1

[back to package description]

Build Status

Hackage

sized-grid

A way of working with grids in Haskell with size encoded at the type level.

Quick tutorial

The core datatype of this library is Grid (cs :: '[k]) (a :: *). cs is a type level list of coordinate types. We could use a single type level number here, but by using different types we can say what happened when we move outside the bounds of a grid. There are three different coordinate types provided.

  • Ordinal n: An ordinal can be an integral number between 0 and n - 1. As numbers outside the grid are not possible, this has the most restrictive API. One can convert between an Ordinal and a number of ordinalToNum and numToOrdinal.

  • HardWrap n: Like Oridnal, HardWrap can only hold intergral numbers between 0 and n - 1, but it allows a more permissive API by clamping values outside of its range. It is an instance of Semigroup and Monoid, where mempty is 0 and <> is addition.

  • Periodic n: This is the most permissive. When a value is generated outside the given range, it wraps that around using modular arithmetic. Is is an instance of Semigroup and Monoid like HardWrap, but also of AdditiveGroup allowing negation.

HardWrap and Periodic are both instances of AffineSpace, with their Diff being Integer. This means there are many occasions where one doesn't have to work directly with these values (which can be cumbersome) and can instead work with their differences as regular numbers.

The last type value of Grid is the type of each element.

The other main type is Coord cs, where cs is, again, a type level list of coordinate types. For example, Coord '[Periodic 3, HardWrap 4] is a coordinate in a 3 by 4 2D space. The different types (Periodic and HardWrap) tell how to handle combining theses different numbers. Coord cs is an instance of Semigroup, Monoid and AdditiveGroup as long as each of the coordinates is also an instance of that typeclass. Coord is also an instance of of AffineSpace, where Diff is a n-tuple, meaning we can pattern match and do all sorts of nice things.

For working directly with Coords, one can construct them with singleCoord and appendCoord and consume and update them with coordHead and coordTail. They are also instances of FieldN from lens, allowing one to directly update or get a certain dimension.

There is a deliberately small number of functions that work over Grid: we instead opt for using typeclasses to create the required functionality. Grid is an instance of the following types (with some required constraints):

  • Functor: Update all values in the grid with the same function
  • Applicative: As the size of the grid is statically known, pure just creates a grid with the same element at each point. <*> combines the grids point wise.
  • Monad: I'm not sure if there is much of a need for this, but an instance exists.
  • Foldable: Combine each element of the grid
  • Traverse: Apply an applicative function over the grid
  • IndexedFunctor, IndexedFoldable and IndexedTraversable: Like Functor, Foldable and Traversable, but with access to the position at each point. These are from the lens package
  • Distributive: Like Traversable, but the other way round. Allows us to put a functor inside the grid
  • Representable: Grid cs a is isomorphic Coord cs -> a, so we can tabulate and index to make this conversion

We also have a FocusedGrid type, which is like Grid but has a certain focused position. This means that we lose many instances, but we gain Comonad and ComonadStore.

When dealing with areas around Coords, we can use moorePoints and vonNeumanPoints to generate Moore and von Neuman neighbourhoods. Note that these include the center point.

We introduce two new typeclasses: IsCoord and IsGrid. IsGrid has gridIndex, which allows us to get a single element of the grid and lenses to convert between FocusedGrid and Grid. IsCoord has CoordSized, which is the size of the coord and an iso to convert between Ordinal and the Coord.

Example - Game of Life

As is traditional for anything with grids and comonads in Haskell, we can reimplement Conway's Game of Life.

This is a literate Haskell file, so we start by turning on some language extensions, importing our library and some other utilities.

{-# LANGUAGE MultiWayIf #-}
{-# LANGUAGE TypeFamilies #-}
{-# LANGUAGE FlexibleContexts #-}
{-# LANGUAGE TypeOperators #-}
{-# LANGUAGE MonoLocalBinds #-}
{-# LANGUAGE DataKinds #-}

import SizedGrid

import Control.Comonad
import Control.Lens
import Control.Comonad.Store
import Data.AdditiveGroup
import Data.AffineSpace
import Data.Distributive
import Data.Functor.Rep
import Data.Semigroup (Semigroup(..))
import GHC.TypeLits
import qualified GHC.TypeLits as GHC
import System.Console.ANSI

We create a datatype for alive or dead.

data TileState = Alive | Dead deriving (Eq,Show)

We encode the rules of the game via a step function.

type Rule = TileState -> [TileState] -> TileState

gameOfLife :: Rule
gameOfLife here neigh =
    let aliveNeigh = length $ filter (== Alive) neigh
    in if | here == Alive && aliveNeigh `elem` [2,3] -> Alive
          | here == Dead && aliveNeigh == 3 -> Alive
          | otherwise -> Dead

We can then write a function to apply this to every point in a grid.

applyRule :: 
       ( All IsCoordLifted cs
       , All Monoid cs
       , All Semigroup cs
       , All AffineSpace cs
       , All Eq cs
       , AllDiffSame Integer cs
       , AllSizedKnown cs
       , IsGrid cs (grid cs)
       )
    => Rule
    -> grid cs TileState
    -> grid cs TileState
applyRule rule = over asFocusedGrid $ 
    extend $ \fg -> rule (extract fg) $ map (\p -> peek p fg) $ 
        filter (/= pos fg) $ moorePoints (1 :: Integer) $ pos fg

We can create a simple drawing function to display it to the screen.

displayTileState :: TileState -> Char
displayTileState Alive = '#'
displayTileState Dead = '.'

displayGrid :: (KnownNat (x GHC.* y), KnownNat x, KnownNat y) => 
      Grid '[f x, g y] TileState -> String
displayGrid = unlines . collapseGrid . fmap displayTileState

Let's create a glider, and watch it move!

glider :: 
      ( KnownNat (CoordNat x GHC.* CoordNat y)
      , Semigroup x
      , Semigroup y
      , Monoid x
      , Monoid y
      , IsCoordLifted x
      , IsCoordLifted y
      , AffineSpace x
      , AffineSpace y
      , Diff x ~ Integer
      , Diff y ~ Integer
      ) 
      => Coord '[x,y] 
      -> Grid '[x,y] TileState
glider offset = pure Dead 
    & gridIndex (offset .+^ (0,-1)) .~ Alive
    & gridIndex (offset .+^ (1,0)) .~ Alive
    & gridIndex (offset .+^ (-1,1)) .~ Alive
    & gridIndex (offset .+^ (0,1)) .~ Alive
    & gridIndex (offset .+^ (1,1)) .~ Alive

We can now make our glider run!

run = 
    let start :: Grid '[Periodic 10, Periodic 10] TileState 
        start = glider (mempty .+^ (3,3))
        doStep grid = do
          clearScreen
          putStrLn $ displayGrid grid
          _ <- getLine
          doStep $ applyRule gameOfLife grid
    in doStep start

main = return ()