Feryll
Feryll

Reputation: 317

Nested List Appending in Haskell

I'm trying to write a function that will append a given value to the innermost lists of a nested list structure, but I'm running into errors with type when I'm not even sure what the type signature of such a function would be.

digpend a xs = case xs of [_:_] -> map (digpend a) xs
                          [[]]  -> [[a]]
                          xs    -> a:xs

For example,

digpend 555 [ [ [ 5,1,-12,33 ] , [ 6,22 ] ] , [ [ -9,0,9,12,83 ] ] ]

should return

[ [ [ 555,5,1,-12,33 ] , [ 555,6,22 ] ] , [ [ 555,-9,0,9,12,83 ] ] ]

and ideally, it would work on any level of nesting by recursion. Is this allowed?

Upvotes: 3

Views: 940

Answers (3)

Alexandros
Alexandros

Reputation: 3064

If you can/are allowed to define your own data type, you can also use the following:

data Tree a = Leaves [a] | InnerNodes [Tree a] deriving (Show)

digpend :: a -> Tree a -> Tree a
digpend x (Leaves xs) = Leaves $ x:xs
digpend x (InnerNodes []) = InnerNodes [Leaves [x]]
digpend x (InnerNodes xs) = InnerNodes . map (digpend x) $ xs

Some output examples:

*Main> digpend 10 $ InnerNodes [ Leaves [], Leaves [], InnerNodes []]
InnerNodes [Leaves [10],Leaves [10],InnerNodes [Leaves [10]]]
*Main> digpend 555 $ InnerNodes [InnerNodes [Leaves [5, 1, -12, 33], Leaves [6, 22]], InnerNodes [Leaves [-9, 0, 9, 12, 83]]]
InnerNodes [InnerNodes [Leaves [555,5,1,-12,33],Leaves [555,6,22]],InnerNodes [Leaves [555,-9,0,9,12,83]]]

Upvotes: 2

PLL
PLL

Reputation: 1631

Here is a not-entirely-satisfactory implementation, using type classes:

{-# LANGUAGE MultiParamTypeClasses, FlexibleInstances #-}

class DigPend a b where
  digpend :: a -> [b] -> [b]

instance DigPend a a where
  digpend x xs = (x:xs)

instance (DigPend a b) => (DigPend a [b]) where
  digpend x xs = map (digpend x) xs

It works well, as long as the type of the arguments is fully specified:

*Main> digpend (5 :: Int) ([6,7,8] :: [Int])
[5,6,7,8]
*Main> digpend (555 :: Int) ([[[5,1,-12,33],[6,22]],[[-9,0,9,12,83]]] :: [[[Int]]])
[[[555,5,1,-12,33],[555,6,22]],[[555,-9,0,9,12,83]]]
*Main> digpend (5 :: Int) ([] :: [Int])
[5]
*Main> digpend (5 :: Int) ([] :: [[Int]])
[]

However, an invocation like digpend 5 [6,7,8] triggers lots of “ambiguous type variable” errors — a numeric literal like 5 is polymorphic (it can inhabit any instance of Num), and while ghci would usually happily default to Integer, it first tries to solve the type class constraints for DigPend, and at that stage, there is not enough type information for it to know which instance of digpend to apply.

Upvotes: 6

Nikita Volkov
Nikita Volkov

Reputation: 43309

Solving this will require a bit of type-level programming skills and some GHC extensions.

{-# LANGUAGE MultiParamTypeClasses #-}
{-# LANGUAGE FlexibleInstances #-}
{-# LANGUAGE FlexibleContexts #-}
{-# LANGUAGE OverlappingInstances #-}

class Digpend a d where
  digpend :: a -> d -> d

instance (Digpend a d) => Digpend a [d] where
  digpend a list = map (digpend a) list

instance Digpend a [a] where
  digpend a list = a : list

main = do
  -- We have to help the compiler disambiguate the numbers by putting explicit
  -- type signatures:
  print $ digpend 
    (555 :: Int) 
    ([ [ [ 5,1,-12,33 ] , [ 6,22 ] ] , [ [ -9,0,9,12,83 ] ] ] :: [[[Int]]])
  -- In case of specific literals, such as `Char`, it's not a problem though.
  print $ digpend '!' [['a', 'b', 'c'], "def"]

Results in:

[[[555,5,1,-12,33],[555,6,22]],[[555,-9,0,9,12,83]]]
["!abc","!def"]

Upvotes: 4

Related Questions