Skip to content

Instantly share code, notes, and snippets.

@roman
Last active February 4, 2017 23:14
Show Gist options
  • Star 0 You must be signed in to star a gist
  • Fork 0 You must be signed in to fork a gist
  • Save roman/c5ae36c2287878b889658a87cd2713cd to your computer and use it in GitHub Desktop.
Save roman/c5ae36c2287878b889658a87cd2713cd to your computer and use it in GitHub Desktop.
module Main where
import Data.List (sort, sortBy)
import Control.Applicative
import Control.Monad (forM, replicateM_)
import Data.Set (Set)
import qualified Data.Set as Set
import qualified Data.Sequence as Seq
import qualified Data.Vector (freeze)
import qualified Data.Vector.Unboxed as V
import qualified Data.Vector.Unboxed.Mutable as VM
--------------------------------------------------------------------------------
-- Queue Implementation
type Queue a = Seq.Seq a
emptyQueue = Seq.empty
enqueue a queue = a Seq.<| queue
dequeue queue =
case Seq.viewl queue of
Seq.EmptyL ->
Nothing
a Seq.:< queue1 ->
Just (a, queue1)
nullQueue = Seq.null
--------------------------------------------------------------------------------
compareSets :: Ord a => Set a -> Set a -> Ordering
compareSets a b =
if Set.size a > Set.size b then
GT
else if Set.size a < Set.size b then
LT
else
compare (Set.toAscList a) (Set.toAscList b)
minSet a b =
case compareSets a b of
GT ->
b
LT ->
a
EQ ->
a
reverseFactorization :: Int -> [Int] -> Maybe (Set Int)
reverseFactorization total numbers =
let
queue0 =
enqueue (1, Set.fromList [1]) emptyQueue
step :: (Set Int, Maybe (Set Int)) -> Queue (Int, Set Int) -> (Set Int, Maybe (Set Int))
step (visited, result) queue =
case dequeue queue of
Nothing ->
(visited, result)
Just ((pathTotal, pathSteps), queue1) ->
if pathTotal == total then
step (visited
, (minSet
<$> result
<*> pure pathSteps)
<|> pure pathSteps) queue1
else
let
queue2 =
foldr (\number queueAcc ->
let
number1 = number * pathTotal
in
if number1 > total || Set.member number1 visited then
queueAcc
else
enqueue (number1, Set.insert number1 pathSteps) queueAcc)
queue1
numbers
visited1 =
Set.insert pathTotal visited
in
step (visited1, result) queue2
in
snd $ step (Set.fromList [1], Nothing) queue0
main :: IO ()
main = do
(n:k:_) <- (map read . words) <$> getLine
numbers <- (sort . map read . take k . words) <$> getLine
case reverseFactorization n numbers of
Nothing ->
print (-1)
Just result ->
putStrLn . unwords . map show . Set.toAscList $ result
Sign up for free to join this conversation on GitHub. Already have an account? Sign in to comment