From 64a0760f9bd5533e0aebc02e1c46567c9c6b807e Mon Sep 17 00:00:00 2001 From: Keagan McClelland Date: Thu, 2 May 2024 22:03:08 -0700 Subject: [PATCH] commit fourmolu diff --- bitcoin-test/lib/Bitcoin/BlockSpec.hs | 2 +- bitcoin-test/lib/Bitcoin/Keys/MnemonicSpec.hs | 2 +- bitcoin-test/lib/Bitcoin/ScriptSpec.hs | 4 +- .../lib/Bitcoin/Util/Arbitrary/Util.hs | 2 +- bitcoin-test/lib/Bitcoin/UtilSpec.hs | 2 +- bitcoin/src/Bitcoin/Address/Bech32.hs | 14 +++---- bitcoin/src/Bitcoin/Block/Headers.hs | 40 +++++++++---------- bitcoin/src/Bitcoin/Constants.hs | 2 +- bitcoin/src/Bitcoin/Crypto/Hash.hs | 14 +++---- bitcoin/src/Bitcoin/Network/Common.hs | 2 +- bitcoin/src/Bitcoin/Script/Standard.hs | 2 +- bitcoin/src/Bitcoin/Transaction/Genesis.hs | 14 +++---- stack.yaml | 4 +- stack.yaml.lock | 21 ++++++---- 14 files changed, 67 insertions(+), 58 deletions(-) diff --git a/bitcoin-test/lib/Bitcoin/BlockSpec.hs b/bitcoin-test/lib/Bitcoin/BlockSpec.hs index 54fdc833..21e99f00 100644 --- a/bitcoin-test/lib/Bitcoin/BlockSpec.hs +++ b/bitcoin-test/lib/Bitcoin/BlockSpec.hs @@ -114,7 +114,7 @@ withChain :: Network -> State HeaderMemory a -> a withChain net f = evalState f (initialChain net) -chain :: BlockHeaders m => Network -> BlockHeader -> Int -> m () +chain :: (BlockHeaders m) => Network -> BlockHeader -> Int -> m () chain net bh i = do bnsE <- connectBlocks net myTime bhs either error (const $ return ()) bnsE diff --git a/bitcoin-test/lib/Bitcoin/Keys/MnemonicSpec.hs b/bitcoin-test/lib/Bitcoin/Keys/MnemonicSpec.hs index 0d12b98b..0848f6db 100644 --- a/bitcoin-test/lib/Bitcoin/Keys/MnemonicSpec.hs +++ b/bitcoin-test/lib/Bitcoin/Keys/MnemonicSpec.hs @@ -306,7 +306,7 @@ invalidMss = ] -binWordsToBS :: Binary a => [a] -> BSL.ByteString +binWordsToBS :: (Binary a) => [a] -> BSL.ByteString binWordsToBS = foldr f BSL.empty where f b a = a `BSL.append` Bin.encode b diff --git a/bitcoin-test/lib/Bitcoin/ScriptSpec.hs b/bitcoin-test/lib/Bitcoin/ScriptSpec.hs index 4755396e..a8535cee 100644 --- a/bitcoin-test/lib/Bitcoin/ScriptSpec.hs +++ b/bitcoin-test/lib/Bitcoin/ScriptSpec.hs @@ -366,8 +366,8 @@ sigHashSpec net = do testSigHashOne :: Network -> Tx -> Script -> Word64 -> Bool -> Property testSigHashOne net tx s val acp = - not (null $ txIn tx) - ==> if length (txIn tx) > length (txOut tx) + not (null $ txIn tx) ==> + if length (txIn tx) > length (txOut tx) then res `shouldBe` one else res `shouldNotBe` one where diff --git a/bitcoin-test/lib/Bitcoin/Util/Arbitrary/Util.hs b/bitcoin-test/lib/Bitcoin/Util/Arbitrary/Util.hs index d75e0b0a..493707c9 100644 --- a/bitcoin-test/lib/Bitcoin/Util/Arbitrary/Util.hs +++ b/bitcoin-test/lib/Bitcoin/Util/Arbitrary/Util.hs @@ -93,7 +93,7 @@ arbitraryNetwork :: Gen Network arbitraryNetwork = elements allNets -arbitraryNetData :: Arbitrary a => Gen (Network, a) +arbitraryNetData :: (Arbitrary a) => Gen (Network, a) arbitraryNetData = do net <- arbitraryNetwork x <- arbitrary diff --git a/bitcoin-test/lib/Bitcoin/UtilSpec.hs b/bitcoin-test/lib/Bitcoin/UtilSpec.hs index ffa91e79..9ad483fc 100644 --- a/bitcoin-test/lib/Bitcoin/UtilSpec.hs +++ b/bitcoin-test/lib/Bitcoin/UtilSpec.hs @@ -114,7 +114,7 @@ testMaybeToEither m str = maybeToEither str m == Left str {-- Test Utilities --} -readTestFile :: A.FromJSON a => FilePath -> IO a +readTestFile :: (A.FromJSON a) => FilePath -> IO a readTestFile fp = A.eitherDecodeFileStrict ("data/" <> fp) >>= either (error . message) return where diff --git a/bitcoin/src/Bitcoin/Address/Bech32.hs b/bitcoin/src/Bitcoin/Address/Bech32.hs index b2cc96bb..01f7cd88 100644 --- a/bitcoin/src/Bitcoin/Address/Bech32.hs +++ b/bitcoin/src/Bitcoin/Address/Bech32.hs @@ -76,7 +76,7 @@ type HRP = Text type Data = [Word8] -(.>>.), (.<<.) :: Bits a => a -> Int -> a +(.>>.), (.<<.) :: (Bits a) => a -> Int -> a (.>>.) = unsafeShiftR (.<<.) = unsafeShiftL @@ -94,14 +94,14 @@ instance Ix Word5 where -- | Convert an integer number into a five-bit word. -word5 :: Integral a => a -> Word5 +word5 :: (Integral a) => a -> Word5 word5 x = UnsafeWord5 (fromIntegral x .&. 31) {-# INLINE word5 #-} {-# SPECIALIZE INLINE word5 :: Word8 -> Word5 #-} -- | Convert a five-bit word into a number. -fromWord5 :: Num a => Word5 -> a +fromWord5 :: (Num a) => Word5 -> a fromWord5 (UnsafeWord5 x) = fromIntegral x {-# INLINE fromWord5 #-} {-# SPECIALIZE INLINE fromWord5 :: Word5 -> Word8 #-} @@ -165,9 +165,9 @@ bech32VerifyChecksum :: HRP -> [Word5] -> Maybe Bech32Encoding bech32VerifyChecksum hrp dat = let poly = bech32Polymod (bech32HRPExpand hrp ++ dat) in if - | poly == bech32Const Bech32 -> Just Bech32 - | poly == bech32Const Bech32m -> Just Bech32m - | otherwise -> Nothing + | poly == bech32Const Bech32 -> Just Bech32 + | poly == bech32Const Bech32m -> Just Bech32m + | otherwise -> Nothing -- | Maximum length of a Bech32 result. @@ -300,7 +300,7 @@ noPadding frombits bits padValue result = do -- \(2^{tobits}\). {frombits} and {twobits} must be positive and -- \(2^{frombits}\) and \(2^{tobits}\) must be smaller than the size of Word. -- Every value in 'dat' must be strictly smaller than \(2^{frombits}\). -convertBits :: Functor f => [Word] -> Int -> Int -> Pad f -> f [Word] +convertBits :: (Functor f) => [Word] -> Int -> Int -> Pad f -> f [Word] convertBits dat frombits tobits pad = concat . reverse <$> go dat 0 0 [] where go [] acc bits result = diff --git a/bitcoin/src/Bitcoin/Block/Headers.hs b/bitcoin/src/Bitcoin/Block/Headers.hs index a4f11d31..81d3d949 100644 --- a/bitcoin/src/Bitcoin/Block/Headers.hs +++ b/bitcoin/src/Bitcoin/Block/Headers.hs @@ -176,7 +176,7 @@ data HeaderMemory = HeaderMemory -- | Typeclass for block header chain storage monad. -class Monad m => BlockHeaders m where +class (Monad m) => BlockHeaders m where -- | Add a new 'BlockNode' to the chain. Does not validate. addBlockHeader :: BlockNode -> m () @@ -198,7 +198,7 @@ class Monad m => BlockHeaders m where addBlockHeaders = mapM_ addBlockHeader -instance Monad m => BlockHeaders (StateT HeaderMemory m) where +instance (Monad m) => BlockHeaders (StateT HeaderMemory m) where addBlockHeader = State.modify' . addBlockHeaderMemory getBlockHeader bh = getBlockHeaderMemory bh <$> State.get getBestBlockHeader = State.gets memoryBestHeader @@ -255,7 +255,7 @@ addBlockToMap node = -- | Get the ancestor of the provided 'BlockNode' at the specified -- 'BlockHeight'. getAncestor :: - BlockHeaders m => + (BlockHeaders m) => BlockHeight -> BlockNode -> m (Maybe BlockNode) @@ -309,7 +309,7 @@ genesisNode net = -- | Validate a list of continuous block headers and import them to the -- block chain. Return 'Left' on failure with error information. connectBlocks :: - BlockHeaders m => + (BlockHeaders m) => Network -> -- | current time Timestamp -> @@ -363,7 +363,7 @@ connectBlocks net t bhs@(bh : _) = -- | Block's parent. If the block header is in the store, its parent must also -- be there. No block header get deleted or pruned from the store. parentBlock :: - BlockHeaders m => + (BlockHeaders m) => BlockHeader -> m (Maybe BlockNode) parentBlock bh = getBlockHeader (prevBlock bh) @@ -372,7 +372,7 @@ parentBlock bh = getBlockHeader (prevBlock bh) -- | Validate and connect single block header to the block chain. Return 'Left' -- if fails to be validated. connectBlock :: - BlockHeaders m => + (BlockHeaders m) => Network -> -- | current time Timestamp -> @@ -479,7 +479,7 @@ invertLowestOne height = height .&. (height - 1) -- | Get a number of parents for the provided block. getParents :: - BlockHeaders m => + (BlockHeaders m) => Int -> BlockNode -> -- | starts from immediate parent @@ -562,7 +562,7 @@ validVersion net height version -- | Find last block with normal, as opposed to minimum difficulty (for test -- networks). -lastNoMinDiff :: BlockHeaders m => Network -> BlockNode -> m BlockNode +lastNoMinDiff :: (BlockHeaders m) => Network -> BlockNode -> m BlockNode lastNoMinDiff _ bn@BlockNode{nodeHeight = 0} = return bn lastNoMinDiff net bn@BlockNode{..} = do let i = nodeHeight `mod` diffInterval net /= 0 @@ -579,7 +579,7 @@ lastNoMinDiff net bn@BlockNode{..} = do else return bn -mtp :: BlockHeaders m => BlockNode -> m Timestamp +mtp :: (BlockHeaders m) => BlockNode -> m Timestamp mtp bn | nodeHeight bn == 0 = return 0 | otherwise = do @@ -588,7 +588,7 @@ mtp bn firstGreaterOrEqual :: - BlockHeaders m => + (BlockHeaders m) => Network -> (BlockNode -> m Ordering) -> m (Maybe BlockNode) @@ -596,7 +596,7 @@ firstGreaterOrEqual = binSearch False lastSmallerOrEqual :: - BlockHeaders m => + (BlockHeaders m) => Network -> (BlockNode -> m Ordering) -> m (Maybe BlockNode) @@ -604,7 +604,7 @@ lastSmallerOrEqual = binSearch True binSearch :: - BlockHeaders m => + (BlockHeaders m) => Bool -> Network -> (BlockNode -> m Ordering) -> @@ -643,13 +643,13 @@ binSearch top net f = runMaybeT $ do | otherwise = return b -extremes :: BlockHeaders m => Network -> m (BlockNode, BlockNode) +extremes :: (BlockHeaders m) => Network -> m (BlockNode, BlockNode) extremes net = do b <- getBestBlockHeader return (genesisNode net, b) -middleBlock :: BlockHeaders m => BlockNode -> BlockNode -> m BlockNode +middleBlock :: (BlockHeaders m) => BlockNode -> BlockNode -> m BlockNode middleBlock a b = getAncestor h b >>= \case Nothing -> error "You fell into a pit full of mud and snakes" @@ -658,7 +658,7 @@ middleBlock a b = h = middleOf (nodeHeight a) (nodeHeight b) -middleOf :: Integral a => a -> a -> a +middleOf :: (Integral a) => a -> a -> a middleOf a b = a + ((b - a) `div` 2) @@ -722,7 +722,7 @@ computeAssertBits halflife anchor_bits time_diff height_diff = -- | Returns the work required on a block header given the previous block. This -- coresponds to bitcoind function GetNextWorkRequired in main.cpp. nextPowWorkRequired :: - BlockHeaders m => Network -> BlockNode -> BlockHeader -> m Word32 + (BlockHeaders m) => Network -> BlockNode -> BlockHeader -> m Word32 nextPowWorkRequired net par bh | nodeHeight par + 1 `mod` diffInterval net /= 0 = if getAllowMinDifficultyBlocks net @@ -811,7 +811,7 @@ chooseBest b1 b2 -- | Get list of blocks for a block locator. -blockLocatorNodes :: BlockHeaders m => BlockNode -> m [BlockNode] +blockLocatorNodes :: (BlockHeaders m) => BlockNode -> m [BlockNode] blockLocatorNodes best = reverse <$> go [] best 1 where @@ -833,7 +833,7 @@ blockLocatorNodes best = -- | Get block locator. -blockLocator :: BlockHeaders m => BlockNode -> m BlockLocator +blockLocator :: (BlockHeaders m) => BlockNode -> m BlockLocator blockLocator bn = map (headerHash . nodeHeader) <$> blockLocatorNodes bn @@ -872,7 +872,7 @@ appendBlocks net seed bh i = -- | Find the last common block ancestor between provided block headers. -splitPoint :: BlockHeaders m => BlockNode -> BlockNode -> m BlockNode +splitPoint :: (BlockHeaders m) => BlockNode -> BlockNode -> m BlockNode splitPoint l r = do let h = min (nodeHeight l) (nodeHeight r) ll <- fromMaybe e <$> getAncestor h l @@ -905,5 +905,5 @@ computeSubsidy net height = else ini `shiftR` fromIntegral halvings -encodeToShort :: Binary a => a -> ShortByteString +encodeToShort :: (Binary a) => a -> ShortByteString encodeToShort = toShort . U.encodeS diff --git a/bitcoin/src/Bitcoin/Constants.hs b/bitcoin/src/Bitcoin/Constants.hs index e8c15aaf..c28d412d 100644 --- a/bitcoin/src/Bitcoin/Constants.hs +++ b/bitcoin/src/Bitcoin/Constants.hs @@ -27,7 +27,7 @@ import Data.String (IsString) -- | Version of Bitcoin package. -versionString :: IsString a => a +versionString :: (IsString a) => a #ifdef CURRENT_PACKAGE_VERSION versionString = CURRENT_PACKAGE_VERSION diff --git a/bitcoin/src/Bitcoin/Crypto/Hash.hs b/bitcoin/src/Bitcoin/Crypto/Hash.hs index 1146b968..5e73ed06 100644 --- a/bitcoin/src/Bitcoin/Crypto/Hash.hs +++ b/bitcoin/src/Bitcoin/Crypto/Hash.hs @@ -172,17 +172,17 @@ instance Binary Hash160 where -- | Use this function to produce hashes during the process of serialization -hashWithL :: HashAlgorithm alg => alg -> BSL.ByteString -> Digest alg +hashWithL :: (HashAlgorithm alg) => alg -> BSL.ByteString -> Digest alg hashWithL _ = hashFinalize . hashUpdates hashInit . BSL.toChunks -- | Calculate SHA512 hash. -sha512 :: ByteArrayAccess b => b -> Hash512 +sha512 :: (ByteArrayAccess b) => b -> Hash512 sha512 = Hash512 . BSS.toShort . BA.convert . hashWith SHA512 -- | Calculate SHA256 hash. -sha256 :: ByteArrayAccess b => b -> Hash256 +sha256 :: (ByteArrayAccess b) => b -> Hash256 sha256 = Hash256 . BSS.toShort . BA.convert . hashWith SHA256 @@ -192,17 +192,17 @@ sha256L = Hash256 . BSS.toShort . BA.convert . hashWithL SHA256 -- | Calculate RIPEMD160 hash. -ripemd160 :: ByteArrayAccess b => b -> Hash160 +ripemd160 :: (ByteArrayAccess b) => b -> Hash160 ripemd160 = Hash160 . BSS.toShort . BA.convert . hashWith RIPEMD160 -- | Claculate SHA1 hash. -sha1 :: ByteArrayAccess b => b -> Hash160 +sha1 :: (ByteArrayAccess b) => b -> Hash160 sha1 = Hash160 . BSS.toShort . BA.convert . hashWith SHA1 -- | Compute two rounds of SHA-256. -doubleSHA256 :: ByteArrayAccess b => b -> Hash256 +doubleSHA256 :: (ByteArrayAccess b) => b -> Hash256 doubleSHA256 = Hash256 . BSS.toShort . BA.convert . hashWith SHA256 . hashWith SHA256 @@ -214,7 +214,7 @@ doubleSHA256L = -- | Compute SHA-256 followed by RIPMED-160. -addressHash :: ByteArrayAccess b => b -> Hash160 +addressHash :: (ByteArrayAccess b) => b -> Hash160 addressHash = Hash160 . BSS.toShort . BA.convert . hashWith RIPEMD160 . hashWith SHA256 diff --git a/bitcoin/src/Bitcoin/Network/Common.hs b/bitcoin/src/Bitcoin/Network/Common.hs index e262c1fb..3c4519ca 100644 --- a/bitcoin/src/Bitcoin/Network/Common.hs +++ b/bitcoin/src/Bitcoin/Network/Common.hs @@ -415,7 +415,7 @@ instance Binary VarInt where Put.putWord64le x -putVarInt :: Integral a => a -> Put +putVarInt :: (Integral a) => a -> Put putVarInt = put . VarInt . fromIntegral diff --git a/bitcoin/src/Bitcoin/Script/Standard.hs b/bitcoin/src/Bitcoin/Script/Standard.hs index c4d428ce..d52622b8 100644 --- a/bitcoin/src/Bitcoin/Script/Standard.hs +++ b/bitcoin/src/Bitcoin/Script/Standard.hs @@ -269,7 +269,7 @@ encodeOutput s = Script $ case s of (DataCarrier d) -> [OP_RETURN, opPushData d] -pushItem :: Binary a => a -> ScriptOp +pushItem :: (Binary a) => a -> ScriptOp pushItem = opPushData . U.encodeS diff --git a/bitcoin/src/Bitcoin/Transaction/Genesis.hs b/bitcoin/src/Bitcoin/Transaction/Genesis.hs index ed3aa141..82307622 100644 --- a/bitcoin/src/Bitcoin/Transaction/Genesis.hs +++ b/bitcoin/src/Bitcoin/Transaction/Genesis.hs @@ -1,14 +1,14 @@ {-# LANGUAGE OverloadedStrings #-} -- | ---Module : Bitcoin.Transaction.Genesis ---Copyright : No rights reserved ---License : UNLICENSE ---Maintainer : jprupp@protonmail.ch ---Stability : experimental ---Portability : POSIX +-- Module : Bitcoin.Transaction.Genesis +-- Copyright : No rights reserved +-- License : UNLICENSE +-- Maintainer : jprupp@protonmail.ch +-- Stability : experimental +-- Portability : POSIX -- ---Code related to transactions parsing and serialization. +-- Code related to transactions parsing and serialization. module Bitcoin.Transaction.Genesis ( genesisTx, ) where diff --git a/stack.yaml b/stack.yaml index baaa6e79..5bdaf80a 100644 --- a/stack.yaml +++ b/stack.yaml @@ -5,9 +5,11 @@ nix: - secp256k1 - pkg-config extra-deps: - - fourmolu-0.14.0.0 - cryptonite-0.30 - libsecp256k1-0.2.0 + # for fourmolu CI + - fourmolu-0.14.0.0 + - ghc-lib-parser-9.6.2.20230523 packages: - ./bitcoin - ./bitcoin-test diff --git a/stack.yaml.lock b/stack.yaml.lock index 729dad23..9232e030 100644 --- a/stack.yaml.lock +++ b/stack.yaml.lock @@ -4,13 +4,6 @@ # https://docs.haskellstack.org/en/stable/lock_files packages: -- completed: - hackage: fourmolu-0.14.0.0@sha256:ba97d135f44cd5fb670dd47228ec3c65d3a886cc293a548510671c78c512c240,6755 - pantry-tree: - sha256: e70f2d81866ac2cb200e8ebc5372186d5bb293e253b4e51fadba2309bb40ed85 - size: 156343 - original: - hackage: fourmolu-0.14.0.0 - completed: hackage: cryptonite-0.30@sha256:12c85dea7be63e5ad90bcb487eb3846bf3c413347f94336fa1dede7b28f9936a,18301 pantry-tree: @@ -25,6 +18,20 @@ packages: size: 902 original: hackage: libsecp256k1-0.2.0 +- completed: + hackage: fourmolu-0.14.0.0@sha256:ba97d135f44cd5fb670dd47228ec3c65d3a886cc293a548510671c78c512c240,6755 + pantry-tree: + sha256: e70f2d81866ac2cb200e8ebc5372186d5bb293e253b4e51fadba2309bb40ed85 + size: 156343 + original: + hackage: fourmolu-0.14.0.0 +- completed: + hackage: ghc-lib-parser-9.6.2.20230523@sha256:160fc11671ce69e756d67f42a75c564863f59b81782a3d23efc27a845d61041b,15694 + pantry-tree: + sha256: 99328c298629fa921985d3de081354625463b659ca7122a1971e548d7051c68a + size: 33893 + original: + hackage: ghc-lib-parser-9.6.2.20230523 snapshots: - completed: sha256: 1b4c2669e26fa828451830ed4725e4d406acc25a1fa24fcc039465dd13d7a575