
Hello, I am trying to solve a simple task, but got stuck with double recursion - for some reason not all list elements get processed. Please advice on a simple solution, using plane old recursion :) *** Task:
From a sequence of chars build all possible chains where each chain consists of chars that can be accessed from one to another. For example, given the sequence: "abcde" In table below chars in a left column can access a list of chars in the right column: a | b c d e
b | c d e c | d e d | e Then chains for this example will be: abcde, acde, ade, ae, bcde, bde, be, cde, cd, ce, de *** My incomplete result, which I get running my program (see at the end of this message): ('a','b'),('b','c'),('c','d'),('d','e'), -- abcde, ('c','e'), -- ce, ('b','d'),('d','e'), -- bde, ('b','e') -- be, ('a','c'),('c','d'),('d','e'), -- acde ('c','e'), ('a','d'),('d','e'), -- ade, ('a','e') -- ae Sequence 'abcde' contains 'bcde', 'cde', 'cd', 'de'. How to add all these sub-sequences as a separate sequences in my output? And I have 'ce' sequence duplicated, which I don't need. Also, how to output chains as a list of lists? Such as: [[abcde, acde, ade, ae,] [bcde, bde, be,] [cde, cd, ce,] de]] *** my code test = chains testPairs 'a' [] testPairs = pairs testSeq testSeq = "abcde" -- From a list of '((from,to),1)' pairs build char chains -- Char chain is a list of chars: [from1, to1 = from2, to2 = from3, to3 = from4, ...] -- 'pairList' - a list of pairs chains pairList from chainList = chainWrk (nextTo pairList from) from chainList where chainWrk [] from chainList = chainList chainWrk (to:tos) from chainList = chainWrk tos from (chains pairList to (chainList ++ [(from,to)])) -- Find direct neighbors for 'from' nextTo pairList from = toList (findPairs pairList from) [] -- From a list of '((from,to),1)' pairs build a list of 'to'-s toList [] tos = tos toList (((from,to),len):ps) tos = toList ps (tos ++ [to]) -- From 'pairList' find elements with 'from' equal to 'start' -- 'pairList' is a list of '((from,to),1)' pairs findPairs pairList search = filter (flt search) pairList where flt search ((from, to), len) = search == from -- From a sequence of chars buid a list of '((from,to),1)' pairs pairs [] = [] pairs (x:xs) = pairWrk x xs [] ++ pairs xs pairWrk hd [] pairLst = pairLst pairWrk hd (x:xs) pairLst = pairWrk hd xs (pairLst ++ [((hd,x),1)])

For some reason, my previous message got truncated, so I repeat it in hope
that it will come complete this time:
---------- Forwarded message ----------
From: Dmitri O.Kondratiev
From a sequence of chars build all possible chains where each chain consists of chars that can be accessed from one to another. For example, given the sequence: "abcde" In table below chars in a left column can access a list of chars in the right column: a | b c d e
b | c d e c | d e d | e Then chains for this example will be: abcde, acde, ade, ae, bcde, bde, be, cde, cd, ce, de *** My incomplete result, which I get running my program (see at the end of this message): ('a','b'),('b','c'),('c','d'),('d','e'), -- abcde, ('c','e'), -- ce, ('b','d'),('d','e'), -- bde, ('b','e') -- be, ('a','c'),('c','d'),('d','e'), -- acde ('c','e'), ('a','d'),('d','e'), -- ade, ('a','e') -- ae Sequence 'abcde' contains 'bcde', 'cde', 'cd', 'de'. How to add all these sub-sequences as a separate sequences in my output? And I have 'ce' sequence duplicated, which I don't need. Also, how to output chains as a list of lists? Such as: [[abcde, acde, ade, ae,] [bcde, bde, be,] [cde, cd, ce,] de]] *** my code test = chains testPairs 'a' [] testPairs = pairs testSeq testSeq = "abcde" -- From a list of '((from,to),1)' pairs build char chains -- Char chain is a list of chars: [from1, to1 = from2, to2 = from3, to3 = from4, ...] -- 'pairList' - a list of pairs chains pairList from chainList = chainWrk (nextTo pairList from) from chainList where chainWrk [] from chainList = chainList chainWrk (to:tos) from chainList = chainWrk tos from (chains pairList to (chainList ++ [(from,to)])) -- Find direct neighbors for 'from' nextTo pairList from = toList (findPairs pairList from) [] -- From a list of '((from,to),1)' pairs build a list of 'to'-s toList [] tos = tos toList (((from,to),len):ps) tos = toList ps (tos ++ [to]) -- From 'pairList' find elements with 'from' equal to 'start' -- 'pairList' is a list of '((from,to),1)' pairs findPairs pairList search = filter (flt search) pairList where flt search ((from, to), len) = search == from -- From a sequence of chars buid a list of '((from,to),1)' pairs pairs [] = [] pairs (x:xs) = pairWrk x xs [] ++ pairs xs pairWrk hd [] pairLst = pairLst pairWrk hd (x:xs) pairLst = pairWrk hd xs (pairLst ++ [((hd,x),1)])

On Saturday 28 May 2011 13:47:10, Dmitri O.Kondratiev wrote:
Hello, I am trying to solve a simple task, but got stuck with double recursion - for some reason not all list elements get processed. Please advice on a simple solution, using plane old recursion :) *** Task: From a sequence of chars build all possible chains where each chain consists of chars that can be accessed from one to another. For example, given the sequence: "abcde" In table below chars in a left column can access a list of chars in the right column: a | b c d e
b | c d e
c | d e
d | e
Then chains for this example will be: abcde, acde, ade, ae, bcde, bde, be, cde, cd, ce, de
I think import Data.List -- pair the first element with all later elements pairsFrom :: [a] -> [(a,a)] pairsFrom (x:xs) = [(x,y) | y <- xs] pairsFrom [] = [] -- pair each element with all later ones allPairs :: [a] -> [(a,a)] allPairs xs = tails xs >>= pairsFrom -- alternative implementation with exlicit recursion: allPairs (x:xs) = pairsFrom (x:xs) ++ allPairs xs allPairs [] = [] Prelude Data.List> allPairs "abcde" [('a','b'),('a','c'),('a','d'),('a','e'),('b','c'),('b','d'),('b','e'), ('c','d'),('c','e'),('d','e')] does what you want

On Sat, May 28, 2011 at 3:57 PM, Daniel Fischer < daniel.is.fischer@googlemail.com> wrote:
On Saturday 28 May 2011 13:47:10, Dmitri O.Kondratiev wrote:
Hello, I am trying to solve a simple task, but got stuck with double recursion - for some reason not all list elements get processed. Please advice on a simple solution, using plane old recursion :) *** Task: From a sequence of chars build all possible chains where each chain consists of chars that can be accessed from one to another. For example, given the sequence: "abcde" In table below chars in a left column can access a list of chars in the right column: a | b c d e
b | c d e
c | d e
d | e
Then chains for this example will be: abcde, acde, ade, ae, bcde, bde, be, cde, cd, ce, de
I think
import Data.List
-- pair the first element with all later elements pairsFrom :: [a] -> [(a,a)] pairsFrom (x:xs) = [(x,y) | y <- xs] pairsFrom [] = []
-- pair each element with all later ones allPairs :: [a] -> [(a,a)] allPairs xs = tails xs >>= pairsFrom
-- alternative implementation with exlicit recursion:
allPairs (x:xs) = pairsFrom (x:xs) ++ allPairs xs allPairs [] = []
Prelude Data.List> allPairs "abcde" [('a','b'),('a','c'),('a','d'),('a','e'),('b','c'),('b','d'),('b','e'), ('c','d'),('c','e'),('d','e')]
does what you want
Thanks for simple and beautiful code to get all pairs. Yet, I need to get to the next step - from all pairs to build all chains, to get as a result a list of lists: [[abcde, acde, ade, ae,] [bcde, bde, be,] [cde, cd, ce,] de]] This is where I got stuck.

On Saturday 28 May 2011 14:19:18, Dmitri O.Kondratiev wrote:
Thanks for simple and beautiful code to get all pairs. Yet, I need to get to the next step - from all pairs to build all chains, to get as a result a list of lists:
[[abcde, acde, ade, ae,] [bcde, bde, be,] [cde, cd, ce,] de]]
This is where I got stuck.
-- instead of pairing with a single later element, we cons with the -- tail beginning at that later element chainsFromFirst :: [a] -> [[a]] chainsFromFirst (x:xs) = [x:ys | ys <- init (tails xs)] chainsFromFirst [] = [] -- we need init (tails xs) becuase we don't want the final empty tail allChains :: [a] -> [[a]] allChains xs = tails xs >>= chainsFromFirst -- we could use init (tails xs) here too, but that is not necessary

On 5/28/11 8:31 AM, Daniel Fischer wrote:
On Saturday 28 May 2011 14:19:18, Dmitri O.Kondratiev wrote:
Thanks for simple and beautiful code to get all pairs. Yet, I need to get to the next step - from all pairs to build all chains, to get as a result a list of lists:
[[abcde, acde, ade, ae,] [bcde, bde, be,] [cde, cd, ce,] de]]
This is where I got stuck.
-- instead of pairing with a single later element, we cons with the -- tail beginning at that later element chainsFromFirst :: [a] -> [[a]] chainsFromFirst (x:xs) = [x:ys | ys<- init (tails xs)] chainsFromFirst [] = []
-- we need init (tails xs) becuase we don't want the final empty tail
allChains :: [a] -> [[a]] allChains xs = tails xs>>= chainsFromFirst
-- we could use init (tails xs) here too, but that is not necessary
The variant I came up with was: allChains xs = do y:ys <- tails xs zs@(_:_) <- tails ys return (y:zs) Which is essentially the same. I only very rarely use list comprehensions, but if you prefer that syntax you can always do: allChains xs = [ (y:zs) | y:ys <- tails xs, zs@(_:_) <- tails ys ] -- Live well, ~wren

On 28/05/2011, at 11:47 PM, Dmitri O.Kondratiev wrote:
Hello, I am trying to solve a simple task, but got stuck with double recursion - for some reason not all list elements get processed. Please advice on a simple solution, using plane old recursion :) *** Task: From a sequence of chars build all possible chains where each chain consists of chars that can be accessed from one to another. For example, given the sequence: "abcde" In table below chars in a left column can access a list of chars in the right column: a | b c d e b | c d e c | d e d | e
You have a set S of characters and a binary relation R ⊆ S × S and a chain is a sequence [x0,x1,...] such that x[0] ∈ S and for all i > 0, x[i-1] R x[i] Can a chain be empty? What constraints on R do you have that lead you to think that each chain is finite, or are you expecting infinite chains as well? (S = {a}, R = {(a,a)} admits chains of any length, including ones that do not terminate.)

On Mon, May 30, 2011 at 11:26 AM, Richard O'Keefe
On 28/05/2011, at 11:47 PM, Dmitri O.Kondratiev wrote:
Hello, I am trying to solve a simple task, but got stuck with double recursion - for some reason not all list elements get processed. Please advice on a simple solution, using plane old recursion :) *** Task: From a sequence of chars build all possible chains where each chain consists of chars that can be accessed from one to another. For example, given the sequence: "abcde" In table below chars in a left column can access a list of chars in the right column: a | b c d e b | c d e c | d e d | e
You have a set S of characters and a binary relation R ⊆ S × S and a chain is a sequence [x0,x1,...] such that x[0] ∈ S and for all i > 0, x[i-1] R x[i]
Can a chain be empty?
What constraints on R do you have that lead you to think that each chain is finite, or are you expecting infinite chains as well? (S = {a}, R = {(a,a)} admits chains of any length, including ones that do not terminate.)
Sorry, I missed to specify that char sequences and chains are finite. Every chain is built from chars that can be accessed from one to another. Chars are examined proceeding from the beginning of the sequence to its end, and never in the opposite direction. Going always in one direction and being bound with sequence end, makes chains finite.
participants (4)
-
Daniel Fischer
-
Dmitri O.Kondratiev
-
Richard O'Keefe
-
wren ng thornton