Skip to content

Commit

Permalink
Use explicit Prelude due to commercialhaskell/stack#5077
Browse files Browse the repository at this point in the history
  • Loading branch information
AdamJKing committed Jul 20, 2020
1 parent 5e09d92 commit afea82d
Show file tree
Hide file tree
Showing 34 changed files with 154 additions and 114 deletions.
2 changes: 1 addition & 1 deletion app/Main.hs
Original file line number Diff line number Diff line change
Expand Up @@ -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
Expand Down
19 changes: 11 additions & 8 deletions hie.yaml
Original file line number Diff line number Diff line change
@@ -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"
22 changes: 16 additions & 6 deletions package.yaml
Original file line number Diff line number Diff line change
Expand Up @@ -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
Expand Down Expand Up @@ -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:
Expand Down
1 change: 1 addition & 0 deletions src/App.hs
Original file line number Diff line number Diff line change
Expand Up @@ -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)
Expand Down
1 change: 1 addition & 0 deletions src/App/Args.hs
Original file line number Diff line number Diff line change
Expand Up @@ -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)
Expand Down
1 change: 1 addition & 0 deletions src/App/Components.hs
Original file line number Diff line number Diff line change
Expand Up @@ -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)

Expand Down
14 changes: 7 additions & 7 deletions src/App/Config.hs
Original file line number Diff line number Diff line change
Expand Up @@ -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
Expand Down
1 change: 1 addition & 0 deletions src/App/State.hs
Original file line number Diff line number Diff line change
Expand Up @@ -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)
Expand Down
1 change: 1 addition & 0 deletions src/Display/Graph.hs
Original file line number Diff line number Diff line change
Expand Up @@ -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)}
Expand Down
4 changes: 2 additions & 2 deletions src/Display/GraphWidget.hs
Original file line number Diff line number Diff line change
Expand Up @@ -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
Expand Down
3 changes: 3 additions & 0 deletions src/Display/Labels.hs
Original file line number Diff line number Diff line change
Expand Up @@ -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

Expand Down
1 change: 1 addition & 0 deletions src/Display/Projection.hs
Original file line number Diff line number Diff line change
Expand Up @@ -3,6 +3,7 @@

module Display.Projection where

import Relude
import Control.Lens
import Display.Projection.Scalable

Expand Down
1 change: 1 addition & 0 deletions src/Display/Projection/Scalable.hs
Original file line number Diff line number Diff line change
Expand Up @@ -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
Expand Down
1 change: 1 addition & 0 deletions src/Display/Types.hs
Original file line number Diff line number Diff line change
Expand Up @@ -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)
Expand Down
17 changes: 10 additions & 7 deletions src/Display/Widgets.hs
Original file line number Diff line number Diff line change
Expand Up @@ -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
Expand All @@ -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]
Expand Down
1 change: 1 addition & 0 deletions src/Events.hs
Original file line number Diff line number Diff line change
Expand Up @@ -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
Expand Down
1 change: 1 addition & 0 deletions src/Events/Types.hs
Original file line number Diff line number Diff line change
Expand Up @@ -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)
Expand Down
1 change: 1 addition & 0 deletions src/Graphite.hs
Original file line number Diff line number Diff line change
Expand Up @@ -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
Expand Down
27 changes: 13 additions & 14 deletions src/Graphite/Types.hs
Original file line number Diff line number Diff line change
Expand Up @@ -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

Expand All @@ -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
Expand Down Expand Up @@ -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
Expand All @@ -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
2 changes: 2 additions & 0 deletions src/Normalisation.hs
Original file line number Diff line number Diff line change
Expand Up @@ -3,6 +3,8 @@ module Normalisation
)
where

import Relude

diff :: Num a => (a, a) -> a
diff (a, b) = b - a

Expand Down
7 changes: 4 additions & 3 deletions test/App/StateSpec.hs
Original file line number Diff line number Diff line change
Expand Up @@ -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
7 changes: 4 additions & 3 deletions test/ArbitraryInstances.hs
Original file line number Diff line number Diff line change
@@ -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 #-}

Expand All @@ -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 [])
Expand Down
1 change: 1 addition & 0 deletions test/CommonProperties.hs
Original file line number Diff line number Diff line change
Expand Up @@ -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
Expand Down
1 change: 1 addition & 0 deletions test/DerivedArbitraryInstances.hs
Original file line number Diff line number Diff line change
Expand Up @@ -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 ()
Expand Down
2 changes: 1 addition & 1 deletion test/Display/GraphSpec.hs
Original file line number Diff line number Diff line change
Expand Up @@ -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 ->
Expand Down
1 change: 1 addition & 0 deletions test/Display/ProjectionSpec.hs
Original file line number Diff line number Diff line change
Expand Up @@ -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)
Expand Down
Loading

0 comments on commit afea82d

Please sign in to comment.