{- Sums recipricals from smallest to largest, using a priority queue. Copyright 2022 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(main) where { import System.Environment(getArgs); import Debug.Trace(trace); import Data.Function((&)); import Control.Category((>>>)); import Prelude hiding((.),(>>)); import qualified Data.PQueue.Min as Pqueue; import Primality2(primes); import qualified Data.Ratio as Ratio; main :: IO(); main = getArgs >>= \case{ ["harmonic",n] -> do { putStr $ n ++ ": " ; makeharmonic (read n) & reduceto1 & print }; ["primes",n] -> do { putStr $ (show $ nthprime $ read n) ++ ": " ; makeprimes (read n) & reduceto1 & print }; _ -> undefined; }; type Ii = Integer; data Expr = Leaf Rational | Plus Expr Expr; value :: Expr -> Rational; value (Leaf x) = x; value (Plus x y) = value x + value y; instance Eq Expr where{ (==) x y = trace ("testing equality between "++show x++ " and "++ show y) $ value x == value y; -- this function is probably not used. }; instance Ord Expr where{ compare x y = compare (value x)(value y) }; instance Show Expr where{ show (Plus x y) = "("++show x++" + "++show y++")"; show (Leaf r) = show (Ratio.numerator r)++"/"++show (Ratio.denominator r); }; recipprime :: Ii -> Expr; recipprime = fromInteger >>> recip >>> Leaf; makeprimes :: Int -> Pqueue.MinQueue Expr; makeprimes n = primes() & take n & map recipprime & Pqueue.fromList; makeharmonic :: Ii -> Pqueue.MinQueue Expr; makeharmonic = enumFromTo 1 >>> map (fromInteger >>> recip >>> Leaf) >>> Pqueue.fromList; reduceto1 :: Pqueue.MinQueue Expr -> Expr; reduceto1 q = let { (a,q2) = Pqueue.deleteFindMin q } in case Pqueue.minView q2 of { Nothing -> a; Just(b,q3) -> reduceto1 $ flip Pqueue.insert q3 $ Plus a b; -- smaller number on the left side of the plus sign }; nthprime :: Int -> Ii; nthprime i = (primes()) !! (i - 1); } --end