{-# LANGUAGE DataKinds #-}
{-# LANGUAGE DeriveAnyClass #-}
{-# LANGUAGE DeriveGeneric #-}
{-# LANGUAGE FlexibleInstances #-}
{-# LANGUAGE GADTs #-}
{-# LANGUAGE MultiParamTypeClasses #-}
{-# LANGUAGE PolyKinds #-}
{-# LANGUAGE TypeFamilies #-}
{-# OPTIONS_GHC -Wno-orphans #-}
module Ouroboros.Consensus.Storage.LedgerDB.V2.Args
( FlavorImplSpecificTrace (..)
, HandleArgs (..)
, LedgerDbFlavorArgs (..)
) where
import Data.Void (Void)
import GHC.Generics
import NoThunks.Class
data LedgerDbFlavorArgs f m = V2Args HandleArgs
data HandleArgs
= InMemoryHandleArgs
| LSMHandleArgs Void
deriving ((forall x. HandleArgs -> Rep HandleArgs x)
-> (forall x. Rep HandleArgs x -> HandleArgs) -> Generic HandleArgs
forall x. Rep HandleArgs x -> HandleArgs
forall x. HandleArgs -> Rep HandleArgs x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cfrom :: forall x. HandleArgs -> Rep HandleArgs x
from :: forall x. HandleArgs -> Rep HandleArgs x
$cto :: forall x. Rep HandleArgs x -> HandleArgs
to :: forall x. Rep HandleArgs x -> HandleArgs
Generic, Context -> HandleArgs -> IO (Maybe ThunkInfo)
Proxy HandleArgs -> String
(Context -> HandleArgs -> IO (Maybe ThunkInfo))
-> (Context -> HandleArgs -> IO (Maybe ThunkInfo))
-> (Proxy HandleArgs -> String)
-> NoThunks HandleArgs
forall a.
(Context -> a -> IO (Maybe ThunkInfo))
-> (Context -> a -> IO (Maybe ThunkInfo))
-> (Proxy a -> String)
-> NoThunks a
$cnoThunks :: Context -> HandleArgs -> IO (Maybe ThunkInfo)
noThunks :: Context -> HandleArgs -> IO (Maybe ThunkInfo)
$cwNoThunks :: Context -> HandleArgs -> IO (Maybe ThunkInfo)
wNoThunks :: Context -> HandleArgs -> IO (Maybe ThunkInfo)
$cshowTypeOf :: Proxy HandleArgs -> String
showTypeOf :: Proxy HandleArgs -> String
NoThunks)
data FlavorImplSpecificTrace
=
TraceLedgerTablesHandleCreate
|
TraceLedgerTablesHandleClose
deriving (Int -> FlavorImplSpecificTrace -> ShowS
[FlavorImplSpecificTrace] -> ShowS
FlavorImplSpecificTrace -> String
(Int -> FlavorImplSpecificTrace -> ShowS)
-> (FlavorImplSpecificTrace -> String)
-> ([FlavorImplSpecificTrace] -> ShowS)
-> Show FlavorImplSpecificTrace
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> FlavorImplSpecificTrace -> ShowS
showsPrec :: Int -> FlavorImplSpecificTrace -> ShowS
$cshow :: FlavorImplSpecificTrace -> String
show :: FlavorImplSpecificTrace -> String
$cshowList :: [FlavorImplSpecificTrace] -> ShowS
showList :: [FlavorImplSpecificTrace] -> ShowS
Show, FlavorImplSpecificTrace -> FlavorImplSpecificTrace -> Bool
(FlavorImplSpecificTrace -> FlavorImplSpecificTrace -> Bool)
-> (FlavorImplSpecificTrace -> FlavorImplSpecificTrace -> Bool)
-> Eq FlavorImplSpecificTrace
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: FlavorImplSpecificTrace -> FlavorImplSpecificTrace -> Bool
== :: FlavorImplSpecificTrace -> FlavorImplSpecificTrace -> Bool
$c/= :: FlavorImplSpecificTrace -> FlavorImplSpecificTrace -> Bool
/= :: FlavorImplSpecificTrace -> FlavorImplSpecificTrace -> Bool
Eq)