Skip to content

Instantly share code, notes, and snippets.

@ygrenzinger
Created December 27, 2016 20:54
Show Gist options
  • Save ygrenzinger/cede4ac879b7c4151a84c111607071cc to your computer and use it in GitHub Desktop.
Save ygrenzinger/cede4ac879b7c4151a84c111607071cc to your computer and use it in GitHub Desktop.
module E where
notThe :: String -> Maybe String
notThe "the" = Nothing
notThe w = Just w
replaceNothing :: Maybe String -> String
replaceNothing (Just w) = w
replaceNothing Nothing = "a"
replaceThe :: String -> String
replaceThe s = concatMap (replaceNothing . notThe) $ words s
countTheBeforeVowel :: String -> Integer
countTheBeforeVowel sentence = countTheBeforeVowel' (head ws) (tail ws) 0
where ws = words sentence
isVowel :: Char -> Bool
isVowel c = c `elem` "aeuio"
countTheBeforeVowel' :: String -> [String] -> Integer -> Integer
countTheBeforeVowel' _ [] acc = acc
countTheBeforeVowel' currentWord (w:ws) acc = if (currentWord == "the") && isVowel (head w)
then countTheBeforeVowel' w ws (acc+1)
else countTheBeforeVowel' w ws acc
countVowels :: String -> Integer
countVowels s = toInteger . length $ filter isVowel s
data Nat = Zero | Succ Nat deriving (Eq, Show)
natToInteger :: Nat -> Integer
natToInteger Zero = 0
natToInteger (Succ n) = 1 + natToInteger n
integerToNat :: Integer -> Maybe Nat
integerToNat 0 = Just Zero
integerToNat n = if n < 0 then Nothing else fmap Succ (integerToNat (n-1))
isJust :: Maybe a -> Bool
isJust Nothing = False
isJust _ = True
isNothing :: Maybe a -> Bool
isNothing = fmap not isJust
mayybee :: b -> (a -> b) -> Maybe a -> b
mayybee defaultVal _ Nothing = defaultVal
mayybee _ f (Just a) = f a
fromMaybe :: a -> Maybe a -> a
fromMaybe defaultVal Nothing = defaultVal
fromMaybe _ (Just a) = a
listToMaybe :: [a] -> Maybe a
listToMaybe [] = Nothing
listToMaybe (x:_) = Just x
maybeToList :: Maybe a -> [a]
maybeToList Nothing = []
maybeToList (Just a) = [a]
catMaybes :: [Maybe a] -> [a]
catMaybes = concatMap maybeToList
flipMaybe :: [Maybe a] -> Maybe [a]
flipMaybe xs = if any isNothing xs then Nothing
else Just (catMaybes xs)
left :: Either a b -> Maybe a
left (Left a) = Just a
left _ = Nothing
right :: Either a b -> Maybe b
right (Right b) = Just b
right _ = Nothing
lefts' :: [Either a b] -> [a]
lefts' = catMaybes . map left
rights' :: [Either a b] -> [b]
rights'= catMaybes . map right
partitionEithers' :: [Either a b] -> ([a], [b])
partitionEithers' xs = (lefts' xs,rights' xs)
eitherMaybe' :: (b -> c) -> Either a b -> Maybe c
eitherMaybe' f (Right b) = Just (f b)
eitherMaybe' _ _ = Nothing
either' :: (a -> c) -> (b -> c) -> Either a b -> c
either' fa _ (Left a) = fa a
either' _ fb (Right b) = fb b
eitherMaybe'' :: (b -> c) -> Either a b -> Maybe c
eitherMaybe'' f = either' (const Nothing) (Just . f)
myIterate :: (a -> a) -> a -> [a]
myIterate f d = d : myIterate f (f d)
--take 10 $ unfoldr (\b -> Just (b, b+1)) 0
myUnfoldr :: (b -> Maybe (a, b)) -> b -> [a]
myUnfoldr f d = case f d of
Nothing -> []
Just (a, b) -> a : myUnfoldr f b
betterIterate :: (a -> a) -> a -> [a]
betterIterate f = myUnfoldr (\b -> Just (b, f b))
data BinaryTree a = Leaf | Node (BinaryTree a) a (BinaryTree a)
deriving (Eq, Ord, Show)
unfold :: (a -> Maybe (a,b,a)) -> a -> BinaryTree b
unfold f n = case f n of
Nothing -> Leaf
Just (a, b, c) -> Node (unfold f a) b (unfold f c)
treeBuild :: Integer -> BinaryTree Integer
treeBuild = unfold (\a -> if a == 0 then Nothing else Just (a-1, a-1, a-1))
Sign up for free to join this conversation on GitHub. Already have an account? Sign in to comment