Skip to content

Commit

Permalink
Use shorter cross-compiler friendly HLint annotations
Browse files Browse the repository at this point in the history
  • Loading branch information
rvl authored and KtorZ committed Oct 16, 2020
1 parent 95c37bc commit 23e9257
Show file tree
Hide file tree
Showing 13 changed files with 16 additions and 22 deletions.
7 changes: 2 additions & 5 deletions lib/core/src/Cardano/Byron/Codec/Cbor.hs
Original file line number Diff line number Diff line change
@@ -1,6 +1,3 @@
-- need this for {-# HLINT ... #-}; see https://github.com/ndmitchell/hlint#ignoring-hints
{-# OPTIONS_GHC -Wno-unrecognised-pragmas #-}

{-# LANGUAGE DataKinds #-}
{-# LANGUAGE FlexibleContexts #-}
{-# LANGUAGE LambdaCase #-}
Expand Down Expand Up @@ -281,7 +278,7 @@ decodeTx = do
_ <- decodeEmptyAttributes
return (ins, outs)

{-# HLINT ignore decodeTxIn "Use <$>" #-}
{- HLINT ignore decodeTxIn "Use <$>" -}
decodeTxIn :: CBOR.Decoder s TxIn
decodeTxIn = do
_ <- CBOR.decodeListLenCanonicalOf 2
Expand All @@ -301,7 +298,7 @@ decodeTxIn = do
tx <- Hash <$> CBOR.decodeBytes
TxIn tx <$> CBOR.decodeWord32

{-# HLINT ignore decodeTxOut "Use <$>" #-}
{- HLINT ignore decodeTxOut "Use <$>" -}
decodeTxOut :: CBOR.Decoder s TxOut
decodeTxOut = do
_ <- CBOR.decodeListLenCanonicalOf 2
Expand Down
3 changes: 1 addition & 2 deletions lib/core/src/Cardano/DB/Sqlite.hs
Original file line number Diff line number Diff line change
Expand Up @@ -13,8 +13,7 @@
{-# LANGUAGE TypeFamilies #-}
{-# LANGUAGE UndecidableInstances #-}

{-# OPTIONS_GHC -Wno-unrecognised-pragmas #-}
{-# HLINT ignore "Redundant flip" #-}
{- HLINT ignore "Redundant flip" -}

-- |
-- Copyright: © 2018-2020 IOHK
Expand Down
2 changes: 1 addition & 1 deletion lib/core/src/Cardano/Pool/DB/Model.hs
Original file line number Diff line number Diff line change
Expand Up @@ -451,7 +451,7 @@ mReadSettings = get #settings
-- `const` isn't more readable than lambdas. Our language is based on
-- lambda calculus and we shouldn't feel ashamed to use them. They also
-- have different strictness properties.
{-# HLINT ignore mPutSettings "Use const" #-}
{- HLINT ignore mPutSettings "Use const" -}
mPutSettings
:: Settings
-> ModelOp ()
Expand Down
3 changes: 1 addition & 2 deletions lib/core/src/Cardano/Pool/DB/Sqlite.hs
Original file line number Diff line number Diff line change
Expand Up @@ -14,8 +14,7 @@
{-# LANGUAGE TypeFamilies #-}
{-# LANGUAGE UndecidableInstances #-}

{-# OPTIONS_GHC -Wno-unrecognised-pragmas #-}
{-# HLINT ignore "Redundant flip" #-}
{- HLINT ignore "Redundant flip" -}

-- |
-- Copyright: © 2018-2020 IOHK
Expand Down
3 changes: 1 addition & 2 deletions lib/core/src/Cardano/Wallet/DB/Sqlite.hs
Original file line number Diff line number Diff line change
Expand Up @@ -12,8 +12,7 @@
{-# LANGUAGE TypeFamilies #-}
{-# LANGUAGE UndecidableInstances #-}

{-# OPTIONS_GHC -Wno-unrecognised-pragmas #-}
{-# HLINT ignore "Redundant flip" #-}
{- HLINT ignore "Redundant flip" -}

-- |
-- Copyright: © 2018-2020 IOHK
Expand Down
2 changes: 1 addition & 1 deletion lib/core/test/unit/Cardano/Byron/Codec/CborSpec.hs
Original file line number Diff line number Diff line change
Expand Up @@ -58,7 +58,7 @@ import qualified Data.ByteArray as BA
import qualified Data.ByteString as BS
import qualified Data.ByteString.Lazy as BL

{-# ANN spec ("HLint: ignore Use head" :: String) #-}
{- HLINT ignore spec "Use head" -}

spec :: Spec
spec = do
Expand Down
4 changes: 2 additions & 2 deletions lib/core/test/unit/Cardano/Wallet/DB/StateMachine.hs
Original file line number Diff line number Diff line change
Expand Up @@ -229,7 +229,7 @@ import qualified Test.QuickCheck as QC
import qualified Test.StateMachine.Types as QSM
import qualified Test.StateMachine.Types.Rank2 as Rank2

{-# ANN module ("HLint: ignore Unused LANGUAGE pragma" :: String) #-}
{- HLINT ignore "Unused LANGUAGE pragma" -}

{-------------------------------------------------------------------------------
Mock implementation
Expand Down Expand Up @@ -569,7 +569,7 @@ lockstep m@(Model _ ws) c (At resp) = Event
Generator
-------------------------------------------------------------------------------}

{-# ANN generator ("HLint: ignore Use ++" :: String) #-}
{- HLINT ignore generator "Use ++" -}
generator
:: forall s. (Arbitrary (Wallet s), GenState s)
=> Model s Symbolic
Expand Down
Original file line number Diff line number Diff line change
Expand Up @@ -84,7 +84,7 @@ import qualified Data.Map.Strict as Map
import qualified Data.Set as Set
import qualified Test.QuickCheck.Monadic as QC

{-# ANN module ("HLint: ignore Use <$>" :: String) #-}
{- HLINT ignore "Use <$>" -}

spec :: Spec
spec = do
Expand Down
2 changes: 1 addition & 1 deletion lib/jormungandr/src/Cardano/Wallet/Jormungandr/Binary.hs
Original file line number Diff line number Diff line change
Expand Up @@ -197,7 +197,7 @@ maxNumberOfOutputs = 254
-------------------------------------------------------------------------------}

-- Do-notation is favoured over applicative syntax for readability:
{-# ANN module ("HLint: ignore Use <$>" :: String) #-}
{- HLINT ignore "Use <$>" -}

data BlockHeader = BlockHeader
{ version :: Word16
Expand Down
Original file line number Diff line number Diff line change
Expand Up @@ -129,7 +129,7 @@ import qualified Cardano.Wallet.Jormungandr.Api.Client as Jormungandr
import qualified Data.ByteString as BS
import qualified Data.ByteString.Char8 as B8

{-# ANN spec ("HLint: ignore Use head" :: String) #-}
{- HLINT ignore spec "Use head" -}

spec :: Spec
spec = do
Expand Down
Original file line number Diff line number Diff line change
Expand Up @@ -8,7 +8,6 @@
{-# LANGUAGE TypeApplications #-}
{-# LANGUAGE TypeFamilies #-}
{-# OPTIONS_GHC -fno-warn-orphans #-}
{-# OPTIONS_GHC -Wno-unrecognised-pragmas #-}

module Cardano.Pool.Jormungandr.MetricsSpec
( spec
Expand Down Expand Up @@ -177,7 +176,7 @@ prop_combineIsLeftBiased mStake_ mProd_ mPerf_ =
mStake = Map.mapKeys getLowEntropy mStake_
mProd = Map.mapKeys getLowEntropy mProd_
mPerf = Map.mapKeys getLowEntropy mPerf_
{-# HLINT ignore prop_combineIsLeftBiased "Use ||" #-}
{- HLINT ignore prop_combineIsLeftBiased "Use ||" -}

-- | A list of chunks of blocks to be served up by the mock network layer.
newtype RegistrationsTest = RegistrationsTest
Expand Down
3 changes: 2 additions & 1 deletion lib/launcher/test/unit/Cardano/LauncherSpec.hs
Original file line number Diff line number Diff line change
Expand Up @@ -81,7 +81,8 @@ import Test.Hspec
import Test.Utils.Windows
( isWindows, pendingOnWine )

{-# ANN spec ("HLint: ignore Use head" :: String) #-}
{- HLINT ignore spec "Use head" -}

spec :: Spec
spec = beforeAll setupMockCommands $ do
it "Buildable Command" $ \MockCommands{..} -> do
Expand Down
2 changes: 1 addition & 1 deletion lib/shelley/bench/Restore.hs
Original file line number Diff line number Diff line change
Expand Up @@ -528,7 +528,7 @@ benchmarksSeq _ w wid wname restoreTime = do
, walletOverview
}

{-# ANN bench_restoration ("HLint: ignore Use camelCase" :: String) #-}
{- HLINT ignore bench_restoration "Use camelCase" -}
bench_restoration
:: forall (n :: NetworkDiscriminant) (k :: Depth -> * -> *) s t results.
( IsOurs s Address
Expand Down

0 comments on commit 23e9257

Please sign in to comment.