You can still define a bottom of type !Int
but writing one of type Int#
is more tricky, as we see below.
{-# LANGUAGE MagicHash #-}
import GHC.Exts (Int#)
data BangInt = I !Int#
bot :: BangInt
bot = bot
botUnlifted :: Int#
botUnlifted = botUnlifted
-- error: Top-level bindings for unlifted types aren't allowed
So it seems your function from
can not be implemented, since there is no value you can map bot
to.
You don’t need to know category theory to grasp adjoints. What you need to know is the specialisation order ⊑ (a partial order) in which ⊥ is the least element in any lifted type and x ⊑ y whenever for any function f, if f(x) yields a value z (and does not diverge), f(y) evaluates to z as well. You can also interpret x ⊑ y as “x is a thunk that when forced might become y.” This order can be defined on every Haskell type, lifted or not. The order on Int#
coincides with equality. Every definable function is monotone in this order. This is why there is no from
: Since from
must be monotone and ⊥ is the least element, the value from ⊥
must be below every other element in Int#
, but the latter type has no such element.
This seems to contrast the unpack
function @jaror has defined above, and indeed calling unpack
on ⊥ results in a type error at runtime in GHCi! It really should not be definable in the first place. Can we say that GHC as the Haskell implementation has two kinds of ⊥? There is the domain-theoretic divergence ⊥ as in bot = bot
and the RTS run-time type error ⊥ which is equivalent to the first one in the sense of “does not yield a value” but which other Haskell implementations might not have due to better type-checking. Funnily enough, GHCi can type the expression
(let bot = bot :: Int in unpack bot) :: Int#
but it refuses to bind this expression to a name:
botUnlifted = let bot = bot :: Int in unpack bot
-- error:
-- can't bind a variable of unlifted type: botUnlifted :: Int#
So I think what you are proposing is an annotation expressing that functions restrict to certain sub-types. For every type T, the set T \ {⊥} is a sub-type that may or may not be definable in Haskell. For any function f: X → Y you can ask whether f restricts to a function X \ {⊥} → Y \ {⊥}, or whether the pre-image of Y \ {⊥} under f is contained in X \ {⊥}.