Newtype: Difference between revisions
NeilMitchell (talk | contribs) No edit summary |
(Add more links and a bit more example) |
||
Line 1: | Line 1: | ||
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. | 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 [http://www.haskell.org/ghc/dist/current/docs/users_guide/type-extensions.html#newtype-deriving extended the deriving syntax] to make usage of newtypes easier. | |||
Newtypes can be used transparently in [http://www.cse.unsw.edu.au/~chak/haskell/ffi/ FFI wrappers], including [http://www.haskell.org/ghc/dist/current/docs/users_guide/ffi.html#id3177212 IO] when using GHC. | |||
The Haskell 98 Report defines newtypes in [http://www.haskell.org/onlinereport/decls.html#sect4.2.3 section 4.2.3]. | |||
<haskell> | <haskell> | ||
module Foo where | module Foo where | ||
data Foo1 = Foo1 Int | data Foo1 = Foo1 Int -- Defines Foo1 constructor that lazily refers to an Int | ||
data Foo2 = Foo2 !Int | data Foo2 = Foo2 !Int -- Defines Foo2 constructor that strictly refers to an Int | ||
newtype Foo3 = Foo3 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 | x1 = case Foo1 undefined of | ||
Foo1 _ -> 1 -- 1 | Foo1 _ -> 1 -- 1 | ||
-- Argument is strict (because of !), so | |||
-- undefined does cause failure. | |||
x2 = case Foo2 undefined of | x2 = case Foo2 undefined of | ||
Foo2 _ -> 1 -- undefined | Foo2 _ -> 1 -- undefined | ||
-- The newtype behaves like Int, see yInt below | |||
x3 = case Foo3 undefined of | x3 = case Foo3 undefined of | ||
Foo3 _ -> 1 -- 1 | Foo3 _ -> 1 -- 1 | ||
-- Constructor pattern match fails | |||
y1 = case undefined of | y1 = case undefined of | ||
Foo1 _ -> 1 -- undefined | Foo1 _ -> 1 -- undefined | ||
-- Constructor pattern match fails | |||
y2 = case undefined of | y2 = case undefined of | ||
Foo2 _ -> 1 -- undefined | Foo2 _ -> 1 -- undefined | ||
-- The newtype behaves like Int, there is no | |||
-- constructor at runtime. | |||
y3 = case undefined of | y3 = case undefined of | ||
Foo3 _ -> 1 -- 1 | Foo3 _ -> 1 -- 1 | ||
-- Demonstration of Int behavior | |||
int :: Int | |||
int = undefined | |||
yInt = case int of | |||
_ -> 1 -- 1 | |||
</haskell> | </haskell> |
Revision as of 22:51, 4 September 2006
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