Skip to content

Instantly share code, notes, and snippets.

@Redchards
Last active September 1, 2015 02:12
Show Gist options
  • Save Redchards/12d3b5602f80854632ed to your computer and use it in GitHub Desktop.
Save Redchards/12d3b5602f80854632ed to your computer and use it in GitHub Desktop.
Learning haskell with http://learnyouahaskell.com. Keeping it for posterity. Nothing very interesting.
module Test where
-- NOTE : I just write every type as training purpose
-- List used for testing purpose
-- Main testing list
mahList :: [Integer]
mahList = [1, 2, 3, 4, 65, 8779 , 11, 64, 15 , 48]
-- List used for rmDup, asit contains a lot of duplicates
mahList2 :: [Integer]
mahList2 = [1, 1, 1, 2, 2, 5, 6, 7, 5, 4, 1, 2, 6, 8, 7, 9, 8, 4, 5, 6]
-- List factorials along with the corresponding number n
factori :: (Num a) => Int -> [(Int, a)]
factori num = zip [1..num] [product (take x (iterate (+1) 1)) | x <- [1..num] ]
-- Returns factorial of num
factorial :: (Num a) => Int -> a
factorial num = product (take num (iterate (+1) 1))
-- Dumb function to learn how to use filters
lucky :: (Integral a) => a -> String
lucky 7 = "Lucky number out there !"
lucky _ = "No lyck, sry :/"
-- let bar x y | x == 0 = 0 | y == 0 = 0 | otherwise = x * y in GHCI
-- Add two vectors together
-- Similare to the 'head' function
addVector2 :: (Num a) => (a, a) -> (a, a) -> (a, a)
addVector2 (x1, y1) (x2, y2) = (x1 + x2, y1 + y2)
-- Returns the first value of a list
frst :: [a] -> a
frst [] = error "Empty list is invalid"
frst (he:_) = he
-- Returns the last value of a list
-- Similare to the 'last' function
lst :: [a] -> a
lst [] = error "Empty list is invalid"
lst [la] = la
lst (_:ta) = lst ta
-- Returns the whole list but the last element
-- Similar to the 'init' function
inti :: [a] -> [a]
inti [] = error "Empty list is invalid"
inti [_] = []
inti (he:ta) = he:inti ta
-- Returns the length of the list.
-- Similare to the 'length' function
-- Simple recursive version
listLen :: (Num b) => [a] -> b
listLen [] = 0
listLen (_:la) = 1 + listLen la
-- Tail recursive version
listLenTerm :: (Num b) => [a] -> b
listLenTerm list = listLenAux list 0
-- Auxilliary function for tail recursion
listLenAux :: (Num b) => [a] -> b -> b
listLenAux (_:ta) aux = listLenAux ta (aux + 1)
listLenAux [] aux = aux
-- Returns the sum of elements in the list
-- Similare to the 'sum' function
-- Simple recursive version
sm :: (Num a) => [a] -> a
sm [] = error "Empty list is invalid"
sm [la] = la
sm (he:ta) = he + sm ta
-- Tail recursive version
smTerm :: (Num a) => [a] -> a
smTerm [] = error "Empty list is invalid"
smTerm list = smAux list 0
-- Auxilliary function for tail recursion
smAux :: (Num a) => [a] -> a -> a
smAux (he:ta) acc = smAux ta (acc + he)
smAux [] acc = acc
-- Yet another version of the sum function
smTerm2 :: (Num a) => [a] -> a
smTerm2 [] = error "Empty list is not valid"
smTerm2 list = foldl (+) 0 list
-- Returns the product of the elements in the list
-- Similar to the 'product' function
prod :: (Num a) => [a] -> a
prod [] = error "Empty list is not valid"
prod [l] = l
prod (h:t) = h * prod t
-- Concatenate each string contained in a list of string, and separate them with space
sentencize :: [String] -> String
sentencize [] = error "Empty list is not valid"
sentencize [la] = la
sentencize (he:ta) = he ++ " " ++ sentencize ta
-- Returns the whole list, but the first element
-- Similar to the 'tail' function
tail' :: [a] -> [a]
tail' [] = error "Empty list is not valid"
tail' [_] = []
tail' (_:t) = t
-- Returns 'True' if the list is empty, 'False' otherwise
-- Similar to the 'null' function
null' :: [a] -> Bool
null' [] = True
null' (_) = False
-- Returns the element at given index
-- Similar to the '!!' function
get :: (Integral a) => a -> [b] -> b
get _ [] = error "Index out of range"
get 0 (h:_) = h
get index (_:t) = get (index - 1) t
-- Returns a given number of elements from a list
-- Similar to the 'take' function
tak :: (Integral a) => a -> [b] -> [b]
tak _ [] = []
tak 1 (h:_) = [h]
tak index (h:t) = h:tak (index - 1) t
-- Same thing here, with yet another presentation
tak' :: (Integral a) => a -> [b] -> [b]
tak' n _
| n <= 0 = []
tak' _ [] = []
tak' n (h : t) = h : tak' (n-1) t
-- Tail recursive version
takTerm :: (Integral b) => b -> [a] -> [a]
takTerm index list = takAux index list []
-- Auxilliary function for tail recursion
takAux :: (Integral b) => b -> [a] -> [a] -> [a]
takAux _ [] _ = []
takAux 0 _ acc = acc
takAux index (h:t) acc = takAux (index - 1) t (acc ++ [h])
-- Returns the given list but the nth last ones
-- Similar to the 'drop' function
drop' :: (Integral b) => b -> [a] -> [a]
drop' _ [] = []
drop' 1 (_:t) = t
drop' index (_:t) = drop' (index - 1) t
-- Returns 'True' if the given element is in the list, 'False' otherwise
-- Similar to the 'elem' function
elefi :: (Eq a) => a -> [a] -> Bool
elefi _ [] = False
elefi el (h:t) = (el == h) || elefi el t
-- Another version
elefi' :: (Eq a) => a -> [a] -> Bool
elefi' _ [] = False
elefi' el (h:t)
| el == h = True
| otherwise = elefi' el t
-- Returns the minimal element contained in the list
-- Similar to the 'minimum' function
min' :: (Ord a) => [a] -> a
min' [] = error "Empty list is invalid"
min' [h1] = h1
min' (h1:h2:t)
| h1 < h2 = min' (h1:t)
| otherwise = min' (h2:t)
-- Another version
min2 :: (Ord a) => [a] -> a
min2 [] = error "Empty list is invalid"
min2 [l] = l
min2 (h:t)
| h < mini = h
| otherwise = mini
where mini = min2 t
-- Yet another version
min3 :: (Ord a) => [a] -> a
min3 [] = error "Empty list is invalid"
min3 [l] = l
min3 (h:t) = min h (min3 t)
-- Returns the maximal element contained in the list
-- Similar to the 'maximum' function
max' :: (Ord a) => [a] -> a
max' [] = error "Empty list is invalid"
max' [h1] = h1
max' (h1:h2:t)
| h1 > h2 = max' (h1:t)
| otherwise = max' (h2:t)
-- Another version
max2 :: (Ord a) => [a] -> a
max2 [] = error "Empty list is invalid"
max2 [l] = l
max2 (h:t)
| h > maxi = h
| otherwise = maxi
where maxi = max2 t
-- Yet another version
max3 :: (Ord a) => [a] -> a
max3 [] = error "Empty list is invalid"
max3 [l] = l
max3 (h:t) = max h (max3 t)
-- min
-- max
-- Offensive function that will compute your bmi, and then mock you !
bmiTell :: (RealFloat a) => a -> a -> String
bmiTell height weight
| bmi <= 15.0 = "You're soooo skinny, my dear !"
| bmi <= 25.0 = "Yep, supposedly perfect. No, just kidding"
| bmi <= 30.0 = "Fatass !! Leul"
| otherwise = "Don't break the floor !!!"
where bmi = h / w ** 2.0
h = height
w = weight
-- Simple function, really, no description required
-- Just wrote it to understand pattern (the sen@(h:_) part)
frstAndAll :: String -> String
frstAndAll [] = "Empty string is invalid"
frstAndAll sen@(h:_) = "The first letter of '" ++ sen ++ "' is '" ++ [h] ++ "'"
-- Similar to the 'compare' function
cmp :: (Ord a) => a -> a -> Ordering
cmp x y
| x > y = GT
| x == y = EQ
| otherwise = LT
-- Return the initials of the given firstname and lastname
tiatial :: String -> String -> String
tiatial firstname lastname = [f1] ++ "." ++ [f2]
where (f1 : _) = firstname
(f2 : _) = lastname
-- Same as above
tialtial2 :: String -> String -> String
tialtial2 [] _ = error "Empty string is invalid"
tialtial2 _ [] = error "Empty string is invalid"
tialtial2 (f1:_) (f2:_) = [f1] ++ "." ++ [f2]
-- Reverse list with O(n²) time complexity
revOn2 :: [a] -> [a]
revOn2 [] = []
revOn2 (h:t) = revOn2 t ++ [h]
-- Reverse list with O(n) time complexity (linear)
-- Using tail recursion
revOn :: [a] -> [a]
revOn list = revAux list []
-- Auxilliary function for tail recursion
revAux :: [a] -> [a] -> [a]
revAux [] aux = aux
revAux (h:t) aux = revAux t (h:aux)
-- Linear time complexity version, using the "foldl" function
oRevOn :: [a] -> [a]
oRevOn = foldl (flip (:)) []
-- Flip the two given arguments
-- Similar to the 'flip' function
flipper :: (a -> b -> c) -> b -> a -> c
flipper fun x y = fun y x
-- Similar to the other 'oRevOn' function, but using my home-made flip function
-- #wow
o2RevOn :: [a] -> [a]
o2RevOn = foldl (flipper (:)) []
-- Remove duplicates inside a list
rmDup :: (Eq a) => [a] -> [a]
rmDup [] = error "Empty list is invalid"
rmDup list = rmDupAux list []
-- Auxilliary for tail recursion
rmDupAux :: (Eq a) => [a] -> [a] -> [a]
rmDupAux [] aux = aux
rmDupAux (h:t) aux
| h `notElem` aux = rmDupAux t (aux ++ [h])
| otherwise = rmDupAux t aux
-- Compute the surface of a cylinder, using the "let ... in" expression type
cylinderSurface :: (RealFloat a) => a -> a -> a
cylinderSurface r h = let sideArea = 2 * pi * r * h
topArea = pi * r ** 2
in sideArea + 2 * topArea
-- Just to train with case expressions, no advantages to do this
-- Similar to the 'cycle' function
cyclic :: [a] -> [a]
cyclic list = case list of [] -> error "Empty list is invalid";
_ -> list ++ cyclic list
-- Similar to the 'repeat' function
repee :: a -> [a]
repee num = num:repee num
-- repeat
-- Just replicate the list n times
-- Like cycle, but finite
replicaList :: (Integral b) => [a] -> b -> [a]
replicaList [] _ = error "Empty list is invalid"
replicaList list 1 = list
replicaList list n = list ++ replicaList list (n - 1)
-- Create a list that contains n times the given number
-- Does not handle negative index ...
replicaNum :: (Num a, Integral b) => a -> b -> [a]
replicaNum num 1 = [num]
replicaNum num n = num:replicaNum num (n-1)
-- This version handle negative index gracefully
replicate' :: (Integral a) => a -> b -> [b]
replicate' n num
| n <= 0 = []
| otherwise = num:replicate' (n-1) num
-- Split a list in two at the given index, returnning a tuple containing to lists
-- If the index is too large, the second list will be empty, and the first on will
-- be the whole initial list
-- This is exactly the invert of the case when the index is 0
-- Similar to the 'splitAt' function
splitAt' :: (Integral a) => a -> [b] -> ([b], [b])
splitAt' _ [] = error "Index out of bound"
splitAt' n list = splitAtAux ([], list) n
-- Auxilliary function for tail recursion
splitAtAux :: (Integral b) => ([a], [a]) -> b -> ([a], [a])
splitAtAux (acc, []) _ = (acc, [])
splitAtAux couple 0 = couple
splitAtAux (acc, (h:t)) n = splitAtAux ((acc ++ [h]), t) (n - 1)
-- Similar the the "zip" function
zippo :: [a] -> [b] -> [(a, b)]
zippo [] _ = []
zippo _ [] = []
zippo (h1:t1) (h2:t2) = (h1, h2):zippo t1 t2
-- Not in place quicksort using lomuto partition
quicky :: (Ord a) => [a] -> [a]
quicky [] = []
quicky (pivot:t) = let low = quicky [ x | x <- t, x < pivot ]
high = quicky [ x | x <- t, x >= pivot ]
in low ++ [pivot] ++ high
module Main where
import Data.List
-- List used for testing purpose
-- Main testing list
mahList :: [Integer]
mahList = [1, 2, 3, 4, 65, 8779 , 11, 64, 15 , 48]
-- List used for rmDup, asit contains a lot of duplicates
mahList2 :: [Integer]
mahList2 = [1, 1, 1, 2, 2, 5, 6, 7, 5, 4, 1, 2, 6, 8, 7, 9, 8, 4, 5, 6]
-- Partial function, yay !
divideByTen :: (Floating a) => a -> a
divideByTen = (/10)
-- Check if the argument is alphanumeric
isAlphanum :: Char -> Bool
isAlphanum = (`elem` (['A' .. 'Z'] ++ ['a' .. 'z']))
-- Apply the same function twice to the argument
-- Simple enough
applyTwice :: (a -> a) -> a -> a
applyTwice f x = f (f x)
zipWith' :: (a -> b -> c) -> [a] -> [b] -> [c]
zipWith' _ [] _ = []
zipWith' _ _ [] = []
zipWith' f (h1:t1) (h2:t2) = f h1 h2 : zipWith' f t1 t2
-- Similar to the 'flip' function
flip' :: (a -> b -> c) -> b -> a -> c
flip' f = g
where g x y = f y x
-- Simpler version
flip2' :: (a -> b -> c) -> b -> a -> c
flip2' f x y = f y x
-- Apply a function to each element of a list
-- Similar to the 'map' function
map' :: (a -> b) -> [a] -> [b]
map' _ [] = []
map' f (h:t) = f h : map' f t
-- Version using list comprehension
mapComp :: (a -> b) -> [a] -> [b]
mapComp f list = [ f x | x <- list ]
filter' :: (a -> Bool) -> [a] -> [a]
filter' _ [] = []
filter' p (h:t)
| p h = h : filter' p t
| otherwise = filter' p t
filterComp :: (a -> Bool) -> [a] -> [a]
filterComp p list = [ x | x <- list, p x]
quicky2 :: (Ord a) => [a] -> [a]
quicky2 [] = []
quicky2 (h:t) = let low = quicky2 (filter (<h) t)
high = quicky2 (filter (>=h) t)
in low ++ [h] ++ high
divisibleBy3829 :: (Integral a) => a
divisibleBy3829 = head (filter p [100000, 99999..])
where p x = x `mod` 3829 == 0
sumOddUnder10k :: (Integral a) => a
sumOddUnder10k = sum (filter p [10000, 9999..0])
where p x = x `mod` 3 == 0
sumOddSquareUnder10k :: (Integral a) => a
sumOddSquareUnder10k = sum (filter p [ x*x | x <- [1000, 999..0]])
where p x = x `mod` 3 == 0
sumOddSquareUnder10k' :: (Integral a) => a
sumOddSquareUnder10k' = sum (takeWhile (<10000) (filter odd (map (^(2 :: Integer)) [1..])))
chain :: (Integral a) => a -> [a]
chain 1 = [1]
chain n
| even n = n : chain (n `div` 2)
| otherwise = n : chain (n*3+1)
-- Three different ways to do it
-- On with a 'where' clause
chainLen15 :: Int -> Int
chainLen15 n
| n <= 0 = error "Number must be higher than 1"
| otherwise = length (filter de (map chain ([1..n] :: [Int])))
where de x = length x > 15
-- One other with a lambda
chainLen15' :: Int -> Int
chainLen15' n
| n <= 0 = error "Number must be higher than 1"
| otherwise = length (filter (\xs -> length xs > 15) (map chain ([1..n] :: [Int])))
-- And finally with a let...in expression
chainLen15'' :: Int -> Int
chainLen15'' n
| n <= 0 = error "Number must be higher than 1"
| otherwise = let p x = length x > 15 in length (filter p (map chain ([1..n] :: [Int])))
sum' :: (Num a) => [a] -> a
sum' = foldl (+) 0
elem' :: (Eq a) => a -> [a] -> Bool
elem' y = foldl (\acc x -> acc || x == y) False
sqrtOver1000Steps :: Int
sqrtOver1000Steps = length (takeWhile (<=1000) (scanl1 (+) (map sqrt ([1..] :: [Double])))) + 1
-- Using 'pointless' notation
fn :: (RealFloat a, Ord a, Integral b) => a -> b
fn x = ceiling (negate (tan (cos (max 50 x))))
-- Using point free notation
fn' :: (RealFloat a, Ord a, Integral b) => a -> b
fn' = ceiling . negate . tan . cos . max 50
uniquesIn :: (Eq a) => [a] -> Int
uniquesIn = length . nub
main :: IO()
main = print "Yhea, exectuable !"
--sqrtOver1000Steps' :: Int
--sqrtOver1000Steps' = last (filter (<=1000) (scanl1 sqrt ([1..])))
module Test where
import Data.List
mahList :: [String]
mahList = ["Hello", "Guys", "Moi"]
mahList2 :: [Integer]
mahList2 = [1, 1, 1, 2, 2, 5, 6, 7, 5, 4, 1, 2, 6, 8, 7, 9, 8, 4, 5, 6]
intersperse' :: a -> [a] -> [a]
intersperse' _ [] = []
intersperse' _ [l] = [l]
intersperse' c (h:t) = h : c : intersperse' c t
intersperse'' :: a -> [a] -> [a]
intersperse'' c = tail . foldr (\x acc -> c : x : acc) []
intercalate' :: [a] -> [[a]] -> [a]
intercalate' _ [] = []
intercalate' _ [l] = l
intercalate' c (h:t) = h ++ c ++ intercalate' c t
intercalate'' :: [a] -> [[a]] -> [a]
intercalate'' _ [] = []
intercalate'' c (h:t) = h ++ foldl (\acc x -> acc ++ c ++ x) [] t
tail' :: [a] -> [a]
tail' [] = []
tail' (_:t) = t
-- Only support lists of the same size !
-- I'll take a look in the standard library to see how they deal with different kind of lists
-- (certainly by cutting them when they detect an empty list)
transpose' :: [[a]] -> [[a]]
transpose' [] = []
transpose' [[], _] = []
transpose' mat = map head mat : transpose' (map tail' mat)
concat' :: [[a]] -> [a]
concat' = foldl1' (++)
concatMap' :: ([a] -> [b]) -> [[a]] -> [b]
concatMap' f = foldl' (\acc x -> acc ++ f x) []
and' :: [Bool] -> Bool
and' = foldl1' (&&)
and'' :: [Bool] -> Bool
and'' [] = True
and'' (h:t) = h && and'' t
or' :: [Bool] -> Bool
or' = foldl1' (||)
or'' :: [Bool] -> Bool
or'' [] = False
or'' (h:t) = h || or'' t
any' :: (a -> Bool) -> [a] -> Bool
any' p = or . map p
any'' :: (a -> Bool) -> [a] -> Bool
any'' p = foldr (\x acc -> acc || p x) False
all' :: (a -> Bool) -> [a] -> Bool
all' p = and . map p
all'' :: (a -> Bool) -> [a] -> Bool
all'' p = foldr (\x acc -> acc && p x) True
iterate' :: (a -> a) -> a -> [a]
iterate' f x = x : iterate' f (f x)
takeWhile' :: (a -> Bool) -> [a] -> [a]
takeWhile' _ [] = []
takeWhile' p (h:t)
| p h = h : rec t
| otherwise = []
where rec = takeWhile' p
dropWhile' :: (a -> Bool) -> [a] -> [a]
dropWhile' _ [] = []
dropWhile' p list@(h:t)
| p h = dropWhile' p t
| otherwise = list
span' :: (a -> Bool) -> [a] -> ([a], [a])
span' p list = (takeWhile p list, dropWhile p list)
break' :: (a -> Bool) -> [a] -> ([a], [a])
break' p = span $ not. p
group' :: (Eq a) => [a] -> [[a]]
group' [] = []
group' list@(h:_) = let du = span (==h) list in fst du: group' (snd du)
numInstance :: (Ord a) => [a] -> [(Int, a)]
numInstance = map (\list@(h:_) -> (length list, h)) . group . sort
--search' :: (Eq a) => [a] -> [a] -> Bool
--search' sublist list = let len = length sublist
-- in foldr (\acc x -> if take len x == sublist then True else acc) False $ tails sublist
g++ -Os -c main.cxx -o main.o
ar rvs libtest.a main.o
ghc -o ffi interopTest.hs -L. -lstdc++ -ltest.a
#include "test.hxx"
#include <iostream>
extern "C" void test()
{
std::cout << "Hello from a lib" << std::endl;
}
Sign up for free to join this conversation on GitHub. Already have an account? Sign in to comment