{- Outputs a sorted list of numbers of the form 26^a * 10^b, and their base-10 logarithm. Copyright 2019 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 . -} {-# LANGUAGE ScopedTypeVariables, LambdaCase, PackageImports #-} module Main where { import System.Environment(getArgs); import Data.Function((&)); import Prelude hiding((.),(>>)); import qualified Data.List as List; import qualified Data.Bifunctor as Bifunctor; import qualified Data.List.Ordered as Ordered; import Data.Ord(comparing); import Text.Printf(printf); type Ii = Integer; main :: IO(); main = getArgs >>= \case{ [] -> mapM_ print1 nums; -- infinite output -- limit to puzzles less than 10^size [size] -> takeWhile (\n -> logn n <= read size * log 10) nums & mapM_ print1; _ -> undefined; }; bases :: [Ii]; bases = [26,10]; data N = N [Ii] deriving (Show,Eq); value :: N -> Ii; value (N x) = zipWith (^) bases x & product; instance Ord N where { compare = comparing value -- OK if the values are not too large -- logn ; }; nums :: [N]; nums = N (map (const 0) bases) : foldr Ordered.union [] (do { index <- zipWith const [0..] bases; -- enumFromTo 0 (length bases -1) return (map (incn index) nums); }); -- We use foldr union and not unionAll because we know the list of -- bases is finite. If it were infinite (e.g., all primes), the -- we would never be able to calculate values for comparison. -- The function below is unsatisfying because splitAt requires linear -- time. However, although using an array would improve this -- subroutine to constant time, the whole algorithm (I think) needs to -- copy the whole array to modify it, so it would still require linear -- time. Note that this is linear time in the number of bases, which -- is typically very small, e.g., 2. -- increment just the nth item in the list incn :: Ii -> N -> N; incn n (N x) = let { (p,q:rest) = List.genericSplitAt n x; } in N $ p ++ (succ q:rest); -- abandoned, don't know how to write this. listofsplitfunctions:: [[a] -> ([a],[a])]; listofsplitfunctions = (\l -> ([],l)): (\(a:x) -> ([a],x)):undefined; -- unused, but inspiration for listofsplitfunctions allsplits :: [a] -> [([a],[a])]; allsplits [] = []; allsplits l@(x:rest) = ([],l):(allsplits rest & map (Bifunctor.first (\z -> x:z))); logn :: N -> Double; logn (N x) = zipWith logpow bases x & sum; logpow :: Ii -> Ii -> Double; logpow base expo = fromInteger expo * log (fromInteger base); print1 :: N -> IO (); print1 n@(N x) = putStrLn $ printf "%.2f" (logn n / log 10) ++ " = log10( " ++ manyzprint x ++ " )"; zprint :: Ii -> Ii -> String; zprint base expo = show base ++ " ^ " ++ printf "%-2d" expo; manyzprint :: [Ii] -> String; manyzprint expos = zipWith zprint bases expos & List.intersperse " * " & concat; } --end