Skip to content

Commit

Permalink
ormolu
Browse files Browse the repository at this point in the history
  • Loading branch information
ShapeOfMatter committed Dec 5, 2024
1 parent 77d2561 commit 5519faa
Show file tree
Hide file tree
Showing 4 changed files with 13 additions and 13 deletions.
2 changes: 1 addition & 1 deletion examples/CLI.hs
Original file line number Diff line number Diff line change
Expand Up @@ -6,8 +6,8 @@
module CLI where

import Control.Monad (unless)
import Control.Monad.IO.Class (MonadIO (liftIO))
import Control.Monad.Freer
import Control.Monad.IO.Class (MonadIO (liftIO))
import Control.Monad.State (MonadState (get, put), StateT (runStateT), lift)
import Data.Typeable (Typeable, typeRep)
import Text.Read (readMaybe)
Expand Down
20 changes: 10 additions & 10 deletions examples/Distribution/TestSuite/QuickCheck.hs
Original file line number Diff line number Diff line change
Expand Up @@ -116,8 +116,8 @@ where

import Data.Bool (bool)
import Data.Functor ((<&>))
import qualified Distribution.TestSuite as T
import qualified Test.QuickCheck as QC
import Distribution.TestSuite qualified as T
import Test.QuickCheck qualified as QC
import Test.QuickCheck.Random (QCGen)
import Text.Read (readMaybe)

Expand Down Expand Up @@ -353,7 +353,7 @@ getOptionDescrs TestArgs {..} =
}
]

getModifiers :: QC.Testable a => TestArgs -> a -> QC.Property
getModifiers :: (QC.Testable a) => TestArgs -> a -> QC.Property
getModifiers TestArgs {verbosity, noShrinking, verboseShrinking, sizeScale} =
foldr (.) QC.property $
snd
Expand All @@ -375,12 +375,12 @@ data PropertyTest prop = PropertyTest
property :: prop
}

qcTestArgs :: QC.Testable a => TestArgs -> a -> IO QC.Result
qcTestArgs :: (QC.Testable a) => TestArgs -> a -> IO QC.Result
qcTestArgs args property = QC.quickCheckWithResult (testArgsToArgs args) (getModifiers args property)

-- | Get a Cabal 'T.Test' with custom 'TestArgs' from a 'PropertyTest' that takes the test arguments and returns a 'QC.testable' value
getPropertyTestWithUsing ::
QC.Testable prop =>
(QC.Testable prop) =>
-- | The arguments for the test
TestArgs ->
-- | A property test whose 'property' takes a 'TestArgs' argument
Expand Down Expand Up @@ -411,7 +411,7 @@ getPropertyTestWithUsing originalArgs PropertyTest {..} =

-- | Get a Cabal 'T.Test' from a 'PropertyTest' that takes the test arguments and returns a 'QC.Testable' value
getPropertyTestUsing ::
QC.Testable prop =>
(QC.Testable prop) =>
-- | A property test whose 'property' takes a 'TestArgs' argument
PropertyTest (TestArgs -> prop) ->
T.Test
Expand All @@ -422,21 +422,21 @@ discardingTestArgs test@PropertyTest {property} = test {property = const propert

-- | Get a Cabal 'T.Test' from a 'PropertyTest' with custom 'TestArgs'
getPropertyTestWith ::
QC.Testable prop =>
(QC.Testable prop) =>
-- | The arguments for the test
TestArgs ->
PropertyTest prop ->
T.Test
getPropertyTestWith args = getPropertyTestWithUsing args . discardingTestArgs

-- | Get a Cabal 'T.Test' from a 'PropertyTest'
getPropertyTest :: QC.Testable prop => PropertyTest prop -> T.Test
getPropertyTest :: (QC.Testable prop) => PropertyTest prop -> T.Test
getPropertyTest = getPropertyTestWithUsing stdTestArgs . discardingTestArgs

-- | Get a list of 'T.Test's from a list of 'PropertyTest's
getPropertyTests :: QC.Testable prop => [PropertyTest prop] -> [T.Test]
getPropertyTests :: (QC.Testable prop) => [PropertyTest prop] -> [T.Test]
getPropertyTests = (getPropertyTest <$>)

-- | Get a named test group from a list of 'PropertyTest's. These are assumed to be able to run in parallel. See 'T.testGroup' and 'T.Group'.
propertyTestGroup :: QC.Testable prop => String -> [PropertyTest prop] -> T.Test
propertyTestGroup :: (QC.Testable prop) => String -> [PropertyTest prop] -> T.Test
propertyTestGroup name = T.testGroup name . getPropertyTests
2 changes: 1 addition & 1 deletion examples/Lottery.hs
Original file line number Diff line number Diff line change
Expand Up @@ -11,7 +11,7 @@ import Choreography
import Choreography.Network.Http
import Control.Exception (Exception, throwIO)
import Control.Monad (unless)
import Control.Monad.IO.Class (MonadIO(liftIO))
import Control.Monad.IO.Class (MonadIO (liftIO))
import Crypto.Hash (Digest)
import Crypto.Hash qualified as Crypto
import Data (TestArgs, reference)
Expand Down
2 changes: 1 addition & 1 deletion examples/ObliviousTransfer.hs
Original file line number Diff line number Diff line change
Expand Up @@ -9,7 +9,7 @@ module ObliviousTransfer (ot2, ot4, main) where
import CLI
import Choreography
import Choreography.Network.Http
import Control.Monad.IO.Class (MonadIO(liftIO))
import Control.Monad.IO.Class (MonadIO (liftIO))
-- For cryptonite

import Crypto.Hash.Algorithms qualified as HASH
Expand Down

0 comments on commit 5519faa

Please sign in to comment.