7.21. Static pointers

The language extension -XStaticPointers adds a new syntactic form static e, which stands for a reference to the closed expression e. This reference is stable and portable, in the sense that it remains valid across different processes on possibly different machines. Thus, a process can create a reference and send it to another process that can resolve it to e.

With this extension turned on, static is no longer a valid identifier.

Static pointers were first proposed in the paper Towards Haskell in the cloud, Jeff Epstein, Andrew P. Black and Simon Peyton-Jones, Proceedings of the 4th ACM Symposium on Haskell, pp. 118-129, ACM, 2011.

7.21.1. Using static pointers

Each reference is given a key which can be used to locate it at runtime with unsafeLookupStaticPtr which uses a global and immutable table called the Static Pointer Table. The compiler includes entries in this table for all static forms found in the linked modules. The value can be obtained from the reference via deRefStaticPtr

The body e of a static e expression must be a closed expression. That is, there can be no free variables occurring in e, i.e. lambda- or let-bound variables bound locally in the context of the expression.

All of the following are permissible:

inc :: Int -> Int
inc x = x + 1

ref1 = static 1
ref2 = static inc
ref3 = static (inc 1)
ref4 = static ((\x -> x + 1) (1 :: Int))
ref5 y = static (let x = 1 in x)

While the following definitions are rejected:

ref6 = let x = 1 in static x
ref7 y = static (let x = 1 in y)

7.21.2. Static semantics of static pointers

Informally, if we have a closed expression

e :: forall a_1 ... a_n . t

the static form is of type

static e :: (Typeable a_1, ... , Typeable a_n) => StaticPtr t

Furthermore, type t is constrained to have a Typeable instance. The following are therefore illegal:

static show                    -- No Typeable instance for (Show a => a -> String)
static Control.Monad.ST.runST  -- No Typeable instance for ((forall s. ST s a) -> a)

That being said, with the appropriate use of wrapper datatypes, the above limitations induce no loss of generality:

{-# LANGUAGE ConstraintKinds           #-}
{-# LANGUAGE DeriveDataTypeable        #-}
{-# LANGUAGE ExistentialQuantification #-}
{-# LANGUAGE Rank2Types                #-}
{-# LANGUAGE StandaloneDeriving        #-}
{-# LANGUAGE StaticPointers            #-}

import Control.Monad.ST
import Data.Typeable
import GHC.StaticPtr

data Dict c = c => Dict
  deriving Typeable

g1 :: Typeable a => StaticPtr (Dict (Show a) -> a -> String)
g1 = static (\Dict -> show)

data Rank2Wrapper f = R2W (forall s. f s)
  deriving Typeable
newtype Flip f a s = Flip { unFlip :: f s a }
  deriving Typeable

g2 :: Typeable a => StaticPtr (Rank2Wrapper (Flip ST a) -> a)
g2 = static (\(R2W f) -> runST (unFlip f))