module I1M.ColaDePrioridad
(CPrioridad,
vacia,
inserta,
primero,
resto,
esVacia,
valida
) where
import qualified I1M.Monticulo as M
newtype CPrioridad a = CP (M.Monticulo a)
deriving (CPrioridad a -> CPrioridad a -> Bool
(CPrioridad a -> CPrioridad a -> Bool)
-> (CPrioridad a -> CPrioridad a -> Bool) -> Eq (CPrioridad a)
forall a. Ord a => CPrioridad a -> CPrioridad a -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: forall a. Ord a => CPrioridad a -> CPrioridad a -> Bool
== :: CPrioridad a -> CPrioridad a -> Bool
$c/= :: forall a. Ord a => CPrioridad a -> CPrioridad a -> Bool
/= :: CPrioridad a -> CPrioridad a -> Bool
Eq, Int -> CPrioridad a -> ShowS
[CPrioridad a] -> ShowS
CPrioridad a -> String
(Int -> CPrioridad a -> ShowS)
-> (CPrioridad a -> String)
-> ([CPrioridad a] -> ShowS)
-> Show (CPrioridad a)
forall a. Show a => Int -> CPrioridad a -> ShowS
forall a. Show a => [CPrioridad a] -> ShowS
forall a. Show a => CPrioridad a -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: forall a. Show a => Int -> CPrioridad a -> ShowS
showsPrec :: Int -> CPrioridad a -> ShowS
$cshow :: forall a. Show a => CPrioridad a -> String
show :: CPrioridad a -> String
$cshowList :: forall a. Show a => [CPrioridad a] -> ShowS
showList :: [CPrioridad a] -> ShowS
Show)
vacia :: Ord a => CPrioridad a
vacia :: forall a. Ord a => CPrioridad a
vacia = Monticulo a -> CPrioridad a
forall a. Monticulo a -> CPrioridad a
CP Monticulo a
forall a. Ord a => Monticulo a
M.vacio
inserta :: Ord a => a -> CPrioridad a -> CPrioridad a
inserta :: forall a. Ord a => a -> CPrioridad a -> CPrioridad a
inserta a
v (CP Monticulo a
c) = Monticulo a -> CPrioridad a
forall a. Monticulo a -> CPrioridad a
CP (a -> Monticulo a -> Monticulo a
forall a. Ord a => a -> Monticulo a -> Monticulo a
M.inserta a
v Monticulo a
c)
primero :: Ord a => CPrioridad a -> a
primero :: forall a. Ord a => CPrioridad a -> a
primero (CP Monticulo a
c) = Monticulo a -> a
forall a. Ord a => Monticulo a -> a
M.menor Monticulo a
c
resto :: Ord a => CPrioridad a -> CPrioridad a
resto :: forall a. Ord a => CPrioridad a -> CPrioridad a
resto (CP Monticulo a
c) = Monticulo a -> CPrioridad a
forall a. Monticulo a -> CPrioridad a
CP (Monticulo a -> Monticulo a
forall a. Ord a => Monticulo a -> Monticulo a
M.resto Monticulo a
c)
esVacia :: Ord a => CPrioridad a -> Bool
esVacia :: forall a. Ord a => CPrioridad a -> Bool
esVacia (CP Monticulo a
c) = Monticulo a -> Bool
forall a. Ord a => Monticulo a -> Bool
M.esVacio Monticulo a
c
valida :: Ord a => CPrioridad a -> Bool
valida :: forall a. Ord a => CPrioridad a -> Bool
valida CPrioridad a
_ = Bool
True