Michael,

On 06/27/2011 01:51 PM, Steffen Schuldenzucker wrote:
>
> Forwarding to -cafe
>
> -------- Original Message --------
> Subject: Re: [Haskell-cafe] Period of a sequence
> Date: Mon, 27 Jun 2011 04:46:10 -0700 (PDT)
> From: michael rice <nowg...@yahoo.com>
> To: Steffen Schuldenzucker <sschuldenzuc...@uni-bonn.de>
>
> Hi Steffen,
>
> Repeating decimals.
>
> 5/7 == 0.714285 714285 7142857 ... Period = 6
>
> It does seem like a difficult problem.
>
> This one is eventually repeating, with Period = 3
>
> 3227/555 = 5.8144 144 144…

why not use the well-known division algorithm: (I hope this is readable)

3227 / 555
= 3227 `div` 555 + 3227 `mod` 555 / 555
= 5 + 452 / 555
= 5 + 0.1 * 4520 / 555
= 5 + 0.1 * (4520 `div` 555 + (4520 `mod` 555) / 555)
= 5 + 0.1 * (8 + 80 / 555)
= 5 + 0.1 * (8 + 0.1 * (800 / 555))
= 5 + 0.1 * (8 + 0.1 * (800 `div` 555 + (800 `mod` 555) / 555))
= 5 + 0.1 * (8 + 0.1 * (1 + 245 / 555))
= 5 + 0.1 * (8 + 0.1 * (1 + 0.1 * 2450 / 555))
= 5 + 0.1 * (8 + 0.1 * (1 + 0.1 * (4 + 230 / 555)))
= 5 + 0.1 * (8 + 0.1 * (1 + 0.1 * (4 + 0.1 * 2300 / 555)))
= 5 + 0.1 * (8 + 0.1 * (1 + 0.1 * (4 + 0.1 * (4 + 80 / 555))))
*whoops*, saw 80 already, namely in line 6. Would go on like that forever if I continued like this, so the final result has to be:

vvv Part before the place where I saw the '80' first
5.8 144 144 144 ...
    ^^^ Part after I saw the '80'

So you could write a recursive function that takes as an accumulating parameter containing the list of numbers already seen:

-- periodOf n m gives the periodic part of n/m as a decimal fraction.
-- (or an empty list if that number has finitely many decimal places)
> periodOf :: (Integral a) => a -> a -> [a]
> periodOf = periodOfWorker []
>   where
>     periodOfWorker seen n m
>         | n `mod` m == 0 = ...
>         | (n `mod` m) `elem` seen = ...
>         | otherwise = ...

--- On *Mon, 6/27/11, Steffen Schuldenzucker
/<sschuldenzuc...@uni-bonn.de>/*wrote:


From: Steffen Schuldenzucker <sschuldenzuc...@uni-bonn.de>
Subject: Re: [Haskell-cafe] Period of a sequence
To: "michael rice" <nowg...@yahoo.com>
Cc: haskell-cafe@haskell.org
Date: Monday, June 27, 2011, 4:32 AM



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


_______________________________________________
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe

_______________________________________________
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe

Reply via email to