Last active
August 29, 2015 14:24
-
-
Save nobsun/f80e78c9e0ca282117cf to your computer and use it in GitHub Desktop.
Haskellでやってみた -- あのプログラミングの5つのお題 ref: http://qiita.com/nobsun/items/0e1da260dd315c7a80ea
This file contains hidden or bidirectional Unicode text that may be interpreted or compiled differently than what appears below. To review, open the file in an editor that reveals hidden Unicode characters.
Learn more about bidirectional Unicode characters
| sumUsingFold :: Num a => [a] -> a | |
| sumUsingFold = foldr (+) 0 | |
| sumUsingFold' :: Num a => [a] -> a | |
| sumUsingFold' = foldl' (+) 0 |
This file contains hidden or bidirectional Unicode text that may be interpreted or compiled differently than what appears below. To review, open the file in an editor that reveals hidden Unicode characters.
Learn more about bidirectional Unicode characters
| for :: Num counter => | |
| (counter -- ループカウンター初期値 | |
| ,counter -> Bool -- 反復条件確認述語 | |
| ,counter -> counter) -- ループカウンター更新関数 | |
| -> ((counter, a) -> a) -- 反復1回分の計算 | |
| -> a -- 初期値 | |
| -> a -- 最終値 | |
| for (i, p, update) f x | |
| | p i = for (update i, p, update) f (f (i,x)) | |
| | otherwise = x | |
| sumUsingForLoop :: Num a => [a] -> a | |
| sumUsingForLoop xs | |
| = fst $ for (0,(< len),(+1)) | |
| (\ (_,(s,ys)) -> (s+head ys,tail ys)) | |
| (0,xs) | |
| where len = length xs |
This file contains hidden or bidirectional Unicode text that may be interpreted or compiled differently than what appears below. To review, open the file in an editor that reveals hidden Unicode characters.
Learn more about bidirectional Unicode characters
| {-# LANGUAGE BangPatterns #-} | |
| sumByRecursion :: Num a => [a] -> a | |
| sumByRecursion (x:xs) = x + sumByRecursion xs | |
| sumByRecursion [] = 0 | |
| sumByRecursion' :: Num a => [a] -> a | |
| sumByRecursion' xs | |
| = iter 0 xs | |
| where | |
| iter !s (y:ys) = iter (s+y) ys | |
| iter !s [] = s |
This file contains hidden or bidirectional Unicode text that may be interpreted or compiled differently than what appears below. To review, open the file in an editor that reveals hidden Unicode characters.
Learn more about bidirectional Unicode characters
| while :: (a -> Bool) -- 反復条件確認述語 | |
| -> (a -> a) -- 反復1回分の計算 | |
| -> a -- 初期値 | |
| -> a -- 最終値 | |
| while p f x | |
| | p x = while p f (f x) | |
| | otherwise = x | |
| sumUsingWhile :: Num a => [a] -> a | |
| sumUsingWhile xs | |
| = fst $ while (\ (_,ys) -> not $ null ys) | |
| (\ (s,zs) -> (s+head zs, tail zs)) | |
| (0,xs) |
This file contains hidden or bidirectional Unicode text that may be interpreted or compiled differently than what appears below. To review, open the file in an editor that reveals hidden Unicode characters.
Learn more about bidirectional Unicode characters
| import Data.List (unfoldr) | |
| interleave :: [a] -> [b] -> [Either a b] | |
| interleave (x:xs) (y:ys) = Left x : Right y : interleave xs ys | |
| interleave _ _ = [] | |
| interleave' :: [a] -> [b] -> [Either a b] | |
| interleave' = curry interleave'' | |
| interleave'' :: ([a],[b]) -> [Either a b] | |
| interleave'' = concat . unfoldr phi | |
| where | |
| phi (x:xs,y:ys) = Just ([Left x, Right y],(xs,ys)) | |
| phi _ = Nothing |
This file contains hidden or bidirectional Unicode text that may be interpreted or compiled differently than what appears below. To review, open the file in an editor that reveals hidden Unicode characters.
Learn more about bidirectional Unicode characters
| fibs100 :: [Integer] | |
| fibs100 = fibList 100 | |
| fibList :: Int -- 長さ | |
| -> [Integer] -- フィボナッチ数列 | |
| fibList = flip take fibs | |
| fibs,fibs' :: [Integer] | |
| fibs@(_:fibs') = 0:1:zipWith (+) fibs fibs' |
This file contains hidden or bidirectional Unicode text that may be interpreted or compiled differently than what appears below. To review, open the file in an editor that reveals hidden Unicode characters.
Learn more about bidirectional Unicode characters
| import Data.List (sortBy) | |
| maxNumeral :: [Int] -> Integer | |
| maxNumeral = read . concat . sortBy (flip cmp) . map show | |
| where | |
| x `cmp` y = (x++y) `compare` (y++x) |
This file contains hidden or bidirectional Unicode text that may be interpreted or compiled differently than what appears below. To review, open the file in an editor that reveals hidden Unicode characters.
Learn more about bidirectional Unicode characters
| import Data.List (intercalate) | |
| type Expr = [Term] | |
| type Term = [Factor] | |
| type Factor = [Digit] | |
| type Digit = Int | |
| showDigit :: Digit -> String | |
| showDigit = show | |
| showFactor :: Factor -> String | |
| showFactor = concatMap showDigit | |
| showTerm :: Term -> String | |
| showTerm = intercalate "-" . map showFactor | |
| showExpr :: Expr -> String | |
| showExpr = intercalate "+" . map showTerm | |
| valExpr :: Expr -> Int | |
| valExpr = sum . map valTerm | |
| valTerm :: Term -> Int | |
| valTerm = foldl1 (-) . map valFact | |
| valFact :: Factor -> Int | |
| valFact = foldl1 (\ n d -> 10 * n + d) | |
| expressions :: [Digit] -> [Expr] | |
| expressions = foldr extend [] | |
| extend :: Digit -> [Expr] -> [Expr] | |
| extend x [] = [[[[x]]]] | |
| extend x es = concatMap (glue x) es | |
| glue :: Digit -> Expr -> [Expr] | |
| glue x ((xs:xss):xsss) = [((x:xs):xss):xsss | |
| ,([x]:xs:xss):xsss | |
| ,[[x]]:(xs:xss):xsss | |
| ] | |
| komachi :: [String] | |
| komachi = map showExpr $ filter ((100 ==) . valExpr) (expressions [1..9]) |
Sign up for free
to join this conversation on GitHub.
Already have an account?
Sign in to comment