
MathWorks has the function seqperiod(x) to return the period of sequence x. Is there an equivalent function in Haskell? Michael

On 06/26/2011 04:16 PM, michael rice wrote:
MathWorks has the function seqperiod(x) to return the period of sequence x. Is there an equivalent function in Haskell?
Could you specify what exactly the function is supposed to do? I am pretty sure that a function like seqPeriod :: (Eq a) => [a] -> Maybe Integer -- Nothing iff non-periodic cannot be written. If "sequences" are represented by the terms that define them (or this information is at least accessible), chances might be better, but I would still be interested how such a function works. The problem seems undecidable to me in general. On finite lists (which may be produced from infinite ones via 'take'), a naive implementation could be this:
import Data.List (inits, cycle, isPrefixOf) import Debug.Trace
-- Given a finite list, calculate its period. -- The first parameter controls what is accepted as a generator. See
below.
-- Set it to False when looking at chunks from an infinite sequence. listPeriod :: (Eq a) => Bool -> [a] -> Int listPeriod precisely xs = case filter (generates precisely xs) (inits xs) of -- as (last $ init xs) == xs, this will always suffice. (g:_) -> length g -- length of the *shortest* generator
-- @generates prec xs g@ iff @g@ generates @xs@ by repitition. If @prec@, the -- lengths have to match, too. Consider -- -- >>> generates True [1,2,3,1,2,1,2] [1,2,3,1,2] -- False -- -- >>> generates False [1,2,3,1,2,1,2] [1,2,3,1,2] -- True generates :: (Eq a) => Bool -> [a] -> [a] -> Bool generates precisely xs g = if null g then null xs else (not precisely || length xs `mod` length g == 0) && xs `isPrefixOf` cycle g
-- Steffen

On 27/06/2011, at 8:32 PM, Steffen Schuldenzucker wrote:
On 06/26/2011 04:16 PM, michael rice wrote:
MathWorks has the function seqperiod(x) to return the period of sequence x. Is there an equivalent function in Haskell?
Could you specify what exactly the function is supposed to do?
Google turns up the documentation pretty quickly. "The period p is computed as the minimum length of a subsequence x(1:p) of x that repeats itself continuously every p samples in x." http://www.mathworks.com/help/toolbox/signal/seqperiod.html (The misuse of the word "continuously" is theirs, not mine.) Incomplete repetitions at the end are allowed, so by that definition every finite sequence _has_ a period which can be found in quadratic time. The times I've wanted something like this, the data have been noisy enough that the implied algorithm would have been guaranteed to be useless.

On 26.06.2011 16:16, michael rice wrote:
MathWorks has the function seqperiod(x) to return the period of sequence x. Is there an equivalent function in Haskell?
seqperiod x = fst $ head $ filter (flip List.isPrefixOf x . snd) $ tail $ zip [0..] $ List.tails x This relies on the fact, that p is a period of x, if isPrefixOf (drop p x) x .
participants (4)
-
Henning Thielemann
-
michael rice
-
Richard O'Keefe
-
Steffen Schuldenzucker