Skip to content

Instantly share code, notes, and snippets.

@CCColda
Last active December 30, 2020 19:00
Show Gist options
  • Save CCColda/0a7b91a9f9aff126e6eac7fef38572a1 to your computer and use it in GitHub Desktop.
Save CCColda/0a7b91a9f9aff126e6eac7fef38572a1 to your computer and use it in GitHub Desktop.
Implementations for 10 of the 99 haskell problems
{-|
See: https://wiki.haskell.org/99_questions/1_to_10
Author: CCCOlda 2020
-}
module ListUtil where
-- || Describes a nested list structure
data NestedList a = Elem a | List [NestedList a]
-- | Inserts a list to a position in another list
insertInto :: [a] -> Int -> [a] -> [a]
insertInto base_list position insert_list
| position <= 0 = insert_list ++ base_list
| position >= (length base_list) = base_list ++ insert_list
| otherwise = (\(base_begin, base_end) ->
(base_begin ++ (insert_list ++ base_end)))
(splitAt position base_list)
-- | Gets the last element of a list
reimpl_last :: [a] -> a
reimpl_last [] = error "Can't get last element of empty array"
reimpl_last [x] = x
reimpl_last (_:x) = reimpl_last x
-- | Gets the first element of a list
reimpl_first :: [a] -> a
reimpl_first [] = error "Can't get first element of empty array"
reimpl_first [x] = x
reimpl_first (x:_) = x
-- | Gets the element before the last element from a list
reimpl_butlast :: [a] -> a
reimpl_butlast [] = error "Can't get but last element of empty array"
reimpl_butlast [_] = error "Can't get but last element of array with 1 element"
reimpl_butlast [x, _] = x
reimpl_butlast (_ : x) = reimpl_butlast x
-- | Gets the n-th element from a list. Indexing starts from 1
reimpl_nth :: [a] -> Int -> a
reimpl_nth _ x | x < 1 = error "N invalid, must be in range 1..+inf"
reimpl_nth [] _ = error "Array insufficient"
reimpl_nth [first] 1 = first
reimpl_nth (first : _) 1 = first
reimpl_nth (_ : list) n = reimpl_nth list (n-1)
-- | Gets the number of elements of a list
reimpl_length :: [a] -> Int
reimpl_length [] = 0
reimpl_length [_] = 1
reimpl_length (_:x) = (reimpl_length x) + 1
-- | Reverses a list
reimpl_reverse :: [a] -> [a]
reimpl_reverse [] = []
reimpl_reverse [x] = [x]
reimpl_reverse (a : x) = reimpl_reverse x ++ [a]
-- | Returns whether a list is a palindrome (reads the same backwards e.g. "madam")
isPalindrome :: Eq a => [a] -> Bool
isPalindrome [] = True
isPalindrome [_] = True
isPalindrome list@(begin : _) =
begin == (last list) &&
(\(_ : middle) ->
(isPalindrome middle))
(take ((length list) - 1) list)
-- | Flattens a nested list
reimpl_flatten :: NestedList a -> [a]
reimpl_flatten (Elem x) = [x]
reimpl_flatten (List []) = []
reimpl_flatten (List [x]) = reimpl_flatten x
reimpl_flatten (List (begin : rest)) = (reimpl_flatten begin) ++ (reimpl_flatten (List rest))
-- | Removes consecutive copies of elements from a list
removeConsecutiveCopies :: Eq a => [a] -> [a]
removeConsecutiveCopies [] = []
removeConsecutiveCopies [x] = [x]
removeConsecutiveCopies (begin : rest @ (second : _)) =
if begin == second then
removeConsecutiveCopies rest
else
[begin] ++ (removeConsecutiveCopies rest)
-- | Separates coonsecutive copies of elements into sublists
separateConsecutiveCopies :: Eq a => [a] -> [[a]]
separateConsecutiveCopies [] = []
separateConsecutiveCopies [x] = [[x]]
separateConsecutiveCopies (begin : rest) =
(\(firstset @ (firstelem : _) : restset) -> (
if firstelem == begin then
[[begin] ++ firstset] ++ (restset)
else
[[begin]] ++ [firstset] ++ (restset)
))
(separateConsecutiveCopies rest)
-- | Encodes a list using the run-length algorithm
runlengthEncode :: Eq a => [a] -> [(Int, a)]
runlengthEncode [] = []
runlengthEncode [x] = [(1, x)]
runlengthEncode (begin : rest) =
(\(firstset @ (firstelemcount, firstelem) : restset) -> (
if firstelem == begin then
[((firstelemcount + 1), firstelem)] ++ (restset)
else
[(1, begin), firstset] ++ (restset)
))
(runlengthEncode rest)
-- | Decodes a list using the run-length algorithm
runlengthDecode :: [(Int, a)] -> [a]
runlengthDecode [] = []
runlengthDecode [(1, element)] = [element]
runlengthDecode [(count, element)] = [element] ++ runlengthDecode [(count - 1, element)]
runlengthDecode (begin : rest) = (runlengthDecode [begin]) ++ (runlengthDecode rest)
Sign up for free to join this conversation on GitHub. Already have an account? Sign in to comment