module Main where import Graphics.Rendering.Diagrams import Data.Colour.SRGB.Linear second f (x,y) = (x,f y) select :: [a] -> [(a,[a])] select [] = [] select (x:xs) = (x,xs) : map (second (x:)) (select xs) permutations :: [a] -> [[a]] permutations [] = [[]] permutations xs = do (e, rest) <- select xs map (e:) $ permutations rest dia :: Diagram dia = arrange $ map colorsToStrip (permutations [red, yellow, blue, green']) where green' = rgb 0 1 0 arrange :: [Diagram] -> Diagram arrange = hsep 10 . map (vsep 5) . groups where groups = takeWhile (not . null) . map (take 6) . iterate (drop 6) colorsToStrip :: Color c => [c] -> Diagram colorsToStrip = hcat . map (\c -> fc c $ rect 10 10) main = renderAs PNG "permutations.png" (Width 300) dia