1 / 31

Grab Bag of Interesting Stuff

Grab Bag of Interesting Stuff. Topics. Higher kinded types Files and handles IOError Arrays. Higher Order types. Type constructors are higher order since they take types as input and return types as output.

karis
Télécharger la présentation

Grab Bag of Interesting Stuff

An Image/Link below is provided (as is) to download presentation Download Policy: Content on the Website is provided to you AS IS for your information and personal use and may not be sold / licensed / shared on other websites without getting consent from its author. Content is provided to you AS IS for your information and personal use only. Download presentation by click this link. While downloading, if for some reason you are not able to download a presentation, the publisher may have deleted the file from their server. During download, if you can't get a presentation, the file might be deleted by the publisher.

E N D

Presentation Transcript


  1. Grab Bag of Interesting Stuff

  2. Topics • Higher kinded types • Files and handles • IOError • Arrays

  3. Higher Order types • Type constructors are higher order since they take types as input and return types as output. • Some type constructors (and also some class definitions) are even higher order, since they take type constructors as arguments. • Haskell’s Kind system • A Kind is haskell’s way of “typing” types • Ordinary types have kind * • Int :: * • [ String ] :: * • Type constructors have kind * -> * • Tree :: * -> * • [] :: * -> * • (,) :: * -> * -> *

  4. The Functor Class class Functor f where fmap :: (a -> b) -> (f a -> f b) • Note how the class Functorrequires a type constructor of kind * -> *as an argument. • The method fmap abstracts the operation of applying a function on every parametric Argument. a a a Type T a = x x x (f x) (f x) (f x) fmap f

  5. Notes • Special syntax for built in type constructors (->) :: * -> * -> * [] :: * -> * (,) :: * -> * -> * (,,) :: * -> * -> * -> * • Most class definitions have some implicit laws that all instances should obey. The laws for Functor are: fmap id = id fmap (f . g) = fmap f . fmap g

  6. Instances of class functor data Tree a = Leaf a | Branch (Tree a) (Tree a) instance Functor Tree where fmap f (Leaf x) = Leaf (f x) fmap f (Branch x y) = Branch (fmap f x) (fmap f y) instance Functor ((,) c) where fmap f (x,y) = (x, f y)

  7. More Instances instance Functor [] where fmap f [] = [] fmap f (x:xs) = f x : fmap f xs instance Functor Maybe where fmap f Nothing = Nothing fmap f (Just x) = Just (f x)

  8. Other uses of Higher order T.C.’s data Tree t a = Tip a | Node (t (Tree t a)) t1 = Node [Tip 3, Tip 0] Main> :t t1 t1 :: Tree [] Int data Bin x = Two x x t2 = Node (Two(Tip 5) (Tip 21)) Main> :t t2 t2 :: Tree Bin Int

  9. What is the kind of Tree? • Tree is a binary type constructor • It’s kind will be something like: ? -> ? -> * • The first argument to Tree is itself a type constructor, the second is just an ordinary type. • Tree :: (* -> *)-> * -> *

  10. Functor instances of Tree instance Functor (Tree2 Bin) where fmap f (Tip x) = Tip(f x) fmap f (Node (Two x y)) = Node (Two (fmap f x) (fmap f y)) instance Functor (Tree2 []) where fmap f (Tip x) = Tip(f x) fmap f (Node xs) = Node (map (fmap f) xs)

  11. Can we do better instance Functor t => Functor (Tree2 t) where fmap f (Tip x) = Tip(f x) fmap f (Node xs) = Node (fmap (fmap f) xs)

  12. The Monad Class Note m is a type constructor class Monad m where (>>=) :: m a -> (a -> m b) -> m b (>>) :: m a -> m b -> m b return :: a -> m a fail :: String -> m a p >> q = p >>= \ _ -> q fail s = error s

  13. Generic Monad functions sequence :: Monad m => [m a] -> m [a] sequence = foldrmcons (return []) where mcons p q = do x <- p xs <- q return (x:xs) sequence_ :: Monad m => [m a] -> m () sequence_ = foldr (>>) (return ()) mapM :: Monad m => (a -> m b) -> [a] -> m [b] mapM f as = sequence (map f as) mapM_ :: Monad m => (a -> m b) -> [a] -> m () mapM_ f as = sequence_ (map f as) (=<<) :: Monad m => (a -> m b) -> m a -> m b f =<< x = x >>= f

  14. Files and Handles • The functions: import System.IO writeFile:: FilePath -> String -> IO () appendFile :: FilePath -> String -> IO () are used to read and write to files, but they incur quite a bit of overhead if they are used many times in a row. Instead we wish to open a file once, then make many actions on the file before we close it for a final time. openFile :: FilePath -> IOMode -> IO Handle hClose :: Handle -> IO () data IOMode = ReadMode | WriteMode | AppendMode deriving (Eq, Ord, Ix, Bounded, Enum, Read, Show)

  15. File Modes • A file mode tells how an open file will be used. Different modes support different operations. • When in WriteMode hPutChar :: Handle -> Char -> IO () hPutStr :: Handle -> String -> IO () hPutStrLn :: Handle -> String -> IO () hPrint :: Show a => Handle -> a -> IO () • When in ReadMode hGetChar :: Handle -> IO Char hGetLine :: Handle -> IO String

  16. Standard Channels and Errors • Predefined standard Channels stdin, stdout, stderr :: Handle • Error Handling while doing IO isEOFError :: IOError -> Bool -- Test if the EOF error ioError :: IOError -> IO a -- Raise an IOError catch :: IO a -> (IOError -> IO a) -> IO a -- Handle an Error • Other IO types of errors and their predicates. isAlreadyExistsError, isDoesNotExistError,  isAlreadyInUseError, isFullError,  isEOFError, isIllegalOperation, isPermissionError, isUserError, 

  17. IOError • IOError is an abstract datatype • NOT and algebraic datatype, defined with data like [ ] orTree • Thus it does not admit pattern matching. • Hence the use of all the IOError recognizing predicates. • isAlreadyExistsError, isDoesNotExistError,  • isAlreadyInUseError, isFullError,  • isEOFError, isIllegalOperation, • isPermissionError, isUserError • This was a concious decision, made to allow easy extension of the kinds of IOErrors, as the system grew.

  18. Handling IO Errors • Any action of type IO a may potentially cause an IO Error. • The function catch ::IO a -> (IOError -> IO a) -> IO a can be used to gracefully handle such an error by providing a “fix” getChar' :: IO Char getChar' = catch getChar (\ e -> return '\n') getChar2 :: IO Char getChar2 = catch getChar (\ e -> if isEOFError e then return '\n' else ioError e) –- pass non EOF errors on

  19. An Example getLine' :: IO String getLine' = catch getLine'' (\ e -> return ("Error: " ++ show e)) where getLine'' = do { c <- getChar2 ; if c == '\n' then return "" else do { l <- getLine' ; return (c:l) } }

  20. Catching errors when opening files getAndOpenFile :: String -> IOMode -> IO Handle getAndOpenFile prompt mode = do { putStr prompt ; name <- getLine ; catch (openFile name mode) (\e -> do { putStrLn ("Cannot open: "++name) ; print e ; getAndOpenFile prompt mode }) }

  21. Copying Files main = do { fromHandle <- getAndOpenFile "Copy from: " ReadMode ; toHandle <- getAndOpenFile "Copy to: " WriteMode ; contents <- hGetContentsfromHandle ; hPutStrtoHandle contents ; hClosefromHandle ; hClosetoHandle ; putStr "Done\n" }

  22. Arrays • x :: Array index elem • In Haskell we have pure arrays • Created in linear time • Access in constant time • Indexed by many things • Store anything (polymorphic elem)

  23. Indexing • Arrays are indexed by scalar types • The class (Ix t) describes types that can be used as indexes class Ord a => Ix a where range :: (a, a) -> [a] index :: (a, a) -> a -> Int inRange :: (a, a) -> a -> Bool rangeSize :: (a, a) -> Int

  24. Ix instances • instance Ix Integer • instance Ix Int • instance Ix Char • instance Ix Bool • instance (Ix a, Ix b) => Ix (a, b)

  25. Deriving Ix for enumerations data Color = Red | Blue | Green | Yellow | White | Black deriving (Ord,Eq,Ix) *> range (Red,Black) [Red,Blue,Green,Yellow,White,Black] *> index (Red,Black) Yellow 3 *> index (Yellow,Black) Yellow 0 *> rangeSize (Yellow,Black) 3

  26. Creating arrays by listing • listArray :: (Ixi) => (i, i) -> [e] -> Array ie • digits = listArray (0,9) "0123456789"

  27. Creating arrays by tagging • array :: (Ixi) => (i, i) -- bounds of the array: -- (lowest,highest) -> [(i, e)] -- list of associations -> Array ie alphabet = array (1,26) (zip [1..26] "abcdefghijklmnopqrstuvwxyz") fifth = alphabet ! 5

  28. Accessing arrays • (!) :: (Ixi) => a i e -> i -> e • Returns the element of an immutable array at the specified index. • indices :: (Ixi) => a i e -> [i] • Returns a list of all the valid indices in an array. • elems :: (Ixi) => a i e -> [e] • Returns a list of all the elements of an array, in the same order as their indices. • assocs :: (Ixi) => a i e -> [(i, e)] • Returns the contents of an array as a list of associations.

  29. Multiple Array libraries • There are many array libraries that share the same interface • class IArray a e where • Class of immutable array types. • An array type has the form (a i e) where a is the array type constructor (kind * -> * -> *), i is the index type (a member of the class Ix), and e is the element type. The IArray class is parameterised over both a and e, so that instances specialized to certain element types can be defined.

  30. Compare • listArray :: (Iarray a e, Ixi) => (i, i) -> [e] -> a ie • Compare to • listArray :: (Ixi) => (i, i) -> [e] -> Array i e

  31. Use • Array use generally follows a pattern • Create a list of array elements • Comprehensions are very useful here • Create the Array from the list using array or listArray • Enter a mode where the many things are looked up in the array in constant time.

More Related