Skip to content

Instantly share code, notes, and snippets.

@scravy
Created April 21, 2020 16:31
Show Gist options
  • Star 0 You must be signed in to star a gist
  • Fork 0 You must be signed in to fork a gist
  • Save scravy/38d3f509bf5409b4bba0a90282a1a1f2 to your computer and use it in GitHub Desktop.
Save scravy/38d3f509bf5409b4bba0a90282a1a1f2 to your computer and use it in GitHub Desktop.
{-# LANGUAGE Haskell2010, LambdaCase #-}
import Data.List (nub)
data Symbol = M | I | U deriving (Eq, Show)
apply = \case
M : xs -> [ M : xs ++ xs ]
I : I : I : xs -> [ U : xs ]
U : U : xs -> [ xs ]
I : [] -> [ I : U : [] ]
xs -> []
applyAll = \case
[] -> []
ss@(s : rs) -> apply ss ++ map (s :) (applyAll rs)
nextGen (curGen, start) = (oldGen, noDupes (start >>= applyAll))
where
noDupes = nub . filter (not . flip elem oldGen)
oldGen = start ++ curGen
enumerateAll start = concatMap snd (iterate nextGen ([], [start]))
main = mapM_ (putStrLn . map (head . show)) (enumerateAll [M, I])
Sign up for free to join this conversation on GitHub. Already have an account? Sign in to comment