In my library I want to expose the name of the underlying monadic state to the user in the documentation, but I don't want them to be able to tear it apart -- I want to make a black box.
So, I started with fully working code using the following type alias:
type Surge e c z m = ErrorT (Failure z) (ReaderT (SurgeChan e c) (Parser' ByteString m))
Then, in order to make it more robust I changed it into a newtype
and enabled GeneralizedNewtypeDeriving
:
newtype Surge e c z m a = Surge
{ runSurge' :: ErrorT (Failure z) (ReaderT (SurgeChan e c) (Parser' ByteString m)) a }
deriving (Monad, Applicative, Functor)
I had some other code which needed to be adjusted like so:
res <- flip St.evalStateT prod . flip runReaderT sc . runErrorT $ pipeline
==>
res <- flip St.evalStateT prod . flip runReaderT sc . runErrorT . runSurge' $ pipeline
Unfortunately, for some reason not all the code would typecheck after I made the type
->newtype
change. This part of the code in-particular:
{-# INLINE decodeAndHandlePacket #-}
decodeAndHandlePacket
= handlePacket ~< errorP (lift.lift.liftM (first DecodeFailure) . decodeGet $ decodePacket)
... now fails to typecheck with quite a long error, whereas it had not before:
src/Surge/Internal.hs:101:27:
Couldn't match type ‘ErrorT
(Failure z0) (t0 (St.StateT (Producer ByteString m0 x0) m0))’
with ‘Surge e c z m’
Expected type: Proxy a' a () p' (Surge e c z m) ByteString
Actual type: Proxy
a'
a
()
p'
(ErrorT
(Failure z0) (t0 (St.StateT (Producer ByteString m0 x0) m0)))
ByteString
Relevant bindings include
decodeAndHandlePacket :: Proxy a' a () p' (Surge e c z m) ()
(bound at src/Surge/Internal.hs:100:5)
handleCommand :: Handler c p' (Surge e c z m)
(bound at src/Surge/Internal.hs:84:7)
handleEvent :: Handler e p' (Surge e c z m)
(bound at src/Surge/Internal.hs:84:7)
handlePacket :: Handler ByteString p' (Surge e c z m)
(bound at src/Surge/Internal.hs:84:7)
stage :: Stage ByteString p' e c (Surge e c z m)
-> Producer ByteString (Surge e c z m) ()
(bound at src/Surge/Internal.hs:84:1)
In the second argument of ‘(~<)’, namely
‘errorP
(lift . lift . liftM (first DecodeFailure) . decodeGet
$ decodePacket)’
In the expression:
handlePacket
~<
errorP
(lift . lift . liftM (first DecodeFailure) . decodeGet
$ decodePacket)
I have no idea what to do. Both sides look identical to me.
Full code available at http://lpaste.net/109472 . Thanks.
You want
decodeAndHandlePacket
= handlePacket ~< hoist Surge (errorP (lift.lift.liftM (first DecodeFailure) . decodeGet $ decodePacket))
Note that the return type of the call to errorP
is
Proxy a'0 a0 () p' (ErrorT (Failure ...)) ByteString
and you want to replace the fifth parameter with the newtype, i.e.
Proxy a'0 a0 () p' (Surge e c z m) ByteString
This newtype is a monad (a type constructor) and you need to "hoist
" the action in the (ErrorT (Failure ...))
into the (Surge ...)
monad.