grab bag of interesting stuff. topics higher kinded types files and handles ioerror arrays

31
Grab Bag of Interesting Stuff

Post on 19-Dec-2015

222 views

Category:

Documents


1 download

TRANSCRIPT

Page 1: Grab Bag of Interesting Stuff. Topics Higher kinded types Files and handles IOError Arrays

Grab Bag of Interesting Stuff

Page 2: Grab Bag of Interesting Stuff. Topics Higher kinded types Files and handles IOError Arrays

Topics

• Higher kinded types• Files and handles• IOError• Arrays

Page 3: 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.• 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 :: * -> *• [] :: * -> *• (,) :: * -> * -> *

Page 4: Grab Bag of Interesting Stuff. Topics Higher kinded types Files and handles IOError Arrays

The Functor Classclass Functor f where fmap :: (a -> b) -> (f a -> f b)

• Note how the class Functor requires a type constructor of kind * -> * as an argument.

• The method fmap abstracts the operation of applying a function on every parametric Argument.

a a aType T a =

x x x

(f x) (f x) (f x)

fmap f

Page 5: Grab Bag of Interesting Stuff. Topics Higher kinded types Files and handles IOError Arrays

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 = idfmap (f . g) = fmap f . fmap g

Page 6: Grab Bag of Interesting Stuff. Topics Higher kinded types Files and handles IOError Arrays

Instances of class functordata 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)

Page 7: Grab Bag of Interesting Stuff. Topics Higher kinded types Files and handles IOError Arrays

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)

Page 8: Grab Bag of Interesting Stuff. Topics Higher kinded types Files and handles IOError Arrays

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 t1t1 :: Tree [] Int

data Bin x = Two x x

t2 = Node (Two(Tip 5) (Tip 21))Main> :t t2t2 :: Tree Bin Int

Page 9: Grab Bag of Interesting Stuff. Topics Higher kinded types Files and handles IOError Arrays

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 :: (* -> *)-> * -> *

Page 10: Grab Bag of Interesting Stuff. Topics Higher kinded types Files and handles IOError Arrays

Functor instances of Treeinstance 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)

Page 11: Grab Bag of Interesting Stuff. Topics Higher kinded types Files and handles IOError Arrays

Can we do betterinstance Functor t => Functor (Tree2 t) where fmap f (Tip x) = Tip(f x) fmap f (Node xs) = Node (fmap (fmap f) xs)

Page 12: Grab Bag of Interesting Stuff. Topics Higher kinded types Files and handles IOError Arrays

The Monad Classclass 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

Note m is atype constructor

Page 13: Grab Bag of Interesting Stuff. Topics Higher kinded types Files and handles IOError Arrays

Generic Monad functionssequence :: Monad m => [m a] -> m [a] sequence = foldr mcons (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 bf =<< x = x >>= f

Page 14: Grab Bag of Interesting Stuff. Topics Higher kinded types Files and handles IOError Arrays

Files and Handles• The functions:

import System.IOwriteFile :: 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)

Page 15: Grab Bag of Interesting Stuff. Topics Higher kinded types Files and handles IOError Arrays

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 CharhGetLine :: Handle -> IO String

Page 16: Grab Bag of Interesting Stuff. Topics Higher kinded types Files and handles IOError Arrays

Standard Channels and Errors• Predefined standard Channels

stdin, stdout, stderr :: Handle

• Error Handling while doing IO

isEOFError :: IOError -> Bool -- Test if the EOF errorioError :: IOError -> IO a -- Raise an IOErrorcatch :: 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, 

Page 17: Grab Bag of Interesting Stuff. Topics Higher kinded types Files and handles IOError Arrays

IOError• IOError is an abstract datatype

– NOT and algebraic datatype, defined with data like [ ] or Tree

• 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.

Page 18: Grab Bag of Interesting Stuff. Topics Higher kinded types Files and handles IOError Arrays

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 ChargetChar' = catch getChar (\ e -> return '\n')

getChar2 :: IO ChargetChar2 = catch getChar (\ e -> if isEOFError e then return '\n' else ioError e) –- pass non EOF errors on

Page 19: Grab Bag of Interesting Stuff. Topics Higher kinded types Files and handles IOError Arrays

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

Page 20: Grab Bag of Interesting Stuff. Topics Higher kinded types Files and handles IOError Arrays

Catching errors when opening files

getAndOpenFile :: String -> IOMode -> IO HandlegetAndOpenFile prompt mode = do { putStr prompt ; name <- getLine ; catch (openFile name mode) (\e -> do { putStrLn ("Cannot open: "++name) ; print e ; getAndOpenFile prompt mode }) }

Page 21: Grab Bag of Interesting Stuff. Topics Higher kinded types Files and handles IOError Arrays

Copying Filesmain = do { fromHandle <- getAndOpenFile "Copy from: " ReadMode ; toHandle <- getAndOpenFile "Copy to: " WriteMode ; contents <- hGetContents fromHandle ; hPutStr toHandle contents ; hClose fromHandle ; hClose toHandle ; putStr "Done\n" }

Page 22: Grab Bag of Interesting Stuff. Topics Higher kinded types Files and handles IOError Arrays

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)

Page 23: Grab Bag of Interesting Stuff. Topics Higher kinded types Files and handles IOError Arrays

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

Page 24: Grab Bag of Interesting Stuff. Topics Higher kinded types Files and handles IOError Arrays

Ix instances

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

Page 25: Grab Bag of Interesting Stuff. Topics Higher kinded types Files and handles IOError Arrays

Deriving Ix for enumerationsdata Color = Red | Blue | Green | Yellow | White | Black deriving (Ord,Eq,Ix)

*> range (Red,Black)[Red,Blue,Green,Yellow,White,Black]

*> index (Red,Black) Yellow3

*> index (Yellow,Black) Yellow0

*> rangeSize (Yellow,Black)3

Page 26: Grab Bag of Interesting Stuff. Topics Higher kinded types Files and handles IOError Arrays

Creating arrays by listing

• listArray :: (Ix i) => (i, i) -> [e] -> Array i e

• digits = listArray (0,9) "0123456789"

Page 27: Grab Bag of Interesting Stuff. Topics Higher kinded types Files and handles IOError Arrays

Creating arrays by tagging• array

:: (Ix i) => (i, i) -- bounds of the array: -- (lowest,highest) -> [(i, e)] -- list of associations -> Array i e

alphabet = array (1,26) (zip [1..26] "abcdefghijklmnopqrstuvwxyz")

fifth = alphabet ! 5

Page 28: Grab Bag of Interesting Stuff. Topics Higher kinded types Files and handles IOError Arrays

Accessing arrays

• (!) :: (Ix i) => a i e -> i -> e– Returns the element of an immutable array at the

specified index. • indices :: (Ix i) => a i e -> [i]– Returns a list of all the valid indices in an array.

• elems :: (Ix i) => a i e -> [e]– Returns a list of all the elements of an array, in the same

order as their indices. • assocs :: (Ix i) => a i e -> [(i, e)]– Returns the contents of an array as a list of associations.

Page 29: Grab Bag of Interesting Stuff. Topics Higher kinded types Files and handles IOError Arrays

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.

Page 31: Grab Bag of Interesting Stuff. Topics Higher kinded types Files and handles IOError Arrays

Use

• Array use generally follows a pattern1. Create a list of array elements• Comprehensions are very useful here

2. Create the Array from the list using array or listArray

3. Enter a mode where the many things are looked up in the array in constant time.