Difference between revisions of "Newtype"

From HaskellWiki
Jump to navigation Jump to search
m (italics are better than bold here)
Line 60: Line 60:
 
must evaluate its argument, even though it seems like the pattern match can't fail: we must check whether <hask>x</hask> is <hask>⊥</hask> or <hask>Any y</hask> for some <hask>y</hask>.
 
must evaluate its argument, even though it seems like the pattern match can't fail: we must check whether <hask>x</hask> is <hask>⊥</hask> or <hask>Any y</hask> for some <hask>y</hask>.
   
This is intrinsic to Haskell's lazy, non-total semantics. The problem is that this means tracking whether a value is wrapped in a constructor or not, which means keeping track of those extra constructors at runtime even when all they do is distinguish an extra bottom value we don't even want. So in order to be consistent, but also allow the exact isomorphism to be preserved, Haskell provides the <hask>newtype</hask> keyword, for the construction of unlifted types. Pattern-matching on a newtype constructor does no work, because there is no separate ⊥ so every value in the type is wrapped in the constructor.
+
This is intrinsic to Haskell's lazy, non-total semantics. The problem is that this means tracking whether a value is wrapped in a constructor or not, which means keeping track of those extra constructors at runtime even when all they do is distinguish an extra bottom value we don't even want. So in order to be consistent, but also allow the exact isomorphism to be preserved, Haskell provides the <hask>newtype</hask> keyword, for the construction of unlifted types. Pattern-matching on a newtype constructor doesn't do any work, because there is no separate ⊥ so every value in the type is wrapped in the constructor.
   
 
== What about strict types? ==
 
== What about strict types? ==

Revision as of 20:44, 11 December 2011

A newtype declaration creates a new type in much the same way as data. The syntax and usage of newtypes is virtually identical to that of data declarations - in fact, you can replace the newtype keyword with data and it'll still compile, indeed there's even a good chance your program will still work. The converse is not true, however - data can only be replaced with newtype if the type has exactly one constructor with exactly one field inside it.

Some examples:

newtype Fd = Fd CInt
-- data Fd = Fd CInt would also be valid

-- newtypes can have deriving clauses just like normal types
newtype Identity a = Identity a
  deriving (Eq, Ord, Read, Show)

-- record syntax is still allowed, but only for one field
newtype State s a = State { runState :: s -> (s, a) }

-- this is *not* allowed:
-- newtype Pair a b = Pair { pairFst :: a, pairSnd :: b }
-- but this is:
data Pair a b = Pair { pairFst :: a, pairSnd :: b }
-- and so is this:
newtype Pair' a b = Pair' (a, b)

Sounds pretty limited! So why does anyone use newtype?

The short version

The restriction to one constructor with one field means that the new type and the type of the field are in direct correspondence:

State :: (s -> (s, a)) -> State s a
runState :: State s a -> (s -> (s, a))

or in mathematical terms they are isomorphic. This means that after the type is checked at compile time, at run time the two types can be treated essentially the same, without the overhead or indirection normally associated with a data constructor. So if you want to declare different type class instances for a particular type, or want to make a type abstract, you can wrap it in a newtype and it'll be considered distinct to the type-checker, but identical at runtime. You can then use all sorts of deep trickery like phantom or recursive types without worrying about GHC shuffling buckets of bytes for no reason.

The messy bits

Why doesn't everyone just use newtype whenever they can, then? Well, quite often they do. But there is a subtle yet sematically significant difference. When we create a data type supposedly isomorphic to Bool like so:

data Any = Any { getAny :: Bool }

we actually find that the isomorphism isn't exact:

Any . getAny $ Any True  = Any True  -- okay, fine
Any . getAny $ Any False = Any False -- also fine
Any . getAny $ Any      = Any     -- so far so good
Any . getAny $          = Any     -- wait a second...

(what's that upside-down T thing?)

The problem is that types declared with the data keyword are lifted - that is, they contain their own ⊥ value that is distinct from all the others. In this example, we have :: Any distinct from Any :: Any. What this means is that the following pattern match:

case x of
  Any _ -> ()

must evaluate its argument, even though it seems like the pattern match can't fail: we must check whether x is or Any y for some y.

This is intrinsic to Haskell's lazy, non-total semantics. The problem is that this means tracking whether a value is wrapped in a constructor or not, which means keeping track of those extra constructors at runtime even when all they do is distinguish an extra bottom value we don't even want. So in order to be consistent, but also allow the exact isomorphism to be preserved, Haskell provides the newtype keyword, for the construction of unlifted types. Pattern-matching on a newtype constructor doesn't do any work, because there is no separate ⊥ so every value in the type is wrapped in the constructor.

What about strict types?

You may notice that a type like

data Identity' a = Identity' !a

has Identity' = and so you might think you have your coveted isomorphism. But all the strictness annotation means is that Identity' really means Identity' $! - the semantics of the type are fundamentally the same, and in particular the case expression still forces the value.

Examples

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

See also

The Haskell 98 Report defines newtypes in section 4.2.3.