Skip to content

Instantly share code, notes, and snippets.

@rampion
Last active September 4, 2024 18:48
Show Gist options
  • Save rampion/be238f32f0201bb4b418389343b985a8 to your computer and use it in GitHub Desktop.
Save rampion/be238f32f0201bb4b418389343b985a8 to your computer and use it in GitHub Desktop.
{-# LANGUAGE BlockArguments #-}
{-# LANGUAGE LambdaCase #-}
{-# LANGUAGE TypeApplications #-}
{-# LANGUAGE ViewPatterns #-}
{-# OPTIONS_GHC -Wall -Wextra -Werror #-}
-- https://exercism.org/tracks/haskell/exercises/crypto-square
module CryptoSquare where
import Data.Char (isLower, toLower)
import Data.List (transpose)
import Test.Hspec
normalize :: String -> String
normalize = filter isLower . map toLower
data Rectangle = Rectangle {columns :: Int, rows :: Int}
-- like div, but rounding up
ceilingDiv :: Integral a => a -> a -> a
ceilingDiv n d = (n + d - 1) `div` d
-- smallest, most square-like rectangle that contains the given area
minimal :: Int -> Rectangle
minimal n = Rectangle {columns, rows}
where
columns = ceiling (sqrt (toEnum @Double n)) -- ⌈√n⌉
rows = n `ceilingDiv` columns -- ⌈n / ⌈√n⌉⌉ ≤ ⌈√n⌉
-- split a list into chunks of the given length
splits :: Int -> [a] -> [[a]]
splits n = \case
[] -> []
(splitAt n -> (as, bs)) -> as : splits n bs
-- reshape a list into a rectangle of the given size
rectangle :: Rectangle -> [a] -> [[a]]
rectangle Rectangle {columns, rows} as = take rows $ splits columns as
encode :: String -> String
encode (normalize -> cs) = unwords . transpose . rectangle (minimal (length cs)) $ cs ++ repeat ' '
spec :: Spec
spec = do
it "should satisfy the example" do
encode "If man was meant to stay on the ground, god would have given us roots."
`shouldBe` "imtgdvs fearwer mayoogo anouuio ntnnlvt wttddes aohghn sseoau "
Sign up for free to join this conversation on GitHub. Already have an account? Sign in to comment