module Hydra.Cardano.Api.Prelude (
  module Cardano.Api,
  module Cardano.Api.Classy,
  module Cardano.Api.Shelley,
  module Data.Aeson,
  HasCallStack,
  Proxy (..),
  Typeable,
  UTxO,
  UTxO' (UTxO),
  StandardCrypto,
  Era,
  LedgerEra,
  ledgerEraVersion,
  UsesStandardCrypto,
  Text,
  decodeUtf8,
  encodeUtf8,
  toStrict,
  fromStrict,
  ByteString,
  Map,
  Set,
  unsafeHashFromBytes,
  Arbitrary (..),
  Gen,
) where

import Cardano.Api hiding (
  UTxO,
  scriptLanguageSupportedInEra,
  toLedgerUTxO,
 )
import Cardano.Api.Classy
import Cardano.Api.Shelley hiding (
  UTxO,
  scriptLanguageSupportedInEra,
  toLedgerUTxO,
 )
import Cardano.Api.UTxO (UTxO, UTxO' (..))
import Cardano.Crypto.Hash.Class qualified as CC
import Cardano.Ledger.Binary qualified as Ledger
import Cardano.Ledger.Core qualified as Ledger
import Cardano.Ledger.Crypto (StandardCrypto)
import Cardano.Ledger.Era (EraCrypto)
import Data.Aeson (FromJSON (..), ToJSON (..))
import Data.ByteString (ByteString)
import Data.ByteString.Lazy (fromStrict, toStrict)
import Data.Map (Map)
import Data.Proxy (Proxy (..))
import Data.Set (Set)
import Data.Text (Text)
import Data.Text.Encoding (decodeUtf8, encodeUtf8)
import Data.Typeable (Typeable)
import GHC.Stack (HasCallStack)
import Test.QuickCheck (Arbitrary (..), Gen)

type Era = BabbageEra

-- | Currently supported ledger era.
type LedgerEra = ShelleyLedgerEra Era

type UsesStandardCrypto era = (EraCrypto (ShelleyLedgerEra era) ~ StandardCrypto)

-- | Associated version for the fixed 'LedgerEra'.
ledgerEraVersion :: Ledger.Version
ledgerEraVersion :: Version
ledgerEraVersion = forall era. Era era => Version
Ledger.eraProtVerLow @LedgerEra

-- | Interpret some raw 'ByteString' as a particular 'Hash'.
--
-- NOTE: This throws if byte string has a length different that the expected
-- target digest length.
unsafeHashFromBytes ::
  (HasCallStack, CC.HashAlgorithm hash) =>
  ByteString ->
  CC.Hash hash a
unsafeHashFromBytes :: forall hash a.
(HasCallStack, HashAlgorithm hash) =>
ByteString -> Hash hash a
unsafeHashFromBytes ByteString
bytes =
  case ByteString -> Maybe (Hash hash a)
forall h a. HashAlgorithm h => ByteString -> Maybe (Hash h a)
CC.hashFromBytes ByteString
bytes of
    Maybe (Hash hash a)
Nothing ->
      [Char] -> Hash hash a
forall a. HasCallStack => [Char] -> a
error ([Char] -> Hash hash a) -> [Char] -> Hash hash a
forall a b. (a -> b) -> a -> b
$ [Char]
"unsafeHashFromBytes: failed to convert hash: " [Char] -> [Char] -> [Char]
forall a. Semigroup a => a -> a -> a
<> ByteString -> [Char]
forall a. Show a => a -> [Char]
show ByteString
bytes
    Just Hash hash a
h ->
      Hash hash a
h