Linting integration

This commit brings in an HLint configuration file
and several recommended modifications such as:

* End-of-line extra spaces removal;
* Import lines ordering;
* Redundant $ removal;
* Generalisation of ++ and map to <> and fmap;
* Preferring `pure` over `return`;
* Removing extraenous extensions.

And finally, a `stylish-haskell` helper script
that detects if code files are dirty. Can be useful for CI,
although manually calling it can be nice if you would rather
first implement then beautify.
This commit is contained in:
Hécate 2020-05-19 12:29:15 +02:00
parent d049b65f1e
commit 41e999ed99
11 changed files with 281 additions and 248 deletions

View file

@ -1,20 +1,20 @@
{-# LANGUAGE OverloadedStrings #-}
module FediChordSpec where
import Test.Hspec
import Control.Exception
import Network.Socket
import Data.Maybe (fromJust)
import qualified Data.Map.Strict as Map
import qualified Data.ByteString as BS
import qualified Data.Set as Set
import Data.ASN1.Parse (runParseASN1)
import Data.Time.Clock.POSIX
import Data.IORef
import Control.Exception
import Data.ASN1.Parse (runParseASN1)
import qualified Data.ByteString as BS
import Data.IORef
import qualified Data.Map.Strict as Map
import Data.Maybe (fromJust)
import qualified Data.Set as Set
import Data.Time.Clock.POSIX
import Network.Socket
import Test.Hspec
import Hash2Pub.FediChord
import Hash2Pub.DHTProtocol
import Hash2Pub.ASN1Coding
import Hash2Pub.ASN1Coding
import Hash2Pub.DHTProtocol
import Hash2Pub.FediChord
spec :: Spec
spec = do
@ -96,19 +96,19 @@ spec = do
-- ignore empty proxy elements in initial cache
nid . cacheGetNodeStateUnvalidated <$> cacheLookupPred (exampleID + 10) emptyCache `shouldBe` Nothing
nid . cacheGetNodeStateUnvalidated <$> cacheLookupSucc exampleID emptyCache `shouldBe` Nothing
-- given situation: 0 < anotherNode < nid exampleLocalNode < maxBound
-- first try non-modular queries between the 2 stored nodes
nid . cacheGetNodeStateUnvalidated <$> cacheLookupPred (exampleID + 10) newCache `shouldBe` Just exampleID
nid . cacheGetNodeStateUnvalidated <$> cacheLookupSucc exampleID newCache `shouldBe` Just exampleID
nid . cacheGetNodeStateUnvalidated <$> cacheLookupPred (exampleID + 10) newCache `shouldBe` Just exampleID
nid . cacheGetNodeStateUnvalidated <$> cacheLookupSucc exampleID newCache `shouldBe` Just exampleID
nid . cacheGetNodeStateUnvalidated <$> cacheLookupSucc (exampleID + 10) newCache `shouldBe` Just anotherID
-- queries that require a (pseudo)modular structure
nid . cacheGetNodeStateUnvalidated <$> cacheLookupPred (exampleID - 2) newCache `shouldBe` Just anotherID
nid . cacheGetNodeStateUnvalidated <$> cacheLookupSucc (anotherID + 2) newCache `shouldBe` Just exampleID
nid . cacheGetNodeStateUnvalidated <$> cacheLookupSucc (anotherID + 2) newCache `shouldBe` Just exampleID
-- now store a node in one of the ProxyEntries
let cacheWithProxyNodeEntry = addCacheEntryPure 10 (RemoteCacheEntry maxNode 10) newCache
nid . cacheGetNodeStateUnvalidated <$> cacheLookupPred (exampleID - 2) cacheWithProxyNodeEntry `shouldBe` Just maxBound
nid . cacheGetNodeStateUnvalidated <$> cacheLookupSucc (anotherID + 2) cacheWithProxyNodeEntry `shouldBe` Just maxBound
nid . cacheGetNodeStateUnvalidated <$> cacheLookupSucc (anotherID + 2) cacheWithProxyNodeEntry `shouldBe` Just maxBound
it "entries can be deleted" $ do
let
nC = addCacheEntryPure 10 (RemoteCacheEntry maxNode 10) newCache
@ -123,7 +123,7 @@ spec = do
nid1 = toNodeID 2^(23::Integer)+1
node1 = do
eln <- exampleLocalNode -- is at 2^23.00000017198264 = 8388609
return $ putPredecessors [nid4] $ eln {nid = nid1}
pure $ putPredecessors [nid4] $ eln {nid = nid1}
nid2 = toNodeID 2^(230::Integer)+12
node2 = exampleNodeState { nid = nid2}
nid3 = toNodeID 2^(25::Integer)+10
@ -156,7 +156,7 @@ spec = do
describe "Messages can be encoded to and decoded from ASN.1" $ do
-- define test messages
let
someNodeIDs = map fromInteger [3..12]
someNodeIDs = fmap fromInteger [3..12]
qidReqPayload = QueryIDRequestPayload {
queryTargetID = nid exampleNodeState
, queryLBestNodes = 3

View file

@ -1,8 +1,8 @@
module Main (main) where
import Test.Hspec
import qualified FediChordSpec
import Test.Hspec
main :: IO ()
main = hspec $ do
main = hspec $
describe "FediChord tests" FediChordSpec.spec