[Haskell-cafe] Use of uninstantiated type class

Yves Parès limestrael at gmail.com
Sat Mar 5 02:49:56 CET 2011


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 <limestrael at gmail.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 <ivan.miljenovic at gmail.com>
>
> On 5 March 2011 10:45, Yves Parès <limestrael at gmail.com> 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 at gmail.com
>> IvanMiljenovic.wordpress.com
>>
>
>
-------------- next part --------------
An HTML attachment was scrubbed...
URL: <http://www.haskell.org/pipermail/haskell-cafe/attachments/20110305/fcceab2c/attachment.htm>


More information about the Haskell-Cafe mailing list