Unboxed type

From HaskellWiki
Revision as of 22:31, 18 March 2021 by Cptwunderlich (talk | contribs) (Updated dead link)
Jump to navigation Jump to search

Unboxed types are types that represent raw values. Unboxed types have kind #.

Note that unboxed types of different storage behaviours (four bytes, eight bytes etc.) are all lumped together under kind #. As a result, type variables must have kinds which are #-free.

Since Haskell values may contain unevaluated thunks in addition to specific values, in general values must be represented by a pointer to a heap-allocated object. This is fairly slow so compilers attempt to replace these boxed values with unboxed raw values when possible. Unboxed values are a feature of some compilers that allows directly manipulating these low level values. Since they behave differently than normal haskell types, generally the type system is extended to type these unboxed values. how it is done is compiler specific.

Compiler Specific

GHC In GHC, by convention(?), unboxed values have a hash mark as a suffix to their name. For instance, the unboxed reprsentation of 42 is 42#. There are some restrictions to their use. In particular, you can't pass them to polymorphic functions (like show or ($) for instance).

In this example, I# is a constructor that takes an unboxed integer and returns the Int that we know and love.

module Main where
import GHC.Exts

showUnboxedInt :: Int# -> String
showUnboxedInt n = (show $ I# n) ++ "#"

Here we wrap the unboxed Int n with the I# constructor and show the regular-old Int, with a hash mark on the end.

JHC

Jhc unboxed values behave similarly to ghc but with some differences, jhc doesn't allow the # in identifiers so by convention uses a trailing underscore to indicate an unboxed type. However it does use the trailing hash for unboxed literals like ghc.

In addition jhc allows a limited polymorphism on unboxed values, they may be used polymorphically but if an exact type is not determined at the end of typechecking, they are defaulted to specific unboxed types. So 1# can be a Bits8_, Int_ or Bool_. The rules for when polymorphic unboxed types may be used without annotation are the same as for when rank n types can be used.

Unboxed Tuples and Arrays

Unboxed tuples use the syntax (# a,b,c #) and may not be assigned to values, they must be immediately scrutinized or used.

When to use Unboxed Types

...

See Also

  1. See the discussion on unboxed types and primitive operations in the GHC's User's Guide.
  2. See the GHC.Exts module.
  3. See Simon L. Peyton Jones and John Launchbury's paper "Unboxed values as first class citizens".

This page is a work in progress by IsaacJones. More input welcome :)