mirror of
https://github.com/koalaman/shellcheck.git
synced 2025-09-30 00:39:19 +08:00
Compare commits
5 Commits
Author | SHA1 | Date | |
---|---|---|---|
|
eb597baa7f | ||
|
fa8c2a0fee | ||
|
279cffd114 | ||
|
01fd944168 | ||
|
2778d658bf |
@@ -53,6 +53,7 @@ library
|
||||
base > 4.6.0.1 && < 5,
|
||||
bytestring,
|
||||
containers >= 0.5,
|
||||
deepseq >= 1.4.0.0,
|
||||
directory,
|
||||
mtl >= 2.2.1,
|
||||
parsec,
|
||||
@@ -89,6 +90,7 @@ executable shellcheck
|
||||
aeson,
|
||||
base >= 4 && < 5,
|
||||
bytestring,
|
||||
deepseq >= 1.4.0.0,
|
||||
ShellCheck,
|
||||
containers,
|
||||
directory,
|
||||
@@ -104,6 +106,7 @@ test-suite test-shellcheck
|
||||
aeson,
|
||||
base >= 4 && < 5,
|
||||
bytestring,
|
||||
deepseq >= 1.4.0.0,
|
||||
ShellCheck,
|
||||
containers,
|
||||
directory,
|
||||
|
@@ -17,14 +17,17 @@
|
||||
You should have received a copy of the GNU General Public License
|
||||
along with this program. If not, see <https://www.gnu.org/licenses/>.
|
||||
-}
|
||||
{-# LANGUAGE DeriveGeneric, DeriveAnyClass #-}
|
||||
module ShellCheck.AST where
|
||||
|
||||
import GHC.Generics (Generic)
|
||||
import Control.Monad.Identity
|
||||
import Control.DeepSeq
|
||||
import Text.Parsec
|
||||
import qualified ShellCheck.Regex as Re
|
||||
import Prelude hiding (id)
|
||||
|
||||
newtype Id = Id Int deriving (Show, Eq, Ord)
|
||||
newtype Id = Id Int deriving (Show, Eq, Ord, Generic, NFData)
|
||||
|
||||
data Quoted = Quoted | Unquoted deriving (Show, Eq)
|
||||
data Dashed = Dashed | Undashed deriving (Show, Eq)
|
||||
|
@@ -241,6 +241,39 @@ isCondition (child:parent:rest) =
|
||||
T_UntilExpression id c l -> take 1 . reverse $ c
|
||||
_ -> []
|
||||
|
||||
-- helpers to build replacements
|
||||
replaceStart id params n r =
|
||||
let tp = tokenPositions params
|
||||
(start, _) = tp Map.! id
|
||||
new_end = start {
|
||||
posColumn = posColumn start + n
|
||||
}
|
||||
in
|
||||
newReplacement {
|
||||
repStartPos = start,
|
||||
repEndPos = new_end,
|
||||
repString = r
|
||||
}
|
||||
replaceEnd id params n r =
|
||||
-- because of the way we count columns 1-based
|
||||
-- we have to offset end columns by 1
|
||||
let tp = tokenPositions params
|
||||
(_, end) = tp Map.! id
|
||||
new_start = end {
|
||||
posColumn = posColumn end - n + 1
|
||||
}
|
||||
new_end = end {
|
||||
posColumn = posColumn end + 1
|
||||
}
|
||||
in
|
||||
newReplacement {
|
||||
repStartPos = new_start,
|
||||
repEndPos = new_end,
|
||||
repString = r
|
||||
}
|
||||
surroundWidth id params s = fixWith [replaceStart id params 0 s, replaceEnd id params 0 s]
|
||||
fixWith fixes = newFix { fixReplacements = fixes }
|
||||
|
||||
prop_checkEchoWc3 = verify checkEchoWc "n=$(echo $foo | wc -c)"
|
||||
checkEchoWc _ (T_Pipeline id _ [a, b]) =
|
||||
when (acmd == ["echo", "${VAR}"]) $
|
||||
@@ -1334,8 +1367,10 @@ checkPS1Assignments _ _ = return ()
|
||||
prop_checkBackticks1 = verify checkBackticks "echo `foo`"
|
||||
prop_checkBackticks2 = verifyNot checkBackticks "echo $(foo)"
|
||||
prop_checkBackticks3 = verifyNot checkBackticks "echo `#inlined comment` foo"
|
||||
checkBackticks _ (T_Backticked id list) | not (null list) =
|
||||
style id 2006 "Use $(...) notation instead of legacy backticked `...`."
|
||||
checkBackticks params (T_Backticked id list) | not (null list) =
|
||||
addComment $
|
||||
makeCommentWithFix StyleC id 2006 "Use $(...) notation instead of legacy backticked `...`."
|
||||
(fixWith [replaceStart id params 1 "$(", replaceEnd id params 1 ")"])
|
||||
checkBackticks _ _ = return ()
|
||||
|
||||
prop_checkIndirectExpansion1 = verify checkIndirectExpansion "${foo$n}"
|
||||
@@ -1639,8 +1674,10 @@ checkSpacefulness params t =
|
||||
makeComment InfoC (getId token) 2223
|
||||
"This default assignment may cause DoS due to globbing. Quote it."
|
||||
else
|
||||
makeComment InfoC (getId token) 2086
|
||||
"Double quote to prevent globbing and word splitting."
|
||||
makeCommentWithFix InfoC (getId token) 2086
|
||||
"Double quote to prevent globbing and word splitting." (surroundWidth (getId token) params "\"")
|
||||
-- makeComment InfoC (getId token) 2086
|
||||
-- "Double quote to prevent globbing and word splitting."
|
||||
|
||||
writeF _ _ name (DataString SourceExternal) = setSpaces name True >> return []
|
||||
writeF _ _ name (DataString SourceInteger) = setSpaces name False >> return []
|
||||
@@ -2537,7 +2574,8 @@ checkUncheckedCdPushdPopd params root =
|
||||
&& not (isSafeDir t)
|
||||
&& not (name t `elem` ["pushd", "popd"] && ("n" `elem` map snd (getAllFlags t)))
|
||||
&& not (isCondition $ getPath (parentMap params) t)) $
|
||||
warn (getId t) 2164 "Use 'cd ... || exit' or 'cd ... || return' in case cd fails."
|
||||
warnWithFix (getId t) 2164 "Use 'cd ... || exit' or 'cd ... || return' in case cd fails."
|
||||
(fixWith [replaceEnd (getId t) params 0 " || exit"])
|
||||
checkElement _ = return ()
|
||||
name t = fromMaybe "" $ getCommandName t
|
||||
isSafeDir t = case oversimplify t of
|
||||
@@ -2694,7 +2732,7 @@ checkArrayAssignmentIndices params root =
|
||||
T_Literal id str -> [(id,str)]
|
||||
_ -> []
|
||||
guard $ '=' `elem` str
|
||||
return $ warn id 2191 "The = here is literal. To assign by index, use ( [index]=value ) with no spaces. To keep as literal, quote it."
|
||||
return $ warnWithFix id 2191 "The = here is literal. To assign by index, use ( [index]=value ) with no spaces. To keep as literal, quote it." (surroundWidth id params "\"")
|
||||
in
|
||||
if null literalEquals && isAssociative
|
||||
then warn (getId t) 2190 "Elements in associative arrays need index, e.g. array=( [index]=value ) ."
|
||||
|
@@ -20,6 +20,7 @@
|
||||
{-# LANGUAGE FlexibleContexts #-}
|
||||
{-# LANGUAGE TemplateHaskell #-}
|
||||
module ShellCheck.AnalyzerLib where
|
||||
|
||||
import ShellCheck.AST
|
||||
import ShellCheck.ASTLib
|
||||
import ShellCheck.Data
|
||||
@@ -28,15 +29,16 @@ import ShellCheck.Parser
|
||||
import ShellCheck.Regex
|
||||
|
||||
import Control.Arrow (first)
|
||||
import Control.DeepSeq
|
||||
import Control.Monad.Identity
|
||||
import Control.Monad.RWS
|
||||
import Control.Monad.State
|
||||
import Control.Monad.Writer
|
||||
import Data.Char
|
||||
import Data.List
|
||||
import qualified Data.Map as Map
|
||||
import Data.Maybe
|
||||
import Data.Semigroup
|
||||
import qualified Data.Map as Map
|
||||
|
||||
import Test.QuickCheck.All (forAllProperties)
|
||||
import Test.QuickCheck.Test (maxSuccess, quickCheckWithResult, stdArgs)
|
||||
@@ -81,7 +83,8 @@ data Parameters = Parameters {
|
||||
parentMap :: Map.Map Id Token, -- A map from Id to parent Token
|
||||
shellType :: Shell, -- The shell type, such as Bash or Ksh
|
||||
shellTypeSpecified :: Bool, -- True if shell type was forced via flags
|
||||
rootNode :: Token -- The root node of the AST
|
||||
rootNode :: Token, -- The root node of the AST
|
||||
tokenPositions :: Map.Map Id (Position, Position) -- map from token id to start and end position
|
||||
}
|
||||
|
||||
-- TODO: Cache results of common AST ops here
|
||||
@@ -142,7 +145,7 @@ makeComment severity id code note =
|
||||
}
|
||||
}
|
||||
|
||||
addComment note = tell [note]
|
||||
addComment note = note `deepseq` tell [note]
|
||||
|
||||
warn :: MonadWriter [TokenComment] m => Id -> Code -> String -> m ()
|
||||
warn id code str = addComment $ makeComment WarningC id code str
|
||||
@@ -150,6 +153,20 @@ err id code str = addComment $ makeComment ErrorC id code str
|
||||
info id code str = addComment $ makeComment InfoC id code str
|
||||
style id code str = addComment $ makeComment StyleC id code str
|
||||
|
||||
warnWithFix id code str fix = addComment $
|
||||
let comment = makeComment WarningC id code str in
|
||||
comment {
|
||||
tcFix = Just fix
|
||||
}
|
||||
|
||||
makeCommentWithFix :: Severity -> Id -> Code -> String -> Fix -> TokenComment
|
||||
makeCommentWithFix severity id code str fix =
|
||||
let comment = makeComment severity id code str
|
||||
withFix = comment {
|
||||
tcFix = Just fix
|
||||
}
|
||||
in withFix `deepseq` withFix
|
||||
|
||||
makeParameters spec =
|
||||
let params = Parameters {
|
||||
rootNode = root,
|
||||
@@ -164,7 +181,8 @@ makeParameters spec =
|
||||
|
||||
shellTypeSpecified = isJust $ asShellType spec,
|
||||
parentMap = getParentTree root,
|
||||
variableFlow = getVariableFlow params root
|
||||
variableFlow = getVariableFlow params root,
|
||||
tokenPositions = asTokenPositions spec
|
||||
} in params
|
||||
where root = asScript spec
|
||||
|
||||
|
@@ -42,7 +42,8 @@ tokenToPosition startMap t = fromMaybe fail $ do
|
||||
return $ newPositionedComment {
|
||||
pcStartPos = fst span,
|
||||
pcEndPos = snd span,
|
||||
pcComment = tcComment t
|
||||
pcComment = tcComment t,
|
||||
pcFix = tcFix t
|
||||
}
|
||||
where
|
||||
fail = error "Internal shellcheck error: id doesn't exist. Please report!"
|
||||
@@ -63,11 +64,20 @@ checkScript sys spec = do
|
||||
psShellTypeOverride = csShellTypeOverride spec
|
||||
}
|
||||
let parseMessages = prComments result
|
||||
let tokenPositions = prTokenPositions result
|
||||
let analysisSpec root =
|
||||
as {
|
||||
asScript = root,
|
||||
asShellType = csShellTypeOverride spec,
|
||||
asCheckSourced = csCheckSourced spec,
|
||||
asExecutionMode = Executed,
|
||||
asTokenPositions = tokenPositions
|
||||
} where as = newAnalysisSpec root
|
||||
let analysisMessages =
|
||||
fromMaybe [] $
|
||||
(arComments . analyzeScript . analysisSpec)
|
||||
<$> prRoot result
|
||||
let translator = tokenToPosition (prTokenPositions result)
|
||||
let translator = tokenToPosition tokenPositions
|
||||
return . nub . sortMessages . filter shouldInclude $
|
||||
(parseMessages ++ map translator analysisMessages)
|
||||
|
||||
@@ -90,13 +100,6 @@ checkScript sys spec = do
|
||||
cMessage comment)
|
||||
getPosition = pcStartPos
|
||||
|
||||
analysisSpec root =
|
||||
as {
|
||||
asScript = root,
|
||||
asShellType = csShellTypeOverride spec,
|
||||
asCheckSourced = csCheckSourced spec,
|
||||
asExecutionMode = Executed
|
||||
} where as = newAnalysisSpec root
|
||||
|
||||
getErrors sys spec =
|
||||
sort . map getCode . crComments $
|
||||
|
@@ -39,7 +39,20 @@ format = do
|
||||
footer = finish ref
|
||||
}
|
||||
|
||||
instance ToJSON (PositionedComment) where
|
||||
instance ToJSON Replacement where
|
||||
toJSON replacement =
|
||||
let start = repStartPos replacement
|
||||
end = repEndPos replacement
|
||||
str = repString replacement in
|
||||
object [
|
||||
"line" .= posLine start,
|
||||
"endLine" .= posLine end,
|
||||
"column" .= posColumn start,
|
||||
"endColumn" .= posColumn end,
|
||||
"replaceWith" .= str
|
||||
]
|
||||
|
||||
instance ToJSON PositionedComment where
|
||||
toJSON comment =
|
||||
let start = pcStartPos comment
|
||||
end = pcEndPos comment
|
||||
@@ -52,7 +65,8 @@ instance ToJSON (PositionedComment) where
|
||||
"endColumn" .= posColumn end,
|
||||
"level" .= severityText comment,
|
||||
"code" .= cCode c,
|
||||
"message" .= cMessage c
|
||||
"message" .= cMessage c,
|
||||
"fix" .= pcFix comment
|
||||
]
|
||||
|
||||
toEncoding comment =
|
||||
@@ -68,8 +82,14 @@ instance ToJSON (PositionedComment) where
|
||||
<> "level" .= severityText comment
|
||||
<> "code" .= cCode c
|
||||
<> "message" .= cMessage c
|
||||
<> "fix" .= pcFix comment
|
||||
)
|
||||
|
||||
instance ToJSON Fix where
|
||||
toJSON fix = object [
|
||||
"replacements" .= fixReplacements fix
|
||||
]
|
||||
|
||||
outputError file msg = hPutStrLn stderr $ file ++ ": " ++ msg
|
||||
collectResult ref result _ =
|
||||
modifyIORef ref (\x -> crComments result ++ x)
|
||||
@@ -77,4 +97,3 @@ collectResult ref result _ =
|
||||
finish ref = do
|
||||
list <- readIORef ref
|
||||
BL.putStrLn $ encode list
|
||||
|
||||
|
@@ -25,6 +25,7 @@ import ShellCheck.Formatter.Format
|
||||
import Control.Monad
|
||||
import Data.IORef
|
||||
import Data.List
|
||||
import Data.Maybe
|
||||
import GHC.Exts
|
||||
import System.IO
|
||||
import System.Info
|
||||
@@ -118,8 +119,8 @@ outputForFile color sys comments = do
|
||||
let fileLines = lines contents
|
||||
let lineCount = fromIntegral $ length fileLines
|
||||
let groups = groupWith lineNo comments
|
||||
mapM_ (\x -> do
|
||||
let lineNum = lineNo (head x)
|
||||
mapM_ (\commentsForLine -> do
|
||||
let lineNum = lineNo (head commentsForLine)
|
||||
let line = if lineNum < 1 || lineNum > lineCount
|
||||
then ""
|
||||
else fileLines !! fromIntegral (lineNum - 1)
|
||||
@@ -127,10 +128,62 @@ outputForFile color sys comments = do
|
||||
putStrLn $ color "message" $
|
||||
"In " ++ fileName ++" line " ++ show lineNum ++ ":"
|
||||
putStrLn (color "source" line)
|
||||
mapM_ (\c -> putStrLn (color (severityText c) $ cuteIndent c)) x
|
||||
mapM_ (\c -> putStrLn (color (severityText c) $ cuteIndent c)) commentsForLine
|
||||
putStrLn ""
|
||||
-- FIXME: Enable when reasonably stable
|
||||
-- showFixedString color comments lineNum line
|
||||
) groups
|
||||
|
||||
hasApplicableFix lineNum comment = fromMaybe False $ do
|
||||
replacements <- fixReplacements <$> pcFix comment
|
||||
guard $ all (\c -> onSameLine (repStartPos c) && onSameLine (repEndPos c)) replacements
|
||||
return True
|
||||
where
|
||||
onSameLine pos = posLine pos == lineNum
|
||||
|
||||
-- FIXME: Work correctly with multiple replacements
|
||||
showFixedString color comments lineNum line =
|
||||
case filter (hasApplicableFix lineNum) comments of
|
||||
(first:_) -> do
|
||||
-- in the spirit of error prone
|
||||
putStrLn $ color "message" "Did you mean: "
|
||||
putStrLn $ fixedString first line
|
||||
putStrLn ""
|
||||
_ -> return ()
|
||||
|
||||
-- need to do something smart about sorting by end index
|
||||
fixedString :: PositionedComment -> String -> String
|
||||
fixedString comment line =
|
||||
case (pcFix comment) of
|
||||
Nothing -> ""
|
||||
Just rs ->
|
||||
applyReplacement (fixReplacements rs) line 0
|
||||
where
|
||||
applyReplacement [] s _ = s
|
||||
applyReplacement (rep:xs) s offset =
|
||||
let replacementString = repString rep
|
||||
start = (posColumn . repStartPos) rep
|
||||
end = (posColumn . repEndPos) rep
|
||||
z = doReplace start end s replacementString
|
||||
len_r = (fromIntegral . length) replacementString in
|
||||
applyReplacement xs z (offset + (end - start) + len_r)
|
||||
|
||||
-- FIXME: Work correctly with tabs
|
||||
-- start and end comes from pos, which is 1 based
|
||||
-- doReplace 0 0 "1234" "A" -> "A1234" -- technically not valid
|
||||
-- doReplace 1 1 "1234" "A" -> "A1234"
|
||||
-- doReplace 1 2 "1234" "A" -> "A234"
|
||||
-- doReplace 3 3 "1234" "A" -> "12A34"
|
||||
-- doReplace 4 4 "1234" "A" -> "123A4"
|
||||
-- doReplace 5 5 "1234" "A" -> "1234A"
|
||||
doReplace start end o r =
|
||||
let si = fromIntegral (start-1)
|
||||
ei = fromIntegral (end-1)
|
||||
(x, xs) = splitAt si o
|
||||
(y, z) = splitAt (ei - si) xs
|
||||
in
|
||||
x ++ r ++ z
|
||||
|
||||
cuteIndent :: PositionedComment -> String
|
||||
cuteIndent comment =
|
||||
replicate (fromIntegral $ colNo comment - 1) ' ' ++
|
||||
|
@@ -17,6 +17,7 @@
|
||||
You should have received a copy of the GNU General Public License
|
||||
along with this program. If not, see <https://www.gnu.org/licenses/>.
|
||||
-}
|
||||
{-# LANGUAGE DeriveGeneric, DeriveAnyClass #-}
|
||||
module ShellCheck.Interface
|
||||
(
|
||||
SystemInterface(..)
|
||||
@@ -24,7 +25,7 @@ module ShellCheck.Interface
|
||||
, CheckResult(crFilename, crComments)
|
||||
, ParseSpec(psFilename, psScript, psCheckSourced, psShellTypeOverride)
|
||||
, ParseResult(prComments, prTokenPositions, prRoot)
|
||||
, AnalysisSpec(asScript, asShellType, asExecutionMode, asCheckSourced)
|
||||
, AnalysisSpec(asScript, asShellType, asExecutionMode, asCheckSourced, asTokenPositions)
|
||||
, AnalysisResult(arComments)
|
||||
, FormatterOptions(foColorOption, foWikiLinkCount)
|
||||
, Shell(Ksh, Sh, Bash, Dash)
|
||||
@@ -34,9 +35,9 @@ module ShellCheck.Interface
|
||||
, Severity(ErrorC, WarningC, InfoC, StyleC)
|
||||
, Position(posFile, posLine, posColumn)
|
||||
, Comment(cSeverity, cCode, cMessage)
|
||||
, PositionedComment(pcStartPos , pcEndPos , pcComment)
|
||||
, PositionedComment(pcStartPos , pcEndPos , pcComment, pcFix)
|
||||
, ColorOption(ColorAuto, ColorAlways, ColorNever)
|
||||
, TokenComment(tcId, tcComment)
|
||||
, TokenComment(tcId, tcComment, tcFix)
|
||||
, emptyCheckResult
|
||||
, newParseResult
|
||||
, newAnalysisSpec
|
||||
@@ -49,10 +50,18 @@ module ShellCheck.Interface
|
||||
, emptyCheckSpec
|
||||
, newPositionedComment
|
||||
, newComment
|
||||
, Fix(fixReplacements)
|
||||
, newFix
|
||||
, Replacement(repStartPos, repEndPos, repString)
|
||||
, newReplacement
|
||||
) where
|
||||
|
||||
import ShellCheck.AST
|
||||
|
||||
import Control.DeepSeq
|
||||
import Control.Monad.Identity
|
||||
import Data.Monoid
|
||||
import GHC.Generics (Generic)
|
||||
import qualified Data.Map as Map
|
||||
|
||||
|
||||
@@ -126,14 +135,16 @@ data AnalysisSpec = AnalysisSpec {
|
||||
asScript :: Token,
|
||||
asShellType :: Maybe Shell,
|
||||
asExecutionMode :: ExecutionMode,
|
||||
asCheckSourced :: Bool
|
||||
asCheckSourced :: Bool,
|
||||
asTokenPositions :: Map.Map Id (Position, Position)
|
||||
}
|
||||
|
||||
newAnalysisSpec token = AnalysisSpec {
|
||||
asScript = token,
|
||||
asShellType = Nothing,
|
||||
asExecutionMode = Executed,
|
||||
asCheckSourced = False
|
||||
asCheckSourced = False,
|
||||
asTokenPositions = Map.empty
|
||||
}
|
||||
|
||||
newtype AnalysisResult = AnalysisResult {
|
||||
@@ -163,12 +174,13 @@ data ExecutionMode = Executed | Sourced deriving (Show, Eq)
|
||||
type ErrorMessage = String
|
||||
type Code = Integer
|
||||
|
||||
data Severity = ErrorC | WarningC | InfoC | StyleC deriving (Show, Eq, Ord)
|
||||
data Severity = ErrorC | WarningC | InfoC | StyleC
|
||||
deriving (Show, Eq, Ord, Generic, NFData)
|
||||
data Position = Position {
|
||||
posFile :: String, -- Filename
|
||||
posLine :: Integer, -- 1 based source line
|
||||
posColumn :: Integer -- 1 based source column, where tabs are 8
|
||||
} deriving (Show, Eq)
|
||||
} deriving (Show, Eq, Generic, NFData)
|
||||
|
||||
newPosition :: Position
|
||||
newPosition = Position {
|
||||
@@ -181,7 +193,7 @@ data Comment = Comment {
|
||||
cSeverity :: Severity,
|
||||
cCode :: Code,
|
||||
cMessage :: String
|
||||
} deriving (Show, Eq)
|
||||
} deriving (Show, Eq, Generic, NFData)
|
||||
|
||||
newComment :: Comment
|
||||
newComment = Comment {
|
||||
@@ -190,27 +202,52 @@ newComment = Comment {
|
||||
cMessage = ""
|
||||
}
|
||||
|
||||
-- only support single line for now
|
||||
data Replacement = Replacement {
|
||||
repStartPos :: Position,
|
||||
repEndPos :: Position,
|
||||
repString :: String
|
||||
} deriving (Show, Eq, Generic, NFData)
|
||||
|
||||
newReplacement = Replacement {
|
||||
repStartPos = newPosition,
|
||||
repEndPos = newPosition,
|
||||
repString = ""
|
||||
}
|
||||
|
||||
data Fix = Fix {
|
||||
fixReplacements :: [Replacement]
|
||||
} deriving (Show, Eq, Generic, NFData)
|
||||
|
||||
newFix = Fix {
|
||||
fixReplacements = []
|
||||
}
|
||||
|
||||
data PositionedComment = PositionedComment {
|
||||
pcStartPos :: Position,
|
||||
pcEndPos :: Position,
|
||||
pcComment :: Comment
|
||||
} deriving (Show, Eq)
|
||||
pcComment :: Comment,
|
||||
pcFix :: Maybe Fix
|
||||
} deriving (Show, Eq, Generic, NFData)
|
||||
|
||||
newPositionedComment :: PositionedComment
|
||||
newPositionedComment = PositionedComment {
|
||||
pcStartPos = newPosition,
|
||||
pcEndPos = newPosition,
|
||||
pcComment = newComment
|
||||
pcComment = newComment,
|
||||
pcFix = Nothing
|
||||
}
|
||||
|
||||
data TokenComment = TokenComment {
|
||||
tcId :: Id,
|
||||
tcComment :: Comment
|
||||
} deriving (Show, Eq)
|
||||
tcComment :: Comment,
|
||||
tcFix :: Maybe Fix
|
||||
} deriving (Show, Eq, Generic, NFData)
|
||||
|
||||
newTokenComment = TokenComment {
|
||||
tcId = Id 0,
|
||||
tcComment = newComment
|
||||
tcComment = newComment,
|
||||
tcFix = Nothing
|
||||
}
|
||||
|
||||
data ColorOption =
|
||||
|
Reference in New Issue
Block a user