diff --git a/app/Main.hs b/app/Main.hs index 5d640cc..5adf4ff 100644 --- a/app/Main.hs +++ b/app/Main.hs @@ -25,7 +25,7 @@ import Display.Widgets import Events import Events.Types import qualified Graphics.Vty as Vty -import Prelude hiding (on) +import Relude hiding (on) main :: IO () main = do diff --git a/hie.yaml b/hie.yaml index 06ac306..a674c3c 100644 --- a/hie.yaml +++ b/hie.yaml @@ -1,13 +1,16 @@ cradle: stack: - - path: "././src" - component: "aphrograph:lib" - - - path: "././app/Main.hs" - component: "aphrograph:exe:aphrograph" - - - path: "././app/Paths_aphrograph.hs" + - path: "./app" component: "aphrograph:exe:aphrograph" - - path: "././test" + - path: "./src" + component: "aphrograph:lib" + + - path: "./test" component: "aphrograph:test:aphrograph-test" + + # - path: "./app/Paths_aphrograph.hs" + # component: "aphrograph:lib" + + - path: "./.stack-work/dist/x86_64-linux-tinfo6/Cabal-3.0.1.0/build/autogen/Paths_aphrograph.hs" + component: "aphrograph:lib" diff --git a/package.yaml b/package.yaml index d415be1..a9a3562 100644 --- a/package.yaml +++ b/package.yaml @@ -3,15 +3,22 @@ dependencies: - transformers-base - monad-control - - name: relude - mixin: (Relude as Prelude) + # Until https://github.com/commercialhaskell/stack/issues/5077 fixed - - name: base - mixin: - - hiding (Prelude) + - relude + - base + + # - name: relude + # mixin: (Relude as Prelude) + + # - name: base + # mixin: + # - hiding (Prelude) ghc-options: - -Werror -Wall -fexcess-precision -funfolding-use-threshold=16 -fwrite-ide-info -fwarn-unused-binds -fwarn-unused-imports -hiedir=.hie -O2 + - -Werror -Wall + - -O2 -fexcess-precision -funfolding-use-threshold=16 + - -fwrite-ide-info -fwarn-unused-binds -fwarn-unused-imports -hiedir=.hie library: source-dirs: ./src @@ -72,6 +79,9 @@ default-extensions: - MultiParamTypeClasses - StrictData + # https://github.com/commercialhaskell/stack/issues/5077 + - NoImplicitPrelude + name: aphrograph version: 0.1.0.0 extra-source-files: diff --git a/src/App.hs b/src/App.hs index bb041fd..0c0b363 100644 --- a/src/App.hs +++ b/src/App.hs @@ -33,6 +33,7 @@ import Display.GraphWidget import Events.Types import Graphite import Graphite.Types +import Relude import Text.Show.Functions () newtype AppChan e = AppChan (Brick.BChan e) diff --git a/src/App/Args.hs b/src/App/Args.hs index 431314b..7d0ec28 100644 --- a/src/App/Args.hs +++ b/src/App/Args.hs @@ -7,6 +7,7 @@ module App.Args where import App.Config as App +import Relude import Control.Lens.Prism import Control.Lens.Setter import Data.Version (showVersion) diff --git a/src/App/Components.hs b/src/App/Components.hs index bca5e5e..79dd1c8 100644 --- a/src/App/Components.hs +++ b/src/App/Components.hs @@ -9,6 +9,7 @@ import Data.Vector (Vector) import Display.Graph import qualified Graphics.Vty.Input.Events as Vty import qualified Graphite.Types as Graphite +import Relude data HorizontalAxisWidget = HorizontalAxis [Graphite.Time] TimeZone deriving (Show) diff --git a/src/App/Config.hs b/src/App/Config.hs index 8146f9c..3331aa3 100644 --- a/src/App/Config.hs +++ b/src/App/Config.hs @@ -9,14 +9,14 @@ module App.Config where import Control.Lens.TH import Graphite.Types +import Relude -data GraphiteConfig - = GraphiteConfig - { _fromTime :: From, - _toTime :: Maybe To, - _targetArg :: Text, - _graphiteUrl :: GraphiteUrl - } +data GraphiteConfig = GraphiteConfig + { _fromTime :: From, + _toTime :: Maybe To, + _targetArg :: Text, + _graphiteUrl :: GraphiteUrl + } deriving (Show, Generic) makeLenses ''GraphiteConfig diff --git a/src/App/State.hs b/src/App/State.hs index f5ac4f7..1037840 100644 --- a/src/App/State.hs +++ b/src/App/State.hs @@ -23,6 +23,7 @@ import Data.Vector (Vector) import Display.Graph as Graph import Events.Types import Graphite.Types +import Relude newtype Error = AppGraphiteError GraphiteError deriving (Show, Generic) diff --git a/src/Display/Graph.hs b/src/Display/Graph.hs index 6132d03..8053df0 100644 --- a/src/Display/Graph.hs +++ b/src/Display/Graph.hs @@ -18,6 +18,7 @@ where import qualified Data.Map as M import qualified Data.Set as Set +import Relude import Graphite.Types newtype Graph x y = Graph {_data :: M.Map x (Set y)} diff --git a/src/Display/GraphWidget.hs b/src/Display/GraphWidget.hs index e7d5aea..6ab478d 100644 --- a/src/Display/GraphWidget.hs +++ b/src/Display/GraphWidget.hs @@ -21,14 +21,14 @@ import Data.Time.LocalTime import Display.Graph as G import Display.Labels import Display.Projection.Scalable -import qualified Graphics.Vty as Vty import Graphics.Vty ( horizJoin, vertCat, vertJoin, ) +import qualified Graphics.Vty as Vty +import Relude import Graphite.Types -import Prelude hiding ((<|>)) graphDisplayWidget :: GraphData -> TimeZone -> GraphDisplayWidget graphDisplayWidget Missing _ = NoDataDisplayWidget diff --git a/src/Display/Labels.hs b/src/Display/Labels.hs index 5f3184d..fd353f4 100644 --- a/src/Display/Labels.hs +++ b/src/Display/Labels.hs @@ -18,10 +18,13 @@ import Display.Projection.Scalable import Formatting import Formatting.Time import Graphite.Types +import Relude data TimeStep = Day | Hour | FiveMinute | Minute | Second | Millisecond deriving (Show, Eq, Generic, Enum) +data Label = Label LText Word8 + with :: MonadReader s m => Getter s a -> (a -> m b) -> m b with lens f = view lens >>= f diff --git a/src/Display/Projection.hs b/src/Display/Projection.hs index bae7f82..1c5120d 100644 --- a/src/Display/Projection.hs +++ b/src/Display/Projection.hs @@ -3,6 +3,7 @@ module Display.Projection where +import Relude import Control.Lens import Display.Projection.Scalable diff --git a/src/Display/Projection/Scalable.hs b/src/Display/Projection/Scalable.hs index c11fdc2..11bc0a1 100644 --- a/src/Display/Projection/Scalable.hs +++ b/src/Display/Projection/Scalable.hs @@ -9,6 +9,7 @@ import Control.Lens import Data.Decimal import Data.Time.Clock import Normalisation +import Relude class Real b => Scalable b where scale :: Real a => a -> (a, a) -> (b, b) -> b diff --git a/src/Display/Types.hs b/src/Display/Types.hs index 6d0e23b..3a0cb48 100644 --- a/src/Display/Types.hs +++ b/src/Display/Types.hs @@ -4,6 +4,7 @@ module Display.Types where import Formatting import Text.Show +import Relude data Dimensions = Dims {width :: !Natural, height :: !Natural} deriving (Eq, Show) diff --git a/src/Display/Widgets.hs b/src/Display/Widgets.hs index 22e741f..db49702 100644 --- a/src/Display/Widgets.hs +++ b/src/Display/Widgets.hs @@ -15,6 +15,7 @@ import Control.Lens.Getter import Control.Lens.Setter import Display.GraphWidget import qualified Graphics.Vty as Vty +import Relude import Graphite.Types class CompileWidget n w where @@ -27,13 +28,15 @@ instance CompileWidget AppComponent MetricsBrowserWidget where compile (MetricsBrowser metricsList) = let hasFocus = True popupSize = (25, 10) - in Widget.centerLayer $ WidgetB.border $ Widget.setAvailableSize popupSize $ - Widget.renderList - ( \active (Metric descriptor) -> - Widget.withAttr ("metric" <> if active then "selected" else "unselcted") (Widget.txt descriptor) - ) - hasFocus - metricsList + in Widget.centerLayer $ + WidgetB.border $ + Widget.setAvailableSize popupSize $ + Widget.renderList + ( \active (Metric descriptor) -> + Widget.withAttr ("metric" <> if active then "selected" else "unselcted") (Widget.txt descriptor) + ) + hasFocus + metricsList instance CompileLayeredWidget AppComponent (AppWidget e) where compileLayered (DefaultDisplay dataDisplay Nothing) = [compile dataDisplay] diff --git a/src/Events.hs b/src/Events.hs index 75b5408..9a8a0dc 100644 --- a/src/Events.hs +++ b/src/Events.hs @@ -29,6 +29,7 @@ import Control.Monad.Morph import Control.Monad.Trans.Control import Events.Types import qualified Graphics.Vty.Input.Events as Vty +import Relude import Graphite.Types pattern KeyDown :: Char -> Vty.Event diff --git a/src/Events/Types.hs b/src/Events/Types.hs index 2b13997..a186efa 100644 --- a/src/Events/Types.hs +++ b/src/Events/Types.hs @@ -8,6 +8,7 @@ import qualified Brick.Types as Brick import qualified Brick.Widgets.List as BWL import Display.Graph import Graphite.Types +import Relude data AppEvent = TriggerUpdate | GraphUpdate (Graph Time Value) deriving (Show, Eq) diff --git a/src/Graphite.hs b/src/Graphite.hs index 3de5c43..2eea9c5 100644 --- a/src/Graphite.hs +++ b/src/Graphite.hs @@ -14,6 +14,7 @@ import Control.Monad.Except import Data.Aeson as JSON import Graphite.Types import Network.HTTP.Req as Req +import Relude with :: MonadReader s m => Getter s a -> (a -> m b) -> m b with lens f = view lens >>= f diff --git a/src/Graphite/Types.hs b/src/Graphite/Types.hs index c3aeaf2..1e2857d 100644 --- a/src/Graphite/Types.hs +++ b/src/Graphite/Types.hs @@ -22,6 +22,7 @@ import Data.Typeable import Display.Projection.Scalable import Network.HTTP.Client as HTTP import Network.HTTP.Req +import Relude import qualified Text.Show as TS import Web.HttpApiData @@ -43,12 +44,11 @@ newtype To = To Text type Target = Text -data GraphiteRequest - = RenderRequest - { _from :: From, - _to :: Maybe To, - _target :: Target - } +data GraphiteRequest = RenderRequest + { _from :: From, + _to :: Maybe To, + _target :: Target + } deriving (Eq, Show, Generic) data GraphiteUrl where @@ -90,13 +90,13 @@ instance JSON.FromJSON Time where instance JSON.FromJSON Value where parseJSON (JSON.Number n) = return $ Value (realFracToDecimal 8 n) - parseJSON _ = Prelude.fail "value" + parseJSON _ = fail "value" instance JSON.FromJSON DataPoint where parseJSON (JSON.Array arr) = case toList arr of [JSON.Null, t] -> DataPoint (Value 0.0) <$> JSON.parseJSON t [v, t] -> DataPoint <$> JSON.parseJSON v <*> JSON.parseJSON t - _unexpected -> Prelude.fail "Couldn't parse datapoint" + _unexpected -> Relude.fail "Couldn't parse datapoint" parseJSON invalid = JSON.typeMismatch "DataPoint" invalid newtype Metric = Metric Text @@ -107,12 +107,11 @@ class Monad m => MonadGraphite m where listMetrics :: m [Metric] getMetrics :: GraphiteRequest -> m [DataPoint] -data MetricsResponse - = MetricsResponse - { target :: Text, - tags :: Map Text Text, - datapoints :: [DataPoint] - } +data MetricsResponse = MetricsResponse + { target :: Text, + tags :: Map Text Text, + datapoints :: [DataPoint] + } deriving (Show, Eq, Generic) instance JSON.FromJSON MetricsResponse diff --git a/src/Normalisation.hs b/src/Normalisation.hs index a256775..676bbd3 100644 --- a/src/Normalisation.hs +++ b/src/Normalisation.hs @@ -3,6 +3,8 @@ module Normalisation ) where +import Relude + diff :: Num a => (a, a) -> a diff (a, b) = b - a diff --git a/test/App/StateSpec.hs b/test/App/StateSpec.hs index de6e41c..9f9fa77 100644 --- a/test/App/StateSpec.hs +++ b/test/App/StateSpec.hs @@ -9,11 +9,12 @@ module App.StateSpec where import ArbitraryInstances () +import Relude import Test.Hspec import Test.Hspec.QuickCheck (prop) spec :: Spec spec = - describe "App.State" - $ describe "Graph updates" - $ prop "overwriting existing graph state" pending + describe "App.State" $ + describe "Graph updates" $ + prop "overwriting existing graph state" pending diff --git a/test/ArbitraryInstances.hs b/test/ArbitraryInstances.hs index 4cfc824..94b53fd 100644 --- a/test/ArbitraryInstances.hs +++ b/test/ArbitraryInstances.hs @@ -1,8 +1,8 @@ -{-# LANGUAGE ScopedTypeVariables #-} {-# LANGUAGE DeriveAnyClass #-} -{-# LANGUAGE TypeApplications #-} {-# LANGUAGE DerivingVia #-} +{-# LANGUAGE ScopedTypeVariables #-} {-# LANGUAGE FlexibleInstances #-} +{-# LANGUAGE TypeApplications #-} {-# LANGUAGE StandaloneDeriving #-} {-# OPTIONS_GHC -fno-warn-orphans #-} @@ -18,13 +18,14 @@ import Graphite.Types as Graphite import qualified Network.HTTP.Client as Http import qualified Network.HTTP.Req as Req import System.Random +import Relude import Test.QuickCheck import Test.QuickCheck.Arbitrary.ADT import Test.QuickCheck.Instances.Time () import Test.QuickCheck.Instances.Vector ( ) - + deriving via (GenArbitrary (MetricsBrowserWidget' [])) instance Arbitrary (MetricsBrowserWidget' []) deriving via (GenArbitrary (App.ActiveState [])) instance Arbitrary (App.ActiveState []) diff --git a/test/CommonProperties.hs b/test/CommonProperties.hs index 418962c..a8f1ab0 100644 --- a/test/CommonProperties.hs +++ b/test/CommonProperties.hs @@ -40,6 +40,7 @@ import DerivedArbitraryInstances import Events.Types import Graphite.Types import Test.Hspec +import Relude import Test.Hspec.QuickCheck (prop) import Test.Orphans () import Test.QuickCheck.Arbitrary diff --git a/test/DerivedArbitraryInstances.hs b/test/DerivedArbitraryInstances.hs index 7570941..958357d 100644 --- a/test/DerivedArbitraryInstances.hs +++ b/test/DerivedArbitraryInstances.hs @@ -20,6 +20,7 @@ import Network.HTTP.Req https, ) import System.Random +import Relude import Test.QuickCheck import Test.QuickCheck.Arbitrary.ADT import Test.QuickCheck.Instances.Text () diff --git a/test/Display/GraphSpec.hs b/test/Display/GraphSpec.hs index 009e210..2fabc26 100644 --- a/test/Display/GraphSpec.hs +++ b/test/Display/GraphSpec.hs @@ -14,10 +14,10 @@ import Data.List.NonEmpty ((<|)) import qualified Data.List.NonEmpty as NE import Display.Graph as Graph import Graphite.Types +import Relude hiding (null) import Test.Hspec as HS import Test.Hspec.QuickCheck import Test.QuickCheck -import Prelude hiding (null) nonEmptyListOf :: Gen a -> Gen (NonEmpty a) nonEmptyListOf gen = sized $ \i -> diff --git a/test/Display/ProjectionSpec.hs b/test/Display/ProjectionSpec.hs index bad7bf1..01bbb6b 100644 --- a/test/Display/ProjectionSpec.hs +++ b/test/Display/ProjectionSpec.hs @@ -7,6 +7,7 @@ import CommonProperties import Display.Projection.Scalable import Formatting import Graphite.Types +import Relude import Test.Hspec as HS import Test.Hspec.QuickCheck import Test.QuickCheck hiding (scale) diff --git a/test/Display/WidgetsSpec.hs b/test/Display/WidgetsSpec.hs index dbed124..c827f52 100644 --- a/test/Display/WidgetsSpec.hs +++ b/test/Display/WidgetsSpec.hs @@ -4,12 +4,9 @@ module Display.WidgetsSpec where -import Test.Hspec as HS -import ArbitraryInstances ( ) -import Display.Projection - -instance (Monad m) => MonadProjector a a (IdentityT m) where - project = pure +import ArbitraryInstances () +import Test.Hspec as HS +import Relude spec :: HS.Spec spec = describe "Widgets" $ it "has no purpose yet" $ True `shouldBe` True diff --git a/test/EventsSpec.hs b/test/EventsSpec.hs index 752676f..4ff83d5 100644 --- a/test/EventsSpec.hs +++ b/test/EventsSpec.hs @@ -5,6 +5,7 @@ where import ArbitraryInstances () import Test.Hspec +import Relude spec :: Spec spec = describe "Events" $ it "has tests" pending diff --git a/test/GraphiteSpec.hs b/test/GraphiteSpec.hs index 77f6d92..69717b5 100644 --- a/test/GraphiteSpec.hs +++ b/test/GraphiteSpec.hs @@ -8,6 +8,7 @@ import qualified Data.Aeson as JSON import Data.Aeson ((.=)) import Graphite import Graphite.Types +import Relude import Network.HTTP.Req import Test.Hspec as HS import Test.Hspec.QuickCheck @@ -70,18 +71,19 @@ spec = describe "Graphite" $ do JSON.decode "[ 0.555 ]" `shouldBe` (Nothing :: Maybe DataPoint) JSON.decode "[ ]" `shouldBe` (Nothing :: Maybe DataPoint) it "treats null values as zero" $ JSON.decode "[ null, 155005500 ]" `shouldBe` Just (DataPoint 0.0 155005500) - describe "GraphiteM" $ describe "MonadHttp" $ do - prop "captures all vanilla http exceptions as http errors" . monadicIO $ do - err <- pick vanillaHttpException - conf <- pick arbitrary - result <- run (runGraphite conf $ handleHttpException err) - return $ case result of - Left (HttpError _) -> True - _unexpected -> False - prop "captures all json parse exceptions as http errors" . monadicIO $ do - err <- pick jsonParseException - conf <- pick arbitrary - result <- run (runGraphite conf $ handleHttpException err) - return $ case result of - Left (ParsingError _) -> True - _unexpected -> False + describe "GraphiteM" $ + describe "MonadHttp" $ do + prop "captures all vanilla http exceptions as http errors" . monadicIO $ do + err <- pick vanillaHttpException + conf <- pick arbitrary + result <- run (runGraphite conf $ handleHttpException err) + return $ case result of + Left (HttpError _) -> True + _unexpected -> False + prop "captures all json parse exceptions as http errors" . monadicIO $ do + err <- pick jsonParseException + conf <- pick arbitrary + result <- run (runGraphite conf $ handleHttpException err) + return $ case result of + Left (ParsingError _) -> True + _unexpected -> False diff --git a/test/LabelsSpec.hs b/test/LabelsSpec.hs index e5c465d..f85a74f 100644 --- a/test/LabelsSpec.hs +++ b/test/LabelsSpec.hs @@ -7,6 +7,7 @@ import CommonProperties import Data.Decimal import Data.Fixed import Data.Time.LocalTime +import Relude import Display.Labels import Test.Hspec as HS import Test.Hspec.QuickCheck diff --git a/test/NormalisationSpec.hs b/test/NormalisationSpec.hs index 5a6bf39..816bca0 100644 --- a/test/NormalisationSpec.hs +++ b/test/NormalisationSpec.hs @@ -2,15 +2,16 @@ {-# LANGUAGE ScopedTypeVariables #-} module NormalisationSpec - ( spec + ( spec, ) where -import Normalisation -import Test.QuickCheck -import Test.Hspec.QuickCheck -import Test.Hspec as HS -import CommonProperties +import CommonProperties +import Normalisation +import Relude +import Test.Hspec as HS +import Test.Hspec.QuickCheck +import Test.QuickCheck factor :: Gen Double factor = getPositive <$> arbitrary @@ -19,38 +20,38 @@ spec :: HS.Spec spec = describe "normalise" $ do prop "has no effect when normalising to the same range" $ do (l, h) <- range @Double - i <- choose (l, h) + i <- choose (l, h) return (i === normalise (l, h) (l, h) i) prop "a range that is linearly smaller/bigger by a factor f is the same as doing ( f * that value )" $ do - f <- factor + f <- factor (l, h) <- range - v <- choose (l, h) + v <- choose (l, h) let outcome = normalise (l, h) (l * f, h * f) v return (1e-3 > abs (outcome - (v * f))) prop - "if the target range has no actual range than the normalised value is that number (ie normalising to (10, 10) always results in 10)" + "if the target range has no actual range than the normalised value is that number (ie normalising to (10, 10) always results in 10)" $ do - origin <- range @Double - v <- choose origin - a <- arbitrary - return (a === normalise origin (a, a) v) + origin <- range @Double + v <- choose origin + a <- arbitrary + return (a === normalise origin (a, a) v) prop - "if the origin has no range, then there is an error because it's impossible to determine what it should be the in the target range" + "if the origin has no range, then there is an error because it's impossible to determine what it should be the in the target range" $ do - target <- range @Double - v <- choose target - a <- arbitrary - let outcome = evaluateNF (normalise (a, a) target v) `shouldThrow` anyErrorCall - return outcome + target <- range @Double + v <- choose target + a <- arbitrary + let outcome = evaluateNF (normalise (a, a) target v) `shouldThrow` anyErrorCall + return outcome prop - "if the origin has no range, then there is an error because it's impossible to determine what it should be the in the target range" + "if the origin has no range, then there is an error because it's impossible to determine what it should be the in the target range" $ do - (lowEnd, highEnd) <- range @Double - target <- range @Double - value <- arbitrary `suchThat` \n -> lowEnd > n || highEnd < n - let outcome = evaluateNF (normalise (lowEnd, highEnd) target value) `shouldThrow` anyErrorCall - return outcome + (lowEnd, highEnd) <- range @Double + target <- range @Double + value <- arbitrary `suchThat` \n -> lowEnd > n || highEnd < n + let outcome = evaluateNF (normalise (lowEnd, highEnd) target value) `shouldThrow` anyErrorCall + return outcome diff --git a/test/Spec.hs b/test/Spec.hs index 40aa0f2..bcec488 100644 --- a/test/Spec.hs +++ b/test/Spec.hs @@ -8,6 +8,7 @@ import qualified GraphiteSpec (spec) import qualified LabelsSpec (spec) import qualified NormalisationSpec (spec) import Test.Hspec +import Relude import qualified WidgetsSpec (spec) main :: IO () diff --git a/test/Test/Orphans.hs b/test/Test/Orphans.hs index 32327e9..7f7d2ea 100644 --- a/test/Test/Orphans.hs +++ b/test/Test/Orphans.hs @@ -1,23 +1,23 @@ +{-# LANGUAGE DerivingVia #-} {-# LANGUAGE KindSignatures #-} {-# LANGUAGE RankNTypes #-} -{-# LANGUAGE DerivingVia #-} - {-# OPTIONS_GHC -fno-warn-orphans #-} module Test.Orphans where -import Test.QuickCheck.GenT +import Relude +import Test.QuickCheck.GenT -instance MonadGen m => MonadGen ( ExceptT e m ) where - liftGen = lift . liftGen - variant n = ExceptT . variant n . runExceptT - sized gen = ExceptT . sized $ runExceptT . gen - resize n = ExceptT . resize n . runExceptT - choose = ExceptT . fmap Right . choose +instance MonadGen m => MonadGen (ExceptT e m) where + liftGen = lift . liftGen + variant n = ExceptT . variant n . runExceptT + sized gen = ExceptT . sized $ runExceptT . gen + resize n = ExceptT . resize n . runExceptT + choose = ExceptT . fmap Right . choose -instance MonadGen m => MonadGen ( ReaderT r m ) where - liftGen = lift . liftGen - variant n op = ReaderT $ variant n . runReaderT op - sized gen = ReaderT $ \r -> sized $ usingReaderT r . gen - resize n op = ReaderT $ resize n . runReaderT op - choose = ReaderT . const . choose +instance MonadGen m => MonadGen (ReaderT r m) where + liftGen = lift . liftGen + variant n op = ReaderT $ variant n . runReaderT op + sized gen = ReaderT $ \r -> sized $ usingReaderT r . gen + resize n op = ReaderT $ resize n . runReaderT op + choose = ReaderT . const . choose diff --git a/test/WidgetsSpec.hs b/test/WidgetsSpec.hs index 93c82e1..d38bb06 100644 --- a/test/WidgetsSpec.hs +++ b/test/WidgetsSpec.hs @@ -7,6 +7,7 @@ import ArbitraryInstances () import Data.Time.LocalTime import Display.GraphWidget import qualified Graphics.Vty.Image as Vty +import Relude import Test.Hspec as HS import Test.Hspec.QuickCheck import Test.QuickCheck