[Haskell-cafe] 3-state, 2-symbol busy beaver
Maurício
briqueabraque at yahoo.com
Sat Oct 25 12:34:06 EDT 2008
Hi,
Just some easy fun:
$> ghci
Prelude> :l busyBeaver.hs
Prelude> map snd busyBeaver
[A,B,A,C,B,A,B,B,B,B,B,A,C,Halt]
Best,
Maurício
-- | busyBeaver.hs
data State = A | B | C | Halt deriving Show
data Value = Blank | NonBlank
type Tape = (Integer -> Value)
moveRight tape = \n -> tape $ n - 1
moveLeft tape = \n -> tape $ n + 1
(write tape) n = if n == 0 then NonBlank else tape n
table :: (Tape,State) -> (Tape,State)
table (tape,state) = case (tape 0,state) of
(Blank,A) -> ((moveRight . write) tape , B)
(NonBlank,A) -> ((moveLeft . write) tape , C)
(Blank,B) -> ((moveLeft . write) tape , A)
(NonBlank,B) -> ((moveRight . write) tape , B)
(Blank,C) -> ((moveLeft . write) tape , B)
(NonBlank,C) ->((moveRight . write) tape , Halt)
(_,Halt) -> (tape,Halt)
busyBeaver = bb (const Blank,A) where
bb t@(_,Halt) = t:[]
bb t = t:(bb $ table t)
More information about the Haskell-Cafe
mailing list