haskoin-0.0.2.1: Implementation of the Bitcoin protocol.

Safe HaskellSafe-Inferred

Network.Haskoin.Util

Contents

Description

This module defines various utility functions used across the Network.Haskoin modules.

Synopsis

ByteString helpers

toStrictBS :: ByteString -> ByteStringSource

Transforms a lazy bytestring into a strict bytestring

toLazyBS :: ByteString -> ByteStringSource

Transforms a strict bytestring into a lazy bytestring

stringToBS :: String -> ByteStringSource

Transforms a string into a strict bytestring

bsToString :: ByteString -> StringSource

Transform a strict bytestring to a string

bsToInteger :: ByteString -> IntegerSource

Decode a big endian Integer from a bytestring

integerToBS :: Integer -> ByteStringSource

Encode an Integer to a bytestring as big endian

bsToHex :: ByteString -> StringSource

Encode a bytestring to a base16 (HEX) representation

hexToBS :: String -> Maybe ByteStringSource

Decode a base16 (HEX) string from a bytestring. This function can fail if the string contains invalid HEX characters

Data.Binary helpers

encode' :: Binary a => a -> ByteStringSource

Strict version of Data.Binary.encode

decode' :: Binary a => ByteString -> aSource

Strict version of Data.Binary.decode

runPut' :: Put -> ByteStringSource

Strict version of Data.Binary.runPut

runGet' :: Binary a => Get a -> ByteString -> aSource

Strict version of Data.Binary.runGet

decodeOrFail' :: Binary a => ByteString -> Either (ByteString, ByteOffset, String) (ByteString, ByteOffset, a)Source

Strict version of Data.Binary.decodeOrFail

runGetOrFail' :: Binary a => Get a -> ByteString -> Either (ByteString, ByteOffset, String) (ByteString, ByteOffset, a)Source

Strict version of Data.Binary.runGetOrFail

fromDecodeSource

Arguments

:: Binary a 
=> ByteString

The bytestring to decode

-> b

Default value to return when decoding fails

-> (a -> b)

Function to apply when decoding succeeds

-> b

Final result

Try to decode a Data.Binary value. If decoding succeeds, apply the function to the result. Otherwise, return the default value.

fromRunGetSource

Arguments

:: Binary a 
=> Get a

The Get monad to run

-> ByteString

The bytestring to decode

-> b

Default value to return when decoding fails

-> (a -> b)

Function to apply when decoding succeeds

-> b

Final result

Try to run a Data.Binary.Get monad. If decoding succeeds, apply a function to the result. Otherwise, return the default value.

decodeToEither :: Binary a => ByteString -> Either String aSource

Decode a Data.Binary value into the Either monad. A Right value is returned with the result upon success. Otherwise a Left value with the error message is returned.

decodeToMaybe :: Binary a => ByteString -> Maybe aSource

Decode a Data.Binary value into the Maybe monad. A Just value is returned with the result upon success. Otherwise, Nothing is returned.

isolate :: Binary a => Int -> Get a -> Get aSource

Isolate a Data.Binary.Get monad for the next Int bytes. Only the next Int bytes of the input bytestring will be available for the Get monad to consume. This function will fail if the Get monad fails or some of the input is not consumed.

Maybe and Either monad helpers

isLeft :: Either a b -> BoolSource

Returns True if the Either value is Left

isRight :: Either a b -> BoolSource

Returns True if the Either value is Right

fromRight :: Either a b -> bSource

Extract the Right value from an Either value. Fails if the value is Left

fromLeft :: Either a b -> aSource

Extract the Left value from an Either value. Fails if the value is Right

eitherToMaybe :: Either a b -> Maybe bSource

Transforms an Either value into a Maybe value. Right is mapped to Just and Left is mapped to Nothing. The value inside Left is lost.

maybeToEither :: b -> Maybe a -> Either b aSource

Transforms a Maybe value into an Either value. Just is mapped to Right and Nothing is mapped to Left. You also pass in an error value in case Left is returned.

liftEither :: Monad m => Either b a -> EitherT b m aSource

Lift a Either computation into the EitherT monad

liftMaybe :: Monad m => b -> Maybe a -> EitherT b m aSource

Lift a Maybe computation into the EitherT monad

Various helpers

updateIndexSource

Arguments

:: Int

The index of the element to change

-> [a]

The list of elements

-> (a -> a)

The function to apply

-> [a]

The result with one element changed

Applies a function to only one element of a list defined by it's index. If the index is out of the bounds of the list, the original list is returned

matchTemplateSource

Arguments

:: [a]

The input list

-> [b]

The list to serve as a template

-> (a -> b -> Bool)

The comparison function

-> [Maybe a]

Results of the template matching

Use the list [b] as a template and try to match the elements of [a] against it. For each element of [b] return the (first) matching element of [a], or Nothing. Output list has same size as [b] and contains results in same order. Elements of [a] can only appear once.

fst3 :: (a, b, c) -> aSource

snd3 :: (a, b, c) -> bSource

lst3 :: (a, b, c) -> cSource

Build monad

data Build a Source

The Build monad represents computations that can be in one of three states:

  • Complete
  • Partial
  • Broken

It extends the Either monad with an additional Partial value to describe a valid computation flagged with a Partial context. The Build monad is useful when you describe computations where parts of the computation are either complete, partially complete or broken. Combining only Complete computations will produce a Complete result. However, if one of the computations is Partial, the whole computation will be Partial as well. And if some computation is Broken, the whole computation will be broken as well.

The Build monad is used by Haskoin to describe the state of the transaction signing computation. To sign a transaction, all input scripts need to be signed. The whole transaction will be completely signed only if all the input scripts are completely signed. If any of the inputs is partially signed, then the whole transaction will be partially signed as well. And the whole transaction is broken if one of the inputs failed to parse or is broken.

Constructors

Complete

Describes a successful complete computation

Fields

runBuild :: a
 
Partial

Describes a successful but partial computation

Fields

runBuild :: a
 
Broken

Describes a broken computation

Fields

runBroken :: String
 

Instances

Monad Build 
Functor Build 
Eq a => Eq (Build a) 
Show a => Show (Build a) 

isComplete :: Build a -> BoolSource

Returns True if the Build value is Complete

isPartial :: Build a -> BoolSource

Returns True if the Build value is Partial

isBroken :: Build a -> BoolSource

Return True if the Build value is Broken

eitherToBuild :: Either String a -> Build aSource

Transforms an Either String value into a Build value. Right is mapped to Complete and Left is mapped to Broken

buildToEither :: Build a -> Either String aSource

Transforms a Build value into an Either String value. Complete and Partial are mapped to Right and Broken is mapped to Left.

guardPartial :: Bool -> Build ()Source

Binds a Partial value to the computation when the predicate is False.

BuildT transformer monad

newtype BuildT m a Source

BuildT transformer monad

Constructors

BuildT 

Fields

runBuildT :: m (Build a)
 

Instances

liftBuild :: Monad m => Build a -> BuildT m aSource

Lift a Build computation into the BuildT monad

Constants

addrPrefix :: Word8Source

Prefix for base58 PubKey hash address

scriptPrefix :: Word8Source

Prefix for base58 script hash address

secretPrefix :: Word8Source

Prefix for private key WIF format

extPubKeyPrefix :: Word32Source

Prefix for extended public keys (BIP32)

extSecretPrefix :: Word32Source

Prefix for extended private keys (BIP32)

networkMagic :: Word32Source

Network magic bytes

genesisHeader :: [Integer]Source

Genesis block header information

maxBlockSize :: IntSource

Maximum size of a block in bytes

walletFile :: StringSource

Wallet database file name

haskoinUserAgent :: StringSource

User agent of this haskoin package