Skip to content

Commit

Permalink
TOSQUASH: stylish-haskell the new files
Browse files Browse the repository at this point in the history
  • Loading branch information
nfrisby committed Mar 27, 2023
1 parent 50d8a78 commit e0bb550
Show file tree
Hide file tree
Showing 13 changed files with 253 additions and 251 deletions.
@@ -1,27 +1,27 @@
{-# LANGUAGE BangPatterns #-}
{-# LANGUAGE DataKinds #-}
{-# LANGUAGE BangPatterns #-}
{-# LANGUAGE DataKinds #-}
{-# LANGUAGE ExistentialQuantification #-}
{-# LANGUAGE FlexibleContexts #-}
{-# LANGUAGE MultiWayIf #-}
{-# LANGUAGE NamedFieldPuns #-}
{-# LANGUAGE PolyKinds #-}
{-# LANGUAGE ScopedTypeVariables #-}
{-# LANGUAGE TypeApplications #-}
{-# LANGUAGE FlexibleContexts #-}
{-# LANGUAGE MultiWayIf #-}
{-# LANGUAGE NamedFieldPuns #-}
{-# LANGUAGE PolyKinds #-}
{-# LANGUAGE ScopedTypeVariables #-}
{-# LANGUAGE TypeApplications #-}

module Test.Ouroboros.Consensus.ChainGenerator.Adversarial (
-- * Generating
AdversarialRecipe (AdversarialRecipe, arHonest, arParams, arPrefix),
CheckedAdversarialRecipe (UnsafeCheckedAdversarialRecipe, carHonest, carParams, carWin),
NoSuchAdversarialChainSchedule (NoSuchAdversarialBlock, NoSuchCompetitor, NoSuchIntersection),
SomeCheckedAdversarialRecipe (SomeCheckedAdversarialRecipe),
checkAdversarialRecipe,
uniformAdversarialChain,
-- * Testing
AdversarialViolation (BadAnchor, BadCount, BadRace),
AnchorViolation (HonestActiveMustAnchorAdversarial),
ChainSchedule (ChainSchedule),
RaceViolation (AdversaryWonRace, rvAdv, rvHon),
checkAdversarialChain,
-- * Generating
AdversarialRecipe (AdversarialRecipe, arHonest, arParams, arPrefix)
, CheckedAdversarialRecipe (UnsafeCheckedAdversarialRecipe, carHonest, carParams, carWin)
, NoSuchAdversarialChainSchedule (NoSuchAdversarialBlock, NoSuchCompetitor, NoSuchIntersection)
, SomeCheckedAdversarialRecipe (SomeCheckedAdversarialRecipe)
, checkAdversarialRecipe
, uniformAdversarialChain
-- * Testing
, AdversarialViolation (BadAnchor, BadCount, BadRace)
, AnchorViolation (HonestActiveMustAnchorAdversarial)
, ChainSchedule (ChainSchedule)
, RaceViolation (AdversaryWonRace, rvAdv, rvHon)
, checkAdversarialChain
) where

import Control.Applicative ((<|>))
Expand All @@ -31,11 +31,14 @@ import Data.Proxy (Proxy (Proxy))
import qualified System.Random.Stateful as R
import qualified Test.Ouroboros.Consensus.ChainGenerator.BitVector as BV
import qualified Test.Ouroboros.Consensus.ChainGenerator.Counting as C
import Test.Ouroboros.Consensus.ChainGenerator.Honest (ChainSchedule (ChainSchedule))
import Test.Ouroboros.Consensus.ChainGenerator.Params (Asc, Delta (Delta), Kcp (Kcp), Scg (Scg))
import Test.Ouroboros.Consensus.ChainGenerator.Honest
(ChainSchedule (ChainSchedule))
import Test.Ouroboros.Consensus.ChainGenerator.Params (Asc,
Delta (Delta), Kcp (Kcp), Scg (Scg))
import qualified Test.Ouroboros.Consensus.ChainGenerator.RaceIterator as RI
import Test.Ouroboros.Consensus.ChainGenerator.Slot
(E (ActiveSlotE, EmptySlotE, SlotE))
import qualified Test.Ouroboros.Consensus.ChainGenerator.Slot as S
import Test.Ouroboros.Consensus.ChainGenerator.Slot (E (ActiveSlotE, EmptySlotE, SlotE))
import qualified Test.Ouroboros.Consensus.ChainGenerator.Some as Some

-----
Expand Down
@@ -1,41 +1,41 @@
{-# LANGUAGE BangPatterns #-}
{-# LANGUAGE DataKinds #-}
{-# LANGUAGE DeriveGeneric #-}
{-# LANGUAGE BangPatterns #-}
{-# LANGUAGE DataKinds #-}
{-# LANGUAGE DeriveGeneric #-}
{-# LANGUAGE ExistentialQuantification #-}
{-# LANGUAGE FlexibleContexts #-}
{-# LANGUAGE LambdaCase #-}
{-# LANGUAGE MultiWayIf #-}
{-# LANGUAGE NamedFieldPuns #-}
{-# LANGUAGE PolyKinds #-}
{-# LANGUAGE ScopedTypeVariables #-}
{-# LANGUAGE TypeApplications #-}
{-# LANGUAGE TypeFamilies #-}
{-# LANGUAGE TypeOperators #-}
{-# LANGUAGE ViewPatterns #-}
{-# LANGUAGE FlexibleContexts #-}
{-# LANGUAGE LambdaCase #-}
{-# LANGUAGE MultiWayIf #-}
{-# LANGUAGE NamedFieldPuns #-}
{-# LANGUAGE PolyKinds #-}
{-# LANGUAGE ScopedTypeVariables #-}
{-# LANGUAGE TypeApplications #-}
{-# LANGUAGE TypeFamilies #-}
{-# LANGUAGE TypeOperators #-}

module Test.Ouroboros.Consensus.ChainGenerator.BitVector (
-- * Finding
MaybeFound (JustFound, NothingFound),
findIthEmptyInV,
findIthEmptyInMV,
-- * Counting
countActivesInV,
countActivesInMV,
-- * Slots
setMV,
testMV,
testV,
-- * Generating
SomeDensityWindow (SomeDensityWindow),
fillInWindow,
-- * Finding
MaybeFound (JustFound, NothingFound)
, findIthEmptyInMV
, findIthEmptyInV
-- * Counting
, countActivesInMV
, countActivesInV
-- * Slots
, setMV
, testMV
, testV
-- * Generating
, SomeDensityWindow (SomeDensityWindow)
, fillInWindow
) where

import Control.Monad.ST (ST, runST)
import qualified Data.Vector.Unboxed.Mutable as MV
import qualified System.Random.Stateful as R
import qualified Test.Ouroboros.Consensus.ChainGenerator.Counting as C
import Test.Ouroboros.Consensus.ChainGenerator.Slot
(E (ActiveSlotE, EmptySlotE, SlotE), POL, PreImage, S)
import qualified Test.Ouroboros.Consensus.ChainGenerator.Slot as S
import Test.Ouroboros.Consensus.ChainGenerator.Slot (E (ActiveSlotE, EmptySlotE, SlotE), POL, PreImage, S)
import qualified Test.Ouroboros.Consensus.ChainGenerator.Some as Some

-----
Expand Down
@@ -1,74 +1,73 @@
{-# LANGUAGE ExistentialQuantification #-}
{-# LANGUAGE FlexibleInstances #-}
{-# LANGUAGE ExistentialQuantification #-}
{-# LANGUAGE FlexibleInstances #-}
{-# LANGUAGE GeneralizedNewtypeDeriving #-}
{-# LANGUAGE MultiParamTypeClasses #-}
{-# LANGUAGE PatternSynonyms #-}
{-# LANGUAGE PolyKinds #-}
{-# LANGUAGE Rank2Types #-}
{-# LANGUAGE ScopedTypeVariables #-}
{-# LANGUAGE StandaloneDeriving #-}
{-# LANGUAGE TypeFamilies #-}
{-# LANGUAGE TypeOperators #-}
{-# LANGUAGE ViewPatterns #-}
{-# LANGUAGE MultiParamTypeClasses #-}
{-# LANGUAGE PatternSynonyms #-}
{-# LANGUAGE PolyKinds #-}
{-# LANGUAGE Rank2Types #-}
{-# LANGUAGE ScopedTypeVariables #-}
{-# LANGUAGE StandaloneDeriving #-}
{-# LANGUAGE TypeFamilies #-}
{-# LANGUAGE TypeOperators #-}

-- | Very strong types for working with indices, counts, etc within sequences.
module Test.Ouroboros.Consensus.ChainGenerator.Counting (
-- * general counts
Count (Count),
(-),
(+),
getCount,
forgetBase,
forgetElem,
-- * indices and sizes
Preds,
Index,
Size,
Total,
forRange_,
lastIndex,
range,
uniformIndex,
-- * windows
Lbl (Lbl),
SomeWindow (SomeWindow),
Win,
Contains (Contains, UnsafeContains),
forgetWindow,
frWin,
frWinVar,
joinWin,
toWin,
windowLast,
windowSize,
windowStart,
withSuffixWindow,
withTopWindow,
withWindow,
withWindowBetween,
-- * vectors
Vector (Vector),
MVector (MVector),
createV,
getMVector,
getVector,
lengthMV,
lengthV,
modifyMV,
readMV,
readV,
replicateMV,
sliceMV,
sliceV,
unsafeThawV,
writeMV,
-- * variables
Other,
Var,
joinVar,
toIndex,
toSize,
toVar,
-- * general counts
Count (Count)
, forgetBase
, forgetElem
, getCount
, (+)
, (-)
-- * indices and sizes
, Index
, Preds
, Size
, Total
, forRange_
, lastIndex
, range
, uniformIndex
-- * windows
, Contains (Contains, UnsafeContains)
, Lbl (Lbl)
, SomeWindow (SomeWindow)
, Win
, forgetWindow
, frWin
, frWinVar
, joinWin
, toWin
, windowLast
, windowSize
, windowStart
, withSuffixWindow
, withTopWindow
, withWindow
, withWindowBetween
-- * vectors
, MVector (MVector)
, Vector (Vector)
, createV
, getMVector
, getVector
, lengthMV
, lengthV
, modifyMV
, readMV
, readV
, replicateMV
, sliceMV
, sliceV
, unsafeThawV
, writeMV
-- * variables
, Other
, Var
, joinVar
, toIndex
, toSize
, toVar
) where

import Control.Monad.ST (ST)
Expand Down
@@ -1,33 +1,33 @@
{-# LANGUAGE DataKinds #-}
{-# LANGUAGE DataKinds #-}
{-# LANGUAGE ExistentialQuantification #-}
{-# LANGUAGE FlexibleContexts #-}
{-# LANGUAGE LambdaCase #-}
{-# LANGUAGE NamedFieldPuns #-}
{-# LANGUAGE PolyKinds #-}
{-# LANGUAGE ScopedTypeVariables #-}
{-# LANGUAGE TypeApplications #-}
{-# LANGUAGE ViewPatterns #-}
{-# LANGUAGE FlexibleContexts #-}
{-# LANGUAGE LambdaCase #-}
{-# LANGUAGE NamedFieldPuns #-}
{-# LANGUAGE PolyKinds #-}
{-# LANGUAGE ScopedTypeVariables #-}
{-# LANGUAGE TypeApplications #-}
{-# LANGUAGE ViewPatterns #-}

module Test.Ouroboros.Consensus.ChainGenerator.Honest (
-- * Generating
ChainSchedule (ChainSchedule),
CheckedHonestRecipe (UnsafeCheckedHonestRecipe, chrEhcgDensity, chrWin),
HonestRecipe (HonestRecipe),
HonestLbl,
NoSuchHonestChainSchedule (BadDeltaScg, BadKcp, BadLen),
SomeCheckedHonestRecipe (SomeCheckedHonestRecipe),
SomeHonestChainSchedule (SomeHonestChainSchedule),
checkHonestRecipe,
countChainSchedule,
uniformTheHonestChain,
ChainSchedule (ChainSchedule)
, CheckedHonestRecipe (UnsafeCheckedHonestRecipe, chrEhcgDensity, chrWin)
, HonestLbl
, HonestRecipe (HonestRecipe)
, NoSuchHonestChainSchedule (BadDeltaScg, BadKcp, BadLen)
, SomeCheckedHonestRecipe (SomeCheckedHonestRecipe)
, SomeHonestChainSchedule (SomeHonestChainSchedule)
, checkHonestRecipe
, countChainSchedule
, uniformTheHonestChain
-- * Testing
EhcgLbl,
EhcgViolation (EhcgViolation, ehcgvPopCount, ehcgvWindow),
HonestChainViolation (BadCount, BadEhcgWindow, BadLength),
checkHonestChain,
prettyChainSchedule,
prettyWindow,
transitionMatrix,
, EhcgLbl
, EhcgViolation (EhcgViolation, ehcgvPopCount, ehcgvWindow)
, HonestChainViolation (BadCount, BadEhcgWindow, BadLength)
, checkHonestChain
, prettyChainSchedule
, prettyWindow
, transitionMatrix
) where

import Control.Arrow ((***))
Expand All @@ -42,9 +42,11 @@ import Prelude hiding (words)
import qualified System.Random.Stateful as R
import qualified Test.Ouroboros.Consensus.ChainGenerator.BitVector as BV
import qualified Test.Ouroboros.Consensus.ChainGenerator.Counting as C
import Test.Ouroboros.Consensus.ChainGenerator.Params (Asc, Delta (Delta), Kcp (Kcp), Len (Len), Scg (Scg), ascVal)
import Test.Ouroboros.Consensus.ChainGenerator.Params (Asc,
Delta (Delta), Kcp (Kcp), Len (Len), Scg (Scg), ascVal)
import Test.Ouroboros.Consensus.ChainGenerator.Slot
(E (ActiveSlotE, SlotE), S)
import qualified Test.Ouroboros.Consensus.ChainGenerator.Slot as S
import Test.Ouroboros.Consensus.ChainGenerator.Slot (E (ActiveSlotE, SlotE), S)
import qualified Test.Ouroboros.Consensus.ChainGenerator.Some as Some

-----
Expand Down
@@ -1,14 +1,14 @@
{-# LANGUAGE PatternSynonyms #-}

module Test.Ouroboros.Consensus.ChainGenerator.Params (
Asc (Asc, UnsafeAsc),
Delta (Delta),
Len (Len),
Kcp (Kcp),
Scg (Scg),
ascFromBits,
ascFromDouble,
ascVal,
Asc (Asc, UnsafeAsc)
, Delta (Delta)
, Kcp (Kcp)
, Len (Len)
, Scg (Scg)
, ascFromBits
, ascFromDouble
, ascVal
) where

import qualified Data.Bits as B
Expand Down

0 comments on commit e0bb550

Please sign in to comment.