Move matrix stuff
This commit is contained in:
parent
451684e928
commit
299e70e1df
25
Matrix.hs
Normal file
25
Matrix.hs
Normal file
@ -0,0 +1,25 @@
|
|||||||
|
module Matrix where
|
||||||
|
|
||||||
|
data Mat a = Mat [[a]]
|
||||||
|
type Pos = (Int, Int)
|
||||||
|
|
||||||
|
instance Functor Mat where
|
||||||
|
fmap f (Mat m) = Mat ((map . map) f m)
|
||||||
|
|
||||||
|
-- | Safely access a list
|
||||||
|
-- [4,1,5,9] ?? 2 == Just 5
|
||||||
|
-- [5,7] ?? 3 == Nothing
|
||||||
|
(??) :: [a] -> Int -> Maybe a
|
||||||
|
xs ?? n | n < 0 = Nothing
|
||||||
|
[] ?? _ = Nothing
|
||||||
|
(x:_) ?? 0 = Just x
|
||||||
|
(_:xs) ?? n = xs ?? (n-1)
|
||||||
|
|
||||||
|
-- | Create a matrix of indeces of a matrix
|
||||||
|
indeces :: Mat a -> Mat Pos
|
||||||
|
indeces (Mat m) = Mat [[(x,y) | y <- [0..length (m !! x)-1]] |
|
||||||
|
x <- [0..length m-1]]
|
||||||
|
|
||||||
|
-- | Create a matrix of zeros
|
||||||
|
zeros :: Int -> Int -> Mat Int
|
||||||
|
zeros x y = Mat (replicate x $ replicate y 0)
|
30
life.hs
30
life.hs
@ -1,16 +1,10 @@
|
|||||||
{-#LANGUAGE TypeSynonymInstances, FlexibleInstances#-}
|
{-#LANGUAGE TypeSynonymInstances, FlexibleInstances#-}
|
||||||
import Data.Maybe (listToMaybe)
|
import Data.Maybe (listToMaybe)
|
||||||
import Data.List (intercalate)
|
import Data.List (intercalate)
|
||||||
|
import Matrix
|
||||||
|
|
||||||
data Mat a = Mat [[a]]
|
|
||||||
type Pos = (Int, Int)
|
|
||||||
|
|
||||||
type Grid = Mat Cell
|
|
||||||
type Cell = Int
|
type Cell = Int
|
||||||
|
type Grid = Mat Cell
|
||||||
|
|
||||||
instance Functor Mat where
|
|
||||||
fmap f (Mat m) = Mat ((map . map) f m)
|
|
||||||
|
|
||||||
instance Show Grid where
|
instance Show Grid where
|
||||||
show (Mat m) = concatMap ((++"\n") . intercalate " " . map replace) m
|
show (Mat m) = concatMap ((++"\n") . intercalate " " . map replace) m
|
||||||
@ -18,20 +12,6 @@ instance Show Grid where
|
|||||||
replace 1 = "■"
|
replace 1 = "■"
|
||||||
replace 0 = "'"
|
replace 0 = "'"
|
||||||
|
|
||||||
-- | Safely access a list
|
|
||||||
-- [4,1,5,9] ?? 2 == Just 5
|
|
||||||
-- [5,7] ?? 3 == Nothing
|
|
||||||
(??) :: [a] -> Int -> Maybe a
|
|
||||||
xs ?? n | n < 0 = Nothing
|
|
||||||
[] ?? _ = Nothing
|
|
||||||
(x:_) ?? 0 = Just x
|
|
||||||
(_:xs) ?? n = xs ?? (n-1)
|
|
||||||
|
|
||||||
-- | Create a Mat of Indeces for a grid
|
|
||||||
indeces :: Grid -> Mat Pos
|
|
||||||
indeces (Mat m) = Mat [[(x,y) | y <- [0..length (m !! x)-1]] |
|
|
||||||
x <- [0..length m-1]]
|
|
||||||
|
|
||||||
-- | Get the state of a cell
|
-- | Get the state of a cell
|
||||||
-- 0 when out of the grid
|
-- 0 when out of the grid
|
||||||
(!) :: Grid -> Pos -> Cell
|
(!) :: Grid -> Pos -> Cell
|
||||||
@ -39,11 +19,7 @@ indeces (Mat m) = Mat [[(x,y) | y <- [0..length (m !! x)-1]] |
|
|||||||
Nothing -> 0
|
Nothing -> 0
|
||||||
Just v -> v
|
Just v -> v
|
||||||
|
|
||||||
-- | Create empty grid
|
-- | List of neighbours cells
|
||||||
void :: Int -> Int -> Grid
|
|
||||||
void x y = Mat (replicate x $ replicate y 0)
|
|
||||||
|
|
||||||
-- | Give the list of neighbours cells
|
|
||||||
near :: Grid -> Pos -> [Cell]
|
near :: Grid -> Pos -> [Cell]
|
||||||
near g (x, y) = [g ! (x+x', y+y') | x' <- [-1..1],
|
near g (x, y) = [g ! (x+x', y+y') | x' <- [-1..1],
|
||||||
y' <- [-1..1],
|
y' <- [-1..1],
|
||||||
|
Loading…
Reference in New Issue
Block a user