
Hi all, I want to convert a type level structure to the value level structure of the same shape. This is the simplified example: {-# LANGUAGE AllowAmbiguousTypes #-} {-# LANGUAGE TypeFamilies #-} {-# LANGUAGE DataKinds #-} {-# LANGUAGE UndecidableInstances #-} module Test where import GHC.TypeLits import Data.Kind import Data.Proxy -- This data structure serves both for 'type level' and 'value level'. data Content n s b = ContentRaw | ContentTable [(n, s)] | ContentBool b deriving instance (Show n, Show s, Show b) => Show (Content n s b) -- Convert from types to values. class IsSchema s where type SchemaVal s :: Type schema :: SchemaVal s instance IsSchema 'ContentRaw where type (SchemaVal 'ContentRaw) = Content Integer String Bool schema = ContentRaw instance IsSchema ('ContentTable '[]) where type (SchemaVal ('ContentTable '[])) = Content Integer String Bool schema = ContentTable [] instance ( IsSchema ('ContentTable ts) , t ~ '(n, s), KnownNat n, KnownSymbol s , SchemaVal ('ContentTable ts) ~ Content Integer String Bool ) => IsSchema ('ContentTable (t ': ts)) where type SchemaVal ('ContentTable (t ': ts)) = Content Integer String Bool schema = case schema @('ContentTable ts) of ContentTable lst -> let n = natVal (Proxy @n) s = symbolVal (Proxy @s) in ContentTable ((n,s) : lst) _ -> error "internal error" If I remove the type parameter 'b', 'ContentBool b' and coresponding 'Bool' from the sample, the conversion works as expected.
schema @'ContentRaw ContentRaw
schema @('ContentTable ( '(1,"test1") ': '(2,"test2") ': '[])) ContentTable [(1,"test1"),(2,"test2")]
But for some reason, as soon as I extend the example with 'b' and 'Bool' as shown above, it results in the following error: * Could not deduce (SchemaVal ('ContentTable ts) ~ Content Integer String b0) from the context: (IsSchema ('ContentTable ts), t ~ '(n, s), KnownNat n, KnownSymbol s, SchemaVal ('ContentTable ts) ~ Content Integer String Bool) bound by the instance declaration at test2.hs:(34,5)-(37,43) The type variable `b1' is ambiguous How do I fix it or how do I rewrite it to get the intended result? regards, Zoran