module Combinatorics.PaperStripGame (
numbersOfGames,
numbersOfGamesSeries,
treeOfGames,
) where
import qualified Combinatorics as Combi
import qualified PowerSeries as PS
import qualified Data.List.HT as ListHT
import qualified Data.Tree as Tree
import Data.Tree (Tree, )
import Data.List (inits, tails, )
import Control.Monad (guard, )
_cutEverywhere0 :: [Int] -> [[Int]]
_cutEverywhere0 xs = do
(ys, z0:z1:zs) <- zip (inits xs) (tails xs)
guard $ succ z0 == z1
return $ ys++zs
cutEverywhere1 :: [Int] -> [[Int]]
cutEverywhere1 zs = do
(xs,n,ys) <- ListHT.splitEverywhere zs
(a,b) <- cutPart n
return $ xs ++ filter (0/=) [a,b] ++ ys
cutPart :: Int -> [(Int, Int)]
cutPart n =
zip [0..] $ takeWhile (>=0) $ iterate pred (n2)
treeOfGames :: Int -> Tree [Int]
treeOfGames n =
Tree.unfoldTree (\ns -> (ns, if null ns then [] else cutEverywhere1 ns)) [n]
lengthOfGames :: Int -> [Int]
lengthOfGames =
let go n ls =
if all (<=1) ls
then [n]
else concatMap (go (succ n)) $ cutEverywhere1 ls
in go 0 . (:[])
numbersOfGames :: [Int]
numbersOfGames =
map (length . lengthOfGames) [0..]
numbersOfGamesSeries :: [Integer]
numbersOfGamesSeries =
foldr (\(x0:x1:xs) ys -> x0 : x1 : PS.add xs ys) [] $
zipWith PS.scale Combi.factorials $ tail Combi.binomials