{- Print out a list of small semiprimes. 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 . -} {-# LANGUAGE ScopedTypeVariables, LambdaCase #-} 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 Primality2(primes); 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{ [] -> semiprimes & take 1000 & out; [n] -> semiprimes & take (read n) & out; _ -> undefined; }; trim_list :: [Integer] -> [Integer]; trim_list l = takeWhile (\x -> x < 2*head l) l; form_products :: [Integer] -> [Prod]; form_products l = map (\x -> Prod (head l) x) l; data Prod = Prod Integer Integer; val :: Prod -> Integer; val (Prod x y) = x*y; instance Eq Prod where{ (==) x y = val x == val y; }; instance Ord Prod where{ compare x y = compare (val x)(val y); }; instance Show Prod where{ showsPrec _precedence p@(Prod x y) rest = show (val p) ++ "=" ++ show x ++ "*" ++ show y ++ rest; }; semiprimelists :: [[Integer]]; semiprimelists = primes () & tails & map trim_list; semiprimes :: [Prod]; semiprimes = semiprimelists & map form_products & Ordered.mergeAll; out :: [Prod] -> IO (); --out = map show >>> unwords >>> putStrLn; out = mapM_ print; } --end