{- Generalized Fibonacci sequence a[n+width] = a[n] + a[n+1] Copyright 2021 Ken Takusagawa This program is free software: you can redistribute it and/or modify it under the terms of the GNU General Public License as published by the Free Software Foundation, either version 3 of the License, or (at your option) any later version. This program is distributed in the hope that it will be useful, but WITHOUT ANY WARRANTY; without even the implied warranty of MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the GNU General Public License for more details. You should have received a copy of the GNU General Public License along with this program. If not, see . $Id: generalizedfibonaccisequence.hs,v 1.1 2021/03/25 06:49:52 kenta Exp kenta $ -} {-# LANGUAGE ScopedTypeVariables, LambdaCase, PackageImports #-} module Main where { --import System.Environment(getArgs); import Control.Exception(assert); import Debug.Trace(trace); import Data.Function((&)); import Control.Category((>>>)); import Prelude hiding((.),(>>)); --import qualified Prelude; import System.IO(hSetBuffering,stdout,BufferMode(LineBuffering)); --import System.IO(stderr,hPutStrLn); import qualified Data.List as List; --import qualified Control.Monad as Monad; --import Control.Monad(guard); --import qualified Data.Maybe as Maybe; --import qualified Data.Map as Map; import Data.Map(Map); --import qualified Data.Set as Set; import Data.Set(Set); --import qualified Data.Bifunctor as Bifunctor; --import Data.Tuple(swap); --import Control.Monad.GenericReplicate(genericReplicateM); -- igenericReplicateM --import Data.Functor((<&>)); --foreach = flip map --import qualified Data.Bifunctor as Bifunctor; -- (first, second) import qualified Data.Sequence as Sequence; import qualified Data.Foldable as Foldable; main :: IO(); main = do{ Sequence.fromList [3,20,100] & iterate forward & take 4 & markdownlist; onezero 5 & iterate forward & take 18 & markdownlist; ones 5 & iterate forward & take 17 & markdownlist; ones 10 & positiveprelude & markdownlist; ones 11 & positiveprelude & markdownlist; map firstmonotonic [2..9] & markdownlist; firstmonotonic 8 & positiveprelude & markdownlist; firstmonotonic 19 & positiveprelude & markdownlist; firstmonotonic 201 & positiveprelude & head & return & markdownlist; }; type Ii = Integer; -- useful for (id :: Endo Integer) to assert a type in a pipeline type Endo a = a->a; -- to avoid the redundancy warning trace_placeholder :: (); trace_placeholder = (trace,assert,printlines) & (id >>> error) "trace_placeholder"; -- ghc -O2 -fno-ignore-asserts printlines :: [String] -> IO(); printlines l = do { hSetBuffering stdout LineBuffering; mapM_ putStrLn l; }; showlines :: (Show a) => [a] -> IO(); showlines = map show >>> printlines; mystart :: Statevector; mystart = Sequence.fromList [1,1,1,1,1,1,1]; type Statevector = Sequence.Seq Ii; forward :: Statevector -> Statevector; forward (a Sequence.:<| rest@(b Sequence.:<| _)) = rest Sequence.|> (a+b); forward _ = undefined; backward :: Statevector -> Statevector; backward (rest@(a Sequence.:<| _) Sequence.:|> c) = (c-a) Sequence.<| rest; backward _ = undefined; isnonnegative :: Statevector -> Bool; isnonnegative = fmap (\x -> x>=0) >>> and ; ismonotonic :: (Ii -> Ii -> Bool) -> Statevector -> Bool; ismonotonic isordered l = Sequence.zipWith isordered l (seqtail l) & and; seqtail :: Sequence.Seq a -> Sequence.Seq a; seqtail (_ Sequence.:<| t) = t; seqtail Sequence.Empty = undefined; -- or: (note: no warning that the following code cannot be reached) seqtail l = Sequence.tails l & flip Sequence.index 1; goodmonotonic :: Statevector -> Bool; goodmonotonic l = ismonotonic (<) l && (forward l & ismonotonic (<)); findgoodmonotonic :: [Statevector] -> Statevector; findgoodmonotonic = dropWhile (goodmonotonic >>> not) >>> head; iteratetogoodmonotonic :: Statevector -> Statevector; iteratetogoodmonotonic = iterate forward >>> findgoodmonotonic; incsequences :: Int -> [Statevector]; incsequences size = enumFrom 0 & List.tails & map (take size >>> Sequence.fromList); firstmonotonic :: Int -> Statevector; firstmonotonic = incsequences >>> findgoodmonotonic; positiveprelude :: Statevector -> [Statevector]; positiveprelude = iterate backward >>> takeWhile isnonnegative >>> reverse; markdownlist :: [Statevector] -> IO(); markdownlist l = do{ map (Foldable.toList >>> show) l & List.intersperse " \n" & mapM_ putStr; putStrLn""; putStrLn""; }; ones :: Int -> Statevector; ones = flip replicate 1 >>> Sequence.fromList; onezero :: Int -> Statevector; onezero n = if n>0 then 1:(replicate (n-1) 0) & Sequence.fromList else undefined; lengthtogoodmonotonic :: Statevector -> Int; lengthtogoodmonotonic = iterate forward >>> takeWhile (goodmonotonic >>> not) >>> length; } --end