0

I have troubles implementing IsList instance for GADT which represents structure of values inside nested arrays. Here is complete code:

{-# LANGUAGE DataKinds         #-}
{-# LANGUAGE FlexibleInstances #-}
{-# LANGUAGE GADTs             #-}
{-# LANGUAGE RankNTypes        #-}
{-# LANGUAGE TypeFamilies      #-}

import GHC.Exts (IsList (..))

data ValType = TInt | TList

data Val (t :: ValType) where
    I :: Int -> Val 'TInt
    L :: [Val a] -> Val 'TList

instance Show (Val t) where
  show (I i) = "I " ++ show i
  show (L a) = show a

instance IsList (Val 'TList) where
    type Item (Val 'TList) = forall a . Val a

    fromList = L
    toList = error "Not implemented!"

I see such error:

GADT.hs:20:10: error:
    • Illegal polymorphic type: forall (a :: ValType). Val a
    • In the type instance declaration for ‘Item’
      In the instance declaration for ‘IsList (Val  'TList)’
   |
20 |     type Item (Val 'TList) = forall a . Val a
   |          ^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^

I partially understand why I have this error. But I would like know if it's possible to implement IsList instance for Val type?

Shersh
  • 9,019
  • 3
  • 33
  • 61
  • Well a `Val 'TList` is either made from a `[Val 'TInt]` or a `[Val 'TList]` and one can’t decide this without inspecting the value. There isn’t a straightforward way to express the type with the definition of `Val` you currently have and there is no way to implement `fromList` in a way that would always work. The type `forall a . Val a` means “if you come up with a type `a` then I will give you a list of `Val a`”, which you clearly don’t satisfy – Dan Robertson Jun 03 '18 at 11:09
  • @DanRobertson but does it really require to inspect value? Types can be known in advance, like `[I 3, I 42, I 10]`. Just need to check that every element of list has same type. I'm okay with having compile time errors when `fromList` can't work because it doesn't know type of value. – Shersh Jun 03 '18 at 11:38
  • Have `data P where P :: Val a -> P` and define functions `[Val a] -> [P]`, `P -> ValType`, and `[P] -> Val 'TList` which throws an error if it’s not possible. Finally you can have `Item (Val 'TList) = P` – Dan Robertson Jun 03 '18 at 11:45
  • @DanRobertson Thanks! I've already have `data AnyValue = forall a . AnyValue (Val a)` which is the same as your `P`. I also thought about this direction of implementation. Though, this approach is not typesafe... I also have `S String` constructor. With `IsString` and `Num` instances it will be possible to write `[3, "foo"]` without static guarantees which I don't like... – Shersh Jun 03 '18 at 11:51
  • 1
    I did say it wouldn’t be safe. I suppose you could also change `ValType` to have `TList ValType`. – Dan Robertson Jun 03 '18 at 11:53
  • When you say nested, what do you mean? With this type, you cannot mix `I`s with `L`s in a single list (like `L [I 1, L [I 1, I 2]]`). Is that ok for what you're looking for? If it's ok for it to continue being like that, I think I might have an idea. (Also, on a different, slightly pedantic, topic: there are no arrays in this code. You only have linked lists in the snippet.) – David Young Jun 03 '18 at 22:02
  • @DavidYoung No, `L [I 1, L [I 1, I 2]]` should not be possible. But this should be possible: `L [L [I 1], L [L [I 1, I 2]]]`. – Shersh Jun 04 '18 at 01:38
  • @Shersh Do you also want `[[I 1], [[I 1, I 2]]]` to work, through `fromList`? If so, I'm pretty sure that would be impossible. – David Young Jun 04 '18 at 02:05
  • @DavidYoung Yeah, I would expect it to work. Okay, if it's not possible. I can live with that. I just hoped there exist some way to achieve this... Should know your limits! – Shersh Jun 04 '18 at 05:38

2 Answers2

1

IsList doesn't seem suited to this since the item type Item l must be determined by the list type l. However, overloading of lists can be pushed further with RebindableSyntax:

{-# LANGUAGE RebindableSyntax, OverloadedLists #-}

fromListN :: _Int -> [Val a] -> Val 'TList
fromListN _ = L

Now [[I 3, I 2]] is sugar for fromListN 1 [fromListN 2 [I 3, I 2]], which reduces to L [L [I 3, I 2]].

We can keep the original behavior using a type class like IsList, but which decouples the item and list types.

class IsList item l where
  fromListN :: Int -> [item] -> l

instance IsList (Val a) (Val 'TList) where
  fromListN _ = L

instance (item ~ item') => IsList item [item'] where
  fromListN _ = id
Li-yao Xia
  • 31,896
  • 2
  • 33
  • 56
1

You are throwing away information by only storing the fact that an L ... contains a list of Val as in its type. If you keep this information around

data ValType = TInt | TList ValType

data Val (t :: ValType) where
    I :: Int     -> Val 'TInt
    L :: [Val a] -> Val ('TList a)

then it becomes possible to implement an instance for the IsList type class from the standard library:

instance IsList (Val ('TList a)) where
    type Item (Val ('TList a)) = Val a

    fromList      = L
    toList (L xs) = xs

-- (For completeness, this example requires the OverloadedLists extension)
example :: String
example = show ([I 1, I 2, I 3] :: Val ('TList TInt))

Also note that you can implement toList. Because this toList has type Val ('TList a) -> [Val a] it cannot be passed a non-list, so the above implementation is not partial. You can verify this type yourself by using a type hole: toList = _. You can also verify that an (attempt at) implementation like the following will give a type error: toList (I x) = undefined.

Every item in the list must have the same type (you cannot have mix integers with lists within a single list, for example), but this was also the case for the original code from the question.

David Young
  • 10,713
  • 2
  • 33
  • 47
  • Thanks, that's a good solution to consider! Unfortunately, it doesn't work to me completely. It should be possible to have list of different types for me. So it's either every element of list is `I` or `L` but if every element of list is `L`, each `L` can contain different types. – Shersh Jun 04 '18 at 01:43