I would like to have a heterogeneous list of String
and [String]
, as such:
strs = ["h", ["x", "y"], "i", ["m", "n", "p"]]
I know I can do this with a custom data type:
data EitherOr t = StringS t | StringL [t]
eitherOrstrs :: [EitherOr String]
eitherOrstrs = [StringS "h", StringL ["x", "y"], StringS "i", StringL ["m", "n", "p"]]
But I'm curious as to whether this is possible without any boilerplate, as in strs
above.
So far I've tried:
{-# LANGUAGE ExistentialQuantification #-}
class Listable a where
toListForm :: [String]
instance Listable String where
toListForm s = [s]
instance Listable [String] where
toListForm = id
strs :: forall a. Listable a => [a]
strs = ["h", ["x", "y"], "i", ["m", "n", "p"]]
But haven't yet found a working method:
The class method ‘toListForm’
mentions none of the type or kind variables of the class ‘Listable a’
When checking the class method: toListForm :: [String]
In the class declaration for ‘Listable’
Does anyone know if this is possible?
This will work for arbitrarily nested lists of strings with a few extension tricks:
{-# LANGUAGE TypeFamilies #-}
{-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE OverloadedLists #-}
import GHC.Exts
import Data.String
data MyStringListThingy
= String String
| List [MyStringListThingy]
deriving (Eq, Show)
instance IsString MyStringListThingy where
fromString = String
instance IsList MyStringListThingy where
type Item MyStringListThingy = MyStringListThingy
fromList = List
fromListN _ = List
toList (String s) = [String s]
toList (List ss) = ss
strs :: MyStringListThingy
strs = ["h", ["x", "y"], "i", ["m", "n", "p", ["q", ["r", "s"]]]]
You need at least GHC 7.8 for this though, possibly 7.10 (I haven't tested with 7.8).
This isn't precisely getting away without boilerplate, the compiler puts implicit function calls in front of each of those literals:
strs = fL [fS "h", fL [fS "x", fS "y"], fS "i", fL [fS "m", fS "n", fS "p", fL [fS "q", fL [fS "r", fS "s"]]]]
where
fL = fromList
fS = fromString
Although without the fL
and fS
aliasing, I only did that so I wouldn't have to type so much. It only feels boilerplate-free because the compiler puts those function calls in there for you, but you still will have the overhead of turning those values into MyStringListThingy
.
You could probably get away with heterogeneous lists of numbers using this trick as well, since numeric literals are also polymorphic, which is what the OverloadedStrings
and OverloadedLists
extensions do for those literals as well. By making a type that wraps lists and strings, then instances the requisite typeclasses you allow Haskell to cast from those literals to your custom type. The TypeFamilies
extension is necessary for the IsList
instance only. If you want to play with it in GHCi you'll have to enable all these extensions there as well, but it definitely works.
A more generic implementation would be
{-# LANGUAGE FlexibleInstances #-}
{-# LANGUAGE TypeFamilies #-}
{-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE OverloadedLists #-}
import GHC.Exts
import Data.String
data NestedList a
= Item a
| List [NestedList a]
deriving (Eq, Show)
instance IsList (NestedList a) where
type Item (NestedList a) = NestedList a
fromList = List
fromListN _ = List
toList (List xs) = xs
toList item = [item]
instance IsString (NestedList String) where
fromString = Item
instance Num a => Num (NestedList a) where
fromInteger = Item . fromInteger
The Num
instance doesn't implement everything it needs to, just enough to show off that this works
> [1, [2, 3]] :: NestedList Int
List [Item 1, List [Item 2, Item 3]]
I wouldn't recommend using this in real code, though.