{-# LANGUAGE NamedFieldPuns #-}
{-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE PatternSynonyms #-}
{-# LANGUAGE ScopedTypeVariables #-}
module Hadolint.Shell where
import Control.Monad.Writer (Writer, execWriter, tell)
import Data.Functor.Identity (runIdentity)
import Data.Maybe (listToMaybe, mapMaybe)
import Data.Semigroup ((<>))
import qualified Data.Set as Set
import Data.Text (Text)
import qualified Data.Text as Text
import ShellCheck.AST (Id (..), Token (..), pattern T_Pipe, pattern T_SimpleCommand)
import qualified ShellCheck.AST
import qualified ShellCheck.ASTLib
import ShellCheck.Checker (checkScript)
import ShellCheck.Interface
import qualified ShellCheck.Parser
data CmdPart = CmdPart
{ CmdPart -> Text
arg :: !Text,
CmdPart -> Int
partId :: !Int
}
deriving (Int -> CmdPart -> ShowS
[CmdPart] -> ShowS
CmdPart -> String
(Int -> CmdPart -> ShowS)
-> (CmdPart -> String) -> ([CmdPart] -> ShowS) -> Show CmdPart
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [CmdPart] -> ShowS
$cshowList :: [CmdPart] -> ShowS
show :: CmdPart -> String
$cshow :: CmdPart -> String
showsPrec :: Int -> CmdPart -> ShowS
$cshowsPrec :: Int -> CmdPart -> ShowS
Show)
data Command = Command
{ Command -> Text
name :: !Text.Text,
Command -> [CmdPart]
arguments :: [CmdPart],
Command -> [CmdPart]
flags :: [CmdPart]
}
deriving (Int -> Command -> ShowS
[Command] -> ShowS
Command -> String
(Int -> Command -> ShowS)
-> (Command -> String) -> ([Command] -> ShowS) -> Show Command
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [Command] -> ShowS
$cshowList :: [Command] -> ShowS
show :: Command -> String
$cshow :: Command -> String
showsPrec :: Int -> Command -> ShowS
$cshowsPrec :: Int -> Command -> ShowS
Show)
data ParsedShell = ParsedShell
{ ParsedShell -> Text
original :: !Text.Text,
ParsedShell -> ParseResult
parsed :: !ParseResult,
ParsedShell -> [Command]
presentCommands :: ![Command]
}
data ShellOpts = ShellOpts
{ ShellOpts -> Text
shellName :: Text.Text,
ShellOpts -> Set Text
envVars :: Set.Set Text.Text
}
defaultShellOpts :: ShellOpts
defaultShellOpts :: ShellOpts
defaultShellOpts = Text -> Set Text -> ShellOpts
ShellOpts Text
"/bin/sh -c" Set Text
defaultVars
where
defaultVars :: Set Text
defaultVars =
[Text] -> Set Text
forall a. Ord a => [a] -> Set a
Set.fromList
[ Text
"HTTP_PROXY",
Text
"http_proxy",
Text
"HTTPS_PROXY",
Text
"https_proxy",
Text
"FTP_PROXY",
Text
"ftp_proxy",
Text
"NO_PROXY",
Text
"no_proxy"
]
addVars :: [Text.Text] -> ShellOpts -> ShellOpts
addVars :: [Text] -> ShellOpts -> ShellOpts
addVars [Text]
vars (ShellOpts Text
n Set Text
v) = Text -> Set Text -> ShellOpts
ShellOpts Text
n (Set Text
v Set Text -> Set Text -> Set Text
forall a. Semigroup a => a -> a -> a
<> [Text] -> Set Text
forall a. Ord a => [a] -> Set a
Set.fromList [Text]
vars)
setShell :: Text.Text -> ShellOpts -> ShellOpts
setShell :: Text -> ShellOpts -> ShellOpts
setShell Text
s (ShellOpts Text
_ Set Text
v) = Text -> Set Text -> ShellOpts
ShellOpts Text
s Set Text
v
shellcheck :: ShellOpts -> ParsedShell -> [PositionedComment]
shellcheck :: ShellOpts -> ParsedShell -> [PositionedComment]
shellcheck (ShellOpts Text
sh Set Text
env) (ParsedShell Text
txt ParseResult
_ [Command]
_) =
if Text
"pwsh" Text -> Text -> Bool
`Text.isPrefixOf` Text
sh
then []
else [PositionedComment]
runShellCheck
where
runShellCheck :: [PositionedComment]
runShellCheck = CheckResult -> [PositionedComment]
crComments (CheckResult -> [PositionedComment])
-> CheckResult -> [PositionedComment]
forall a b. (a -> b) -> a -> b
$ Identity CheckResult -> CheckResult
forall a. Identity a -> a
runIdentity (Identity CheckResult -> CheckResult)
-> Identity CheckResult -> CheckResult
forall a b. (a -> b) -> a -> b
$ SystemInterface Identity -> CheckSpec -> Identity CheckResult
forall (m :: * -> *).
Monad m =>
SystemInterface m -> CheckSpec -> m CheckResult
checkScript SystemInterface Identity
si CheckSpec
spec
si :: SystemInterface Identity
si = [(String, String)] -> SystemInterface Identity
mockedSystemInterface [(String
"", String
"")]
spec :: CheckSpec
spec =
CheckSpec
emptyCheckSpec
{ csFilename :: String
csFilename = String
"",
csScript :: String
csScript = String
script,
csCheckSourced :: Bool
csCheckSourced = Bool
False,
csExcludedWarnings :: [Integer]
csExcludedWarnings = [Integer]
exclusions,
csShellTypeOverride :: Maybe Shell
csShellTypeOverride = Maybe Shell
forall a. Maybe a
Nothing,
csMinSeverity :: Severity
csMinSeverity = Severity
StyleC
}
script :: String
script = String
"#!" String -> ShowS
forall a. [a] -> [a] -> [a]
++ Text -> String
extractShell Text
sh String -> ShowS
forall a. [a] -> [a] -> [a]
++ String
"\n" String -> ShowS
forall a. [a] -> [a] -> [a]
++ String
printVars String -> ShowS
forall a. [a] -> [a] -> [a]
++ Text -> String
Text.unpack Text
txt
exclusions :: [Integer]
exclusions =
[ Integer
2187,
Integer
1090
]
extractShell :: Text -> String
extractShell Text
s =
String -> (Text -> String) -> Maybe Text -> String
forall b a. b -> (a -> b) -> Maybe a -> b
maybe String
"" Text -> String
Text.unpack ([Text] -> Maybe Text
forall a. [a] -> Maybe a
listToMaybe ([Text] -> Maybe Text) -> (Text -> [Text]) -> Text -> Maybe Text
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Text -> [Text]
Text.words (Text -> Maybe Text) -> Text -> Maybe Text
forall a b. (a -> b) -> a -> b
$ Text
s)
printVars :: String
printVars = Text -> String
Text.unpack (Text -> String) -> (Set Text -> Text) -> Set Text -> String
forall b c a. (b -> c) -> (a -> b) -> a -> c
. [Text] -> Text
Text.unlines ([Text] -> Text) -> (Set Text -> [Text]) -> Set Text -> Text
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Set Text -> [Text]
forall a. Set a -> [a]
Set.toList (Set Text -> String) -> Set Text -> String
forall a b. (a -> b) -> a -> b
$ (Text -> Text) -> Set Text -> Set Text
forall b a. Ord b => (a -> b) -> Set a -> Set b
Set.map (\Text
v -> Text
"export " Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text
v Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text
"=1") Set Text
env
parseShell :: Text.Text -> ParsedShell
parseShell :: Text -> ParsedShell
parseShell Text
txt = ParsedShell :: Text -> ParseResult -> [Command] -> ParsedShell
ParsedShell {original :: Text
original = Text
txt, parsed :: ParseResult
parsed = ParseResult
parsedResult, presentCommands :: [Command]
presentCommands = [Command]
commands}
where
parsedResult :: ParseResult
parsedResult =
Identity ParseResult -> ParseResult
forall a. Identity a -> a
runIdentity (Identity ParseResult -> ParseResult)
-> Identity ParseResult -> ParseResult
forall a b. (a -> b) -> a -> b
$
SystemInterface Identity -> ParseSpec -> Identity ParseResult
forall (m :: * -> *).
Monad m =>
SystemInterface m -> ParseSpec -> m ParseResult
ShellCheck.Parser.parseScript
([(String, String)] -> SystemInterface Identity
mockedSystemInterface [(String
"", String
"")])
ParseSpec
newParseSpec
{ psFilename :: String
psFilename = String
"",
psScript :: String
psScript = String
"#!/bin/bash\n" String -> ShowS
forall a. [a] -> [a] -> [a]
++ Text -> String
Text.unpack Text
txt,
psCheckSourced :: Bool
psCheckSourced = Bool
False
}
commands :: [Command]
commands = (Token -> Maybe Command) -> [Token] -> [Command]
forall a b. (a -> Maybe b) -> [a] -> [b]
mapMaybe Token -> Maybe Command
extractNames (ParseResult -> [Token]
findCommandsInResult ParseResult
parsedResult)
extractNames :: Token -> Maybe Command
extractNames Token
token =
case Token -> Maybe String
ShellCheck.ASTLib.getCommandName Token
token of
Maybe String
Nothing -> Maybe Command
forall a. Maybe a
Nothing
Just String
n -> Command -> Maybe Command
forall a. a -> Maybe a
Just (Command -> Maybe Command) -> Command -> Maybe Command
forall a b. (a -> b) -> a -> b
$ Text -> [CmdPart] -> [CmdPart] -> Command
Command (String -> Text
Text.pack String
n) [CmdPart]
allArgs ([CmdPart] -> [CmdPart]
getAllFlags [CmdPart]
allArgs)
where
allArgs :: [CmdPart]
allArgs = Token -> [CmdPart]
extractAllArgs Token
token
findCommandsInResult :: ParseResult -> [Token]
findCommandsInResult :: ParseResult -> [Token]
findCommandsInResult = (Token -> Maybe Token) -> ParseResult -> [Token]
forall a. (Token -> Maybe a) -> ParseResult -> [a]
extractTokensWith Token -> Maybe Token
commandsExtractor
where
commandsExtractor :: Token -> Maybe Token
commandsExtractor = Token -> Maybe Token
ShellCheck.ASTLib.getCommand
extractTokensWith :: forall a. (Token -> Maybe a) -> ParseResult -> [a]
Token -> Maybe a
extractor ParseResult
ast =
case ParseResult -> Maybe Token
prRoot ParseResult
ast of
Maybe Token
Nothing -> []
Just Token
script -> Writer [a] Token -> [a]
forall w a. Writer w a -> w
execWriter (Writer [a] Token -> [a]) -> Writer [a] Token -> [a]
forall a b. (a -> b) -> a -> b
$ (Token -> WriterT [a] Identity ()) -> Token -> Writer [a] Token
forall (m :: * -> *).
Monad m =>
(Token -> m ()) -> Token -> m Token
ShellCheck.AST.doAnalysis Token -> WriterT [a] Identity ()
extract Token
script
where
extract :: Token -> Writer [a] ()
extract :: Token -> WriterT [a] Identity ()
extract Token
token =
case Token -> Maybe a
extractor Token
token of
Maybe a
Nothing -> () -> WriterT [a] Identity ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()
Just a
t -> [a] -> WriterT [a] Identity ()
forall w (m :: * -> *). MonadWriter w m => w -> m ()
tell [a
t]
findPipes :: ParsedShell -> [Token]
findPipes :: ParsedShell -> [Token]
findPipes (ParsedShell Text
_ ParseResult
ast [Command]
_) = (Token -> Maybe Token) -> ParseResult -> [Token]
forall a. (Token -> Maybe a) -> ParseResult -> [a]
extractTokensWith Token -> Maybe Token
pipesExtractor ParseResult
ast
where
pipesExtractor :: Token -> Maybe Token
pipesExtractor pipe :: Token
pipe@T_Pipe {} = Token -> Maybe Token
forall a. a -> Maybe a
Just Token
pipe
pipesExtractor Token
_ = Maybe Token
forall a. Maybe a
Nothing
hasPipes :: ParsedShell -> Bool
hasPipes :: ParsedShell -> Bool
hasPipes = Bool -> Bool
not (Bool -> Bool) -> (ParsedShell -> Bool) -> ParsedShell -> Bool
forall b c a. (b -> c) -> (a -> b) -> a -> c
. [Token] -> Bool
forall (t :: * -> *) a. Foldable t => t a -> Bool
null ([Token] -> Bool)
-> (ParsedShell -> [Token]) -> ParsedShell -> Bool
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ParsedShell -> [Token]
findPipes
allCommands :: (Command -> Bool) -> ParsedShell -> Bool
allCommands :: (Command -> Bool) -> ParsedShell -> Bool
allCommands Command -> Bool
check ParsedShell
script = (Command -> Bool) -> [Command] -> Bool
forall (t :: * -> *) a. Foldable t => (a -> Bool) -> t a -> Bool
all Command -> Bool
check (ParsedShell -> [Command]
presentCommands ParsedShell
script)
noCommands :: (Command -> Bool) -> ParsedShell -> Bool
noCommands :: (Command -> Bool) -> ParsedShell -> Bool
noCommands Command -> Bool
check = (Command -> Bool) -> ParsedShell -> Bool
allCommands (Bool -> Bool
not (Bool -> Bool) -> (Command -> Bool) -> Command -> Bool
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Command -> Bool
check)
anyCommands :: (Command -> Bool) -> ParsedShell -> Bool
anyCommands :: (Command -> Bool) -> ParsedShell -> Bool
anyCommands Command -> Bool
check ParsedShell
script = (Command -> Bool) -> [Command] -> Bool
forall (t :: * -> *) a. Foldable t => (a -> Bool) -> t a -> Bool
any Command -> Bool
check (ParsedShell -> [Command]
presentCommands ParsedShell
script)
findCommandNames :: ParsedShell -> [Text]
findCommandNames :: ParsedShell -> [Text]
findCommandNames ParsedShell
script = (Command -> Text) -> [Command] -> [Text]
forall a b. (a -> b) -> [a] -> [b]
map Command -> Text
name (ParsedShell -> [Command]
presentCommands ParsedShell
script)
cmdHasArgs :: Text.Text -> [Text.Text] -> Command -> Bool
cmdHasArgs :: Text -> [Text] -> Command -> Bool
cmdHasArgs Text
expectedName [Text]
expectedArgs (Command Text
n [CmdPart]
args [CmdPart]
_)
| Text
expectedName Text -> Text -> Bool
forall a. Eq a => a -> a -> Bool
/= Text
n = Bool
False
| Bool
otherwise = Bool -> Bool
not (Bool -> Bool) -> Bool -> Bool
forall a b. (a -> b) -> a -> b
$ [Text] -> Bool
forall (t :: * -> *) a. Foldable t => t a -> Bool
null [Text
arg | CmdPart Text
arg Int
_ <- [CmdPart]
args, Text
arg Text -> [Text] -> Bool
forall (t :: * -> *) a. (Foldable t, Eq a) => a -> t a -> Bool
`elem` [Text]
expectedArgs]
cmdHasPrefixArg :: Text.Text -> Text.Text -> Command -> Bool
cmdHasPrefixArg :: Text -> Text -> Command -> Bool
cmdHasPrefixArg Text
expectedName Text
expectedArg (Command Text
n [CmdPart]
args [CmdPart]
_)
| Text
expectedName Text -> Text -> Bool
forall a. Eq a => a -> a -> Bool
/= Text
n = Bool
False
| Bool
otherwise = Bool -> Bool
not (Bool -> Bool) -> Bool -> Bool
forall a b. (a -> b) -> a -> b
$ [Text] -> Bool
forall (t :: * -> *) a. Foldable t => t a -> Bool
null [Text
arg | CmdPart Text
arg Int
_ <- [CmdPart]
args, Text
expectedArg Text -> Text -> Bool
`Text.isPrefixOf` Text
arg]
extractAllArgs :: Token -> [CmdPart]
(T_SimpleCommand Id
_ [Token]
_ (Token
_ : [Token]
allArgs)) = (Token -> CmdPart) -> [Token] -> [CmdPart]
forall a b. (a -> b) -> [a] -> [b]
map Token -> CmdPart
mkPart [Token]
allArgs
where
mkPart :: Token -> CmdPart
mkPart Token
token =
Text -> Int -> CmdPart
CmdPart
(String -> Text
Text.pack (String -> Text) -> ([String] -> String) -> [String] -> Text
forall b c a. (b -> c) -> (a -> b) -> a -> c
. [String] -> String
forall (t :: * -> *) a. Foldable t => t [a] -> [a]
concat ([String] -> Text) -> [String] -> Text
forall a b. (a -> b) -> a -> b
$ Token -> [String]
ShellCheck.ASTLib.oversimplify Token
token)
(Id -> Int
mkId (Token -> Id
ShellCheck.AST.getId Token
token))
mkId :: Id -> Int
mkId (Id Int
i) = Int
i
extractAllArgs Token
_ = []
getArgs :: Command -> [Text.Text]
getArgs :: Command -> [Text]
getArgs Command
cmd = (CmdPart -> Text) -> [CmdPart] -> [Text]
forall a b. (a -> b) -> [a] -> [b]
map CmdPart -> Text
arg (Command -> [CmdPart]
arguments Command
cmd)
getAllFlags :: [CmdPart] -> [CmdPart]
getAllFlags :: [CmdPart] -> [CmdPart]
getAllFlags = (CmdPart -> [CmdPart]) -> [CmdPart] -> [CmdPart]
forall (t :: * -> *) a b. Foldable t => (a -> [b]) -> t a -> [b]
concatMap CmdPart -> [CmdPart]
flag
where
flag :: CmdPart -> [CmdPart]
flag (CmdPart Text
arg Int
pId)
| Text
arg Text -> Text -> Bool
forall a. Eq a => a -> a -> Bool
== Text
"--" Bool -> Bool -> Bool
|| Text
arg Text -> Text -> Bool
forall a. Eq a => a -> a -> Bool
== Text
"-" = []
| Text
"--" Text -> Text -> Bool
`Text.isPrefixOf` Text
arg = [Text -> Int -> CmdPart
CmdPart (Int -> Text -> Text
Text.drop Int
2 (Text -> Text) -> (Text -> Text) -> Text -> Text
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (Char -> Bool) -> Text -> Text
Text.takeWhile (Char -> Char -> Bool
forall a. Eq a => a -> a -> Bool
/= Char
'=') (Text -> Text) -> Text -> Text
forall a b. (a -> b) -> a -> b
$ Text
arg) Int
pId]
| Text
"-" Text -> Text -> Bool
`Text.isPrefixOf` Text
arg = (Text -> CmdPart) -> [Text] -> [CmdPart]
forall a b. (a -> b) -> [a] -> [b]
map (Text -> Int -> CmdPart
`CmdPart` Int
pId) (Int -> Text -> [Text]
Text.chunksOf Int
1 (Text -> Text
Text.tail Text
arg))
| Bool
otherwise = []
getArgsNoFlags :: Command -> [Text.Text]
getArgsNoFlags :: Command -> [Text]
getArgsNoFlags Command
args = (CmdPart -> Text) -> [CmdPart] -> [Text]
forall a b. (a -> b) -> [a] -> [b]
map CmdPart -> Text
arg ([CmdPart] -> [Text]) -> [CmdPart] -> [Text]
forall a b. (a -> b) -> a -> b
$ (CmdPart -> Bool) -> [CmdPart] -> [CmdPart]
forall a. (a -> Bool) -> [a] -> [a]
filter (Int -> Bool
notAFlagId (Int -> Bool) -> (CmdPart -> Int) -> CmdPart -> Bool
forall b c a. (b -> c) -> (a -> b) -> a -> c
. CmdPart -> Int
partId) (Command -> [CmdPart]
arguments Command
args)
where
notAFlagId :: Int -> Bool
notAFlagId Int
pId = Int
pId Int -> [Int] -> Bool
forall (t :: * -> *) a. (Foldable t, Eq a) => a -> t a -> Bool
`notElem` (CmdPart -> Int) -> [CmdPart] -> [Int]
forall a b. (a -> b) -> [a] -> [b]
map CmdPart -> Int
partId (Command -> [CmdPart]
flags Command
args)
hasFlag :: Text.Text -> Command -> Bool
hasFlag :: Text -> Command -> Bool
hasFlag Text
flag Command {[CmdPart]
flags :: [CmdPart]
flags :: Command -> [CmdPart]
flags} = Bool -> Bool
not (Bool -> Bool) -> Bool -> Bool
forall a b. (a -> b) -> a -> b
$ [Text] -> Bool
forall (t :: * -> *) a. Foldable t => t a -> Bool
null [Text
f | CmdPart Text
f Int
_ <- [CmdPart]
flags, Text
f Text -> Text -> Bool
forall a. Eq a => a -> a -> Bool
== Text
flag]
hasAnyFlag :: [Text.Text] -> Command -> Bool
hasAnyFlag :: [Text] -> Command -> Bool
hasAnyFlag [Text]
fs Command {[CmdPart]
flags :: [CmdPart]
flags :: Command -> [CmdPart]
flags} = Bool -> Bool
not (Bool -> Bool) -> Bool -> Bool
forall a b. (a -> b) -> a -> b
$ [Text] -> Bool
forall (t :: * -> *) a. Foldable t => t a -> Bool
null [Text
f | CmdPart Text
f Int
_ <- [CmdPart]
flags, Text
f Text -> [Text] -> Bool
forall (t :: * -> *) a. (Foldable t, Eq a) => a -> t a -> Bool
`elem` [Text]
fs]
hasArg :: Text.Text -> Command -> Bool
hasArg :: Text -> Command -> Bool
hasArg Text
arg Command {[CmdPart]
arguments :: [CmdPart]
arguments :: Command -> [CmdPart]
arguments} = Bool -> Bool
not (Bool -> Bool) -> Bool -> Bool
forall a b. (a -> b) -> a -> b
$ [Text] -> Bool
forall (t :: * -> *) a. Foldable t => t a -> Bool
null [Text
a | CmdPart Text
a Int
_ <- [CmdPart]
arguments, Text
a Text -> Text -> Bool
forall a. Eq a => a -> a -> Bool
== Text
arg]
dropFlagArg :: [Text.Text] -> Command -> Command
dropFlagArg :: [Text] -> Command -> Command
dropFlagArg [Text]
flagsToDrop Command {Text
name :: Text
name :: Command -> Text
name, [CmdPart]
arguments :: [CmdPart]
arguments :: Command -> [CmdPart]
arguments, [CmdPart]
flags :: [CmdPart]
flags :: Command -> [CmdPart]
flags} = Text -> [CmdPart] -> [CmdPart] -> Command
Command Text
name [CmdPart]
filterdArgs [CmdPart]
flags
where
idsToDrop :: Set Int
idsToDrop = [Int] -> Set Int
forall a. Ord a => [a] -> Set a
Set.fromList [Int -> [CmdPart] -> Int
getValueId Int
fId [CmdPart]
arguments | CmdPart Text
f Int
fId <- [CmdPart]
flags, Text
f Text -> [Text] -> Bool
forall (t :: * -> *) a. (Foldable t, Eq a) => a -> t a -> Bool
`elem` [Text]
flagsToDrop]
filterdArgs :: [CmdPart]
filterdArgs = [CmdPart
arg | arg :: CmdPart
arg@(CmdPart Text
_ Int
aId) <- [CmdPart]
arguments, Bool -> Bool
not (Int
aId Int -> Set Int -> Bool
forall a. Ord a => a -> Set a -> Bool
`Set.member` Set Int
idsToDrop)]
getValueId :: Int -> [CmdPart] -> Int
getValueId :: Int -> [CmdPart] -> Int
getValueId Int
fId [CmdPart]
flags = (Int -> Int -> Int) -> Int -> [Int] -> Int
forall (t :: * -> *) b a.
Foldable t =>
(b -> a -> b) -> b -> t a -> b
foldl Int -> Int -> Int
forall a. Ord a => a -> a -> a
min (Int
forall a. Bounded a => a
maxBound :: Int) ([Int] -> Int) -> [Int] -> Int
forall a b. (a -> b) -> a -> b
$ (Int -> Bool) -> [Int] -> [Int]
forall a. (a -> Bool) -> [a] -> [a]
filter (Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
> Int
fId) ([Int] -> [Int]) -> [Int] -> [Int]
forall a b. (a -> b) -> a -> b
$ (CmdPart -> Int) -> [CmdPart] -> [Int]
forall a b. (a -> b) -> [a] -> [b]
map CmdPart -> Int
partId [CmdPart]
flags