[Haskell-cafe] Hidden types and scope
Lana Black
lanablack at amok.cc
Wed Jul 10 15:43:30 UTC 2019
Hello cafe,
While writing some code, I stumbled upon quite an interesting behavior.
See the code example below.
-------------------------------------------------------------
{-# LANGUAGE ExistentialQuantification #-}
{-# LANGUAGE GeneralizedNewtypeDeriving #-}
{-# LANGUAGE RankNTypes #-}
data Wrapper = forall m. Monad m =>
Wrapper { runAction :: forall a. m a -> IO a
, someAction :: String -> m ()
}
newtype MyIO a = MyIO { runIO :: IO a } deriving (Monad)
ex :: Wrapper
ex = Wrapper runIO (\s -> MyIO (putStrLn s))
{- This doesn't work -}
--main :: IO ()
--main = do let Wrapper r a = ex
-- r (a "Hello")
{- This works -}
main :: IO ()
main = case ex of
Wrapper r a -> r (a "Hello")
-------------------------------------------------------------
The idea is to hide the exact type `m` used in the wrapper, making the
wrapper somewhat opaque to the user, while exposing some functionality
and making sure that using `runAction` with the rest of the members of
Wrapper is type-safe and `m` is always the same type within one instance
of Wrapper.
The problem that I ran into is that the first version of `main` doesn't
compile with the following error:
• Couldn't match expected type ‘p’
with actual type ‘forall a. m a -> IO a’
because type variable ‘m’ would escape its scope
This (rigid, skolem) type variable is bound by
a pattern with constructor:
Wrapper :: forall (m :: * -> *).
Monad m =>
(forall a. m a -> IO a) -> (String -> m ()) ->
Wrapper,
in a pattern binding
at wildcards.hs:18:15-25
• In the pattern: Wrapper r a
In a pattern binding: Wrapper r a = ex
In the expression:
do let Wrapper r a = ex
r (a "Hello")
This is repeated for every member of Wrapper that is matched in a let
expression. However, if let expression is replaced with case, everything
builds and works just fine.
Is there a way to make it work with let expressions? That way the code
is a lot cleaner, especially with RecordWildCards involved.
More information about the Haskell-Cafe
mailing list