|
| 1 | +module Main where |
| 2 | + |
| 3 | +elm :: (Eq a) => a -> [a] -> Bool |
| 4 | +elm _ [] = False |
| 5 | +elm a (x:xs) = (a == x) || (elm a xs) |
| 6 | + |
| 7 | +nub :: (Eq a) => [a] -> [a] |
| 8 | + |
| 9 | +nub [] = [] |
| 10 | +nub (x:xs) |
| 11 | + | elm x xs = nub xs |
| 12 | + | otherwise = (x : nub xs) |
| 13 | + |
| 14 | +isAsc :: [Int] -> Bool |
| 15 | +isAsc [] = True |
| 16 | +isAsc [x] = True |
| 17 | +isAsc (x:y:xs) = (x <= y) && isAsc(y:xs) |
| 18 | + |
| 19 | +hasPath :: [(Int, Int)] -> Int -> Int -> Bool |
| 20 | +hasPath xs x y |
| 21 | + | (x == y ) = True |
| 22 | + | otherwise = or [hasPath xs' n y | (m, n) <- xs, m == x] |
| 23 | + where |
| 24 | + xs' = [(m, n) | (m, n) <- xs, m /= x] |
| 25 | + |
| 26 | +rev :: [a] ->[a] |
| 27 | +rev xs = rev' xs [] |
| 28 | + where |
| 29 | + rev' [] ys = ys |
| 30 | + rev' (x:xs') ys = rev' xs' (x:ys) |
| 31 | + |
| 32 | +-- Reverse using fold |
| 33 | +revf :: [a] ->[a] |
| 34 | +revf xs = foldl (\acc x -> x:acc) [] xs |
| 35 | + |
| 36 | +-- Reverse using fold with flip |
| 37 | +revff :: [a] ->[a] |
| 38 | +revff = foldl (flip (:)) [] |
| 39 | + |
| 40 | +prefixes :: [a] -> [[a]] |
| 41 | +prefixes l = rev $ map rev $ foldl customAdd [] l |
| 42 | + where |
| 43 | + customAdd [] y = [[y]] |
| 44 | + customAdd (x:xs) y = ((y:x):(x:xs)) |
| 45 | + |
| 46 | +prefixes2 :: [a] -> [[a]] |
| 47 | +prefixes2 = foldr (\x acc -> [x] : map (x:) acc) [] |
| 48 | + |
| 49 | +lagrange :: [(Float, Float)] -> Float -> Float |
| 50 | +lagrange xs a = foldl (\acc (x, y) -> acc + (y * (lbp x))) 0 xs |
| 51 | + where lbp x' = foldl (\acc (x, _) -> acc * (a - x) / (x' - x) ) 1 [(x,y) | (x,y) <- xs, x /= x'] |
| 52 | + |
| 53 | +data Trie a = Leaf a | Node a [Trie a] |
| 54 | +foldtrie :: (b -> a -> b) -> b -> Trie a -> b |
| 55 | +foldtrie f acc (Leaf a) = f acc a |
| 56 | +foldtrie f acc (Node a as) = foldl (foldtrie f) (f acc a) as |
| 57 | + |
| 58 | +main = do |
| 59 | + print (elm 2 [1, 3, 2]) |
| 60 | + print (nub [2, 1, 2, 3, 1, 4]) |
| 61 | + print (isAsc [1, 2, 3]) |
| 62 | + print (isAsc [1, 2, 3, 1]) |
| 63 | + print (hasPath [(1, 2), (2, 3), (3, 4)] 1 4) |
| 64 | + print (hasPath [(1, 2), (2, 3), (3, 4)] 3 1) |
| 65 | + print (hasPath [(1, 2), (2, 3), (3, 4)] 2 4) |
| 66 | + print (rev [1, 2, 3]) |
| 67 | + print (revf [1, 2, 3]) |
| 68 | + print (revff [1, 2, 3]) |
| 69 | + print $ prefixes [1, 2, 3] |
| 70 | + print $ prefixes2 [1, 2, 3] |
| 71 | + print $ lagrange [(1, 1), (2, 8), (3, 27), (4, 64)] 6 |
| 72 | + print $ foldtrie (flip (:)) [] (Node 'c' [(Node 'a' [Leaf 'r', Leaf 't']),(Node 'o' [Node 'o' [Leaf 'l']])]) |
| 73 | + |
0 commit comments