{-# LANGUAGE FlexibleInstances, MultiParamTypeClasses, FlexibleContexts, UndecidableInstances #-} -- | Generic queue wrapper to transform a min-queue into a max-queue. module Data.Queue.ReverseQueue (Down(..), ReverseQueue) where import Data.Queue.Class newtype Down a = Down {unDown :: a} deriving (Eq) instance Ord a => Ord (Down a) where Down x `compare` Down y = case x `compare` y of LT -> GT EQ -> EQ GT -> LT Down x <= Down y = x >= y Down x >= Down y = x <= y Down x < Down y = x > y Down x > Down y = x < y -- | Wrapper around a generic queue that reverses the ordering on its elements. newtype ReverseQueue q e = RQ {getQueue :: q (Down e)} instance Queuelike (q (Down e)) (Down e) => Queuelike (ReverseQueue q e) e where singleton x = RQ (singleton (Down x)) empty = RQ empty fromList xs = RQ (fromList (map Down xs)) toList (RQ q) = map unDown (toList q) toList_ (RQ q) = map unDown (toList_ q) x `insert` RQ q = RQ (Down x `insert` q) extract (RQ q) = fmap (\ (Down x, q) -> (x, RQ q)) (extract q) peek (RQ q) = fmap unDown (peek q) delete (RQ q) = fmap RQ (delete q) insertAll xs (RQ q) = RQ (insertAll (map Down xs) q) isEmpty (RQ q) = isEmpty q RQ q1 `merge` RQ q2 = RQ (q1 `merge` q2)