Skip to content

Instantly share code, notes, and snippets.

@seizo3
Created October 19, 2017 16:42
Show Gist options
  • Save seizo3/9f6de206106b66e0c8d70c86095a3fd8 to your computer and use it in GitHub Desktop.
Save seizo3/9f6de206106b66e0c8d70c86095a3fd8 to your computer and use it in GitHub Desktop.
This is a set of functions/data structures I wrote while learning more about haskell and recursion, I referred back to it often mostly for syntax.
module Scratch where
import Control.Monad
import Data.Char
import Data.List (genericLength)
import Data.Maybe (fromJust)
-- creates a palindrome of a list
palindrome :: [a] -> [a]
palindrome xs = xs ++ reverse xs
-- synonym with length
len :: [a] -> Int
len [] = 0
len (_:xs) = 1 + len xs
-- calculate the mean of a list of numbers
mean :: (Real a, Fractional b) => [a] -> b
mean xs = realToFrac(sum xs) / genericLength xs
-- check if palindrome
checkPalindrome :: (Eq a) => [a] -> Bool
checkPalindrome [_] = False
checkPalindrome xs =
take (quot l 2) xs == take (quot l 2) (reverse xs)
where l = length xs
-- reverse a list of elements (synonym with reverse)
rev :: [a] -> [a]
rev [] = []
rev [x] = [x]
rev (x:xs) = rev xs ++ [x]
-- sum of odd elements
sumOdd :: [Int] -> Int
sumOdd xs = sum $ filter odd xs
-- pair elements in a list
pair :: [a] -> [(a, a)]
pair [] = []
pair [_] = []
pair (x1:x2:xs) = [(x1, x2)] ++ pair xs
-- unpair elements in a list
unpair :: [(a, a)] -> [a]
unpair [] = []
unpair (x:xs) = [fst x] ++ [snd x] ++ unpair xs
-- swap elements of a list of pairs
swapPair :: [a] -> [a]
swapPair [] = []
swapPair xs = unpair $ foldr (\x -> (++) [(snd x, fst x)]) [] (pair xs)
-- union's in c
type Vector = (Double, Double)
type Radius = Double
data Shape = Circle Vector Radius
| Poly [Vector]
-- enums
data Colors = Red
| Orange
| Blue
| Green
deriving (Eq, Show)
-- nullable type
--data Maybe a = Just a
-- | Nothing
-- aliases
type CustomerID = Int
type CardHolder = String
type CardNumber = String
type Address = [String]
-- short-hand for creating data structures
data Customer = Customer {
customerID :: CustomerID,
customerName :: String,
customerAddress :: Address
} deriving (Show)
-- instantiate value (order doesn't matter)
customer2 :: Customer
customer2 = Customer {
customerID = 19349,
customerAddress = ["test", "test"],
customerName = "bob"
}
-- another way to declare data types
data BillingInfo = CreditCard CardNumber CardHolder Address
| CashOnDelivery
| Invoice CustomerID
deriving (Show)
-- data type, ch3
data BookInfo = Book Int String [String]
deriving (Show)
-- accessor methods for BookInfo
bookID :: BookInfo -> Int
bookID (Book idx _ _) = idx
bookTitle :: BookInfo -> String
bookTitle (Book _ title _) = title
bookAuthors :: BookInfo -> [String]
bookAuthors (Book _ _ authors) = authors
-- compress string
-- aabb = a2b2
-- aaabbb = a3b3
compressString :: String -> (Int, Maybe Char) -> String
compressString [] _ = []
compressString [x1] c
| fst c > 1 && x1 == fromJust (snd c) = x1:show (fst c)
| otherwise = [x1]
compressString (x1 : (x2 : xs)) c
| x1 == x2 = compressString (x2:xs) (fst c + 1, Just x1)
| fst c >= 2 = [x1] ++ show (fst c) ++ compressString (x2:xs) (1, Nothing)
| otherwise = x1 : compressString (x2:xs) (1, Nothing)
-- multi line comments (original version of compressString)
{-
compressString (x1:x2:xs) c =
if x1 == x2
then compressString ([x2] ++ xs) (c + 1)
else if c >= 2
then [x1] ++ (show c) ++ compressString ([x2] ++ xs) 1
else [x1] ++ compressString ([x2] ++ xs) 1
-}
-- driver for recursive calls
compress :: String -> String
compress [] = []
compress xs = compressString xs (1, Nothing)
letterCount :: String -> Int
letterCount input =
length (filter isLetter input)
-- take second to last element
lastButOne :: [a] -> Maybe a
lastButOne xs =
if length xs <= 1
then Nothing
else Just (last (init xs))
{-
--very useful for reading n lines of input (uses Control.Monad)
n <- getLine
inputs <- replicateM (read n) getLine
--different ways of handling input
input <- fmap (take n . lines) getContents
mapM_ (print . unlines) . swapPair $ inputs
putStrLn $ unlines $ map swapPair inputs
msg <- getLine
putStrLn $ compress msg
input <- getContents
print input
mapM_ (putStr . show) . swapPair $ input
-}
Sign up for free to join this conversation on GitHub. Already have an account? Sign in to comment