
Sorry for the wonky formatting. Here is a corrected version: {-# LANGUAGE GADTs #-} import Control.Category import Prelude hiding (id, (.)) data Flow a b where Id :: Flow a a Compose :: Flow a b -> Flow b c -> Flow a c ShowId :: Show a => Flow a a instance Category Flow where id = Id (.) = flip Compose runFlow :: Flow a b -> a -> IO b runFlow f x = case f of Id -> pure x Compose f1 f2 -> runFlow f1 x >>= runFlow f2 ShowId -> print x >> pure x main :: IO () main = runFlow (ShowId >>> ShowId) () On Fri, Jun 02, 2023 at 03:15:02PM +0100, Tom Ellis wrote:
`Compose` allows you to join together `Flow a b` and `Flow b c`, regardless of what `b` is, even if it doesn't have a `Show` instance, so how can you possibly show it in the recursive call `runFlow f2`?
Changing the definition of `Flow` to
data Flow a b where Id :: Flow a a Compose :: Show b => Flow a b -> Flow b c -> Flow a c
would allow you to write `runFlow` but then you can't define a `Category` instance, since `(.)` is not allowed to be constrained.
Perhaps you want something like this:
{-# LANGUAGE GADTs #-}
import Control.Category import Prelude hiding (id, (.))
data Flow a b where Id :: Flow a a Compose :: Flow a b -> Flow b c -> Flow a c ShowId :: Show a => Flow a a
instance Category Flow where id = Id (.) = flip Compose
runFlow :: Flow a b -> a -> IO b runFlow f x = case f of Id -> pure x Compose f1 f2 -> runFlow f1 x >>= runFlow f2 ShowId -> print x >> pure x
main :: IO () main = runFlow (ShowId >>> ShowId) ()
Tom
On Fri, Jun 02, 2023 at 01:32:47PM +0000, Zoran Bošnjak wrote:
Dear haskell cafe members, I would appreciate a suggestion how to fix compile error on this simple test program (I am using ghc 9.0.2).
The idea is to have 'data Flow a b' unrestricted and create necessary constraints only when running/interpreting the flow. The problem is obviously an intermediate type 'b' in 'Compose', where the 'Show' instance is not deduced. I have a vague clue that some type families might be necessary to propagate Show constraint, or a type class with associated type family, but I don't know exactly how.
---
import Prelude hiding ((.), id) import Control.Category
data Flow a b where Id :: Flow a a Compose :: Flow a b -> Flow b c -> Flow a c
instance Category Flow where id = Id (.) = flip Compose
runFlow :: Show a => Flow a b -> a -> IO b runFlow f x = case f of Id -> print x >> pure x Compose f1 f2 -> runFlow f1 x >>= runFlow f2
main :: IO () main = runFlow (Id >>> Id) ()
---
The error is:
• Could not deduce (Show b1) arising from a use of ‘runFlow’ from the context: Show a bound by the type signature for: runFlow :: forall a b. Show a => Flow a b -> a -> IO b at a02.hs:13:1-42 Possible fix: add (Show b1) to the context of the data constructor ‘Compose’ • In the second argument of ‘(>>=)’, namely ‘runFlow f2’ In the expression: runFlow f1 x >>= runFlow f2 In a case alternative: Compose f1 f2 -> runFlow f1 x >>= runFlow f2 | 16 | Compose f1 f2 -> runFlow f1 x >>= runFlow f2 | ^^^^^^^^^^
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.