mirror of
https://github.com/NorfairKing/feedback.git
synced 2024-11-25 08:53:20 +03:00
Weeder
This commit is contained in:
parent
a7bdef3966
commit
c727298d7b
@ -1,4 +1,3 @@
|
|||||||
{-# LANGUAGE DeriveGeneric #-}
|
|
||||||
{-# LANGUAGE DerivingVia #-}
|
{-# LANGUAGE DerivingVia #-}
|
||||||
{-# LANGUAGE LambdaCase #-}
|
{-# LANGUAGE LambdaCase #-}
|
||||||
{-# LANGUAGE OverloadedLists #-}
|
{-# LANGUAGE OverloadedLists #-}
|
||||||
@ -16,9 +15,7 @@ import qualified Data.Map as M
|
|||||||
import Data.Maybe
|
import Data.Maybe
|
||||||
import qualified Data.Text as T
|
import qualified Data.Text as T
|
||||||
import Data.Version
|
import Data.Version
|
||||||
import Data.Yaml (FromJSON, ToJSON)
|
|
||||||
import qualified Env
|
import qualified Env
|
||||||
import GHC.Generics (Generic)
|
|
||||||
import Options.Applicative as OptParse
|
import Options.Applicative as OptParse
|
||||||
import qualified Options.Applicative.Help as OptParse (pretty)
|
import qualified Options.Applicative.Help as OptParse (pretty)
|
||||||
import Path
|
import Path
|
||||||
@ -31,7 +28,7 @@ data LoopSettings = LoopSettings
|
|||||||
loopSettingOutputSettings :: !OutputSettings,
|
loopSettingOutputSettings :: !OutputSettings,
|
||||||
loopSettingHooksSettings :: !HooksSettings
|
loopSettingHooksSettings :: !HooksSettings
|
||||||
}
|
}
|
||||||
deriving (Show, Eq, Generic)
|
deriving (Show)
|
||||||
|
|
||||||
combineToLoopSettings :: Flags -> Environment -> Maybe OutputConfiguration -> LoopConfiguration -> IO LoopSettings
|
combineToLoopSettings :: Flags -> Environment -> Maybe OutputConfiguration -> LoopConfiguration -> IO LoopSettings
|
||||||
combineToLoopSettings Flags {..} Environment {} mDefaultOutputConfig LoopConfiguration {..} = do
|
combineToLoopSettings Flags {..} Environment {} mDefaultOutputConfig LoopConfiguration {..} = do
|
||||||
@ -48,7 +45,7 @@ data RunSettings = RunSettings
|
|||||||
runSettingExtraEnv :: !(Map String String),
|
runSettingExtraEnv :: !(Map String String),
|
||||||
runSettingWorkingDir :: !(Maybe (Path Abs Dir))
|
runSettingWorkingDir :: !(Maybe (Path Abs Dir))
|
||||||
}
|
}
|
||||||
deriving (Show, Eq, Generic)
|
deriving (Show)
|
||||||
|
|
||||||
combineToRunSettings :: RunConfiguration -> IO RunSettings
|
combineToRunSettings :: RunConfiguration -> IO RunSettings
|
||||||
combineToRunSettings RunConfiguration {..} = do
|
combineToRunSettings RunConfiguration {..} = do
|
||||||
@ -61,7 +58,7 @@ data FilterSettings = FilterSettings
|
|||||||
{ filterSettingGitignore :: !Bool,
|
{ filterSettingGitignore :: !Bool,
|
||||||
filterSettingFind :: !(Maybe String)
|
filterSettingFind :: !(Maybe String)
|
||||||
}
|
}
|
||||||
deriving (Show, Eq, Generic)
|
deriving (Show)
|
||||||
|
|
||||||
combineToFilterSettings :: FilterConfiguration -> FilterSettings
|
combineToFilterSettings :: FilterConfiguration -> FilterSettings
|
||||||
combineToFilterSettings FilterConfiguration {..} =
|
combineToFilterSettings FilterConfiguration {..} =
|
||||||
@ -72,7 +69,7 @@ combineToFilterSettings FilterConfiguration {..} =
|
|||||||
data OutputSettings = OutputSettings
|
data OutputSettings = OutputSettings
|
||||||
{ outputSettingClear :: !Clear
|
{ outputSettingClear :: !Clear
|
||||||
}
|
}
|
||||||
deriving (Show, Eq, Generic)
|
deriving (Show)
|
||||||
|
|
||||||
combineToOutputSettings :: OutputFlags -> OutputConfiguration -> OutputSettings
|
combineToOutputSettings :: OutputFlags -> OutputConfiguration -> OutputSettings
|
||||||
combineToOutputSettings OutputFlags {..} mConf =
|
combineToOutputSettings OutputFlags {..} mConf =
|
||||||
@ -85,7 +82,7 @@ data HooksSettings = HooksSettings
|
|||||||
{ hooksSettingBeforeAll :: Maybe RunSettings,
|
{ hooksSettingBeforeAll :: Maybe RunSettings,
|
||||||
hooksSettingAfterFirst :: Maybe RunSettings
|
hooksSettingAfterFirst :: Maybe RunSettings
|
||||||
}
|
}
|
||||||
deriving (Show, Eq, Generic)
|
deriving (Show)
|
||||||
|
|
||||||
combineToHooksSettings :: HooksConfiguration -> IO HooksSettings
|
combineToHooksSettings :: HooksConfiguration -> IO HooksSettings
|
||||||
combineToHooksSettings HooksConfiguration {..} = do
|
combineToHooksSettings HooksConfiguration {..} = do
|
||||||
@ -97,8 +94,6 @@ data Configuration = Configuration
|
|||||||
{ configLoops :: !(Map String LoopConfiguration),
|
{ configLoops :: !(Map String LoopConfiguration),
|
||||||
configOutputConfiguration :: !(Maybe OutputConfiguration)
|
configOutputConfiguration :: !(Maybe OutputConfiguration)
|
||||||
}
|
}
|
||||||
deriving stock (Show, Eq, Generic)
|
|
||||||
deriving (FromJSON, ToJSON) via (Autodocodec Configuration)
|
|
||||||
|
|
||||||
instance HasCodec Configuration where
|
instance HasCodec Configuration where
|
||||||
codec =
|
codec =
|
||||||
@ -123,8 +118,7 @@ data LoopConfiguration = LoopConfiguration
|
|||||||
loopConfigOutputConfiguration :: !OutputConfiguration,
|
loopConfigOutputConfiguration :: !OutputConfiguration,
|
||||||
loopConfigHooksConfiguration :: !HooksConfiguration
|
loopConfigHooksConfiguration :: !HooksConfiguration
|
||||||
}
|
}
|
||||||
deriving stock (Show, Eq, Generic)
|
deriving (Eq)
|
||||||
deriving (FromJSON, ToJSON) via (Autodocodec LoopConfiguration)
|
|
||||||
|
|
||||||
instance HasCodec LoopConfiguration where
|
instance HasCodec LoopConfiguration where
|
||||||
codec =
|
codec =
|
||||||
@ -192,8 +186,7 @@ data RunConfiguration = RunConfiguration
|
|||||||
runConfigExtraEnv :: !(Map String String),
|
runConfigExtraEnv :: !(Map String String),
|
||||||
runConfigWorkingDir :: !(Maybe FilePath)
|
runConfigWorkingDir :: !(Maybe FilePath)
|
||||||
}
|
}
|
||||||
deriving stock (Show, Eq, Generic)
|
deriving (Eq)
|
||||||
deriving (FromJSON, ToJSON) via (Autodocodec RunConfiguration)
|
|
||||||
|
|
||||||
instance HasCodec RunConfiguration where
|
instance HasCodec RunConfiguration where
|
||||||
codec =
|
codec =
|
||||||
@ -234,8 +227,7 @@ data FilterConfiguration = FilterConfiguration
|
|||||||
{ filterConfigGitignore :: !(Maybe Bool),
|
{ filterConfigGitignore :: !(Maybe Bool),
|
||||||
filterConfigFind :: !(Maybe String)
|
filterConfigFind :: !(Maybe String)
|
||||||
}
|
}
|
||||||
deriving stock (Show, Eq, Generic)
|
deriving (Eq)
|
||||||
deriving (FromJSON, ToJSON) via (Autodocodec FilterConfiguration)
|
|
||||||
|
|
||||||
instance HasCodec FilterConfiguration where
|
instance HasCodec FilterConfiguration where
|
||||||
codec =
|
codec =
|
||||||
@ -269,8 +261,7 @@ emptyFilterConfiguration =
|
|||||||
data OutputConfiguration = OutputConfiguration
|
data OutputConfiguration = OutputConfiguration
|
||||||
{ outputConfigClear :: !(Maybe Clear)
|
{ outputConfigClear :: !(Maybe Clear)
|
||||||
}
|
}
|
||||||
deriving stock (Show, Eq, Generic)
|
deriving (Eq)
|
||||||
deriving (FromJSON, ToJSON) via (Autodocodec OutputConfiguration)
|
|
||||||
|
|
||||||
instance HasCodec OutputConfiguration where
|
instance HasCodec OutputConfiguration where
|
||||||
codec =
|
codec =
|
||||||
@ -299,7 +290,7 @@ data HooksConfiguration = HooksConfiguration
|
|||||||
{ hooksConfigurationBeforeAll :: !(Maybe RunConfiguration),
|
{ hooksConfigurationBeforeAll :: !(Maybe RunConfiguration),
|
||||||
hooksConfigurationAfterFirst :: !(Maybe RunConfiguration)
|
hooksConfigurationAfterFirst :: !(Maybe RunConfiguration)
|
||||||
}
|
}
|
||||||
deriving (Show, Eq, Generic)
|
deriving (Eq)
|
||||||
|
|
||||||
instance HasCodec HooksConfiguration where
|
instance HasCodec HooksConfiguration where
|
||||||
codec =
|
codec =
|
||||||
@ -339,7 +330,6 @@ defaultConfigFile = do
|
|||||||
data Environment = Environment
|
data Environment = Environment
|
||||||
{ envConfigFile :: !(Maybe FilePath)
|
{ envConfigFile :: !(Maybe FilePath)
|
||||||
}
|
}
|
||||||
deriving (Show, Eq, Generic)
|
|
||||||
|
|
||||||
getEnvironment :: IO Environment
|
getEnvironment :: IO Environment
|
||||||
getEnvironment = Env.parse (Env.header "Environment") environmentParser
|
getEnvironment = Env.parse (Env.header "Environment") environmentParser
|
||||||
@ -386,13 +376,11 @@ data Flags = Flags
|
|||||||
flagConfigFile :: !(Maybe FilePath),
|
flagConfigFile :: !(Maybe FilePath),
|
||||||
flagOutputFlags :: !OutputFlags
|
flagOutputFlags :: !OutputFlags
|
||||||
}
|
}
|
||||||
deriving (Show, Eq, Generic)
|
|
||||||
|
|
||||||
data OutputFlags = OutputFlags
|
data OutputFlags = OutputFlags
|
||||||
{ outputFlagClear :: !(Maybe Clear),
|
{ outputFlagClear :: !(Maybe Clear),
|
||||||
outputFlagDebug :: Bool
|
outputFlagDebug :: Bool
|
||||||
}
|
}
|
||||||
deriving (Show, Eq, Generic)
|
|
||||||
|
|
||||||
parseFlags :: OptParse.Parser Flags
|
parseFlags :: OptParse.Parser Flags
|
||||||
parseFlags =
|
parseFlags =
|
||||||
@ -440,7 +428,7 @@ parseOutputFlags =
|
|||||||
)
|
)
|
||||||
|
|
||||||
newtype Command = CommandScript {unScript :: String}
|
newtype Command = CommandScript {unScript :: String}
|
||||||
deriving (Show, Eq, Generic)
|
deriving (Show, Eq)
|
||||||
|
|
||||||
instance HasCodec Command where
|
instance HasCodec Command where
|
||||||
codec = dimapCodec CommandScript unScript codec
|
codec = dimapCodec CommandScript unScript codec
|
||||||
@ -452,7 +440,7 @@ commandObjectCodec =
|
|||||||
(requiredField "command" "the command to run on change (alias for 'script' for backward compatibility)")
|
(requiredField "command" "the command to run on change (alias for 'script' for backward compatibility)")
|
||||||
|
|
||||||
data Clear = ClearScreen | DoNotClearScreen
|
data Clear = ClearScreen | DoNotClearScreen
|
||||||
deriving (Show, Eq, Generic)
|
deriving (Show, Eq)
|
||||||
|
|
||||||
instance HasCodec Clear where
|
instance HasCodec Clear where
|
||||||
codec = dimapCodec f g codec
|
codec = dimapCodec f g codec
|
||||||
|
@ -37,9 +37,6 @@ indicatorChunk = fore cyan . chunk . T.pack . printf "%-12s"
|
|||||||
loopNameChunk :: String -> Chunk
|
loopNameChunk :: String -> Chunk
|
||||||
loopNameChunk = fore yellow . chunk . T.pack
|
loopNameChunk = fore yellow . chunk . T.pack
|
||||||
|
|
||||||
commandChunk :: String -> Chunk
|
|
||||||
commandChunk = fore blue . chunk . T.pack
|
|
||||||
|
|
||||||
startingLines :: RunSettings -> [[Chunk]]
|
startingLines :: RunSettings -> [[Chunk]]
|
||||||
startingLines RunSettings {..} =
|
startingLines RunSettings {..} =
|
||||||
let RunSettings _ _ _ = undefined
|
let RunSettings _ _ _ = undefined
|
||||||
|
@ -174,7 +174,6 @@ getTermCaps = pure WithoutColours
|
|||||||
data RestartEvent
|
data RestartEvent
|
||||||
= FSEvent !FS.Event
|
= FSEvent !FS.Event
|
||||||
| StdinEvent !Char
|
| StdinEvent !Char
|
||||||
deriving (Show, Eq)
|
|
||||||
|
|
||||||
worker ::
|
worker ::
|
||||||
ThreadId ->
|
ThreadId ->
|
||||||
@ -308,7 +307,6 @@ data Output
|
|||||||
| OutputKilled
|
| OutputKilled
|
||||||
| OutputProcessStarted !RunSettings
|
| OutputProcessStarted !RunSettings
|
||||||
| OutputProcessExited !ExitCode !Word64
|
| OutputProcessExited !ExitCode !Word64
|
||||||
deriving (Show)
|
|
||||||
|
|
||||||
putOutput :: OutputSettings -> TerminalCapabilities -> ZonedTime -> Output -> IO ()
|
putOutput :: OutputSettings -> TerminalCapabilities -> ZonedTime -> Output -> IO ()
|
||||||
putOutput OutputSettings {..} terminalCapabilities loopBegin =
|
putOutput OutputSettings {..} terminalCapabilities loopBegin =
|
||||||
|
@ -149,16 +149,6 @@ standardFilter here =
|
|||||||
]
|
]
|
||||||
}
|
}
|
||||||
|
|
||||||
hidden :: Path Rel File -> Bool
|
|
||||||
hidden = goFile
|
|
||||||
where
|
|
||||||
goFile :: Path Rel File -> Bool
|
|
||||||
goFile f = isHiddenIn (parent f) f || goDir (parent f)
|
|
||||||
goDir :: Path Rel Dir -> Bool
|
|
||||||
goDir f
|
|
||||||
| parent f == f = False
|
|
||||||
| otherwise = isHiddenIn (parent f) f || goDir (parent f)
|
|
||||||
|
|
||||||
isHiddenIn :: Path b Dir -> Path b t -> Bool
|
isHiddenIn :: Path b Dir -> Path b t -> Bool
|
||||||
isHiddenIn curdir ad =
|
isHiddenIn curdir ad =
|
||||||
case stripProperPrefix curdir ad of
|
case stripProperPrefix curdir ad of
|
||||||
|
@ -18,7 +18,7 @@ getSettings = do
|
|||||||
data TestSettings = TestSettings
|
data TestSettings = TestSettings
|
||||||
{ testSettingLoops :: !(Map String LoopSettings)
|
{ testSettingLoops :: !(Map String LoopSettings)
|
||||||
}
|
}
|
||||||
deriving (Show, Eq)
|
deriving (Show)
|
||||||
|
|
||||||
combineToTestSettings :: Flags -> Environment -> Maybe Configuration -> IO TestSettings
|
combineToTestSettings :: Flags -> Environment -> Maybe Configuration -> IO TestSettings
|
||||||
combineToTestSettings flags@Flags {..} environment mConf = do
|
combineToTestSettings flags@Flags {..} environment mConf = do
|
||||||
|
19
flake.lock
19
flake.lock
@ -182,7 +182,8 @@
|
|||||||
"pre-commit-hooks": "pre-commit-hooks",
|
"pre-commit-hooks": "pre-commit-hooks",
|
||||||
"safe-coloured-text": "safe-coloured-text",
|
"safe-coloured-text": "safe-coloured-text",
|
||||||
"sydtest": "sydtest",
|
"sydtest": "sydtest",
|
||||||
"validity": "validity"
|
"validity": "validity",
|
||||||
|
"weeder-nix": "weeder-nix"
|
||||||
}
|
}
|
||||||
},
|
},
|
||||||
"safe-coloured-text": {
|
"safe-coloured-text": {
|
||||||
@ -247,6 +248,22 @@
|
|||||||
"repo": "validity",
|
"repo": "validity",
|
||||||
"type": "github"
|
"type": "github"
|
||||||
}
|
}
|
||||||
|
},
|
||||||
|
"weeder-nix": {
|
||||||
|
"flake": false,
|
||||||
|
"locked": {
|
||||||
|
"lastModified": 1712652513,
|
||||||
|
"narHash": "sha256-etbllbKKJNVHogT89VkgevuaSLa0SA24OGpSDKTrGX0=",
|
||||||
|
"owner": "NorfairKing",
|
||||||
|
"repo": "weeder-nix",
|
||||||
|
"rev": "d49eebf716fd512d5e521bfed49c3281ca12dc1c",
|
||||||
|
"type": "github"
|
||||||
|
},
|
||||||
|
"original": {
|
||||||
|
"owner": "NorfairKing",
|
||||||
|
"repo": "weeder-nix",
|
||||||
|
"type": "github"
|
||||||
|
}
|
||||||
}
|
}
|
||||||
},
|
},
|
||||||
"root": "root",
|
"root": "root",
|
||||||
|
@ -8,6 +8,8 @@
|
|||||||
inputs = {
|
inputs = {
|
||||||
nixpkgs.url = "github:NixOS/nixpkgs?ref=nixos-23.11";
|
nixpkgs.url = "github:NixOS/nixpkgs?ref=nixos-23.11";
|
||||||
pre-commit-hooks.url = "github:cachix/pre-commit-hooks.nix";
|
pre-commit-hooks.url = "github:cachix/pre-commit-hooks.nix";
|
||||||
|
weeder-nix.url = "github:NorfairKing/weeder-nix";
|
||||||
|
weeder-nix.flake = false;
|
||||||
validity.url = "github:NorfairKing/validity";
|
validity.url = "github:NorfairKing/validity";
|
||||||
validity.flake = false;
|
validity.flake = false;
|
||||||
autodocodec.url = "github:NorfairKing/autodocodec";
|
autodocodec.url = "github:NorfairKing/autodocodec";
|
||||||
@ -26,6 +28,7 @@
|
|||||||
{ self
|
{ self
|
||||||
, nixpkgs
|
, nixpkgs
|
||||||
, pre-commit-hooks
|
, pre-commit-hooks
|
||||||
|
, weeder-nix
|
||||||
, validity
|
, validity
|
||||||
, safe-coloured-text
|
, safe-coloured-text
|
||||||
, sydtest
|
, sydtest
|
||||||
@ -46,6 +49,7 @@
|
|||||||
(import (fast-myers-diff + "/nix/overlay.nix"))
|
(import (fast-myers-diff + "/nix/overlay.nix"))
|
||||||
(import (validity + "/nix/overlay.nix"))
|
(import (validity + "/nix/overlay.nix"))
|
||||||
(import (dekking + "/nix/overlay.nix"))
|
(import (dekking + "/nix/overlay.nix"))
|
||||||
|
(import (weeder-nix + "/nix/overlay.nix"))
|
||||||
];
|
];
|
||||||
};
|
};
|
||||||
pkgs = pkgsFor nixpkgs;
|
pkgs = pkgsFor nixpkgs;
|
||||||
@ -66,6 +70,10 @@
|
|||||||
coverables = [ "feedback" ];
|
coverables = [ "feedback" ];
|
||||||
coverage = [ "feedback-test-harness" ];
|
coverage = [ "feedback-test-harness" ];
|
||||||
};
|
};
|
||||||
|
weeder-check = pkgs.weeder-nix.makeWeederCheck {
|
||||||
|
weederToml = ./weeder.toml;
|
||||||
|
packages = [ "feedback" "feedback-test-harness" ];
|
||||||
|
};
|
||||||
pre-commit = pre-commit-hooks.lib.${system}.run {
|
pre-commit = pre-commit-hooks.lib.${system}.run {
|
||||||
src = ./.;
|
src = ./.;
|
||||||
hooks = {
|
hooks = {
|
||||||
|
9
weeder.toml
Normal file
9
weeder.toml
Normal file
@ -0,0 +1,9 @@
|
|||||||
|
unused-types = true
|
||||||
|
type-class-roots = false
|
||||||
|
roots = [
|
||||||
|
# General
|
||||||
|
".main$",
|
||||||
|
"^Paths_.*",
|
||||||
|
]
|
||||||
|
root-instances = [
|
||||||
|
]
|
Loading…
Reference in New Issue
Block a user