[Haskell-cafe] Promoting associated data types
Kosyrev Serge
_deepfire at feelingofgreen.ru
Thu Jun 25 06:44:16 UTC 2015
Good day!
DataKinds doesn't allow promotion of type/data families.
However, in the specific case of associated data families -- aren't
they constrained more, and sufficiently so that the following, for example,
could be made to work without stepping into dangerous territories:
--
{-# LANGUAGE DataKinds #-}
{-# LANGUAGE KindSignatures #-}
{-# LANGUAGE TypeFamilies #-}
{-# LANGUAGE UnicodeSyntax #-}
module M where
class C a where
data D a ∷ *
data I
instance C I where
data D I
class C1 a (b ∷ D I) where
-- ..or, maybe, perhaps even the following:
class C1 a (b ∷ D) where
--
respectfully,
Косырев Серёга
More information about the Haskell-Cafe
mailing list