Elementary cellular automaton/Infinite length: Difference between revisions

→‎{{header|Haskell}}: Added Haskell solution
(→‎{{header|Elixir}}: change Dict(deprecated) -> Map, String.rjust -> String.pad_leading)
(→‎{{header|Haskell}}: Added Haskell solution)
Line 210:
##..#...###..####...##.#####...#.#####.#..#.....#
</pre>
 
=={{header|Haskell}}==
Infinite lists are natural in Haskell, however the task forces us to deal with lists that are infinite in both directions. These structures could be efficiently implemented as a ''zipper lists''. Moreover, zipper lists are instances of magic <code>Comonad</code> class, which gives beautifull implementation of cellular automata.
 
This solution is kinda involved, but it is guaranteed to be total and correct by type checker.
 
First we provide the datatype, the viewer and constructor:
 
<lang Haskell>{-# LANGUAGE DeriveFunctor #-}
 
import Control.Comonad
import Data.InfList (InfList (..), (+++))
import qualified Data.InfList as Inf
 
data Cells a = Cells (InfList a) a (InfList a) deriving Functor
 
view n (Cells l x r) = reverse (Inf.take n l) ++ [x] ++ (Inf.take n r)
 
fromList [] = fromList [0]
fromList (x:xs) = let zeros = Inf.repeat 0
in Cells zeros x (xs +++ zeros)</lang>
 
In order to run the CA on the domain we make it an instance of <code>Comonad</code> class. Running the CA turns to be just an iterative comonadic ''extension'' of the rule:
 
<lang Haskell>instance Comonad Cells where
extract (Cells _ x _) = x
duplicate x = Cells (rewind left x) x (rewind right x)
where
rewind dir = Inf.iterate dir . dir
right (Cells l x (r ::: rs)) = Cells (x ::: l) r rs
left (Cells (l ::: ls) x r) = Cells ls l (x ::: r)
 
runCA rule = iterate (=>> step)
where step (Cells (l ::: _) x (r ::: _)) = rule l x r</lang>
 
Following is the rule definition and I/O routine:
 
<lang Haskell>rule n l x r = n `div` (2^(4*l + 2*x + r)) `mod` 2
 
displayCA n w rule init = mapM_ putStrLn $ take n result
where result = fmap display . view w <$> runCA rule init
display 0 = ' '
display _ = '*'</lang>
 
{{Out}}
<pre>λ> displayCA 30 20 (rule 90) (fromList [1])
*
* *
* *
* * * *
* *
* * * *
* * * *
* * * * * * * *
* *
* * * *
* * * *
* * * * * * * *
* * * *
* * * * * * * *
* * * * * * * *
* * * * * * * * * * * * * * * *
* *
* * * *
* * * *
* * * * * * * *
* * * *
* * * * * *
* * * * * *
* * * * * * * * * * * *
* *
* * * *
* * * *
* * * * * * * *
* * * * * *
* * * * * * * * * * </pre>
 
See also [[Elementary cellular automaton#Haskell]]
 
=={{header|J}}==
Anonymous user