Skip to content

Commit 41a92ea

Browse files
GambolingPangolinProofOfKeags
authored andcommitted
Makes hlint pass
1 parent 0293da9 commit 41a92ea

File tree

7 files changed

+101
-78
lines changed

7 files changed

+101
-78
lines changed

src/Haskoin/Constants.hs

Lines changed: 0 additions & 2 deletions
Original file line numberDiff line numberDiff line change
@@ -1,6 +1,4 @@
11
{-# LANGUAGE CPP #-}
2-
{-# LANGUAGE DeriveAnyClass #-}
3-
{-# LANGUAGE DeriveGeneric #-}
42
{-# LANGUAGE OverloadedStrings #-}
53

64
{- |

src/Haskoin/Crypto/Hash.hs

Lines changed: 3 additions & 3 deletions
Original file line numberDiff line numberDiff line change
@@ -97,23 +97,23 @@ instance Show Hash512 where
9797
instance Read Hash512 where
9898
readPrec = do
9999
R.String str <- lexP
100-
maybe pfail return $ Hash512 . BSS.toShort <$> decodeHex (cs str)
100+
maybe pfail (return . Hash512 . BSS.toShort) (decodeHex (cs str))
101101

102102
instance Show Hash256 where
103103
showsPrec _ = shows . encodeHex . BSS.fromShort . getHash256
104104

105105
instance Read Hash256 where
106106
readPrec = do
107107
R.String str <- lexP
108-
maybe pfail return $ Hash256 . BSS.toShort <$> decodeHex (cs str)
108+
maybe pfail (return . Hash256 . BSS.toShort) (decodeHex (cs str))
109109

110110
instance Show Hash160 where
111111
showsPrec _ = shows . encodeHex . BSS.fromShort . getHash160
112112

113113
instance Read Hash160 where
114114
readPrec = do
115115
R.String str <- lexP
116-
maybe pfail return $ Hash160 . BSS.toShort <$> decodeHex (cs str)
116+
maybe pfail (return . Hash160 . BSS.toShort) (decodeHex (cs str))
117117

118118
instance IsString Hash512 where
119119
fromString str =

src/Haskoin/Keys/Extended.hs

Lines changed: 27 additions & 27 deletions
Original file line numberDiff line numberDiff line change
@@ -173,16 +173,16 @@ type KeyIndex = Word32
173173
parent node and an index to differentiate it from other siblings.
174174
-}
175175
data XPrvKey = XPrvKey
176-
{ -- | depth in the tree
177-
xPrvDepth :: !Word8
178-
, -- | fingerprint of parent
179-
xPrvParent :: !Fingerprint
180-
, -- | derivation index
181-
xPrvIndex :: !KeyIndex
182-
, -- | chain code
183-
xPrvChain :: !ChainCode
184-
, -- | private key of this node
185-
xPrvKey :: !SecKey
176+
{ xPrvDepth :: !Word8
177+
-- ^ depth in the tree
178+
, xPrvParent :: !Fingerprint
179+
-- ^ fingerprint of parent
180+
, xPrvIndex :: !KeyIndex
181+
-- ^ derivation index
182+
, xPrvChain :: !ChainCode
183+
-- ^ chain code
184+
, xPrvKey :: !SecKey
185+
-- ^ private key of this node
186186
}
187187
deriving (Generic, Eq, Show, Read, NFData, Hashable)
188188

@@ -194,7 +194,8 @@ instance Serial XPrvKey where
194194
serialize $ xPrvChain k
195195
putPadPrvKey $ xPrvKey k
196196
deserialize =
197-
XPrvKey <$> getWord8
197+
XPrvKey
198+
<$> getWord8
198199
<*> deserialize
199200
<*> getWord32be
200201
<*> deserialize
@@ -224,16 +225,16 @@ xPrvFromJSON net =
224225

225226
-- | Data type representing an extended BIP32 public key.
226227
data XPubKey = XPubKey
227-
{ -- | depth in the tree
228-
xPubDepth :: !Word8
229-
, -- | fingerprint of parent
230-
xPubParent :: !Fingerprint
231-
, -- | derivation index
232-
xPubIndex :: !KeyIndex
233-
, -- | chain code
234-
xPubChain :: !ChainCode
235-
, -- | public key of this node
236-
xPubKey :: !PubKey
228+
{ xPubDepth :: !Word8
229+
-- ^ depth in the tree
230+
, xPubParent :: !Fingerprint
231+
-- ^ fingerprint of parent
232+
, xPubIndex :: !KeyIndex
233+
-- ^ derivation index
234+
, xPubChain :: !ChainCode
235+
-- ^ chain code
236+
, xPubKey :: !PubKey
237+
-- ^ public key of this node
237238
}
238239
deriving (Generic, Eq, Show, Read, NFData, Hashable)
239240

@@ -245,7 +246,8 @@ instance Serial XPubKey where
245246
serialize $ xPubChain k
246247
serialize $ wrapPubKey True (xPubKey k)
247248
deserialize =
248-
XPubKey <$> getWord8
249+
XPubKey
250+
<$> getWord8
249251
<*> deserialize
250252
<*> getWord32be
251253
<*> deserialize
@@ -804,7 +806,7 @@ instance Read DerivPath where
804806
readPrec = parens $ do
805807
R.Ident "DerivPath" <- lexP
806808
R.String str <- lexP
807-
maybe pfail return $ getParsedPath <$> parsePath str
809+
maybe pfail (return . getParsedPath) (parsePath str)
808810

809811
instance Show HardPath where
810812
showsPrec d p =
@@ -961,14 +963,12 @@ instance Read Bip32PathIndex where
961963
parens $ do
962964
R.Ident "Bip32HardIndex" <- lexP
963965
R.Number n <- lexP
964-
maybe pfail return $
965-
Bip32HardIndex . fromIntegral <$> numberToInteger n
966+
maybe pfail (return . Bip32HardIndex . fromIntegral) (numberToInteger n)
966967
s =
967968
parens $ do
968969
R.Ident "Bip32SoftIndex" <- lexP
969970
R.Number n <- lexP
970-
maybe pfail return $
971-
Bip32SoftIndex . fromIntegral <$> numberToInteger n
971+
maybe pfail (return . Bip32SoftIndex . fromIntegral) (numberToInteger n)
972972

973973
-- | Test whether the number could be a valid BIP32 derivation index.
974974
is31Bit :: (Integral a) => a -> Bool

src/Haskoin/Transaction/Builder.hs

Lines changed: 14 additions & 7 deletions
Original file line numberDiff line numberDiff line change
@@ -315,8 +315,12 @@ guessMSSize (m, n) =
315315
-- OP_M + n*PubKey + OP_N + OP_CHECKMULTISIG
316316

317317
rdm =
318-
fromIntegral $
319-
B.length $ runPutS $ serialize $ opPushData $ B.replicate (n * 34 + 3) 0
318+
fromIntegral
319+
. B.length
320+
. runPutS
321+
. serialize
322+
. opPushData
323+
$ B.replicate (n * 34 + 3) 0
320324
-- Redeem + m*sig + OP_0
321325
scp = rdm + m * 73 + 1
322326

@@ -453,8 +457,10 @@ mergeTxInput net txs tx ((so, val), i) = do
453457
case out of
454458
PayMulSig msPubs r ->
455459
let sigs =
456-
take r $
457-
catMaybes $ matchTemplate allSigs msPubs $ f out
460+
take r
461+
. catMaybes
462+
. matchTemplate allSigs msPubs
463+
$ f out
458464
in return $ RegularInput $ SpendMulSig sigs
459465
PayScriptHash _ ->
460466
case rdmM of
@@ -510,9 +516,10 @@ verifyStdInput net tx i so0 val
510516

511517
nestedScriptOutput :: Either String ScriptOutput
512518
nestedScriptOutput =
513-
scriptOps <$> runGetS deserialize inp >>= \case
514-
[OP_PUSHDATA bs _] -> decodeOutputBS bs
515-
_ -> Left "nestedScriptOutput: not a nested output"
519+
runGetS deserialize inp
520+
>>= \case
521+
Script [OP_PUSHDATA bs _] -> decodeOutputBS bs
522+
_ -> Left "nestedScriptOutput: not a nested output"
516523

517524
verifyLegacyInput :: ScriptOutput -> ScriptInput -> Bool
518525
verifyLegacyInput so si = case (so, si) of

src/Haskoin/Util/Arbitrary/Block.hs

Lines changed: 11 additions & 10 deletions
Original file line numberDiff line numberDiff line change
@@ -28,7 +28,8 @@ arbitraryBlock net = do
2828
-- | Block header with random hash.
2929
arbitraryBlockHeader :: Gen BlockHeader
3030
arbitraryBlockHeader =
31-
BlockHeader <$> arbitrary
31+
BlockHeader
32+
<$> arbitrary
3233
<*> arbitraryBlockHash
3334
<*> arbitraryHash256
3435
<*> arbitrary
@@ -42,14 +43,16 @@ arbitraryBlockHash = BlockHash <$> arbitraryHash256
4243
-- | Arbitrary 'GetBlocks' object with at least one block hash.
4344
arbitraryGetBlocks :: Gen GetBlocks
4445
arbitraryGetBlocks =
45-
GetBlocks <$> arbitrary
46+
GetBlocks
47+
<$> arbitrary
4648
<*> listOf1 arbitraryBlockHash
4749
<*> arbitraryBlockHash
4850

4951
-- | Arbitrary 'GetHeaders' object with at least one block header.
5052
arbitraryGetHeaders :: Gen GetHeaders
5153
arbitraryGetHeaders =
52-
GetHeaders <$> arbitrary
54+
GetHeaders
55+
<$> arbitrary
5356
<*> listOf1 arbitraryBlockHash
5457
<*> arbitraryBlockHash
5558

@@ -71,13 +74,11 @@ arbitraryMerkleBlock = do
7174
-- | Arbitrary 'BlockNode'
7275
arbitraryBlockNode :: Gen BlockNode
7376
arbitraryBlockNode =
74-
oneof
75-
[ BlockNode
76-
<$> arbitraryBlockHeader
77-
<*> choose (0, maxBound)
78-
<*> arbitrarySizedNatural
79-
<*> arbitraryBlockHash
80-
]
77+
BlockNode
78+
<$> arbitraryBlockHeader
79+
<*> choose (0, maxBound)
80+
<*> arbitrarySizedNatural
81+
<*> arbitraryBlockHash
8182

8283
-- | Arbitrary 'HeaderMemory'
8384
arbitraryHeaderMemory :: Gen HeaderMemory

test/Haskoin/Address/Bech32Spec.hs

Lines changed: 30 additions & 19 deletions
Original file line numberDiff line numberDiff line change
@@ -27,32 +27,43 @@ spec = do
2727
it "should be invalid" $
2828
forM_ invalidChecksums testInvalidChecksum
2929
it "should be case-insensitive" $
30-
all (== Just "test12hrzfj") $
31-
map (flip (bech32Encode Bech32) []) hrpCaseVariants
30+
all ((== Just "test12hrzfj") . flip (bech32Encode Bech32) []) hrpCaseVariants
3231
describe "bech32 address" $ do
3332
it "should be valid" $
3433
forM_ validChecksums (uncurry testValidChecksum)
3534
it "should be invalid" $
3635
forM_ invalidChecksums testInvalidChecksum
3736
it "should be case-insensitive" $
38-
all (== Just "test12hrzfj") $
39-
map (flip (bech32Encode Bech32) []) hrpCaseVariants
37+
all ((== Just "test12hrzfj") . flip (bech32Encode Bech32) []) hrpCaseVariants
4038
describe "bech32 encoding/decoding" $ do
41-
it "should not encode long data string" $
42-
assert . isNothing $
43-
bech32Encode Bech32 "bc" (replicate 82 (word5 (1 :: Word8)))
44-
it "should not encode bad version number" $
45-
assert $ isNothing $ segwitEncode "bc" 17 []
46-
it "should not encode invalid length for version 0" $
47-
assert $ isNothing $ segwitEncode "bc" 0 (replicate 30 1)
48-
it "should relax length restrictions for versions other than 0" $
49-
assert $ isJust $ segwitEncode "bc" 1 (replicate 30 1)
50-
it "should not encode another long data string" $
51-
assert $ isNothing $ segwitEncode "bc" 1 (replicate 41 1)
52-
it "should not encode empty human readable part" $
53-
assert $ isNothing $ bech32Encode Bech32 "" []
54-
it "should not decode empty human-readable part" $
55-
assert $ isNothing $ bech32Decode "10a06t8"
39+
it "should not encode long data string"
40+
. assert
41+
. isNothing
42+
$ bech32Encode Bech32 "bc" (replicate 82 (word5 (1 :: Word8)))
43+
it "should not encode bad version number"
44+
. assert
45+
. isNothing
46+
$ segwitEncode "bc" 17 []
47+
it "should not encode invalid length for version 0"
48+
. assert
49+
. isNothing
50+
$ segwitEncode "bc" 0 (replicate 30 1)
51+
it "should relax length restrictions for versions other than 0"
52+
. assert
53+
. isJust
54+
$ segwitEncode "bc" 1 (replicate 30 1)
55+
it "should not encode another long data string"
56+
. assert
57+
. isNothing
58+
$ segwitEncode "bc" 1 (replicate 41 1)
59+
it "should not encode empty human readable part"
60+
. assert
61+
. isNothing
62+
$ bech32Encode Bech32 "" []
63+
it "should not decode empty human-readable part"
64+
. assert
65+
. isNothing
66+
$ bech32Decode "10a06t8"
5667
it "human-readable part should be case-insensitive" $
5768
bech32Encode Bech32 "HRP" [] `shouldBe` bech32Encode Bech32 "hrp" []
5869

test/Haskoin/TransactionSpec.hs

Lines changed: 16 additions & 10 deletions
Original file line numberDiff line numberDiff line change
@@ -60,9 +60,11 @@ spec = do
6060
testIdentity serialVals readVals jsonVals []
6161
describe "Transaction properties" $ do
6262
prop "decode and encode txid" $
63-
forAll arbitraryTxHash $ \h -> hexToTxHash (txHashToHex h) == Just h
63+
forAll arbitraryTxHash $
64+
\h -> hexToTxHash (txHashToHex h) == Just h
6465
prop "from string transaction id" $
65-
forAll arbitraryTxHash $ \h -> fromString (cs $ txHashToHex h) == h
66+
forAll arbitraryTxHash $
67+
\h -> fromString (cs $ txHashToHex h) == h
6668
prop "building address tx" $
6769
forAll arbitraryNetwork $ \net ->
6870
forAll arbitraryAddress $
@@ -246,7 +248,8 @@ testBuildAddrTx net a (TestCoin v)
246248
out =
247249
decodeOutputBS $
248250
scriptOutput $
249-
head $ txOut (fromRight (error "Could not build transaction") tx)
251+
head $
252+
txOut (fromRight (error "Could not build transaction") tx)
250253

251254
-- We compute an upper bound but it should be close enough to the real size
252255
-- We give 2 bytes of slack on every signature (1 on r and 1 on s)
@@ -260,7 +263,8 @@ testGuessSize net tx =
260263
ins = map f $ txIn tx
261264
f i =
262265
fromRight (error "Could not decode input") $
263-
decodeInputBS net $ scriptInput i
266+
decodeInputBS net $
267+
scriptInput i
264268
pki = length $ filter isSpendPKHash ins
265269
msi = concatMap shData ins
266270
shData (ScriptHashInput _ (PayMulSig keys r)) = [(r, length keys)]
@@ -277,8 +281,8 @@ testGuessSize net tx =
277281

278282
testChooseCoins :: [TestCoin] -> Word64 -> Word64 -> Int -> Property
279283
testChooseCoins coins target byteFee nOut =
280-
nOut >= 0
281-
==> case chooseCoins target byteFee nOut True coins of
284+
nOut >= 0 ==>
285+
case chooseCoins target byteFee nOut True coins of
282286
Right (chosen, change) ->
283287
let outSum = sum $ map coinValue chosen
284288
fee = guessTxFee byteFee nOut (length chosen)
@@ -297,8 +301,8 @@ testChooseMSCoins ::
297301
Int ->
298302
Property
299303
testChooseMSCoins (m, n) coins target byteFee nOut =
300-
nOut >= 0
301-
==> case chooseMSCoins target byteFee (m, n) nOut True coins of
304+
nOut >= 0 ==>
305+
case chooseMSCoins target byteFee (m, n) nOut True coins of
302306
Right (chosen, change) ->
303307
let outSum = sum $ map coinValue chosen
304308
fee = guessMSTxFee byteFee (m, n) nOut (length chosen)
@@ -360,8 +364,10 @@ testMergeTx net (txs, os) =
360364
isValid = verifyStdTx net mergedTx outs
361365
enoughSigs = all (\(m, c) -> c >= m) sigMap
362366
sigMap =
363-
map (\((_, _, _, m, _), inp) -> (m, sigCnt inp)) $
364-
zip os $ txIn mergedTx
367+
zipWith
368+
(\(_, _, _, m, _) inp -> (m, sigCnt inp))
369+
os
370+
(txIn mergedTx)
365371
sigCnt inp =
366372
case decodeInputBS net $ scriptInput inp of
367373
Right (RegularInput (SpendMulSig sigs)) -> length sigs

0 commit comments

Comments
 (0)