Last active
August 29, 2015 14:22
-
-
Save khajavi/1cb217edeb131719bc60 to your computer and use it in GitHub Desktop.
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 ViewPatterns #-} | |
| > import qualified Data.Set as Set | |
| > import qualified Data.Map as Map | |
| > import qualified Data.Sequence ((><), (<|), (|>), fromList, length) | |
| > data List a = Empty | Cons a (List a) deriving Show | |
| > l1 = Cons 1 (Cons 2 (Empty)) | |
| Function Application | |
| ==================== | |
| > l2 = Cons 3 $ Empty | |
| > main = do | |
| > print l1 | |
| > print l2 | |
| تابعی که اولین عضو لیست را آپدیت میکند: | |
| > updateFirst :: List a -> a -> List a | |
| > updateFirst Empty y = Empty | |
| > updateFirst (Cons x xs) y = Cons y xs | |
| > update = updateFirst l1 5 | |
| Set | |
| === | |
| * Unordered Collection | |
| > set = Set.fromList "abcde" | |
| > mainset = print $ Set.size set | |
| Map | |
| === | |
| > lang = Map.fromList [(1, "Lisp"), (2, "Haskell")] | |
| > mainmap = do | |
| > print lang | |
| > print $ Map.lookup 1 lang | |
| > print $ Map.lookup 3 lang | |
| Seq | |
| === | |
| > myseq = Data.Sequence.fromList "This is a sequence of characters" | |
| add element to front of Seq | |
| > left = Data.Sequence.fromList "This is a sequence" | |
| > right = Data.Sequence.fromList " of characters" | |
| > lr = left Data.Sequence.>< right | |
| > mainseq = do | |
| > print myseq | |
| > print $ Data.Sequence.length myseq | |
| Input | |
| ===== | |
| The symbol <- pronounced "drawn from" | |
| > maininput = do | |
| > input <- getLine | |
| > putStrLn ("you wrote: " ++ input) | |
| Enumeration Types | |
| ================= | |
| > data Thing = Shoe | |
| > | Ship | |
| > | SealingWax | |
| > | Cabbage | |
| > | King | |
| > deriving Show | |
| میتوان نوع لیست را مشخص کرد | |
| > listofthings :: [Thing] | |
| > listofthings = [Shoe, SealingWax, King] | |
| اگر نوع لیست را مشخص نکنیم خود هسکل نوع آن را تشخیص میدهد. | |
| > myList = [Shoe] | |
| Pattern Matching | |
| ================ | |
| > isSmall :: Thing -> Bool | |
| > isSmall Shoe = True | |
| > isSmall Ship = False | |
| > isSmall King = False | |
| > isSmall _ = False | |
| Beyond enumeration | |
| ================== | |
| به فیلیر و اوکی، دیتا کانستراکتور گویند. | |
| > data FailableDouble = Failure | |
| > | OK Double | |
| > deriving Show | |
| > ex01 = Failure | |
| > ex02 = OK 3.4 | |
| > safeDiv :: Double -> Double -> FailableDouble | |
| > safeDiv _ 0 = Failure | |
| > safeDiv x y = OK (x / y) | |
| > failureToZero :: FailableDouble -> Double | |
| > failureToZero Failure = 0 | |
| > failureToZero (OK d) = d | |
| دیتا کانستراکتورها میتوانند چندین آرگومان بگیرند: | |
| Store a person's name, age, and favourite Things. | |
| > data Person = Person String Int Thing | |
| > deriving Show | |
| > ahmad :: Person | |
| > ahmad = Person "Ahmad" 26 King | |
| > saeed :: Person | |
| > saeed = Person "Saeed" 34 Cabbage | |
| > getAge :: Person -> Int | |
| underscore (_): wildcard patterns | |
| > getAge (Person _ a _) = a | |
| Algebric data types in general | |
| ============================== | |
| data AlgDataType = Constr1 Type11 Type12 | |
| | Constr2 Type21 | |
| | Constr3 Type31 Type32 Type33 | |
| | Constr4 | |
| Case Expressions | |
| ================ | |
| > failureToZero' :: FailableDouble -> Double | |
| > failureToZero' x = case x of | |
| > Failure -> 0 | |
| > OK d -> d | |
| Recursive Data Types | |
| ==================== | |
| > data IntList = Empty' | Cons' Int IntList | |
| > intListProd :: IntList -> Int | |
| > intListProd Empty' = 1 | |
| > intListProd (Cons' x intlist) = x * intListProd intlist | |
| > data Tree = Node Tree Int Tree | Leaf Char | |
| > deriving Show | |
| > tree :: Tree | |
| > tree = Node (Leaf 'x') 1 (Node (Leaf 'y') 2 (Leaf 'z')) | |
| > absAll :: IntList -> IntList | |
| > absAll Empty' = Empty' | |
| > absAll (Cons' x xs) = Cons' (abs x) (absAll xs) | |
| > squareAll :: IntList -> IntList | |
| > squareAll Empty' = Empty' | |
| > squareAll (Cons' x xs) = Cons' (x*x) (squareAll xs) | |
| Filter on IntList | |
| ================= | |
| > keepOnlyEven :: IntList -> IntList | |
| > keepOnlyEven Empty' = Empty' | |
| > keepOnlyEven (Cons' x xs) | |
| > | even x = Cons' x (keepOnlyEven xs) | |
| > | otherwise = keepOnlyEven xs | |
| Polymorphic Data Types | |
| ====================== | |
| t -> is a type variables | |
| > data List' t = E | C t (List' t) | |
| > deriving Show | |
| > lst1 :: List' Int | |
| > lst1 = C 4 (C 3 (C 2 (C 1 (E)))) | |
| > lst2 :: List' Char | |
| > lst2 = C 'x' $ C 'y' $ C 'z' E | |
| > lst3 :: List' Bool | |
| > lst3 = C True $ C False E | |
| Polymorphic functions | |
| ===================== | |
| > filterList :: (t -> Bool) -> List' t -> List' t | |
| > filterList _ E = E | |
| > filterList p (C x xs) | |
| > | p x = C x $ filterList p xs | |
| > | otherwise = filterList p xs | |
| > isEven' :: Integral a => a -> Bool | |
| > isEven' t = t `rem` 2 == 0 | |
| > lst4 = filterList isEven' lst1 | |
| > mapList _ E = E | |
| > mapList f (C x xs) = C (f x) $ mapList f xs | |
| > addOne :: Num a => a -> a | |
| > addOne x = x + 1 | |
| > addedList = mapList addOne lst1 | |
| The Prelude | |
| =========== | |
| partial function | |
| ================ | |
| * there are certain inputs for which function will crash. | |
| * Functions which have certain inputs that will make them recurse infinitely are also called partial. | |
| * It is good Haskell practice to avoid partial functions as much as possible. | |
| Total Function | |
| ============== | |
| * Functions which are well-defined on all possible inputs are known as total functions. | |
| Anonymous functions | |
| =================== | |
| > greaterThan100 :: [Integer] -> [Integer] | |
| > greaterThan100 xs = filter (\x -> x > 100) xs | |
| > greaterThan100' xs = filter (>100) xs | |
| > gt100 x = x > 100 | |
| > gt100' = \x -> x > 100 | |
| > gt100'' = (>100) | |
| Function Composition | |
| ==================== | |
| > dot :: (b -> c) -> (a -> b) -> (a -> c) | |
| > dot f g = \x -> f (g x) | |
| dot function is a `function composition` | |
| > myTest xs = even (length (greaterThan100 xs)) | |
| we can rewrite this as: | |
| > myTest' = even . length . greaterThan100 | |
| > producBy10 xs = map (*10) 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
| format: markdown+lhs | |
| gist-id: 1cb217edeb131719bc60 | |
| ------ | |
| > import Data.Char | |
| توابع بازگشتی | |
| ==== | |
| > fib :: Integer -> Integer | |
| > fib n | |
| > | n == 0 = 0 | |
| > | n == 1 = 1 | |
| > | n > 1 = fib (n-1) + fib (n-2) | |
| interact | |
| ======== | |
| > main :: IO () | |
| > main = interact ( map toUpper ) |
Sign up for free
to join this conversation on GitHub.
Already have an account?
Sign in to comment