Skip to content

Commit

Permalink
display call stack for unnecessful unsafe calls
Browse files Browse the repository at this point in the history
  • Loading branch information
KtorZ committed Sep 9, 2019
1 parent a57e665 commit 9d6e22b
Showing 1 changed file with 11 additions and 6 deletions.
17 changes: 11 additions & 6 deletions lib/core/src/Cardano/Wallet/Unsafe.hs
@@ -1,3 +1,4 @@
{-# LANGUAGE FlexibleContexts #-}
{-# LANGUAGE LambdaCase #-}
{-# LANGUAGE RankNTypes #-}
{-# LANGUAGE ScopedTypeVariables #-}
Expand Down Expand Up @@ -38,6 +39,8 @@ import Data.Proxy
( Proxy )
import Data.Text
( Text )
import GHC.Stack
( HasCallStack )

import qualified Cardano.Crypto.Wallet as CC
import qualified Codec.CBOR.Decoding as CBOR
Expand All @@ -46,29 +49,30 @@ import qualified Data.ByteString.Lazy as BL


-- | Decode an hex-encoded 'ByteString' into raw bytes, or fail.
unsafeFromHex :: ByteString -> ByteString
unsafeFromHex :: HasCallStack => ByteString -> ByteString
unsafeFromHex =
either (error . show) id . convertFromBase @ByteString @ByteString Base16

-- | Decode a bech32-encoded 'Text' into an 'Address', or fail.
unsafeDecodeAddress :: DecodeAddress t => Proxy t -> Text -> Address
unsafeDecodeAddress :: (HasCallStack, DecodeAddress t) => Proxy t -> Text -> Address
unsafeDecodeAddress proxy =
either (error . show ) id . decodeAddress proxy

-- | Run a decoder on a hex-encoded 'ByteString', or fail.
unsafeDecodeHex :: Get a -> ByteString -> a
unsafeDecodeHex :: HasCallStack => Get a -> ByteString -> a
unsafeDecodeHex get = runGet get . BL.fromStrict . unsafeFromHex

-- | Build a 'XPrv' from an hex-encoded bytestring
unsafeXPrv :: ByteString -> XPrv
unsafeXPrv :: HasCallStack => ByteString -> XPrv
unsafeXPrv hex =
case convertFromBase @_ @ByteString Base16 hex >>= CC.xprv of
Left e -> error $ "unsafeXPrv: " <> e
Right a -> a

-- | Build 'Mnemonic' from literals
unsafeMkMnemonic
:: forall mw n csz. (ConsistentEntropy n mw csz, EntropySize mw ~ n)
:: forall mw n csz
. (ConsistentEntropy n mw csz, EntropySize mw ~ n, HasCallStack)
=> [Text]
-> Mnemonic mw
unsafeMkMnemonic m =
Expand All @@ -88,7 +92,8 @@ unsafeRunExceptT = runExceptT >=> \case

-- | CBOR deserialise without error handling - handy for prototypes or testing.
unsafeDeserialiseCbor
:: (forall s. CBOR.Decoder s a)
:: HasCallStack
=> (forall s. CBOR.Decoder s a)
-> BL.ByteString
-> a
unsafeDeserialiseCbor decoder bytes = either
Expand Down

0 comments on commit 9d6e22b

Please sign in to comment.