{-# LANGUAGE ScopedTypeVariables, LambdaCase #-} {- List perfect powers x^y (x<=y) in increasing order. Copyright 2018 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 . -} 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 System.IO(hSetBuffering,stdout,BufferMode(LineBuffering)); --import Data.List; --import Control.Monad; --import Data.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.Ord; import qualified Data.List.Ordered as Ordered; -- to avoid the redundancy warning trace_placeholder :: (); trace_placeholder = (trace,assert) & (id >>> error) "trace_placeholder"; main :: IO(); main = getArgs >>= \case{ [x,y] -> calcss x y & out; [x,y,"length"] -> calcss x y & length & print; _ -> undefined; }; calcss :: String -> String -> [Exp]; calcss x y = all_large_expo & takeWhile (\n -> n <= Exp (read x) (read y)); -- signifying it is the log of a value; data Exp = Exp Integer Integer deriving (Show,Eq); -- log (base ^ expn) expo :: Exp -> Double; expo (Exp base expn) = fromInteger expn * log (fromInteger base); -- inspired by original cunningham table limits maxval :: Exp; maxval = Exp 2 1200; instance Ord Exp where { compare x y = compare (expo x) (expo y); }; pows :: Integer -> [Integer]; pows base = iterate (\x->x*base) 1; -- 4^n = (2^2)^n = 2^(2n), etc. badbases :: [Integer]; badbases = [2..] & map (pows >>> drop 2) & Ordered.unionAll; goodbases :: [Integer]; goodbases = Ordered.minus [2..] badbases ; large_expo :: Integer -> [Exp]; large_expo b = map (Exp b) (enumFrom b); all_large_expo :: [Exp]; all_large_expo = map large_expo goodbases & Ordered.mergeAll; myshow :: Exp -> String; myshow (Exp x y) = (show x)++"^"++(show y); out :: [Exp] -> IO(); out = map myshow >>> unwords >>> putStrLn; } --end