Newtype

From HaskellWiki
Revision as of 09:14, 6 July 2007 by Lemming (talk | contribs) (Category:FAQ)
Jump to navigation Jump to search
The printable version is no longer supported and may have rendering errors. Please update your browser bookmarks and please use the default browser print function instead.

One frequent question is what is the difference between data and newtype? The answer has to do with the level of undefinedness that occurs in the values. The following sample code shows how three different data declarations behave with undefined present. This shows the difference in behavior.

Another difference is that newtypes can be compiled to have only the overhead of the wrapped type, probably making them more efficient than data types. And at least GHC has extended the deriving syntax to make usage of newtypes easier.

Newtypes can be used transparently in FFI wrappers, including IO when using GHC.

The Haskell 98 Report defines newtypes in section 4.2.3.

module Foo where

data Foo1 = Foo1 Int    -- Defines Foo1 constructor that lazily refers to an Int
data Foo2 = Foo2 !Int   -- Defines Foo2 constructor that strictly refers to an Int
newtype Foo3 = Foo3 Int -- Defines Foo3 constructor that is synonymous with Int

-- Argument is lazy and ignored, so 
-- undefined does not cause failure since
-- the contructor pattern match succeeds.
x1 = case Foo1 undefined of
     Foo1 _ -> 1		-- 1

-- Argument is strict (because of !), so
-- undefined does cause failure.
x2 = case Foo2 undefined of
     Foo2 _ -> 1		-- undefined

-- The newtype behaves like Int, see yInt below
x3 = case Foo3 undefined of
     Foo3 _ -> 1		-- 1

-- Constructor pattern match fails
y1 = case undefined of
     Foo1 _ -> 1		-- undefined

-- Constructor pattern match fails
y2 = case undefined of
     Foo2 _ -> 1		-- undefined

-- The newtype behaves like Int, there is no
-- constructor at runtime.
y3 = case undefined of
     Foo3 _ -> 1		-- 1

-- Demonstration of Int behavior
int :: Int
int = undefined

yInt = case int of
       _ -> 1                   -- 1