How recursively call subsequences in haskell

418 views Asked by At

I tried to make recursive function which call the subsequences and I had got some errors.

My Code:

recursive 1 list = subsequences list
recursive n list = subsequences (recursive (n-1) list)

Error:

Occurs check: cannot construct the infinite type: a1 ~ [a1]
    Expected type: [a1]
      Actual type: [[a1]]

    Relevant bindings include
      recursive :: a -> t -> [[a1]] (bound at p.hs:6:1)
    In the first argument of ‘subsequences’, namely
      ‘(recursive (n - 1) list)’
    In the expression: subsequences (recursive (n - 1) list)

Could you help me to solve this problem or find another way to call subsequences n times?

Sorry for my bad English

3

There are 3 answers

1
luqui On BEST ANSWER

I haven't worked with polymorphic recursion much, so I wanted to try this. Here's what I got:

{-# LANGUAGE DeriveFunctor #-}

import Data.List (subsequences)

-- Any multiply-nested list such as a, [a], [[a]], [[[a]]], ...
data MultiList a
  = Leaf a
  | Nest (MultiList [a])
  deriving (Show, Functor)

recursive :: Int -> [a] -> MultiList [[a]]
recursive 1 list = Leaf (subsequences list)
recursive n list = Nest (fmap subsequences (recursive (n-1) list))
0
effectfully On

It's pretty straightforward with singletons.

{-# LANGUAGE GADTs, DataKinds, TypeFamilies, UndecidableInstances, TemplateHaskell, TypeOperators #-}

import Data.List
import Data.Singletons.TH
import Data.Singletons.Prelude
import qualified GHC.TypeLits as Lit

$(singletons [d| data Nat = Z | S Nat |])

type family Nested n a where
    Nested  Z    a = a
    Nested (S n) a = [Nested n a]

subsequenceses :: Sing n -> [a] -> [Nested n a]
subsequenceses  SZ     xs = xs
subsequenceses (SS sn) xs = subsequences (subsequenceses sn xs)

type family Lit i where
    Lit 0 = Z
    Lit n = S (Lit (n Lit.- 1))

type SLit n = Sing (Lit n)

main = print $ subsequenceses (sing :: SLit 2) [1..2]

subsequenceses (sing :: SLit 0) xs is xs

subsequenceses (sing :: SLit 1) xs is subsequences xs

subsequenceses (sing :: SLit 2) xs is subsequences (subsequences xs)

and so on.

2
dfeuer On

If I call your function with 1, it will return a list of lists of elements. If I call it with 2, it will return a list of lists of lists of elements. In a dependently typed language, this would be fine, but Haskell is not dependently typed, so you will need to represent the result in some other way, encoding the depth in the result type.