Difference between `type` and `newtype` in type checking

Hi, I was studying this post ( http://www.haskellforall.com/2012/12/the-continuation-monad.html) on CPS and I tried the following code: module Main where newtype Cont r a = Cont { runCont :: (a -> r) -> r } onInput :: Cont (IO ()) String onInput f = do s <- getLine f s onInput f main :: IO () main = onInput print I fails to compile: "Couldn't match expected type ‘Cont (IO ()) String’ with actual type ‘(String -> IO a0) -> IO b0’ • The equation(s) for ‘onInput’ have one argument, but its type ‘Cont (IO ()) String’ has none" But I thought Cont a b would be expanded to (b -> a) -> a so that Cont (IO ()) String became (String -> IO ()) -> IO (), and if I give that type using `type` instead of `newtype`, it does type-check: type Cont r a = (a -> r) -> r What am I missing here about Haskell? thanks folks!

Although a newtype has the same representation at runtime as the type
inside, you still have to use the constructor as for a 'data' type. This
makes sense, as it is a *new type*, whose values must be distinguished from
those of the inner type, and the only way to do that is if they are
decorated with a constructor.
On Mon, Sep 10, 2018 at 5:55 PM Rodrigo Stevaux
Hi, I was studying this post ( http://www.haskellforall.com/2012/12/the-continuation-monad.html) on CPS and I tried the following code:
module Main where
newtype Cont r a = Cont { runCont :: (a -> r) -> r }
onInput :: Cont (IO ()) String onInput f = do s <- getLine f s onInput f
main :: IO () main = onInput print
I fails to compile:
"Couldn't match expected type ‘Cont (IO ()) String’ with actual type ‘(String -> IO a0) -> IO b0’ • The equation(s) for ‘onInput’ have one argument, but its type ‘Cont (IO ()) String’ has none"
But I thought Cont a b would be expanded to (b -> a) -> a so that Cont (IO ()) String became (String -> IO ()) -> IO (), and if I give that type using `type` instead of `newtype`, it does type-check:
type Cont r a = (a -> r) -> r
What am I missing here about Haskell?
thanks folks! _______________________________________________ Haskell-Cafe mailing list To (un)subscribe, modify options or view archives go to: http://mail.haskell.org/cgi-bin/mailman/listinfo/haskell-cafe Only members subscribed via the mailman list are allowed to post.
participants (2)
-
Rodrigo Stevaux
-
Ryan Reich