[Haskell-cafe] Deep concatenation [Was: Incorrectly inferring type [t]]

oleg at okmij.org oleg at okmij.org
Thu Dec 30 12:52:59 CET 2010


William Murphy wrote:
> I've spent a lot of time trying to write a version of concat, which
> concatenates lists of any "depth":

It is a little bit more involved, but quite possible. The code is not
much longer than the one you wrote (essentially, three lines: one
class and two instance declarations). Here is the complete code:


{-# LANGUAGE MultiParamTypeClasses, FunctionalDependencies #-}
{-# LANGUAGE TypeFamilies, FlexibleInstances #-}
{-# LANGUAGE UndecidableInstances #-}
{-# LANGUAGE OverlappingInstances #-}

module DeepFlat where


class DeepFlat a b | a -> b where
    dflat :: [a] -> [b]

-- If we flatten a list of lists
instance DeepFlat a b => DeepFlat [a] b where
    dflat = concatMap dflat

-- If we are given a list of non-lists
instance a ~ b => DeepFlat a b where
    dflat = id

test1 = dflat "abracadabra"
-- "abracadabra"

test2 = dflat ["abra","cadabra"]

test3 = dflat [["ab","ra"],["cad","abra"]]
test4 = dflat [[["a","b"],["ra"]],[["cad","abra"]]]






More information about the Haskell-Cafe mailing list