Search code examples
haskellphantom-types

Eliminating phantom types in a list


I'm having some trouble figuring out how to run computations in the ST monad on a list.

import Data.STRef
import Control.Monad.ST

makeST :: Int -> ST s Int
makeST x = do
    r <- newSTRef x
    readSTRef r

main :: IO [Int]
main = pure $ map runST sts
  where sts = map makeST [0..5]

But trying to compile this gives the following error:

    • Couldn't match type ‘ST s0 Int’ with ‘forall s. ST s Int’
      Expected type: ST s0 Int -> Int
        Actual type: (forall s. ST s Int) -> Int
    • In the first argument of ‘map’, namely ‘runST’
      In the second argument of ‘($)’, namely ‘map runST sts’
      In the expression: pure $ map runST sts

If I were running this in the IO monad, this would be a simple matter of replacing pure . map runST with traverse runIO (or whatever), but I haven't figured out how to get around the presence of the phantom type parameter. I suspect the list sts needs to have different type parameters for the different list elements, and hence needs to be a heterogeneous list of some persuation, but wrapping the ST monads just introduces a new error in addition to the old one.

{-# LANGUAGE RankNTypes #-}

newtype WrappedST = WrappedST { unwrap :: forall s. ST s Int }

main :: IO [Int]
main = pure $ map (runST . unwrap) sts
  where sts = map (WrappedST . makeST) [0..5]
    • Couldn't match type ‘ST s1 Int’ with ‘forall s. ST s Int’
      Expected type: ST s1 Int -> WrappedST
        Actual type: (forall s. ST s Int) -> WrappedST
    • In the first argument of ‘(.)’, namely ‘WrappedST’
      In the first argument of ‘map’, namely ‘(WrappedST . makeST)’
      In the expression: map (WrappedST . makeST) [0 .. 5]

What is the best way to handle this issue, where the phantom type variables are eliminated by a function runST and so should be unifiable, but I'm having trouble convincing the typechecker of that?

Note: The actual example I'm trying to figure out involves the R monad in the inline-r package, which also has a phantom type and is eliminated with the function runRegion :: NFData a => (forall s. R s a) -> IO a. I believe this example in the ST monad should also capture the root problem here, and is more widely known.


Solution

  • Perhaps this is good enough:

    import Data.STRef
    import Control.Monad.ST
    
    makeST :: Int -> ST s Int
    makeST x = do
        r <- newSTRef x
        readSTRef r
    
    main :: IO [Int]
    main = pure $ runST (mapM makeST [0..5])
    

    In short, don't store ST actions in a list; instead, use an ST action to compute a list.

    If that isn't good enough for some reason (what reason?), then simply delta-expanding the (.)s in your second example lets it compile:

    {-# LANGUAGE RankNTypes #-}
    import Data.STRef
    import Control.Monad.ST
    
    makeST :: Int -> ST s Int
    makeST x = do
        r <- newSTRef x
        readSTRef r
    
    newtype WrappedST = WrappedST { unwrap :: forall s. ST s Int }
    
    main :: IO [Int]
    main = pure $ map (\x -> runST (unwrap x)) sts
      where sts = map (\x -> WrappedST (makeST x)) [0..5]