fbpx
Wikipedia

Haskell features

This article describes the features in the programming language Haskell.

Examples edit

Factorial edit

A simple example that is often used to demonstrate the syntax of functional languages is the factorial function for non-negative integers, shown in Haskell:

factorial :: Integer -> Integer factorial 0 = 1 factorial n = n * factorial (n-1) 

Or in one line:

factorial n = if n > 1 then n * factorial (n-1) else 1 

This describes the factorial as a recursive function, with one terminating base case. It is similar to the descriptions of factorials found in mathematics textbooks. Much of Haskell code is similar to standard mathematical notation in facility and syntax.

The first line of the factorial function describes the type of this function; while it is optional, it is considered to be good style[1] to include it. It can be read as the function factorial (factorial) has type (::) from integer to integer (Integer -> Integer). That is, it takes an integer as an argument, and returns another integer. The type of a definition is inferred automatically if no type annotation is given.

The second line relies on pattern matching, an important feature of Haskell. Note that parameters of a function are not in parentheses but separated by spaces. When the function's argument is 0 (zero) it will return the integer 1 (one). For all other cases the third line is tried. This is the recursion, and executes the function again until the base case is reached.

Using the product function from the Prelude, a number of small functions analogous to C's standard library, and using the Haskell syntax for arithmetic sequences, the factorial function can be expressed in Haskell as follows:

factorial n = product [1..n] 

Here [1..n] denotes the arithmetic sequence 1, 2, …, n in list form. Using the Prelude function enumFromTo, the expression [1..n] can be written as enumFromTo 1 n, allowing the factorial function to be expressed as

factorial n = product (enumFromTo 1 n) 

which, using the function composition operator (expressed as a dot in Haskell) to compose the product function with the curried enumeration function can be rewritten in point-free style:[2]

factorial = product . enumFromTo 1 

In the Hugs interpreter, one often needs to define the function and use it on the same line separated by a where or let..in. For example, to test the above examples and see the output 120:

let { factorial n | n > 0 = n * factorial (n-1); factorial _ = 1 } in factorial 5 

or

factorial 5 where factorial = product . enumFromTo 1 

The GHCi interpreter doesn't have this restriction and function definitions can be entered on one line (with the let syntax without the in part), and referenced later.

More complex examples edit

Calculator edit

In the Haskell source immediately below, :: can be read as "has type"; a -> b can be read as "is a function from a to b". (Thus the Haskell calc :: String -> [Float] can be read as "calc has type of a function from Strings to lists of Floats".) In the second line calc = ... the equals sign can be read as "can be"; thus multiple lines with calc = ... can be read as multiple possible values for calc, depending on the circumstance detailed in each line.

A simple Reverse Polish notation calculator expressed with the higher-order function foldl whose argument f is defined in a where clause using pattern matching and the type class Read:

calc :: String -> [Float] calc = foldl f [] . words  where   f (x:y:zs) "+" = (y + x):zs  f (x:y:zs) "-" = (y - x):zs  f (x:y:zs) "*" = (y * x):zs  f (x:y:zs) "/" = (y / x):zs  f (x:y:zs) "FLIP" = y:x:zs  f zs w = read w : zs 

The empty list is the initial state, and f interprets one word at a time, either as a function name, taking two numbers from the head of the list and pushing the result back in, or parsing the word as a floating-point number and prepending it to the list.

Fibonacci sequence edit

The following definition produces the list of Fibonacci numbers in linear time:

fibs = 0 : 1 : zipWith (+) fibs (tail fibs) 

The infinite list is produced by corecursion — the latter values of the list are computed on demand starting from the initial two items 0 and 1. This kind of a definition relies on lazy evaluation, an important feature of Haskell programming. For an example of how the evaluation evolves, the following illustrates the values of fibs and tail fibs after the computation of six items and shows how zipWith (+) has produced four items and proceeds to produce the next item:

fibs = 0 : 1 : 1 : 2 : 3 : 5 : ...   + + + + + + tail fibs = 1 : 1 : 2 : 3 : 5 : ...   = = = = = = zipWith ... = 1 : 2 : 3 : 5 : 8 : ... fibs = 0 : 1 : 1 : 2 : 3 : 5 : 8 : ... 

The same function, written using Glasgow Haskell Compiler's parallel list comprehension syntax (GHC extensions must be enabled using a special command-line flag, here -XParallelListComp, or by starting the source file with {-# LANGUAGE ParallelListComp #-}):

fibs = 0 : 1 : [ a+b | a <- fibs | b <- tail fibs ] 

or with regular list comprehensions:

fibs = 0 : 1 : [ a+b | (a,b) <- zip fibs (tail fibs) ] 

or directly self-referencing:

fibs = 0 : 1 : next fibs where next (a : t@(b:_)) = (a+b) : next t 

With stateful generating function:

fibs = next (0,1) where next (a,b) = a : next (b, a+b) 

or with unfoldr:

fibs = unfoldr (\(a,b) -> Just (a, (b, a+b))) (0, 1) 

or scanl:

fibs = 0 : scanl (+) 1 fibs 

Using data recursion with Haskell's predefined fixpoint combinator:

fibs = fix (\xs -> 0 : 1 : zipWith (+) xs (tail xs)) -- zipWith version  = fix ((0:) . (1:) . (zipWith (+) <*> tail)) -- same as above, pointfree  = fix ((0:) . scanl (+) 1) -- scanl version 

Factorial edit

The factorial we saw previously can be written as a sequence of functions:

factorial n = foldr ((.) . (*)) id [1..n] $ 1 -- factorial 5 == ((1*) .) ( ((2*) .) ( ((3*) .) ( ((4*) .) ( ((5*) .) id )))) 1 -- == (1*) . (2*) . (3*) . (4*) . (5*) . id $ 1 -- == 1* ( 2* ( 3* ( 4* ( 5* ( id 1 ))))) factorial n = foldr ((.) . (*)) (const 1) [1..n] $ () -- factorial 5 == ((1*) .) ( ((2*) .) ( ((3*) .) ( ((4*) .) ( ((5*) .) (const 1) )))) () -- == (1*) . (2*) . (3*) . (4*) . (5*) . const 1 $ () -- == 1* ( 2* ( 3* ( 4* ( 5* ( const 1 () ))))) factorial n = foldr (($) . (*)) 1 [1..n] = foldr ($) 1 $ map (*) [1..n] -- factorial 5 == ((1*) $) ( ((2*) $) ( ((3*) $) ( ((4*) $) ( ((5*) $) 1 )))) -- == (1*) $ (2*) $ (3*) $ (4*) $ (5*) $ 1 -- == 1* ( 2* ( 3* ( 4* ( 5* 1 )))) 

More examples edit

Hamming numbers edit

A remarkably concise function that returns the list of Hamming numbers in order:

hamming = 1 : map (2*) hamming `union` map (3*) hamming   `union` map (5*) hamming 

Like the various fibs solutions displayed above, this uses corecursion to produce a list of numbers on demand, starting from the base case of 1 and building new items based on the preceding part of the list.

Here the function union is used as an operator by enclosing it in back-quotes. Its case clauses define how it merges two ascending lists into one ascending list without duplicate items, representing sets as ordered lists. Its companion function minus implements set difference:

union (x:xs) (y:ys) = case compare x y of  LT -> x : union xs (y:ys)   EQ -> x : union xs ys   GT -> y : union (x:xs) ys  union xs [] = xs  union [] ys = ys 
minus (x:xs) (y:ys) = case compare x y of   LT -> x : minus xs (y:ys)  EQ -> minus xs ys   GT -> minus (x:xs) ys minus xs _ = xs -- 

It is possible to generate only the unique multiples, for more efficient operation. Since there are no duplicates, there's no need to remove them:

smooth235 = 1 : foldr (\p s -> fix $ mergeBy (<) s . map (p*) . (1:)) [] [2,3,5]  where  fix f = x where x = f x -- fixpoint combinator, with sharing 

This uses the more efficient function merge which doesn't concern itself with the duplicates (also used in the following next function, mergesort ):

mergeBy less xs ys = merge xs ys where  merge xs [] = xs   merge [] ys = ys  merge (x:xs) (y:ys) | less y x = y : merge (x:xs) ys  | otherwise = x : merge xs (y:ys) 

Each vertical bar ( | ) starts a guard clause with a guard expression before the = sign and the corresponding definition after it, that is evaluated if the guard is true.

Mergesort edit

Here is a bottom-up merge sort, defined using the higher-order function until:

mergesortBy less [] = [] mergesortBy less xs = head $  until (null . tail) (pairwise $ mergeBy less) [[x] | x <- xs] pairwise f (a:b:t) = f a b : pairwise f t pairwise f t = t 

Prime numbers edit

The mathematical definition of primes can be translated pretty much word for word into Haskell:

-- "Integers above 1 that cannot be divided by a smaller integer above 1" -- primes = { n ∈ [2..] | ~ ∃ d ∈ [2..n-1] ⇒ rem n d = 0 } -- = { n ∈ [2..] | ∀ d ∈ [2..n-1] ⇒ rem n d ≠ 0 } primes = [ n | n <- [2..], all (\d -> rem n d /= 0) [2..(n-1)] ] 

This finds primes by trial division. Note that it is not optimized for efficiency and has very poor performance. Slightly faster (but still very slow)[3] is this code by David Turner:

primes = sieve [2..] where   sieve (p:xs) = p : sieve [x | x <- xs, rem x p /= 0] 

Much faster is the optimal trial division algorithm

primes = 2 : [ n | n <- [3..], all ((> 0) . rem n) $   takeWhile ((<= n) . (^2)) primes] 

or an unbounded sieve of Eratosthenes with postponed sieving in stages,[4]

primes = 2 : sieve primes [3..] where  sieve (p:ps) (span (< p*p) -> (h, t)) =   h ++ sieve ps (minus t [p*p, p*p+p..]) 

or the combined sieve implementation by Richard Bird,[5]

-- "Integers above 1 without any composite numbers which -- are found by enumeration of each prime's multiples" primes = 2 : minus [3..]  (foldr (\(m:ms) r -> m : union ms r) []   [[p*p, p*p+p ..] | p <- primes]) 

or an even faster tree-like folding variant[6] with nearly optimal (for a list-based code) time complexity and very low space complexity achieved through telescoping multistage recursive production of primes:

primes = 2 : _Y ((3 :) . minus [5,7..] . _U   . map (\p -> [p*p, p*p+2*p..]))  where  -- non-sharing Y combinator:  _Y g = g (_Y g) -- (g (g (g (g (...)))))  -- big union ~= nub.sort.concat  _U ((x:xs):t) = x : (union xs . _U . pairwise union) t 

Working on arrays by segments between consecutive squares of primes, it's

import Data.Array import Data.List (tails, inits) primes = 2 : [ n |  (r:q:_, px) <- zip (tails (2 : [p*p | p <- primes]))  (inits primes),  (n, True) <- assocs ( accumArray (\_ _ -> False) True  (r+1,q-1)  [ (m,()) | p <- px  , s <- [ div (r+p) p * p]  , m <- [s,s+p..q-1] ] ) ] 

The shortest possible code is probably  nubBy (((>1) .) . gcd) [2..].  It is quite slow.

Syntax edit

Layout edit

Haskell allows indentation to be used to indicate the beginning of a new declaration. For example, in a where clause:

product xs = prod xs 1  where  prod [] a = a  prod (x:xs) a = prod xs (a*x) 

The two equations for the nested function prod are aligned vertically, which allows the semi-colon separator to be omitted. In Haskell, indentation can be used in several syntactic constructs, including do, let, case, class, and instance.

The use of indentation to indicate program structure originates in Peter J. Landin's ISWIM language, where it was called the off-side rule. This was later adopted by Miranda, and Haskell adopted a similar (but rather more complex) version of Miranda's off-side rule, which is called "layout". Other languages to adopt whitespace character-sensitive syntax include Python and F#.

The use of layout in Haskell is optional. For example, the function product above can also be written:

product xs = prod xs 1  where { prod [] a = a; prod (x:xs) a = prod xs (a*x) } 

The explicit open brace after the where keyword indicates that separate declarations will use explicit semi-colons, and the declaration-list will be terminated by an explicit closing brace. One reason for wanting support for explicit delimiters is that it makes automatic generation of Haskell source code easier.

Haskell's layout rule has been criticised for its complexity. In particular, the definition states that if the parser encounters a parse error during processing of a layout section, then it should try inserting a close brace (the "parse error" rule). Implementing this rule in a traditional parsing and lexical analysis combination requires two-way cooperation between the parser and lexical analyser, whereas in most languages, these two phases can be considered independently.

Function calls edit

Applying a function f to a value x is expressed as simply f x.

Haskell distinguishes function calls from infix operators syntactically, but not semantically. Function names which are composed of punctuation characters can be used as operators, as can other function names if surrounded with backticks; and operators can be used in prefix notation if surrounded with parentheses.

This example shows the ways that functions can be called:

add a b = a + b ten1 = 5 + 5 ten2 = (+) 5 5 ten3 = add 5 5 ten4 = 5 `add` 5 

Functions which are defined as taking several parameters can always be partially applied. Binary operators can be partially applied using section notation:

ten5 = (+ 5) 5 ten6 = (5 +) 5   addfive = (5 +) ten7 = addfive 5 

List comprehensions edit

See List comprehension#Overview for the Haskell example.

Pattern matching edit

Pattern matching is used to match on the different constructors of algebraic data types. Here are some functions, each using pattern matching on each of the types below:

-- This type signature says that empty takes a list containing any type, and returns a Bool empty :: [a] -> Bool empty (x:xs) = False empty [] = True -- Will return a value from a Maybe a, given a default value in case a Nothing is encountered fromMaybe :: a -> Maybe a -> a fromMaybe x (Just y) = y fromMaybe x Nothing = x isRight :: Either a b -> Bool isRight (Right _) = True isRight (Left _) = False getName :: Person -> String getName (Person name _ _) = name getSex :: Person -> Sex getSex (Person _ sex _) = sex getAge :: Person -> Int getAge (Person _ _ age) = age 

Using the above functions, along with the map function, we can apply them to each element of a list, to see their results:

map empty [[1,2,3],[],[2],[1..]] -- returns [False,True,False,False] map (fromMaybe 0) [Just 2,Nothing,Just 109238, Nothing] -- returns [2,0,109238,0] map isRight [Left "hello", Right 6, Right 23, Left "world"] -- returns [False, True, True, False] map getName [Person "Sarah" Female 20, Person "Alex" Male 20, tom] -- returns ["Sarah", "Alex", "Tom"], using the definition for tom above 
  • Abstract Types
  • Lists

Tuples edit

Tuples in haskell can be used to hold a fixed number of elements. They are used to group pieces of data of differing types:

account :: (String, Integer, Double) -- The type of a three-tuple, representing   -- a name, balance, and interest rate account = ("John Smith",102894,5.25) 

Tuples are commonly used in the zip* functions to place adjacent elements in separate lists together in tuples (zip4 to zip7 are provided in the Data.List module):

-- The definition of the zip function. Other zip* functions are defined similarly zip :: [x] -> [y] -> [(x,y)] zip (x:xs) (y:ys) = (x,y) : zip xs ys zip _ _ = [] zip [1..5] "hello" -- returns [(1,'h'),(2,'e'),(3,'l'),(4,'l'),(5,'o')] -- and has type [(Integer, Char)] zip3 [1..5] "hello" [False, True, False, False, True] -- returns [(1,'h',False),(2,'e',True),(3,'l',False),(4,'l',False),(5,'o',True)] -- and has type [(Integer,Char,Bool)] 

In the GHC compiler, tuples are defined with sizes from 2 elements up to 62 elements.

Namespaces edit

In the § More complex examples section above, calc is used in two senses, showing that there is a Haskell type class namespace and also a namespace for values:

  1. a Haskell type class for calc. The domain and range can be explicitly denoted in a Haskell type class.
  2. a Haskell value, formula, or expression for calc.

Typeclasses and polymorphism edit

Algebraic data types edit

Algebraic data types are used extensively in Haskell. Some examples of these are the built in list, Maybe and Either types:

-- A list of a's ([a]) is either an a consed (:) onto another list of a's, or an empty list ([]) data [a] = a : [a] | [] -- Something of type Maybe a is either Just something, or Nothing data Maybe a = Just a | Nothing -- Something of type Either atype btype is either a Left atype, or a Right btype data Either a b = Left a | Right b 

Users of the language can also define their own abstract data types. An example of an ADT used to represent a person's name, sex and age might look like:

data Sex = Male | Female data Person = Person String Sex Int -- Notice that Person is both a constructor and a type -- An example of creating something of type Person tom :: Person tom = Person "Tom" Male 27 

Type system edit

  • Type classes
  • Type defaulting
  • Overloaded literals
  • Higher kinded polymorphism
  • Multi-parameter type classes
  • Functional dependencies

Monads and input/output edit

  • Overview of the monad framework:
  • Applications
    • Monadic IO
    • Do-notation
    • References
    • Exceptions

ST monad edit

The ST monad allows writing imperative programming algorithms in Haskell, using mutable variables (STRefs) and mutable arrays (STArrays and STUArrays). The advantage of the ST monad is that it allows writing code that has internal side effects, such as destructively updating mutable variables and arrays, while containing these effects inside the monad. The result of this is that functions written using the ST monad appear pure to the rest of the program. This allows using imperative code where it may be impractical to write functional code, while still keeping all the safety that pure code provides.

Here is an example program (taken from the Haskell wiki page on the ST monad) that takes a list of numbers, and sums them, using a mutable variable:

import Control.Monad.ST import Data.STRef import Control.Monad sumST :: Num a => [a] -> a sumST xs = runST $ do -- runST takes stateful ST code and makes it pure.  summed <- newSTRef 0 -- Create an STRef (a mutable variable)  forM_ xs $ \x -> do -- For each element of the argument list xs ..  modifySTRef summed (+x) -- add it to what we have in n.  readSTRef summed -- read the value of n, which will be returned by the runST above. 

STM monad edit

The STM monad is an implementation of Software Transactional Memory in Haskell. It is implemented in the GHC compiler, and allows for mutable variables to be modified in transactions.

Arrows edit

  • Applicative Functors
  • Arrows

As Haskell is a pure functional language, functions cannot have side effects. Being non-strict, it also does not have a well-defined evaluation order. This is a challenge for real programs, which among other things need to interact with an environment. Haskell solves this with monadic types that leverage the type system to ensure the proper sequencing of imperative constructs. The typical example is input/output (I/O), but monads are useful for many other purposes, including mutable state, concurrency and transactional memory, exception handling, and error propagation.

Haskell provides a special syntax for monadic expressions, so that side-effecting programs can be written in a style similar to current imperative programming languages; no knowledge of the mathematics behind monadic I/O is required for this. The following program reads a name from the command line and outputs a greeting message:

main = do putStrLn "What's your name?"  name <- getLine  putStr ("Hello, " ++ name ++ "!\n") 

The do-notation eases working with monads. This do-expression is equivalent to, but (arguably) easier to write and understand than, the de-sugared version employing the monadic operators directly:

main = putStrLn "What's your name?" >> getLine >>= \ name -> putStr ("Hello, " ++ name ++ "!\n") 
See also wikibooks:Transwiki:List of hello world programs#Haskell for another example that prints text.

Concurrency edit

The Haskell language definition includes neither concurrency nor parallelism, although GHC supports both.

Concurrent Haskell is an extension to Haskell that supports threads and synchronization.[7] GHC's implementation of Concurrent Haskell is based on multiplexing lightweight Haskell threads onto a few heavyweight operating system (OS) threads,[8] so that Concurrent Haskell programs run in parallel via symmetric multiprocessing. The runtime can support millions of simultaneous threads.[9]

The GHC implementation employs a dynamic pool of OS threads, allowing a Haskell thread to make a blocking system call without blocking other running Haskell threads.[10] Hence the lightweight Haskell threads have the characteristics of heavyweight OS threads, and a programmer can be unaware of the implementation details.

Recently,[when?] Concurrent Haskell has been extended with support for software transactional memory (STM), which is a concurrency abstraction in which compound operations on shared data are performed atomically, as transactions.[11] GHC's STM implementation is the only STM implementation to date to provide a static compile-time guarantee preventing non-transactional operations from being performed within a transaction. The Haskell STM library also provides two operations not found in other STMs: retry and orElse, which together allow blocking operations to be defined in a modular and composable fashion.

References edit

  1. ^ HaskellWiki: Type signatures as good style
  2. ^ HaskellWiki: Pointfree
  3. ^ "Prime numbers - HaskellWiki". www.haskell.org.
  4. ^ "Prime numbers - HaskellWiki". www.haskell.org.
  5. ^ O'Neill, Melissa E., "The Genuine Sieve of Eratosthenes", Journal of Functional Programming, Published online by Cambridge University Press 9 October 2008 doi:10.1017/S0956796808007004, pp. 10, 11.
  6. ^ "Prime numbers - HaskellWiki". www.haskell.org.
  7. ^ Simon Peyton Jones, Andrew Gordon, and Sigbjorn Finne. Concurrent Haskell. ACM SIGPLAN-SIGACT Symposium on Principles of Programming Languages (PoPL). 1996. (Some sections are out of date with respect to the current implementation.)
  8. ^ Runtime Support for Multicore Haskell 2010-07-05 at the Wayback Machine (Simon Marlow, Simon Peyton Jones, Satnam Singh) ICFP '09: Proceedings of the 14th ACM SIGPLAN international conference on Functional programming, Edinburgh, Scotland, August 2009
  9. ^ "DEFUN 2009: Multicore Programming in Haskell Now!". 5 September 2009.
  10. ^ Extending the Haskell Foreign Function Interface with Concurrency 2010-07-03 at the Wayback Machine (Simon Marlow, Simon Peyton Jones, Wolfgang Thaller) Proceedings of the ACM SIGPLAN workshop on Haskell, pages 57--68, Snowbird, Utah, USA, September 2004
  11. ^ Harris, Tim; Marlow, Simon; Peyton Jones, Simon; Herlihy, Maurice (2005). "Composable memory transactions". Proceedings of the tenth ACM SIGPLAN symposium on Principles and practice of parallel programming. CiteSeerX 10.1.1.67.3686.

haskell, features, this, article, possibly, contains, original, research, please, improve, verifying, claims, made, adding, inline, citations, statements, consisting, only, original, research, should, removed, september, 2018, learn, when, remove, this, templa. This article possibly contains original research Please improve it by verifying the claims made and adding inline citations Statements consisting only of original research should be removed September 2018 Learn how and when to remove this template message This article describes the features in the programming language Haskell Contents 1 Examples 1 1 Factorial 1 2 More complex examples 1 2 1 Calculator 1 2 2 Fibonacci sequence 1 2 3 Factorial 1 3 More examples 1 3 1 Hamming numbers 1 3 2 Mergesort 1 3 3 Prime numbers 2 Syntax 2 1 Layout 2 2 Function calls 2 3 List comprehensions 2 4 Pattern matching 2 5 Tuples 3 Namespaces 4 Typeclasses and polymorphism 4 1 Algebraic data types 4 2 Type system 5 Monads and input output 5 1 ST monad 5 2 STM monad 5 3 Arrows 6 Concurrency 7 ReferencesExamples editFactorial edit A simple example that is often used to demonstrate the syntax of functional languages is the factorial function for non negative integers shown in Haskell factorial Integer gt Integer factorial 0 1 factorial n n factorial n 1 Or in one line factorial n if n gt 1 then n factorial n 1 else 1 This describes the factorial as a recursive function with one terminating base case It is similar to the descriptions of factorials found in mathematics textbooks Much of Haskell code is similar to standard mathematical notation in facility and syntax The first line of the factorial function describes the type of this function while it is optional it is considered to be good style 1 to include it It can be read as the function factorial factorial has type from integer to integer Integer gt Integer That is it takes an integer as an argument and returns another integer The type of a definition is inferred automatically if no type annotation is given The second line relies on pattern matching an important feature of Haskell Note that parameters of a function are not in parentheses but separated by spaces When the function s argument is 0 zero it will return the integer 1 one For all other cases the third line is tried This is the recursion and executes the function again until the base case is reached Using the product function from the Prelude a number of small functions analogous to C s standard library and using the Haskell syntax for arithmetic sequences the factorial function can be expressed in Haskell as follows factorial n product 1 n Here 1 n denotes the arithmetic sequence 1 2 n in list form Using the Prelude function enumFromTo the expression 1 n can be written as enumFromTo 1 n allowing the factorial function to be expressed as factorial n product enumFromTo 1 n which using the function composition operator expressed as a dot in Haskell to compose the product function with the curried enumeration function can be rewritten in point free style 2 factorial product enumFromTo 1 In the Hugs interpreter one often needs to define the function and use it on the same line separated by a where or let in For example to test the above examples and see the output 120 let factorial n n gt 0 n factorial n 1 factorial 1 in factorial 5 or factorial 5 where factorial product enumFromTo 1 The GHCi interpreter doesn t have this restriction and function definitions can be entered on one line with the b let b syntax without the b in b part and referenced later More complex examples edit Calculator edit In the Haskell source immediately below can be read as has type a gt b can be read as is a function from a to b Thus the Haskell calc String gt Float can be read as calc has type of a function from Strings to lists of Floats In the second line calc the equals sign can be read as can be thus multiple lines with calc can be read as multiple possible values for calc depending on the circumstance detailed in each line A simple Reverse Polish notation calculator expressed with the higher order function a href Foldl html class mw redirect title Foldl foldl a whose argument f is defined in a where clause using pattern matching and the type class Read calc String gt Float calc foldl f words where f x y zs y x zs f x y zs y x zs f x y zs y x zs f x y zs y x zs f x y zs FLIP y x zs f zs w read w zs The empty list is the initial state and f interprets one word at a time either as a function name taking two numbers from the head of the list and pushing the result back in or parsing the word as a floating point number and prepending it to the list Fibonacci sequence edit The following definition produces the list of Fibonacci numbers in linear time fibs 0 1 zipWith fibs tail fibs The infinite list is produced by corecursion the latter values of the list are computed on demand starting from the initial two items 0 and 1 This kind of a definition relies on lazy evaluation an important feature of Haskell programming For an example of how the evaluation evolves the following illustrates the values of fibs and tail fibs after the computation of six items and shows how zipWith has produced four items and proceeds to produce the next item fibs 0 1 1 2 3 5 tail fibs 1 1 2 3 5 zipWith 1 2 3 5 8 fibs 0 1 1 2 3 5 8 The same function written using Glasgow Haskell Compiler s parallel list comprehension syntax GHC extensions must be enabled using a special command line flag here XParallelListComp or by starting the source file with LANGUAGE ParallelListComp fibs 0 1 a b a lt fibs b lt tail fibs or with regular list comprehensions fibs 0 1 a b a b lt zip fibs tail fibs or directly self referencing fibs 0 1 next fibs where next a t b a b next t With stateful generating function fibs next 0 1 where next a b a next b a b or with unfoldr fibs unfoldr a b gt Just a b a b 0 1 or scanl fibs 0 scanl 1 fibs Using data recursion with Haskell s predefined fixpoint combinator fibs fix xs gt 0 1 zipWith xs tail xs zipWith version fix 0 1 zipWith lt gt tail same as above pointfree fix 0 scanl 1 scanl version Factorial edit The factorial we saw previously can be written as a sequence of functions factorial n foldr id 1 n 1 factorial 5 1 2 3 4 5 id 1 1 2 3 4 5 id 1 1 2 3 4 5 id 1 factorial n foldr const 1 1 n factorial 5 1 2 3 4 5 const 1 1 2 3 4 5 const 1 1 2 3 4 5 const 1 factorial n foldr 1 1 n foldr 1 map 1 n factorial 5 1 2 3 4 5 1 1 2 3 4 5 1 1 2 3 4 5 1 More examples edit Hamming numbers edit A remarkably concise function that returns the list of Hamming numbers in order hamming 1 map 2 hamming union map 3 hamming union map 5 hamming Like the various fibs solutions displayed above this uses corecursion to produce a list of numbers on demand starting from the base case of 1 and building new items based on the preceding part of the list Here the function union is used as an operator by enclosing it in back quotes Its case clauses define how it merges two ascending lists into one ascending list without duplicate items representing sets as ordered lists Its companion function minus implements set difference union x xs y ys case compare x y of LT gt x union xs y ys EQ gt x union xs ys GT gt y union x xs ys union xs xs union ys ys minus x xs y ys case compare x y of LT gt x minus xs y ys EQ gt minus xs ys GT gt minus x xs ys minus xs xs It is possible to generate only the unique multiples for more efficient operation Since there are no duplicates there s no need to remove them smooth235 1 foldr p s gt fix mergeBy lt s map p 1 2 3 5 where fix f x where x f x fixpoint combinator with sharing This uses the more efficient function merge which doesn t concern itself with the duplicates also used in the following next function mergesort mergeBy less xs ys merge xs ys where merge xs xs merge ys ys merge x xs y ys less y x y merge x xs ys otherwise x merge xs y ys Each vertical bar starts a guard clause with a guard expression before the sign and the corresponding definition after it that is evaluated if the guard is true Mergesort edit Here is a bottom up merge sort defined using the higher order function until mergesortBy less mergesortBy less xs head until null tail pairwise mergeBy less x x lt xs pairwise f a b t f a b pairwise f t pairwise f t t Prime numbers edit The mathematical definition of primes can be translated pretty much word for word into Haskell Integers above 1 that cannot be divided by a smaller integer above 1 primes n 2 d 2 n 1 rem n d 0 n 2 d 2 n 1 rem n d 0 primes n n lt 2 all d gt rem n d 0 2 n 1 This finds primes by trial division Note that it is not optimized for efficiency and has very poor performance Slightly faster but still very slow 3 is this code by David Turner primes sieve 2 where sieve p xs p sieve x x lt xs rem x p 0 Much faster is the optimal trial division algorithm primes 2 n n lt 3 all gt 0 rem n takeWhile lt n 2 primes or an unbounded sieve of Eratosthenes with postponed sieving in stages 4 primes 2 sieve primes 3 where sieve p ps span lt p p gt h t h sieve ps minus t p p p p p or the combined sieve implementation by Richard Bird 5 Integers above 1 without any composite numbers which are found by enumeration of each prime s multiples primes 2 minus 3 foldr m ms r gt m union ms r p p p p p p lt primes or an even faster tree like folding variant 6 with nearly optimal for a list based code time complexity and very low space complexity achieved through telescoping multistage recursive production of primes primes 2 Y 3 minus 5 7 U map p gt p p p p 2 p where non sharing Y combinator Y g g Y g g g g g big union nub sort concat U x xs t x union xs U pairwise union t Working on arrays by segments between consecutive squares of primes it s import Data Array import Data List tails inits primes 2 n r q px lt zip tails 2 p p p lt primes inits primes n True lt assocs accumArray gt False True r 1 q 1 m p lt px s lt div r p p p m lt s s p q 1 The shortest possible code is probably nubBy gt 1 gcd 2 It is quite slow Syntax editLayout edit Haskell allows indentation to be used to indicate the beginning of a new declaration For example in a where clause product xs prod xs 1 where prod a a prod x xs a prod xs a x The two equations for the nested function prod are aligned vertically which allows the semi colon separator to be omitted In Haskell indentation can be used in several syntactic constructs including do let case class and instance The use of indentation to indicate program structure originates in Peter J Landin s ISWIM language where it was called the off side rule This was later adopted by Miranda and Haskell adopted a similar but rather more complex version of Miranda s off side rule which is called layout Other languages to adopt whitespace character sensitive syntax include Python and F The use of layout in Haskell is optional For example the function product above can also be written product xs prod xs 1 where prod a a prod x xs a prod xs a x The explicit open brace after the where keyword indicates that separate declarations will use explicit semi colons and the declaration list will be terminated by an explicit closing brace One reason for wanting support for explicit delimiters is that it makes automatic generation of Haskell source code easier Haskell s layout rule has been criticised for its complexity In particular the definition states that if the parser encounters a parse error during processing of a layout section then it should try inserting a close brace the parse error rule Implementing this rule in a traditional parsing and lexical analysis combination requires two way cooperation between the parser and lexical analyser whereas in most languages these two phases can be considered independently Function calls edit Applying a function f to a value x is expressed as simply f x Haskell distinguishes function calls from infix operators syntactically but not semantically Function names which are composed of punctuation characters can be used as operators as can other function names if surrounded with backticks and operators can be used in prefix notation if surrounded with parentheses This example shows the ways that functions can be called add a b a b ten1 5 5 ten2 5 5 ten3 add 5 5 ten4 5 add 5 Functions which are defined as taking several parameters can always be partially applied Binary operators can be partially applied using section notation ten5 5 5 ten6 5 5 addfive 5 ten7 addfive 5 List comprehensions edit See List comprehension Overview for the Haskell example Pattern matching edit Pattern matching is used to match on the different constructors of algebraic data types Here are some functions each using pattern matching on each of the types below This type signature says that empty takes a list containing any type and returns a Bool empty a gt Bool empty x xs False empty True Will return a value from a Maybe a given a default value in case a Nothing is encountered fromMaybe a gt Maybe a gt a fromMaybe x Just y y fromMaybe x Nothing x isRight Either a b gt Bool isRight Right True isRight Left False getName Person gt String getName Person name name getSex Person gt Sex getSex Person sex sex getAge Person gt Int getAge Person age age Using the above functions along with the map function we can apply them to each element of a list to see their results map empty 1 2 3 2 1 returns False True False False map fromMaybe 0 Just 2 Nothing Just 109238 Nothing returns 2 0 109238 0 map isRight Left hello Right 6 Right 23 Left world returns False True True False map getName Person Sarah Female 20 Person Alex Male 20 tom returns Sarah Alex Tom using the definition for tom above Abstract Types ListsTuples edit Tuples in haskell can be used to hold a fixed number of elements They are used to group pieces of data of differing types account String Integer Double The type of a three tuple representing a name balance and interest rate account John Smith 102894 5 25 Tuples are commonly used in the zip functions to place adjacent elements in separate lists together in tuples zip4 to zip7 are provided in the Data List module The definition of the zip function Other zip functions are defined similarly zip x gt y gt x y zip x xs y ys x y zip xs ys zip zip 1 5 hello returns 1 h 2 e 3 l 4 l 5 o and has type Integer Char zip3 1 5 hello False True False False True returns 1 h False 2 e True 3 l False 4 l False 5 o True and has type Integer Char Bool In the GHC compiler tuples are defined with sizes from 2 elements up to 62 elements RecordsNamespaces editIn the More complex examples section above calc is used in two senses showing that there is a Haskell type class namespace and also a namespace for values a Haskell type class for calc The domain and range can be explicitly denoted in a Haskell type class a Haskell value formula or expression for calc Typeclasses and polymorphism editAlgebraic data types edit This section needs expansion You can help by adding to it December 2009 Algebraic data types are used extensively in Haskell Some examples of these are the built in list Maybe and Either types A list of a s a is either an a consed onto another list of a s or an empty list data a a a Something of type Maybe a is either Just something or Nothing data Maybe a Just a Nothing Something of type Either atype btype is either a Left atype or a Right btype data Either a b Left a Right b Users of the language can also define their own abstract data types An example of an ADT used to represent a person s name sex and age might look like data Sex Male Female data Person Person String Sex Int Notice that Person is both a constructor and a type An example of creating something of type Person tom Person tom Person Tom Male 27 Type system edit This section needs expansion You can help by adding to it December 2009 Type classes Type defaulting Overloaded literals Higher kinded polymorphism Multi parameter type classes Functional dependenciesMonads and input output editThis section needs expansion You can help by adding to it December 2009 Overview of the monad framework Applications Monadic IO Do notation References ExceptionsST monad edit The ST monad allows writing imperative programming algorithms in Haskell using mutable variables STRefs and mutable arrays STArrays and STUArrays The advantage of the ST monad is that it allows writing code that has internal side effects such as destructively updating mutable variables and arrays while containing these effects inside the monad The result of this is that functions written using the ST monad appear pure to the rest of the program This allows using imperative code where it may be impractical to write functional code while still keeping all the safety that pure code provides Here is an example program taken from the Haskell wiki page on the ST monad that takes a list of numbers and sums them using a mutable variable import Control Monad ST import Data STRef import Control Monad sumST Num a gt a gt a sumST xs runST do runST takes stateful ST code and makes it pure summed lt newSTRef 0 Create an STRef a mutable variable forM xs x gt do For each element of the argument list xs modifySTRef summed x add it to what we have in n readSTRef summed read the value of n which will be returned by the runST above STM monad edit Main article Concurrent Haskell The STM monad is an implementation of Software Transactional Memory in Haskell It is implemented in the GHC compiler and allows for mutable variables to be modified in transactions Arrows edit Applicative Functors ArrowsAs Haskell is a pure functional language functions cannot have side effects Being non strict it also does not have a well defined evaluation order This is a challenge for real programs which among other things need to interact with an environment Haskell solves this with monadic types that leverage the type system to ensure the proper sequencing of imperative constructs The typical example is input output I O but monads are useful for many other purposes including mutable state concurrency and transactional memory exception handling and error propagation Haskell provides a special syntax for monadic expressions so that side effecting programs can be written in a style similar to current imperative programming languages no knowledge of the mathematics behind monadic I O is required for this The following program reads a name from the command line and outputs a greeting message main do putStrLn What s your name name lt getLine putStr Hello name n The do notation eases working with monads This do expression is equivalent to but arguably easier to write and understand than the de sugared version employing the monadic operators directly main putStrLn What s your name gt gt getLine gt gt name gt putStr Hello name n See also wikibooks Transwiki List of hello world programs Haskell for another example that prints text Concurrency editThe Haskell language definition includes neither concurrency nor parallelism although GHC supports both Main article Concurrent Haskell Concurrent Haskell is an extension to Haskell that supports threads and synchronization 7 GHC s implementation of Concurrent Haskell is based on multiplexing lightweight Haskell threads onto a few heavyweight operating system OS threads 8 so that Concurrent Haskell programs run in parallel via symmetric multiprocessing The runtime can support millions of simultaneous threads 9 The GHC implementation employs a dynamic pool of OS threads allowing a Haskell thread to make a blocking system call without blocking other running Haskell threads 10 Hence the lightweight Haskell threads have the characteristics of heavyweight OS threads and a programmer can be unaware of the implementation details Recently when Concurrent Haskell has been extended with support for software transactional memory STM which is a concurrency abstraction in which compound operations on shared data are performed atomically as transactions 11 GHC s STM implementation is the only STM implementation to date to provide a static compile time guarantee preventing non transactional operations from being performed within a transaction The Haskell STM library also provides two operations not found in other STMs retry and orElse which together allow blocking operations to be defined in a modular and composable fashion References edit HaskellWiki Type signatures as good style HaskellWiki Pointfree Prime numbers HaskellWiki www haskell org Prime numbers HaskellWiki www haskell org O Neill Melissa E The Genuine Sieve of Eratosthenes Journal of Functional Programming Published online by Cambridge University Press 9 October 2008 doi 10 1017 S0956796808007004 pp 10 11 Prime numbers HaskellWiki www haskell org Simon Peyton Jones Andrew Gordon and Sigbjorn Finne Concurrent Haskell ACM SIGPLAN SIGACT Symposium on Principles of Programming Languages PoPL 1996 Some sections are out of date with respect to the current implementation Runtime Support for Multicore Haskell Archived 2010 07 05 at the Wayback Machine Simon Marlow Simon Peyton Jones Satnam Singh ICFP 09 Proceedings of the 14th ACM SIGPLAN international conference on Functional programming Edinburgh Scotland August 2009 DEFUN 2009 Multicore Programming in Haskell Now 5 September 2009 Extending the Haskell Foreign Function Interface with Concurrency Archived 2010 07 03 at the Wayback Machine Simon Marlow Simon Peyton Jones Wolfgang Thaller Proceedings of the ACM SIGPLAN workshop on Haskell pages 57 68 Snowbird Utah USA September 2004 Harris Tim Marlow Simon Peyton Jones Simon Herlihy Maurice 2005 Composable memory transactions Proceedings of the tenth ACM SIGPLAN symposium on Principles and practice of parallel programming CiteSeerX 10 1 1 67 3686 Retrieved from https en wikipedia org w index php title Haskell features amp oldid 1210545958 Syntax, wikipedia, wiki, book, books, library,

article

, read, download, free, free download, mp3, video, mp4, 3gp, jpg, jpeg, gif, png, picture, music, song, movie, book, game, games.