nestedMap :: how to implement

Hi everyone,
I had an idea and wanted to implement it
obviously we know map and what it does on a list
but say you have a list of lists, and you wanna map the elements in the deepest sublist
you’d put something like map (map f) xs
but what if you want to generalize this for a an n-nested list?

what if you want to pass any nested list to some function and it always maps the individual elements in
the deepest sublist

So I kinda wanted to make this function
nest :: [[[Integer]]]
nest = [[[1, 1], [2, 2], [3, 3], [4, 4]], [[5, 5], [6, 6], [7, 7], [8, 8]], [[9, 9], [10, 10], [11, 11], [12, 12]]]

nestedMap :: [a] -> Int -> (a -> b) -> [a]
nestedMap [] _ _ = []
nestedMap xs n f
| n > 0 = map nestedMap xs (n - 1) f
| n == 0 = (map f) xs

nest is a test variabel in this code, and nestedMap is supposed to take care of the work
n is basically the degree that you pass along. n eventually hits zero for any nested list
so I basically wanted to create an expression of maps upon maps upon maps and then eventually
applied with f on xs. However this code gives bugs. type wrong this that. probably some parentheses wrong too if I compare it to the actual expression of map (map f) xs for 2 dimensional lists
Is there a way to create something like this?
I’m curious to find out
*** side note: f maps a’s to b’s, yet the final typing is still [a], but yeah I can’t just put [b] right
because it should work for any nested list. Like I don’t wanna just do something static like
[[[a]]] …-> …[[[b]]]

Hi,
The issue here is that you want some type (the type of the nested list) to depend on a value (your n). It’s doable but it requires the use of some dependent types. Basically we need to have n at the type-level using DataKinds and then we need some type-class machinery to handle the recursion:

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

module M where

import Data.Proxy
import GHC.TypeNats
import Data.Kind

-- inductive naturals
data SNat
  = Z
  | S SNat

-- type of a n-level nested list
type family L (n :: SNat) a where
  L Z     a = [a]
  L (S n) a = [L n a]

class NestedMap (n :: SNat) a b where
  nestedMap_ :: Proxy n -> (a -> b) -> L n a -> L n b

instance NestedMap Z a b where
  nestedMap_ _ f xs = map f xs

instance forall n a b.
  ( L n [a] ~ [L n a]
  , L n [b] ~ [L n b]
  , NestedMap n [a] [b]
  ) => NestedMap (S n) a b where
  nestedMap_ _ f xs = nestedMap_ (Proxy :: Proxy n) (map f) xs



-- helper to convert between Nat and SNat
-- (SNat is inductive hence GHC can check that NestedMap instances don't
-- overlap, while it can't with Nat afaik)
type family ToSNat (n :: Nat) where
  ToSNat 0 = Z
  ToSNat n = S (ToSNat (n-1))

-- user friendly interface
nestedMap :: forall n a b. NestedMap (ToSNat n) a b => (a -> b) -> L (ToSNat n) a -> L (ToSNat n) b
nestedMap f xs = nestedMap_ (Proxy :: Proxy (ToSNat n)) f xs

-- examples
nest :: [[[Integer]]]
nest = [[[1, 1], [2, 2], [3, 3], [4, 4]], [[5, 5], [6, 6], [7, 7], [8, 8]], [[9, 9], [10, 10], [11, 11], [12, 12]]]

example1 = nestedMap @2 (+33) nest
example2 = nestedMap @1 length nest

-- > example1
-- [[[34,34],[35,35],[36,36],[37,37]],[[38,38],[39,39],[40,40],[41,41]],[[42,42],[43,43],[44,44],[45,45]]]
--
-- > example2
-- [[2,2,2,2],[2,2,2,2],[2,2,2,2]]
--
-- > :t nestedMap @18
-- nestedMap @18
--   :: (a -> b)
--      -> [[[[[[[[[[[[[[[[[[[a]]]]]]]]]]]]]]]]]]]
--      -> [[[[[[[[[[[[[[[[[[[b]]]]]]]]]]]]]]]]]]]

1 Like

I would choose L Z a = a and nestedMap @0 f x = f x