1

He recently started studying Haskell. I have a task: Program the function bubl N A with two computational arguments - the number N and the atom A. The function builds a list of depth N; at the deepest level an element of the list is A, and at any other level the list consists of one element. For example: bubl 3 5 => [[[5]]].

Here is my failed attempt to solve this problem:

bubl :: Integer -> a -> [a] -> [a]
bubl n b list
  | n == 0 = take 1 ([head list] : list)
  | n /= 0 = bubl (n - 1) b (take 1 [head list] : ---list)

I'm just a beginner on this way so I need your help)

Drosden
  • 13
  • 3
  • 4
    You don't. The idea is that the types are fixed at compile time: a list where the depth is depending on a value at run time is thus not possible. For that you use a recursive data structure like a `Tree`: https://hackage.haskell.org/package/containers-0.6.5.1/docs/Data-Graph.html#t:Tree – Willem Van Onsem Mar 26 '22 at 10:52
  • 2
    You can't precisely type a function takes a number N and returns a list-of-lists-of-lists-...(N times nested). The codomain of the function type would depend on the input value, and that's something that Haskell can't do (it would require dependent types as those in Agda/Idris/Coq). One could achieve something similar using GADTs, but that's not a task I would recommend to a beginner. Alternatively, one could use `data T a = Leaf a | Nest [T a]` for the type of "lists nested any number of times", which is tree-like. Not one of the first exercises I would recommend to a beginner, though. – chi Mar 26 '22 at 12:28
  • 3
    @chi Of course, that type can represent many kinds of trees that this exercise can't output. Arguably the best type for representing such a "tree" is just `(Integer, a)`! – amalloy Mar 26 '22 at 13:00
  • A common substitute for multilevel lists in Haskell is the [free monad](https://hackage.haskell.org/package/free), with plain lists as the argument functor. See an example in that [earlier SO question](https://stackoverflow.com/questions/70544106/haskell-nested-function-order). So with a type definition: `data MLL a = Pure a | Free [MLL a] deriving (Eq,Show)`, you could have a general case: `bubl k n = Free [bubl (k-1) n]` and a base case: `bubl 0 n = Pure n` – jpmarinier Mar 26 '22 at 13:17
  • with `data NL a = Z a | N (NL [a])` you can have `Z 1`, `N$Z[1,2]`, `N$N$Z[[1,1],[1],[1]]` etc. notice the depth of list is reflected in the constructor tags in front of it. – Will Ness Mar 27 '22 at 09:40
  • and so, you can define `nnl :: Int -> a -> NL a ; nnl n a | n==0 = Z a | n1 <- (n-1) = N $ nnl n1 [a]` (don't forget to derive `Show` for the data type). you must give the explicit type signature for the polymorphic recursion to work here. then e.g. `nnl 3 5` returns `N (N (N (Z [[[5]]] )))`. (I saw this type first some years ago in a comment by Daniel Wagner IIRC). or you could define e.g. ``nnn :: Int -> a -> NL a ; nnn n a | n==0 = Z a | n1 <- (n-1) = N $ nnn n1 $ replicate n a``. – Will Ness Mar 28 '22 at 15:06

1 Answers1

2

There are a few advanced approaches to solving this problem (see below), but the Haskell type system -- by design -- will prevent you from writing a straightforward solution for this task.

The issue is that a Haskell function generally can't change the type of its result based on an input argument, so you can't write a function definition in Haskell that looks like this:

weird 1 = False            -- type is Bool
weird 2 = "Hello world!"   -- type is String
weird 3 = 42               -- type is Int, say

The bubl function you're trying to write presents a similar problem, because a given list type has a fixed depth, and if the depth depends on the first argument, the type of the result will differ depending on that argument:

bubl 1 5 = [5]     -- type is [Int]
bubl 2 5 = [[5]]   -- type is [[Int]]
bubl 3 5 = [[[5]]] -- type is [[[Int]]]

The simplest solution (though still somewhat advanced for a beginner) is to define a new, user-defined type that can represent "lists" of different depths, but only using a single type. In a real program, the form of this type would depend on the context for using bubl. In an artificial programming task like this, we have to guess. If you wanted to be able to represent "lists" of integers that could be arbitrarily nested to different depths, like a hypothetical "list":

[1,[1,2,3],[[4,[5],[[[[6]]]]]]]   -- note: not a valid Haskell list!

then you'd probably define a Haskell type something like:

data NestedList = Atom Int | Nest [NestedList]

or more generally for nested lists with potentially non-integer atoms:

data NestedList a = Atom a | Nest [NestedList a]

The hypothetical list above would look like this when defined using this new type:

ex1 = Nest [ Atom 1
           , Nest [Atom 1, Atom 2, Atom 3]
           , Nest [Nest [ Atom 4
                        , Nest [Atom 5]
                        , Nest [Nest [Nest [Nest [Atom 6]]]]
                        ]
                  ]
           ]

and you could define a version of bubl that uses this representation:

bubl :: Integer -> a -> NestedList a
bubl 0 b = Atom b
bubl n b = Nest [bubl (n-1) b]

If you write a function to convert a NestedList to a nice string representation:

import Data.List (intercalate)

showNest :: (Show a) => NestedList a -> String
showNest (Atom a) = show a
showNest (Nest xs) = "[" ++ intercalate "," (map showNest xs) ++ "]"

you can get the sort of output you're hoping for:

λ> putStrLn $ showNest (bubl 3 5)
[[[5]]]

There are additional solutions that stick with normal Haskell lists, but they are much more advanced. One clever solution uses type classes to let the caller determine the depth of the list, eliminating the need to pass the depth as an argument:

class Bubl a where
  bubl :: Int -> a
instance Bubl a => Bubl [a] where
  bubl x = [bubl x]
instance Bubl Int where
  bubl = id

main = do
  print (bubl 3 :: Int)
  print (bubl 3 :: [Int])
  print (bubl 3 :: [[[Int]]])

With a lot of complicated extensions you can adapt this solution to take a type-level depth argument, which solves the original task with slightly modified syntax (an @-sign in the call). I'm only including this example to show that it's technically possible with a lot of advanced Haskell features. The complexity illustrates that you're really not supposed to be doing this in "normal" Haskell code.

{-# LANGUAGE AllowAmbiguousTypes #-}
{-# LANGUAGE DataKinds #-}
{-# LANGUAGE FlexibleContexts #-}
{-# LANGUAGE ScopedTypeVariables #-}
{-# LANGUAGE TypeApplications #-}
{-# LANGUAGE TypeFamilies #-}
{-# LANGUAGE TypeOperators #-}
{-# LANGUAGE UndecidableInstances #-}

import GHC.TypeLits

class Bubl a where
  bubl :: Int -> a
instance Bubl a => Bubl [a] where
  bubl x = [bubl x]
instance Bubl Int where
  bubl = id

type family Nested n where
  Nested 0 = Int
  Nested n = [Nested (n-1)]

bubl' :: forall n. (Bubl (Nested n)) => Int -> Nested n
bubl' = bubl

main = do
  print $ bubl' @0 5   -- prints "5"
  print $ bubl' @3 5   -- prints "[[[5]]]"
K. A. Buhr
  • 45,621
  • 3
  • 45
  • 71
  • `data NL a = Z a | N (NL [a])` is also a possibility; it gives us [lists of uniform depth](https://stackoverflow.com/questions/71627381/how-to-create-a-list-of-a-certain-depth-in-haskell/71631522#comment126628309_71627381), which might be closer to what the Q asks for. – Will Ness Apr 09 '22 at 10:16