Use of uninstantiated type class

Hello, For testing purposes, I am trying to make an overlay to IO which carries a phantom type to ensure a context. I define contexts using empty type classes : class CtxFoo c class CtxBar c The overlay : newtype MyIO c a = MyIO (IO a) Then I define some methods that run only a specific context : runFoo :: (CtxFoo c) => MyIO c a -> IO a runFoo (MyIO x) = x runBar :: (CtxBar c) => MyIO c a -> IO a runBar (MyIO x) = x And then an action that runs in context 'Foo' : someAction :: (CtxFoo c) => MyIO c () someAction = putStrLn "FOO" Then I run it : main = runFoo someAction But obiously, GHC complains that my type 'c' remains uninstantiated : Ambiguous type variable `c' in the constraint: (CtxFoo c) arising from a use of `runFoo' Probable fix: add a type signature that fixes these type variable(s) In the expression: runFoo someAction In an equation for `main': main = runFoo someAction Is there a way to deal with this ? The interest of using type classes and not empty types to represent the contexts is that it stays simple, and that I can do that : someAction2 :: (CtxFoo c, CtxBar c) => MyIO c () someAction2 = putStrLn "FOO and BAR" ... a function that can run in both contexts.

On 5 March 2011 10:45, Yves Parès
Hello,
For testing purposes, I am trying to make an overlay to IO which carries a phantom type to ensure a context. I define contexts using empty type classes :
class CtxFoo c class CtxBar c
The overlay :
newtype MyIO c a = MyIO (IO a)
Then I define some methods that run only a specific context :
runFoo :: (CtxFoo c) => MyIO c a -> IO a runFoo (MyIO x) = x
runBar :: (CtxBar c) => MyIO c a -> IO a runBar (MyIO x) = x
And then an action that runs in context 'Foo' :
someAction :: (CtxFoo c) => MyIO c () someAction = putStrLn "FOO"
Then I run it :
main = runFoo someAction
But obiously, GHC complains that my type 'c' remains uninstantiated :
Ambiguous type variable `c' in the constraint: (CtxFoo c) arising from a use of `runFoo' Probable fix: add a type signature that fixes these type variable(s) In the expression: runFoo someAction In an equation for `main': main = runFoo someAction
Is there a way to deal with this ?
Provide an explicit type signature for either runFoo or someAction; this is the same problem as doing "show . read" in that GHC can't tell which instance to use. -- Ivan Lazar Miljenovic Ivan.Miljenovic@gmail.com IvanMiljenovic.wordpress.com

But I don't have an explicit type to put.
I cound do:
data CtxFooInst
instance CtxFoo CtxFooInst
and declare runFoo as this:
runFoo :: MyIO CtxFooInst a -> IO a
But I loose the ability to make functions that can run several contexts.
2011/3/5 Ivan Lazar Miljenovic
On 5 March 2011 10:45, Yves Parès
wrote: Hello,
For testing purposes, I am trying to make an overlay to IO which carries a phantom type to ensure a context. I define contexts using empty type classes :
class CtxFoo c class CtxBar c
The overlay :
newtype MyIO c a = MyIO (IO a)
Then I define some methods that run only a specific context :
runFoo :: (CtxFoo c) => MyIO c a -> IO a runFoo (MyIO x) = x
runBar :: (CtxBar c) => MyIO c a -> IO a runBar (MyIO x) = x
And then an action that runs in context 'Foo' :
someAction :: (CtxFoo c) => MyIO c () someAction = putStrLn "FOO"
Then I run it :
main = runFoo someAction
But obiously, GHC complains that my type 'c' remains uninstantiated :
Ambiguous type variable `c' in the constraint: (CtxFoo c) arising from a use of `runFoo' Probable fix: add a type signature that fixes these type variable(s) In the expression: runFoo someAction In an equation for `main': main = runFoo someAction
Is there a way to deal with this ?
Provide an explicit type signature for either runFoo or someAction; this is the same problem as doing "show . read" in that GHC can't tell which instance to use.
-- Ivan Lazar Miljenovic Ivan.Miljenovic@gmail.com IvanMiljenovic.wordpress.com

Okay, I found something which I'm sure already exists somewhere:
{-# LANGUAGE TypeFamilies, TypeOperators, EmptyDataDecls #-}
data True
type family a `Or` b :: *
type instance True `Or` a = True
type instance a `Or` True = True
type family Ctx ref impl :: *
data Foo
data Bar
type instance Ctx Foo Foo = True
type instance Ctx Bar Bar = True
runFoo :: MyIO Foo a -> IO a
runBar :: MyIO Bar a -> IO a
fooCtxAction :: (Ctx Foo c) ~ True => MyIO c ()
bothCtxAction :: (Ctx Foo c `Or` Ctx Bar c) ~ True => MyIO c ()
allCtxAction :: MyIO c ()
2011/3/5 Yves Parès
But I don't have an explicit type to put. I cound do:
data CtxFooInst instance CtxFoo CtxFooInst
and declare runFoo as this:
runFoo :: MyIO CtxFooInst a -> IO a
But I loose the ability to make functions that can run several contexts.
2011/3/5 Ivan Lazar Miljenovic
On 5 March 2011 10:45, Yves Parès
wrote: Hello,
For testing purposes, I am trying to make an overlay to IO which carries a phantom type to ensure a context. I define contexts using empty type classes :
class CtxFoo c class CtxBar c
The overlay :
newtype MyIO c a = MyIO (IO a)
Then I define some methods that run only a specific context :
runFoo :: (CtxFoo c) => MyIO c a -> IO a runFoo (MyIO x) = x
runBar :: (CtxBar c) => MyIO c a -> IO a runBar (MyIO x) = x
And then an action that runs in context 'Foo' :
someAction :: (CtxFoo c) => MyIO c () someAction = putStrLn "FOO"
Then I run it :
main = runFoo someAction
But obiously, GHC complains that my type 'c' remains uninstantiated :
Ambiguous type variable `c' in the constraint: (CtxFoo c) arising from a use of `runFoo' Probable fix: add a type signature that fixes these type variable(s) In the expression: runFoo someAction In an equation for `main': main = runFoo someAction
Is there a way to deal with this ?
Provide an explicit type signature for either runFoo or someAction; this is the same problem as doing "show . read" in that GHC can't tell which instance to use.
-- Ivan Lazar Miljenovic Ivan.Miljenovic@gmail.com IvanMiljenovic.wordpress.com

On Sat, 2011-03-05 at 00:51 +0100, Yves Parès wrote:
But I don't have an explicit type to put. I cound do:
data CtxFooInst instance CtxFoo CtxFooInst
and declare runFoo as this:
runFoo :: MyIO CtxFooInst a -> IO a
But I loose the ability to make functions that can run several contexts.
He meant: newtype MyIO c a = MyIO (IO a) data CtxFooInst instance CtxFoo CtxFooInst runMyIO :: CtxFoo c => MyIO c a -> IO a runMyIO (MyIO x) = x someAction :: CtxFoo c => MyIO c () someAction = MyIO (PutStrLn "Foo") main = runMyIO (someAction :: MyIO CtxFooInst ()) In such way you push the abstraction down to main but actions are contex-independent. Regards

On Fri, Mar 4, 2011 at 3:45 PM, Yves Parès
Hello,
For testing purposes, I am trying to make an overlay to IO which carries a phantom type to ensure a context. I define contexts using empty type classes :
class CtxFoo c class CtxBar c
The overlay :
newtype MyIO c a = MyIO (IO a)
Then I define some methods that run only a specific context :
runFoo :: (CtxFoo c) => MyIO c a -> IO a runFoo (MyIO x) = x
runBar :: (CtxBar c) => MyIO c a -> IO a runBar (MyIO x) = x
And then an action that runs in context 'Foo' :
someAction :: (CtxFoo c) => MyIO c () someAction = putStrLn "FOO"
Then I run it :
main = runFoo someAction
But obiously, GHC complains that my type 'c' remains uninstantiated :
Ambiguous type variable `c' in the constraint: (CtxFoo c) arising from a use of `runFoo' Probable fix: add a type signature that fixes these type variable(s) In the expression: runFoo someAction In an equation for `main': main = runFoo someAction
Is there a way to deal with this ? The interest of using type classes and not empty types to represent the contexts is that it stays simple, and that I can do that :
someAction2 :: (CtxFoo c, CtxBar c) => MyIO c () someAction2 = putStrLn "FOO and BAR"
... a function that can run in both contexts.
data X instance CtxFoo X runFoo (someAction :: MyIO X ()) data Y instance CtxFoo Y instance CtxBar Y runFoo (someAction2 :: MyIO Y ()) runBar (someAction2 :: MyIO Y ()) runFoo (someAction :: MyIO Y ()) -- also works since Y provides both a Foo and Bar context) -- ryan
_______________________________________________ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe
participants (4)
-
Ivan Lazar Miljenovic
-
Maciej Marcin Piechotka
-
Ryan Ingram
-
Yves Parès