~vonfry/maze-escape

e1c1e94611457e40238865fa9a34275011d353c1 — Vonfry 2 years ago 70ae5e5
maze/data: instance
3 files changed, 26 insertions(+), 5 deletions(-)

M .nix/maze-escape.nix
M lib/Game/Maze/Data.hs
M maze-escape.cabal
M .nix/maze-escape.nix => .nix/maze-escape.nix +2 -2
@@ 1,9 1,9 @@
{ mkDerivation, base, hspec, ilist, lib, mtl }:
{ mkDerivation, base, hspec, ilist, lib, mtl, utility-ht }:
mkDerivation {
  pname = "maze-escape";
  version = "0.1.0.0";
  src = ../.;
  libraryHaskellDepends = [ base ilist mtl ];
  libraryHaskellDepends = [ base ilist mtl utility-ht ];
  testHaskellDepends = [ base hspec ilist mtl ];
  homepage = "https://gitlab.com/Vonfry/maze-escape";
  license = lib.licenses.gpl3Plus;

M lib/Game/Maze/Data.hs => lib/Game/Maze/Data.hs +23 -3
@@ 1,10 1,18 @@
{-# LANGUAGE MultiParamTypeClasses #-}
{-# LANGUAGE FlexibleInstances #-}
{-# LANGUAGE MultiWayIf #-}

module Game.Maze.Data where
module Game.Maze.Data
  ( MazeCell(..)
  , MazeMapList(..)
  , MazeMapListPos
  )
where

import Game.Maze
import Data.List.Index (ifoldr)
import Control.Monad (unless)
import Data.Monoid.HT (when)

data MazeCell = S -- ^ source
              | D -- ^ destination


@@ 21,8 29,20 @@ instance MovableCell MazeCell where
  movable _ = True

instance Maze2D MazeMapList MazeMapListPos MazeCell where
  -- | assume the map is a matrix istead of atactic one.
  adjacence map pos = [] -- TODO
  adjacence (MazeMapList cells) (x, y) =
    withUp <> withDown <> withLeft <> withRight
      where
        withUp = when (y > 0) $ pure up
        withDown = when (y < lcol - 1) $ pure down
        withLeft = when (x > 0) $ pure left
        withRight = when (x < lrow - 1) $ pure right
        row = cells !! x
        lrow = length row
        lcol = length cells
        up    = (x, y - 1)
        down  = (x, y + 1)
        left  = (x - 1, y)
        right = (x + 1, y)

  getCell (MazeMapList cells) (x,y) = cells !! x !! y


M maze-escape.cabal => maze-escape.cabal +1 -0
@@ 22,6 22,7 @@ common deps
    build-depends:    base ==4.*
                    , mtl
                    , ilist
                    , utility-ht

library
    import:           deps