FAQ

From HaskellWiki
Revision as of 00:10, 15 August 2011 by Keegan (talk | contribs) (add answer about type vs. data vs. newtype)
Jump to navigation Jump to search

This FAQ is based on actual frequently-asked questions from #haskell IRC. The goal is simply to collect and edit some common answers. Beginner questions are still welcome on IRC, as always.

This is a wiki, so please edit the text with any improvements you have. And feel free to add new questions, if they are frequently asked.

See also

The real world

Should I learn Haskell?

That depends on your goals. In general, Haskellers will tell you that you should learn Haskell. :)

Learning Haskell is fun. It will expand your mind and make you a better programmer in other languages. These are the immediate benefits.

Haskell is also a great tool for solving real-world problems, but it can take many months of study to get to that point.

Is Haskell hard to learn?

Any competent programmer can learn Haskell, but it will take more time and motivation than you may expect.

Haskell requires learning a new way to think, not just new syntax for old concepts. This can be incredibly frustrating, as simple tasks seem impossibly difficult.

Those with no prior programming experience may actually have an easier time learning Haskell, because they have less to un-learn.

How can I get started with Haskell right now?

Check out Try Haskell.

What should I read for learning Haskell?

The most popular resources are Learn You a Haskell and Real World Haskell. Each is available online for free, or can be purchased in hardcopy.

Many other tutorials, books, and other resources are available.

How can I get help with learning Haskell?

Your options include:

Will Haskell get me a job?

There are plenty of companies using Haskell, but it's still a tiny number compared to the software industry as a whole.

There are also many companies which do not use Haskell, but prefer to hire people who know Haskell. It indicates that you learned something hard and obscure just for fun, which employers take as a sign of intelligence.

Is Haskell similar to Language X?

Probably not. It's best if you approach Haskell with a clean slate. Most analogies to another language will break down somewhere, often in a subtle and misleading way. If you first learn the Haskell concepts for what they are, you can then draw useful connections to other languages.

What's the relationship between Haskell and GHC?

Haskell is not a piece of software; it is a specification for a standardized programming language. The latest version of the spec is the Haskell 2010 Report.

GHC is the Glorious Glasgow Haskell Compiler. It is by far the most popular and "production-ready" implementation of the standard Haskell language. It also implements many extension features that go above and beyond standard Haskell. Many programs use these features and so aren't "written in Haskell" in the strictest sense.

You can use the term "Haskell" to refer to the standard language, and "GHC Haskell" when including GHC extensions.

Besides GHC, several other implementations of Haskell are available. Each one provides its own extensions, some of which don't exist in GHC.

What is the Haskell Platform?

The Haskell Platform is a copy of GHC bundled with a "blessed" set of useful libraries. It is the easiest way to get started with Haskell. It's not essential to start with the Platform, because you can install the same libraries as needed.

What is Haskell Prime (Haskell')?

Haskell Prime is a process which produces new versions of the Haskell language spec. It does not refer to a particular present or future version of Haskell.

My textbook uses Haskell 98. Is it very different from Haskell 2010?

No. Haskell 2010 is a very conservative change to Haskell 98. It fixes small syntactic flaws, and standardizes several well-behaved extensions which GHC has supported for years.

The standardization process is very slow because standardizing a flawed language can be a costly mistake. Extensions are accepted only once they are considered mature and well-understood.

How do I get libraries for Haskell?

You can find libraries on Hackage, and install them with cabal-install.

Is Haskell compiled?

Usually. GHC, the most popular Haskell implementation, has an optimizing ahead-of-time native-code compiler, as well as a bytecode compiler and interpreter for interactive use.

Haskell itself is not a "compiled language" because nothing in the Haskell spec requires implementations to be compilers.

Does Haskell have an interpreter?

Yes, but maybe you instead mean "Is there a program where I can type Haskell code and see it run immediately?". GHCi provides such a "read-evaluate-print loop".

Paradigms

Is learning Haskell the best way to learn functional programming?

Not necessarily! Haskell is not a typical functional language. It can be overwhelming to learn the basic concepts of functional programming alongside static types, algebraic data, laziness, type classes, first-class IO, etc. For an introduction to FP by itself you might want to learn Scheme, or play with the FP features in your current favorite language.

That said, many people choose Haskell as an introduction to FP and have success with that approach. Haskell has an extremely active community of people teaching, doing research, writing libraries, etc. Haskell is where interesting things happen in the FP space, so it's an exciting place to jump in.

I heard Haskell is pure functional. Does that mean I can't do imperative / OOP / aspect-oriented / logic programming in Haskell?

No, "pure functional" has a specific technical meaning. It doesn't mean that functional is the only supported paradigm.

Paradigms describe the techniques used in a particular program. For example, the Linux kernel is written in C, with pervasive use of functional, object-oriented, and aspect-oriented programming. The most we can say about a language is that it encourages or discourages a particular paradigm. Haskell is very flexible and can comfortably accommodate most paradigms, even when there is no built-in support.

I heard Haskell is pure functional. Does that mean it can't do IO?

No; IO in Haskell is straightforward.

I heard Haskell is pure functional. Does that mean it doesn't have mutable state?

No; see IORef for a simple example. A more sophisticated example is software transactional memory, which provides concurrent state more sophisticated than you'll find in most other imperative languages.

Wait, is Haskell imperative or is it functional?

Both. In Haskell, functions are first class, and so are imperative actions.

There is no reason to consider "imperative language" and "functional language" as opposites. It's only a historical accident that a few of the most popular imperative languages are unusually bad at functional programming. Functional imperative programming is extremely powerful and is supported by many languages.

Math

Was Haskell designed by mathematicians?

Haskell was designed by people studying programming language design. Perhaps programmers would consider them to be mathematicians, while mathematicians would consider them to be programmers.

Designing a programming language is a hard thing to do. There are many non-obvious tradeoffs, and many lessons to be learned from past failures and successes. Yet many of today's most popular languages were designed by people who hadn't done their homework.

Haskell was designed by people who knew what they were doing. It's not perfect, but the contrast to an amateur's design is striking.

Do I need to know advanced math in order to use Haskell?

No. Certain concepts in Haskell are named after concepts in advanced math. But other languages also appropriate math terminology: consider "singleton", not to mention "function" and "variable". The way these programming concepts relate to actual mathematics is not necessarily important or relevant.

In addition, some people write articles about advanced math, using Haskell syntax as their notation. These articles are interesting, but the connection to everyday programming work is usually remote.

Knowing advanced math will enrich your experience using Haskell, but is by no means a prerequisite.

Types

Doesn't a static type system just make it harder to write programs?

Yes. In particular, it makes it much harder to write incorrect programs.

The tradeoff is that correct programs also become somewhat harder to write. In Haskell, features like type inference mitigate this burden to a large extent.

How do I make a list with elements of different types?

Are you sure that's what you want? Consider instead creating a single data type to encompass the alternatives:

data Identifier
    = ByNumber Int
    | ByName   String

doStuff :: [Identifier] -> Whatever

In many dynamically-typed languages you aren't allowed to create "variant types" like this. The type system itself is used as a single ad-hoc global variant type. Keep this in mind if you're translating designs from a dynamically-typed language to Haskell.

No really, how do I make a list of elements of different types?

Well, you can't avoid putting all your values into one type. But sometimes the "variant type" approach above is too restrictive. Maybe you need to let other people add to the set of allowed types, the way Control.Exception allows users to define new exception types.

You can use an existential type, possibly with a type class. Or you can use Data.Dynamic.

I'm making an RPG. Should I define a type for each kind of monster, and a type class for them?

Probably not. Some languages require a new type for each new behavior. In Haskell, behaviors are functions or IO actions, which are first-class values. So you can store behaviors in an ordinary data type:

data MonsterOps = MonsterOps
    { new    :: Monster
    , move   :: Monster -> Monster
    , attack :: Monster -> Player -> Player }

data Monster = Monster
    { position  :: (Int, Int)
    , hitpoints :: Double }

beholder :: MonsterOps
beholder = MonsterOps new move attack where
    new = Monster (0,0) 9000
    move   self = ...
    attack self player = ...

This approach is especially nice if you want to generate or transform behaviors on the fly. See the article "Haskell Antipattern: Existential Typeclass" for a longer discussion.

What's the difference between Integer and Int?

Integer can represent arbitrarily large integers, up to using all of the storage on your machine.

Int can only represent integers in a finite range. The language standard only guarantees a range of -229 to (229 - 1). Most implementations will provide a full machine-size signed integer, i.e. 32 or 64 bits.

Operations on Int can be much faster than operations on Integer, but overflow and underflow can cause weird bugs. Using Int in an initial design could be considered premature optimization. Unfortunately, many standard library functions (e.g. length, take) use Int.

How do I convert type A to type B?

This is just another way of asking for a function of type A -> B. For example, you can convert Double to Int with round, ceil, or floor. Haskell does not privilege one of these as the conversion.

Does Haskell have type casts?

The word "cast" can mean a lot of different things.

  • You want to convert a value from one type to another, preserving some idea of what it means. For example, you might convert an Int to a Double which represents the same integer. In this case you'd just use a function of type Int -> Double, such as fromIntegral. Haskell doesn't provide special rules or syntax for these functions. See also the previous question.
  • You want to pass a value of more specific type to a function expecting a less specific type. There's no syntax for this in Haskell; you just do it. For example you can pass x :: Int to show :: (Show a) => a -> String, which automatically specializes the type of show to Int -> String. Note that Haskell does not have subtyping, so this only happens in the context of instantiating type variables.
  • You want to use a value of less specific type under the assumption of a more specific type, with a checkable runtime error if they do not match. This is rarely the right way to do things in Haskell, and probably indicates a conceptual / design problem instead. If you really do need such a cast, you can use cast from Data.Typeable. In this case the "checkable runtime error" is cast returning Nothing. Note that Haskell does not have subtyping, so this only happens in the context of instantiating type variables.
  • You want to use a value of less specific type under the assumption of a more specific type, and if the assumption is incorrect, the program is allowed to segfault / silently corrupt data / give the attacker a root shell / send illicit photos to your boss. Also known as "C cast". GHC Haskell has a way to do this, but I dare not speak its name. It's so dangerous and so unlikely to be what you want that it has no place in a general FAQ. You can ask on IRC or read the docs if you have the right kind of morbid curiosity.

How do I convert from one numeric type to another?

Probably using one of these:

fromIntegral :: (Integral a, Num b       ) => a -> b
realToFrac   :: (Real a,     Fractional b) => a -> b

fromIntegral converts to a wider range of types, but realToFrac converts from types which aren't integers.

How do I convert Maybe Int to Int?

Use pattern-matching. If mx :: Maybe Int:

case mx of
    Just x  -> ...
    Nothing -> ...

This forces you to consider the Nothing case, and is the main advantage of Maybe, compared to adding a null value to every type.

See also the functions maybe and fromMaybe in the module Data.Maybe.

Do not use fromJust, because passing Nothing will crash your program with a supremely unhelpful error message. Even when you want to assume the value is not Nothing, you can provide a better error message:

let x = fromMaybe (error "custom error message") mx in ...

If you pattern-match without a Nothing case:

let Just x = mx in ...

you'll at least get a line number in the error message:

*** Exception: foo.hs:2:9-24: Irrefutable pattern failed for pattern Data.Maybe.Just x

How do I convert IO Int to Int?

You can't; they represent totally different things. An Int is an integer. An IO Int is a description of how some IO could be performed, in the future, to produce an integer. The IO hasn't been performed yet, and might never happen or might happen more than once.

See the Introduction to IO.

How do I convert between String (or Text) and ByteString?

String represents a sequence of Unicode characters. ByteString represents a sequence of bytes. There are many different, incompatible ways to represent Unicode characters as bytes. See this article if you're fuzzy on the character / byte distinction.

The module Data.Text.Encoding from the text package provides functions for common Unicode encodings. For more obscure / legacy encodings, see the text-icu package.

How do I catch the error thrown by read on a parse failure?

Don't. Instead use

reads :: (Read a) => String -> [(a, String)]

which returns a list of parses, each with a value and a remaining string. An example:

safeRead :: (Read a) => String -> Maybe a
safeRead x = case reads x of
    [(v,"")] -> Just v
    _        -> Nothing

What's the difference between type, data, and newtype?

type introduces a synonym, which is fully interchangeable with the original type:

type Foo = Int

main = print ((2 :: Int) + (3 :: Foo))

So it provides convenience and documentation, but no additional type checking.

data is used to define new data types, distinct from any existing type.

newtype can mostly be understood as a restricted form of data. You can use newtype when you have exactly one constructor with exactly one field. In those cases, newtype can give better performance than data.

There is, however, a subtle difference between data and newtype semantics, which is why the newtype optimization is not applied automatically.

Making it work

How can I find type errors?

There's no silver bullet, but here are a few useful techniques:

  • Comment out type signatures and see what GHC infers, using :t in GHCi.
  • Add more type signatures, for example inside let. This makes your assumptions clearer, so GHC's error message may better explain how your assumptions are inconsistent.
  • Replace some subexpressions with undefined, which can assume any type.

How can I find bugs that occur at runtime?

With pure functions, correctness is a matter of getting the right output for a given input. If one function gives incorrect results, you test the functions it calls, and so on until the bad code is located. You can perform these tests directly in GHCi, or with the help of a tool like QuickCheck.

You can trace evaluation using Debug.Trace. You'll get a printout when the expression is evaluated. Due to lazy evaluation, this might be at an unexpected time. But this property is useful when debugging problems related to excessive laziness.

GHCi also implements a "simple imperative-style debugger".

Haskell is a natural fit for novel "declarative debugging" tools but to our knowledge, no such tool is production-ready.

Why do I get an "undefined symbol" linker error when compiling?

If you're using GHC 6, you should pass --make so that GHC will automatically link the appropriate Haskell libraries.

How can I get a stack backtrace when my program throws an exception?

The standard stack in GHC Haskell doesn't represent nested function calls. The more informative stack is the profiling cost-center stack, which only exists if your code is built for profiling.

With GHC 7 you can do something like this:

$ ghc -fforce-recomp -prof -auto-all -rtsopts foo.hs

For GHC 6 you should leave off -rtsopts, and you'll probably want --make.

You can then run your program with the -xc RTS option`:

$ ./foo +RTS -xc

How can I do automated unit testing?

See the testing chapter in Real World Haskell.

How can I find and fix performance problems?

See the profiling and optimization chapter in Real World Haskell.

The M-word

See also "What a Monad is not".

I heard Haskell is about monads. I heard that the core feature of Haskell is monads. Is that true?

Absolutely not.

I heard monads are like burritos or space suits full of nuclear waste. Is that true?

These analogies are not helpful. See "Abstraction, intuition, and the 'monad tutorial fallacy"'.

I can use monads but I feel like I still don't "get" them. What am I missing?

You're not necessarily missing anything. "Monad" is just the name of a generic API that applies to many different types. The types implementing the Monad API don't have a lot in common.

You might want to read "Typeclassopedia" to see how Monad fits in with other similar APIs.

Do I need to understand monads in order to do IO?

Not really. "Monad" is the name of a generic API that applies to many different types, including the IO type. If you're only thinking about IO, you don't need to worry about how this API generalizes.

See the Introduction to IO.

What's the difference between State and ST monads?

State s a is just a wrapper for the function type s -> (a, s): a function that takes an "old state" and returns a "new state" along with its result. You can implement State in a few lines of standard Haskell, without any special help from the compiler.

ST gives you true mutable variables with in-place update. You can't implement it yourself in standard Haskell. In GHC, STRef and IORef will behave the same way at runtime. The difference is the extra compile-time safety checking associated with runST.