{-# LANGUAGE DeriveAnyClass    #-}
{-# LANGUAGE DeriveFoldable    #-}
{-# LANGUAGE DeriveFunctor     #-}
{-# LANGUAGE DeriveGeneric     #-}
{-# LANGUAGE DeriveTraversable #-}

module Ouroboros.Network.Point
  ( WithOrigin (..)
  , Block (..)
  , origin
  , at
  , block
  , fromWithOrigin
  , withOrigin
  , withOriginToMaybe
  , withOriginFromMaybe
  ) where

import           GHC.Generics (Generic)
import           NoThunks.Class (NoThunks)

import           Cardano.Slotting.Slot

data Block slot hash = Block
  { Block slot hash -> slot
blockPointSlot :: !slot
  , Block slot hash -> hash
blockPointHash :: !hash
  }
  deriving (Block slot hash -> Block slot hash -> Bool
(Block slot hash -> Block slot hash -> Bool)
-> (Block slot hash -> Block slot hash -> Bool)
-> Eq (Block slot hash)
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
forall slot hash.
(Eq slot, Eq hash) =>
Block slot hash -> Block slot hash -> Bool
/= :: Block slot hash -> Block slot hash -> Bool
$c/= :: forall slot hash.
(Eq slot, Eq hash) =>
Block slot hash -> Block slot hash -> Bool
== :: Block slot hash -> Block slot hash -> Bool
$c== :: forall slot hash.
(Eq slot, Eq hash) =>
Block slot hash -> Block slot hash -> Bool
Eq, Eq (Block slot hash)
Eq (Block slot hash)
-> (Block slot hash -> Block slot hash -> Ordering)
-> (Block slot hash -> Block slot hash -> Bool)
-> (Block slot hash -> Block slot hash -> Bool)
-> (Block slot hash -> Block slot hash -> Bool)
-> (Block slot hash -> Block slot hash -> Bool)
-> (Block slot hash -> Block slot hash -> Block slot hash)
-> (Block slot hash -> Block slot hash -> Block slot hash)
-> Ord (Block slot hash)
Block slot hash -> Block slot hash -> Bool
Block slot hash -> Block slot hash -> Ordering
Block slot hash -> Block slot hash -> Block slot hash
forall a.
Eq a
-> (a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
forall slot hash. (Ord slot, Ord hash) => Eq (Block slot hash)
forall slot hash.
(Ord slot, Ord hash) =>
Block slot hash -> Block slot hash -> Bool
forall slot hash.
(Ord slot, Ord hash) =>
Block slot hash -> Block slot hash -> Ordering
forall slot hash.
(Ord slot, Ord hash) =>
Block slot hash -> Block slot hash -> Block slot hash
min :: Block slot hash -> Block slot hash -> Block slot hash
$cmin :: forall slot hash.
(Ord slot, Ord hash) =>
Block slot hash -> Block slot hash -> Block slot hash
max :: Block slot hash -> Block slot hash -> Block slot hash
$cmax :: forall slot hash.
(Ord slot, Ord hash) =>
Block slot hash -> Block slot hash -> Block slot hash
>= :: Block slot hash -> Block slot hash -> Bool
$c>= :: forall slot hash.
(Ord slot, Ord hash) =>
Block slot hash -> Block slot hash -> Bool
> :: Block slot hash -> Block slot hash -> Bool
$c> :: forall slot hash.
(Ord slot, Ord hash) =>
Block slot hash -> Block slot hash -> Bool
<= :: Block slot hash -> Block slot hash -> Bool
$c<= :: forall slot hash.
(Ord slot, Ord hash) =>
Block slot hash -> Block slot hash -> Bool
< :: Block slot hash -> Block slot hash -> Bool
$c< :: forall slot hash.
(Ord slot, Ord hash) =>
Block slot hash -> Block slot hash -> Bool
compare :: Block slot hash -> Block slot hash -> Ordering
$ccompare :: forall slot hash.
(Ord slot, Ord hash) =>
Block slot hash -> Block slot hash -> Ordering
$cp1Ord :: forall slot hash. (Ord slot, Ord hash) => Eq (Block slot hash)
Ord, Int -> Block slot hash -> ShowS
[Block slot hash] -> ShowS
Block slot hash -> String
(Int -> Block slot hash -> ShowS)
-> (Block slot hash -> String)
-> ([Block slot hash] -> ShowS)
-> Show (Block slot hash)
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
forall slot hash.
(Show slot, Show hash) =>
Int -> Block slot hash -> ShowS
forall slot hash.
(Show slot, Show hash) =>
[Block slot hash] -> ShowS
forall slot hash.
(Show slot, Show hash) =>
Block slot hash -> String
showList :: [Block slot hash] -> ShowS
$cshowList :: forall slot hash.
(Show slot, Show hash) =>
[Block slot hash] -> ShowS
show :: Block slot hash -> String
$cshow :: forall slot hash.
(Show slot, Show hash) =>
Block slot hash -> String
showsPrec :: Int -> Block slot hash -> ShowS
$cshowsPrec :: forall slot hash.
(Show slot, Show hash) =>
Int -> Block slot hash -> ShowS
Show, (forall x. Block slot hash -> Rep (Block slot hash) x)
-> (forall x. Rep (Block slot hash) x -> Block slot hash)
-> Generic (Block slot hash)
forall x. Rep (Block slot hash) x -> Block slot hash
forall x. Block slot hash -> Rep (Block slot hash) x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
forall slot hash x. Rep (Block slot hash) x -> Block slot hash
forall slot hash x. Block slot hash -> Rep (Block slot hash) x
$cto :: forall slot hash x. Rep (Block slot hash) x -> Block slot hash
$cfrom :: forall slot hash x. Block slot hash -> Rep (Block slot hash) x
Generic, Context -> Block slot hash -> IO (Maybe ThunkInfo)
Proxy (Block slot hash) -> String
(Context -> Block slot hash -> IO (Maybe ThunkInfo))
-> (Context -> Block slot hash -> IO (Maybe ThunkInfo))
-> (Proxy (Block slot hash) -> String)
-> NoThunks (Block slot hash)
forall a.
(Context -> a -> IO (Maybe ThunkInfo))
-> (Context -> a -> IO (Maybe ThunkInfo))
-> (Proxy a -> String)
-> NoThunks a
forall slot hash.
(NoThunks slot, NoThunks hash) =>
Context -> Block slot hash -> IO (Maybe ThunkInfo)
forall slot hash.
(NoThunks slot, NoThunks hash) =>
Proxy (Block slot hash) -> String
showTypeOf :: Proxy (Block slot hash) -> String
$cshowTypeOf :: forall slot hash.
(NoThunks slot, NoThunks hash) =>
Proxy (Block slot hash) -> String
wNoThunks :: Context -> Block slot hash -> IO (Maybe ThunkInfo)
$cwNoThunks :: forall slot hash.
(NoThunks slot, NoThunks hash) =>
Context -> Block slot hash -> IO (Maybe ThunkInfo)
noThunks :: Context -> Block slot hash -> IO (Maybe ThunkInfo)
$cnoThunks :: forall slot hash.
(NoThunks slot, NoThunks hash) =>
Context -> Block slot hash -> IO (Maybe ThunkInfo)
NoThunks)

block :: slot -> hash -> WithOrigin (Block slot hash)
block :: slot -> hash -> WithOrigin (Block slot hash)
block slot
slot hash
hash = Block slot hash -> WithOrigin (Block slot hash)
forall t. t -> WithOrigin t
at (slot -> hash -> Block slot hash
forall slot hash. slot -> hash -> Block slot hash
Block slot
slot hash
hash)