[Haskell-cafe] Multi-Class monadic type?

Alexander Treptow alexander.treptow at googlemail.com
Wed Feb 3 08:10:52 EST 2010


Hi,
i got a little problem and don't know how to solve that. Hope you can
help me.

code:
----------
module Test where
{-# LANGUAGE Rank2Types, RankNTypes #-}
import Control.Monad.Trans

data TestType = TestType
  {tst :: (Conf a, MonadIO m) => m a}

class Conf a where
  get :: MonadIO m => m a

testFunc :: (forall a. Conf a, MonadIO m => m a) -> TestType
testFunc = TestType
--------------
error:
--------------
Test.hs:11:23
    Class `Conf' used as a type
    In the type signature for `testFunc':
      testFunc :: (forall a. Conf a, (MonadIO m) => m a) -> TestType
--------------

explanation:
I need a data type that creates a record with a member that has no fixed
type, because its not known at compile-time. The Rank2Types language
extension fits that need, but i figured out that i ll need to make that
time monadic to avoid the use of unsafePerformIO in the program that
uses this lib.

Thanks and greetings,
    Alex



More information about the Haskell-Cafe mailing list