Skip to content

Instantly share code, notes, and snippets.

@Cmdv
Last active November 2, 2018 11:48
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 Cmdv/922c5b9faae3b50e93eabcd3b830eecb to your computer and use it in GitHub Desktop.
Save Cmdv/922c5b9faae3b50e93eabcd3b830eecb to your computer and use it in GitHub Desktop.
Flatten a nested List of any given depth into a single level deep list.
module NestedListExercise where
import Test.QuickCheck
import Test.QuickCheck.Monadic
-------------------------------------------------------------------------------
-- ** Implemetation
-------------------------------------------------------------------------------
-- I wanted to do this little test using Haskell due to the type safety and how
-- we can randomly generate different nested lists to tests against our implementation.
-- The implementation is really small but the testing is where this code shines.
data NestedList a = Nested [NestedList a]
| List [a]
| Value a
deriving Show
flatten :: NestedList a -> [a]
flatten (Nested []) = []
flatten (Nested (x:xs)) = flatten x ++ flatten (Nested xs)
flatten (List xs) = xs
flatten (Value a) = [a]
-- flatten $ Nested [Value 1, Nested [Value 2,List [3,4]],Nested [Value 5, List [6,7,8]], List [9,10]]
-- > [1,2,3,4,5,6,7,8,9,10]
-- using Haskell you can't represent a nested array without creating an Algebraic Data Type
-- in a real life scenario this value would come from say an API responce, so to convert it to an ADT
-- it would require something like `decode` form Aeson for conversion.
-- This function can flatten random infinite depth of nested lists (Arrays) not just 2 levels!
-------------------------------------------------------------------------------
-- ** Define a monoid and Semigroup instance for `NestedList`
-------------------------------------------------------------------------------
-- If we want to concatenate nested lists in a consistent way, we should define
-- a monoid instance for `NestedList`:
instance Monoid (NestedList a) where
mempty = Nested []
Nested n `mappend` List l = Nested $ n ++ [List l]
Nested n `mappend` Value x = Nested $ n ++ [Value x]
Nested n1 `mappend` Nested n2 = Nested [Nested n1, Nested n2]
List l1 `mappend` List l2 = Nested [List l1, List l2]
List l `mappend` Nested n = Nested $ List l : n
List l `mappend` Value x = List $ l ++ [x]
Value x `mappend` List l = List $ x:l
Value x `mappend` Nested n = Nested $ Value x:n
Value x1 `mappend` Value x2 = List [x1, x2]
instance Semigroup (NestedList a) where
(<>) = mappend
-- Nested [Value 1,List [2,3,4,5]] <> Nested [List [6,7,8],Value 9, Value 10]
-- > Nested [Nested [Value 1,List [2,3,4,5]],Nested [List [6,7,8],Value 9,Value 10]]
-------------------------------------------------------------------------------
-- ** Set up QuickCheck testing
-------------------------------------------------------------------------------
-- Now let's do some testing. We can use QuickCheck to automatically generate
-- random instances of arbitrarily nested lists:
genNested :: Arbitrary a => NestedList a -> Gen (NestedList a)
genNested (Nested []) = return $ Nested []
genNested (List []) = return $ List []
genNested (List [x]) = return $ Value x
genNested (List xs) = do
shouldSplit <- elements splitProb
if shouldSplit then segmentList xs
else return $ List xs
genNested (Nested xs) = do
shouldSplit <- elements splitProb
if shouldSplit then segmentNested xs
else return $ Nested xs
-- We can change the proportions of Trues/Falses to change the probability we'll split.
-- Obviously not the best way to go about it...
splitProb :: [Bool]
splitProb = [True, True, True, False]
-- Splits a list at randomly selected point between 1 and n-1
-- where n is length of list.
splitList :: [a] -> Gen ([a], [a])
splitList xs = do
(Positive p) <- arbitrary
let len = length xs
let n = max 1 (p * len `mod` (len - 1))
return (take n xs, drop n xs)
-- Segments a list into random sublists
segmentList :: Arbitrary a => [a] -> Gen (NestedList a)
segmentList [x] = return $ List [x]
segmentList xs = do
(s1, s2) <- splitList xs
(<>) <$> genNested (List s1) <*> genNested (List s2)
-- Segments a nested list into random sublists
segmentNested :: Arbitrary a => [NestedList a] -> Gen (NestedList a)
segmentNested xs = do
(s1, s2) <- splitList xs
(<>) <$> genNested (Nested s1) <*> genNested (Nested s2)
-- Returns a randomly nested list generated from a given list of ints.
nestList :: [Int] -> Gen (NestedList Int)
nestList = genNested . List
-- generate $ nestList [1..10]
-- > Nested [Value 1,Value 2,List [3,4,5],List [6,7,8],List [9,10]]
-------------------------------------------------------------------------------
-- ** Define test properties
-------------------------------------------------------------------------------
compareNested :: ([Int] -> NestedList Int -> Bool) -> Property
compareNested compare = monadicIO $ do
list <- run $ generate arbitrary
nested <- run . generate $ nestList list
assert $ compare list nested
-- Flattening a nested list N generated from a list L is the same as L
prop_flatten :: Property
prop_flatten = compareNested $ \list nested -> list == flatten nested
-------------------------------------------------------------------------------
-- ** Run tests
-------------------------------------------------------------------------------
-- Now we can use QuickCheck to randomly generate random test cases, and
-- check if the given property holds for all of them.
-- This is extremly usefull for catching edge cases.
runAllTests :: IO ()
runAllTests = mapM_ quickCheck
[ label "Flatten" prop_flatten ]
-- > +++ OK, passed 100 tests (100% Flatten).
Sign up for free to join this conversation on GitHub. Already have an account? Sign in to comment