{-# LANGUAGE DeriveAnyClass #-}
{-# LANGUAGE DerivingVia #-}
{-# LANGUAGE TypeApplications #-}
module Sel.Hashing.Short
(
ShortHash
, hashByteString
, hashText
, shortHashToBinary
, shortHashToHexText
, shortHashToHexByteString
, ShortHashKey
, newKey
, shortHashKeyToBinary
, shortHashKeyToHexText
, shortHashKeyToHexByteString
, binaryToShortHashKey
, hexTextToShortHashKey
, hexByteStringToShortHashKey
, ShortHashingException (..)
)
where
import Control.Exception (throw)
import Control.Monad (void, when)
import Data.ByteString (StrictByteString)
import qualified Data.ByteString as BS
import qualified Data.ByteString.Base16 as Base16
import qualified Data.ByteString.Internal as BS
import qualified Data.ByteString.Unsafe as BS
import Data.Text (Text)
import qualified Data.Text as Text
import qualified Data.Text.Encoding as Text
import qualified Data.Text.Lazy.Builder as Builder
import Foreign hiding (void)
import Foreign.C (CSize, CUChar, CULLong)
import GHC.Exception (Exception)
import GHC.IO.Handle.Text (memcpy)
import System.IO.Unsafe (unsafeDupablePerformIO)
import qualified Data.Base16.Types as Base16
import Data.Text.Display
import LibSodium.Bindings.ShortHashing
( cryptoShortHashSipHashX24Bytes
, cryptoShortHashSipHashX24KeyBytes
, cryptoShortHashX24
, cryptoShortHashX24KeyGen
)
import Sel.Internal
newtype ShortHash = ShortHash (ForeignPtr CUChar)
instance Eq ShortHash where
(ShortHash ForeignPtr CUChar
sh1) == :: ShortHash -> ShortHash -> Bool
== (ShortHash ForeignPtr CUChar
sh2) =
IO Bool -> Bool
forall a. IO a -> a
unsafeDupablePerformIO (IO Bool -> Bool) -> IO Bool -> Bool
forall a b. (a -> b) -> a -> b
$
ForeignPtr CUChar -> ForeignPtr CUChar -> CSize -> IO Bool
forall a. ForeignPtr a -> ForeignPtr a -> CSize -> IO Bool
foreignPtrEq ForeignPtr CUChar
sh1 ForeignPtr CUChar
sh2 CSize
cryptoShortHashSipHashX24Bytes
instance Ord ShortHash where
compare :: ShortHash -> ShortHash -> Ordering
compare (ShortHash ForeignPtr CUChar
sh1) (ShortHash ForeignPtr CUChar
sh2) =
IO Ordering -> Ordering
forall a. IO a -> a
unsafeDupablePerformIO (IO Ordering -> Ordering) -> IO Ordering -> Ordering
forall a b. (a -> b) -> a -> b
$
ForeignPtr CUChar -> ForeignPtr CUChar -> CSize -> IO Ordering
forall a. ForeignPtr a -> ForeignPtr a -> CSize -> IO Ordering
foreignPtrOrd ForeignPtr CUChar
sh1 ForeignPtr CUChar
sh2 CSize
cryptoShortHashSipHashX24Bytes
instance Show ShortHash where
show :: ShortHash -> String
show = Text -> String
Text.unpack (Text -> String) -> (ShortHash -> Text) -> ShortHash -> String
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ShortHash -> Text
shortHashToHexText
instance Display ShortHash where
displayBuilder :: ShortHash -> Builder
displayBuilder = Text -> Builder
Builder.fromText (Text -> Builder) -> (ShortHash -> Text) -> ShortHash -> Builder
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ShortHash -> Text
shortHashToHexText
hashByteString
:: ShortHashKey
-> StrictByteString
-> IO ShortHash
hashByteString :: ShortHashKey -> StrictByteString -> IO ShortHash
hashByteString (ShortHashKey ForeignPtr CUChar
keyFPtr) StrictByteString
message =
StrictByteString -> (CStringLen -> IO ShortHash) -> IO ShortHash
forall a. StrictByteString -> (CStringLen -> IO a) -> IO a
BS.unsafeUseAsCStringLen StrictByteString
message ((CStringLen -> IO ShortHash) -> IO ShortHash)
-> (CStringLen -> IO ShortHash) -> IO ShortHash
forall a b. (a -> b) -> a -> b
$ \(Ptr CChar
cString, Int
cStringLen) -> do
ForeignPtr CUChar
shortHashFPtr <- Int -> IO (ForeignPtr CUChar)
forall a. Int -> IO (ForeignPtr a)
Foreign.mallocForeignPtrBytes (CSize -> Int
forall a b. (Integral a, Num b) => a -> b
fromIntegral CSize
cryptoShortHashSipHashX24Bytes)
ForeignPtr CUChar -> (Ptr CUChar -> IO ShortHash) -> IO ShortHash
forall a b. ForeignPtr a -> (Ptr a -> IO b) -> IO b
Foreign.withForeignPtr ForeignPtr CUChar
keyFPtr ((Ptr CUChar -> IO ShortHash) -> IO ShortHash)
-> (Ptr CUChar -> IO ShortHash) -> IO ShortHash
forall a b. (a -> b) -> a -> b
$ \Ptr CUChar
keyPtr ->
ForeignPtr CUChar -> (Ptr CUChar -> IO ShortHash) -> IO ShortHash
forall a b. ForeignPtr a -> (Ptr a -> IO b) -> IO b
Foreign.withForeignPtr ForeignPtr CUChar
shortHashFPtr ((Ptr CUChar -> IO ShortHash) -> IO ShortHash)
-> (Ptr CUChar -> IO ShortHash) -> IO ShortHash
forall a b. (a -> b) -> a -> b
$ \Ptr CUChar
shortHashPtr -> do
CInt
result <-
Ptr CUChar -> Ptr CUChar -> CULLong -> Ptr CUChar -> IO CInt
cryptoShortHashX24
Ptr CUChar
shortHashPtr
(Ptr CChar -> Ptr CUChar
forall a b. Ptr a -> Ptr b
Foreign.castPtr Ptr CChar
cString)
(forall a b. (Integral a, Num b) => a -> b
fromIntegral @Int @CULLong Int
cStringLen)
Ptr CUChar
keyPtr
Bool -> IO () -> IO ()
forall (f :: * -> *). Applicative f => Bool -> f () -> f ()
when (CInt
result CInt -> CInt -> Bool
forall a. Eq a => a -> a -> Bool
/= CInt
0) (IO () -> IO ()) -> IO () -> IO ()
forall a b. (a -> b) -> a -> b
$ ShortHashingException -> IO ()
forall a e. Exception e => e -> a
throw ShortHashingException
ShortHashingException
ShortHash -> IO ShortHash
forall a. a -> IO a
forall (f :: * -> *) a. Applicative f => a -> f a
pure (ShortHash -> IO ShortHash) -> ShortHash -> IO ShortHash
forall a b. (a -> b) -> a -> b
$ ForeignPtr CUChar -> ShortHash
ShortHash ForeignPtr CUChar
shortHashFPtr
hashText
:: ShortHashKey
-> Text
-> IO ShortHash
hashText :: ShortHashKey -> Text -> IO ShortHash
hashText ShortHashKey
key Text
message = ShortHashKey -> StrictByteString -> IO ShortHash
hashByteString ShortHashKey
key (Text -> StrictByteString
Text.encodeUtf8 Text
message)
shortHashToBinary :: ShortHash -> StrictByteString
shortHashToBinary :: ShortHash -> StrictByteString
shortHashToBinary (ShortHash ForeignPtr CUChar
hashFPtr) =
ForeignPtr Word8 -> Int -> Int -> StrictByteString
BS.fromForeignPtr
(ForeignPtr CUChar -> ForeignPtr Word8
forall a b. ForeignPtr a -> ForeignPtr b
Foreign.castForeignPtr ForeignPtr CUChar
hashFPtr)
Int
0
(forall a b. (Integral a, Num b) => a -> b
fromIntegral @CSize @Int CSize
cryptoShortHashSipHashX24Bytes)
shortHashToHexByteString :: ShortHash -> StrictByteString
shortHashToHexByteString :: ShortHash -> StrictByteString
shortHashToHexByteString = Base16 StrictByteString -> StrictByteString
forall a. Base16 a -> a
Base16.extractBase16 (Base16 StrictByteString -> StrictByteString)
-> (ShortHash -> Base16 StrictByteString)
-> ShortHash
-> StrictByteString
forall b c a. (b -> c) -> (a -> b) -> a -> c
. StrictByteString -> Base16 StrictByteString
Base16.encodeBase16' (StrictByteString -> Base16 StrictByteString)
-> (ShortHash -> StrictByteString)
-> ShortHash
-> Base16 StrictByteString
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ShortHash -> StrictByteString
shortHashToBinary
shortHashToHexText :: ShortHash -> Text
shortHashToHexText :: ShortHash -> Text
shortHashToHexText = Base16 Text -> Text
forall a. Base16 a -> a
Base16.extractBase16 (Base16 Text -> Text)
-> (ShortHash -> Base16 Text) -> ShortHash -> Text
forall b c a. (b -> c) -> (a -> b) -> a -> c
. StrictByteString -> Base16 Text
Base16.encodeBase16 (StrictByteString -> Base16 Text)
-> (ShortHash -> StrictByteString) -> ShortHash -> Base16 Text
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ShortHash -> StrictByteString
shortHashToBinary
newtype ShortHashKey = ShortHashKey (ForeignPtr CUChar)
instance Eq ShortHashKey where
(ShortHashKey ForeignPtr CUChar
sh1) == :: ShortHashKey -> ShortHashKey -> Bool
== (ShortHashKey ForeignPtr CUChar
sh2) =
IO Bool -> Bool
forall a. IO a -> a
unsafeDupablePerformIO (IO Bool -> Bool) -> IO Bool -> Bool
forall a b. (a -> b) -> a -> b
$
ForeignPtr CUChar -> ForeignPtr CUChar -> CSize -> IO Bool
forall a. ForeignPtr a -> ForeignPtr a -> CSize -> IO Bool
foreignPtrEq ForeignPtr CUChar
sh1 ForeignPtr CUChar
sh2 CSize
cryptoShortHashSipHashX24Bytes
instance Ord ShortHashKey where
compare :: ShortHashKey -> ShortHashKey -> Ordering
compare (ShortHashKey ForeignPtr CUChar
sh1) (ShortHashKey ForeignPtr CUChar
sh2) =
IO Ordering -> Ordering
forall a. IO a -> a
unsafeDupablePerformIO (IO Ordering -> Ordering) -> IO Ordering -> Ordering
forall a b. (a -> b) -> a -> b
$
ForeignPtr CUChar -> ForeignPtr CUChar -> CSize -> IO Ordering
forall a. ForeignPtr a -> ForeignPtr a -> CSize -> IO Ordering
foreignPtrOrd ForeignPtr CUChar
sh1 ForeignPtr CUChar
sh2 CSize
cryptoShortHashSipHashX24Bytes
instance Show ShortHashKey where
show :: ShortHashKey -> String
show = Text -> String
Text.unpack (Text -> String)
-> (ShortHashKey -> Text) -> ShortHashKey -> String
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ShortHashKey -> Text
shortHashKeyToHexText
instance Display ShortHashKey where
displayBuilder :: ShortHashKey -> Builder
displayBuilder = Text -> Builder
Builder.fromText (Text -> Builder)
-> (ShortHashKey -> Text) -> ShortHashKey -> Builder
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ShortHashKey -> Text
shortHashKeyToHexText
newKey :: IO ShortHashKey
newKey :: IO ShortHashKey
newKey = do
ForeignPtr CUChar
shortHashKeyForeignPtr <-
Int -> IO (ForeignPtr CUChar)
forall a. Int -> IO (ForeignPtr a)
Foreign.mallocForeignPtrBytes (CSize -> Int
forall a b. (Integral a, Num b) => a -> b
fromIntegral CSize
cryptoShortHashSipHashX24KeyBytes)
ForeignPtr CUChar -> (Ptr CUChar -> IO ()) -> IO ()
forall a b. ForeignPtr a -> (Ptr a -> IO b) -> IO b
Foreign.withForeignPtr ForeignPtr CUChar
shortHashKeyForeignPtr ((Ptr CUChar -> IO ()) -> IO ()) -> (Ptr CUChar -> IO ()) -> IO ()
forall a b. (a -> b) -> a -> b
$ \Ptr CUChar
shortHashKeyPtr ->
IO () -> IO ()
forall (f :: * -> *) a. Functor f => f a -> f ()
void (IO () -> IO ()) -> IO () -> IO ()
forall a b. (a -> b) -> a -> b
$ Ptr CUChar -> IO ()
cryptoShortHashX24KeyGen Ptr CUChar
shortHashKeyPtr
ShortHashKey -> IO ShortHashKey
forall a. a -> IO a
forall (f :: * -> *) a. Applicative f => a -> f a
pure (ShortHashKey -> IO ShortHashKey)
-> ShortHashKey -> IO ShortHashKey
forall a b. (a -> b) -> a -> b
$ ForeignPtr CUChar -> ShortHashKey
ShortHashKey ForeignPtr CUChar
shortHashKeyForeignPtr
shortHashKeyToBinary :: ShortHashKey -> StrictByteString
shortHashKeyToBinary :: ShortHashKey -> StrictByteString
shortHashKeyToBinary (ShortHashKey ForeignPtr CUChar
hashKeyFPtr) =
ForeignPtr Word8 -> Int -> Int -> StrictByteString
BS.fromForeignPtr
(ForeignPtr CUChar -> ForeignPtr Word8
forall a b. ForeignPtr a -> ForeignPtr b
Foreign.castForeignPtr ForeignPtr CUChar
hashKeyFPtr)
Int
0
(forall a b. (Integral a, Num b) => a -> b
fromIntegral @CSize @Int CSize
cryptoShortHashSipHashX24KeyBytes)
shortHashKeyToHexByteString :: ShortHashKey -> StrictByteString
shortHashKeyToHexByteString :: ShortHashKey -> StrictByteString
shortHashKeyToHexByteString = Base16 StrictByteString -> StrictByteString
forall a. Base16 a -> a
Base16.extractBase16 (Base16 StrictByteString -> StrictByteString)
-> (ShortHashKey -> Base16 StrictByteString)
-> ShortHashKey
-> StrictByteString
forall b c a. (b -> c) -> (a -> b) -> a -> c
. StrictByteString -> Base16 StrictByteString
Base16.encodeBase16' (StrictByteString -> Base16 StrictByteString)
-> (ShortHashKey -> StrictByteString)
-> ShortHashKey
-> Base16 StrictByteString
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ShortHashKey -> StrictByteString
shortHashKeyToBinary
shortHashKeyToHexText :: ShortHashKey -> Text
shortHashKeyToHexText :: ShortHashKey -> Text
shortHashKeyToHexText = Base16 Text -> Text
forall a. Base16 a -> a
Base16.extractBase16 (Base16 Text -> Text)
-> (ShortHashKey -> Base16 Text) -> ShortHashKey -> Text
forall b c a. (b -> c) -> (a -> b) -> a -> c
. StrictByteString -> Base16 Text
Base16.encodeBase16 (StrictByteString -> Base16 Text)
-> (ShortHashKey -> StrictByteString)
-> ShortHashKey
-> Base16 Text
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ShortHashKey -> StrictByteString
shortHashKeyToBinary
binaryToShortHashKey :: StrictByteString -> Maybe ShortHashKey
binaryToShortHashKey :: StrictByteString -> Maybe ShortHashKey
binaryToShortHashKey StrictByteString
binaryKey =
if StrictByteString -> Int
BS.length StrictByteString
binaryKey Int -> Int -> Bool
forall a. Eq a => a -> a -> Bool
/= CSize -> Int
forall a b. (Integral a, Num b) => a -> b
fromIntegral CSize
cryptoShortHashSipHashX24KeyBytes
then Maybe ShortHashKey
forall a. Maybe a
Nothing
else IO (Maybe ShortHashKey) -> Maybe ShortHashKey
forall a. IO a -> a
unsafeDupablePerformIO (IO (Maybe ShortHashKey) -> Maybe ShortHashKey)
-> IO (Maybe ShortHashKey) -> Maybe ShortHashKey
forall a b. (a -> b) -> a -> b
$ do
StrictByteString
-> (Ptr CChar -> IO (Maybe ShortHashKey))
-> IO (Maybe ShortHashKey)
forall a. StrictByteString -> (Ptr CChar -> IO a) -> IO a
BS.unsafeUseAsCString StrictByteString
binaryKey ((Ptr CChar -> IO (Maybe ShortHashKey)) -> IO (Maybe ShortHashKey))
-> (Ptr CChar -> IO (Maybe ShortHashKey))
-> IO (Maybe ShortHashKey)
forall a b. (a -> b) -> a -> b
$ \Ptr CChar
cString -> do
ForeignPtr CUChar
shortHashKeyFPtr <- Int -> IO (ForeignPtr CUChar)
forall a. Int -> IO (ForeignPtr a)
Foreign.mallocForeignPtrBytes (CSize -> Int
forall a b. (Integral a, Num b) => a -> b
fromIntegral CSize
cryptoShortHashSipHashX24KeyBytes)
ForeignPtr CUChar -> (Ptr CUChar -> IO (Ptr ())) -> IO (Ptr ())
forall a b. ForeignPtr a -> (Ptr a -> IO b) -> IO b
Foreign.withForeignPtr ForeignPtr CUChar
shortHashKeyFPtr ((Ptr CUChar -> IO (Ptr ())) -> IO (Ptr ()))
-> (Ptr CUChar -> IO (Ptr ())) -> IO (Ptr ())
forall a b. (a -> b) -> a -> b
$ \Ptr CUChar
shortHashKeyPtr ->
Ptr CUChar -> Ptr CUChar -> CSize -> IO (Ptr ())
forall a. Ptr a -> Ptr a -> CSize -> IO (Ptr ())
memcpy Ptr CUChar
shortHashKeyPtr (Ptr CChar -> Ptr CUChar
forall a b. Ptr a -> Ptr b
Foreign.castPtr Ptr CChar
cString) CSize
cryptoShortHashSipHashX24KeyBytes
Maybe ShortHashKey -> IO (Maybe ShortHashKey)
forall a. a -> IO a
forall (f :: * -> *) a. Applicative f => a -> f a
pure (Maybe ShortHashKey -> IO (Maybe ShortHashKey))
-> Maybe ShortHashKey -> IO (Maybe ShortHashKey)
forall a b. (a -> b) -> a -> b
$ ShortHashKey -> Maybe ShortHashKey
forall a. a -> Maybe a
Just (ShortHashKey -> Maybe ShortHashKey)
-> ShortHashKey -> Maybe ShortHashKey
forall a b. (a -> b) -> a -> b
$ ForeignPtr CUChar -> ShortHashKey
ShortHashKey ForeignPtr CUChar
shortHashKeyFPtr
hexTextToShortHashKey :: Text -> Maybe ShortHashKey
hexTextToShortHashKey :: Text -> Maybe ShortHashKey
hexTextToShortHashKey = StrictByteString -> Maybe ShortHashKey
hexByteStringToShortHashKey (StrictByteString -> Maybe ShortHashKey)
-> (Text -> StrictByteString) -> Text -> Maybe ShortHashKey
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Text -> StrictByteString
Text.encodeUtf8
hexByteStringToShortHashKey :: StrictByteString -> Maybe ShortHashKey
hexByteStringToShortHashKey :: StrictByteString -> Maybe ShortHashKey
hexByteStringToShortHashKey StrictByteString
hexByteString =
case StrictByteString -> Either Text StrictByteString
Base16.decodeBase16Untyped StrictByteString
hexByteString of
Right StrictByteString
binary -> StrictByteString -> Maybe ShortHashKey
binaryToShortHashKey StrictByteString
binary
Left Text
_ -> Maybe ShortHashKey
forall a. Maybe a
Nothing
data ShortHashingException = ShortHashingException
deriving stock
( Int -> ShortHashingException -> ShowS
[ShortHashingException] -> ShowS
ShortHashingException -> String
(Int -> ShortHashingException -> ShowS)
-> (ShortHashingException -> String)
-> ([ShortHashingException] -> ShowS)
-> Show ShortHashingException
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> ShortHashingException -> ShowS
showsPrec :: Int -> ShortHashingException -> ShowS
$cshow :: ShortHashingException -> String
show :: ShortHashingException -> String
$cshowList :: [ShortHashingException] -> ShowS
showList :: [ShortHashingException] -> ShowS
Show
, ShortHashingException -> ShortHashingException -> Bool
(ShortHashingException -> ShortHashingException -> Bool)
-> (ShortHashingException -> ShortHashingException -> Bool)
-> Eq ShortHashingException
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: ShortHashingException -> ShortHashingException -> Bool
== :: ShortHashingException -> ShortHashingException -> Bool
$c/= :: ShortHashingException -> ShortHashingException -> Bool
/= :: ShortHashingException -> ShortHashingException -> Bool
Eq
, Eq ShortHashingException
Eq ShortHashingException =>
(ShortHashingException -> ShortHashingException -> Ordering)
-> (ShortHashingException -> ShortHashingException -> Bool)
-> (ShortHashingException -> ShortHashingException -> Bool)
-> (ShortHashingException -> ShortHashingException -> Bool)
-> (ShortHashingException -> ShortHashingException -> Bool)
-> (ShortHashingException
-> ShortHashingException -> ShortHashingException)
-> (ShortHashingException
-> ShortHashingException -> ShortHashingException)
-> Ord ShortHashingException
ShortHashingException -> ShortHashingException -> Bool
ShortHashingException -> ShortHashingException -> Ordering
ShortHashingException
-> ShortHashingException -> ShortHashingException
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
$ccompare :: ShortHashingException -> ShortHashingException -> Ordering
compare :: ShortHashingException -> ShortHashingException -> Ordering
$c< :: ShortHashingException -> ShortHashingException -> Bool
< :: ShortHashingException -> ShortHashingException -> Bool
$c<= :: ShortHashingException -> ShortHashingException -> Bool
<= :: ShortHashingException -> ShortHashingException -> Bool
$c> :: ShortHashingException -> ShortHashingException -> Bool
> :: ShortHashingException -> ShortHashingException -> Bool
$c>= :: ShortHashingException -> ShortHashingException -> Bool
>= :: ShortHashingException -> ShortHashingException -> Bool
$cmax :: ShortHashingException
-> ShortHashingException -> ShortHashingException
max :: ShortHashingException
-> ShortHashingException -> ShortHashingException
$cmin :: ShortHashingException
-> ShortHashingException -> ShortHashingException
min :: ShortHashingException
-> ShortHashingException -> ShortHashingException
Ord
)
deriving anyclass
( Show ShortHashingException
Typeable ShortHashingException
(Typeable ShortHashingException, Show ShortHashingException) =>
(ShortHashingException -> SomeException)
-> (SomeException -> Maybe ShortHashingException)
-> (ShortHashingException -> String)
-> Exception ShortHashingException
SomeException -> Maybe ShortHashingException
ShortHashingException -> String
ShortHashingException -> SomeException
forall e.
(Typeable e, Show e) =>
(e -> SomeException)
-> (SomeException -> Maybe e) -> (e -> String) -> Exception e
$ctoException :: ShortHashingException -> SomeException
toException :: ShortHashingException -> SomeException
$cfromException :: SomeException -> Maybe ShortHashingException
fromException :: SomeException -> Maybe ShortHashingException
$cdisplayException :: ShortHashingException -> String
displayException :: ShortHashingException -> String
Exception
)
deriving
( Int -> ShortHashingException -> Builder
[ShortHashingException] -> Builder
ShortHashingException -> Builder
(ShortHashingException -> Builder)
-> ([ShortHashingException] -> Builder)
-> (Int -> ShortHashingException -> Builder)
-> Display ShortHashingException
forall a.
(a -> Builder)
-> ([a] -> Builder) -> (Int -> a -> Builder) -> Display a
$cdisplayBuilder :: ShortHashingException -> Builder
displayBuilder :: ShortHashingException -> Builder
$cdisplayList :: [ShortHashingException] -> Builder
displayList :: [ShortHashingException] -> Builder
$cdisplayPrec :: Int -> ShortHashingException -> Builder
displayPrec :: Int -> ShortHashingException -> Builder
Display
)
via (ShowInstance ShortHashingException)