hans-3.0.1: Network Stack

Safe HaskellSafe
LanguageHaskell2010

Hans.Time

Synopsis

Documentation

nextEvent :: ExpireHeap a -> Maybe UTCTime Source #

The next time that something in the heap will expire, if the heap is non-empty.

dropExpired :: UTCTime -> ExpireHeap a -> ExpireHeap a Source #

Remove all expired entries from the heap.

partitionExpired :: UTCTime -> ExpireHeap a -> (ExpireHeap a, ExpireHeap a) Source #

Given the current time, partition the heap into valid entries, and entries that have expired.

expireAt :: UTCTime -> a -> ExpireHeap a -> (ExpireHeap a, UTCTime) Source #

Add an entry to the ExpireHeap, and return the time of the next expiration event.

expirationDelay :: UTCTime -> ExpireHeap a -> Maybe NominalDiffTime Source #

The amount of time until the top of the heap expires, relative to the time given.

toUSeconds :: NominalDiffTime -> Int Source #

Convert a NominalDiffTime into microseconds for use with threadDelay.

data Entry p a :: * -> * -> * #

Explicit priority/payload tuples. Useful to build a priority queue using a Heap, since the payload is ignored in the Eq/Ord instances.

myHeap = fromList [Entry 2 "World", Entry 1 "Hello", Entry 3 "!"]

==> foldMap payload myHeap ≡ "HelloWorld!"

Constructors

Entry 

Fields

Instances

Functor (Entry p) 

Methods

fmap :: (a -> b) -> Entry p a -> Entry p b #

(<$) :: a -> Entry p b -> Entry p a #

Foldable (Entry p) 

Methods

fold :: Monoid m => Entry p m -> m #

foldMap :: Monoid m => (a -> m) -> Entry p a -> m #

foldr :: (a -> b -> b) -> b -> Entry p a -> b #

foldr' :: (a -> b -> b) -> b -> Entry p a -> b #

foldl :: (b -> a -> b) -> b -> Entry p a -> b #

foldl' :: (b -> a -> b) -> b -> Entry p a -> b #

foldr1 :: (a -> a -> a) -> Entry p a -> a #

foldl1 :: (a -> a -> a) -> Entry p a -> a #

toList :: Entry p a -> [a] #

null :: Entry p a -> Bool #

length :: Entry p a -> Int #

elem :: Eq a => a -> Entry p a -> Bool #

maximum :: Ord a => Entry p a -> a #

minimum :: Ord a => Entry p a -> a #

sum :: Num a => Entry p a -> a #

product :: Num a => Entry p a -> a #

Traversable (Entry p) 

Methods

traverse :: Applicative f => (a -> f b) -> Entry p a -> f (Entry p b) #

sequenceA :: Applicative f => Entry p (f a) -> f (Entry p a) #

mapM :: Monad m => (a -> m b) -> Entry p a -> m (Entry p b) #

sequence :: Monad m => Entry p (m a) -> m (Entry p a) #

Eq p => Eq (Entry p a) 

Methods

(==) :: Entry p a -> Entry p a -> Bool #

(/=) :: Entry p a -> Entry p a -> Bool #

(Data p, Data a) => Data (Entry p a) 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Entry p a -> c (Entry p a) #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (Entry p a) #

toConstr :: Entry p a -> Constr #

dataTypeOf :: Entry p a -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c (Entry p a)) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (Entry p a)) #

gmapT :: (forall b. Data b => b -> b) -> Entry p a -> Entry p a #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Entry p a -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Entry p a -> r #

gmapQ :: (forall d. Data d => d -> u) -> Entry p a -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> Entry p a -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> Entry p a -> m (Entry p a) #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Entry p a -> m (Entry p a) #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Entry p a -> m (Entry p a) #

Ord p => Ord (Entry p a) 

Methods

compare :: Entry p a -> Entry p a -> Ordering #

(<) :: Entry p a -> Entry p a -> Bool #

(<=) :: Entry p a -> Entry p a -> Bool #

(>) :: Entry p a -> Entry p a -> Bool #

(>=) :: Entry p a -> Entry p a -> Bool #

max :: Entry p a -> Entry p a -> Entry p a #

min :: Entry p a -> Entry p a -> Entry p a #

(Read p, Read a) => Read (Entry p a) 
(Show p, Show a) => Show (Entry p a) 

Methods

showsPrec :: Int -> Entry p a -> ShowS #

show :: Entry p a -> String #

showList :: [Entry p a] -> ShowS #

toUnsortedList :: Heap a -> [a] #

O(n). Returns the elements in the heap in some arbitrary, very likely unsorted, order.

>>> toUnsortedList (fromList [3,1,2])
[1,3,2]
fromList . toUnsortedListid