Skip to content

Commit

Permalink
feat: add linter to check for gendered pronouns in comments
Browse files Browse the repository at this point in the history
  • Loading branch information
zugz committed Apr 24, 2022
1 parent f63b737 commit 694640a
Show file tree
Hide file tree
Showing 4 changed files with 87 additions and 0 deletions.
2 changes: 2 additions & 0 deletions src/Tokstyle/Linter.hs
Original file line number Diff line number Diff line change
Expand Up @@ -16,6 +16,7 @@ import qualified Tokstyle.Linter.CallbackNames as CallbackNames
import qualified Tokstyle.Linter.Callgraph as Callgraph
import qualified Tokstyle.Linter.CallocArgs as CallocArgs
import qualified Tokstyle.Linter.CallocType as CallocType
import qualified Tokstyle.Linter.Comments as Comments
import qualified Tokstyle.Linter.CompoundInit as CompoundInit
import qualified Tokstyle.Linter.Constness as Constness
import qualified Tokstyle.Linter.EnumNames as EnumNames
Expand Down Expand Up @@ -58,6 +59,7 @@ localLinters =
, ("callback-names" , CallbackNames.analyse )
, ("calloc-args" , CallocArgs.analyse )
, ("calloc-type" , CallocType.analyse )
, ("comments" , Comments.analyse )
, ("compound-init" , CompoundInit.analyse )
, ("constness" , Constness.analyse )
, ("enum-names" , EnumNames.analyse )
Expand Down
48 changes: 48 additions & 0 deletions src/Tokstyle/Linter/Comments.hs
Original file line number Diff line number Diff line change
@@ -0,0 +1,48 @@
{-# LANGUAGE NamedFieldPuns #-}
{-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE Strict #-}
{-# LANGUAGE StrictData #-}
module Tokstyle.Linter.Comments (analyse) where

import Control.Monad (when)
import Control.Monad.State.Strict (State)
import qualified Control.Monad.State.Strict as State
import Data.Fix (Fix (..))
import Data.Text (Text)
import Language.Cimple (Lexeme (..), Node, CommentF (..), NodeF (..), lexemeText)
import Language.Cimple.Diagnostics (Diagnostics, warn)
import Language.Cimple.TraverseAst (AstActions, astActions, doComment, doNode,
traverseAst)


isGendered :: Text -> Bool
isGendered = (`elem`
[ "she"
, "her"
, "herself"
, "he"
, "him"
, "his"
, "himself"
])

checkCommentLexeme :: FilePath -> Lexeme Text -> Diagnostics ()
checkCommentLexeme file w =
when (isGendered $ lexemeText w) $
warn file w $ "inappropriately gendered pronoun: " <> lexemeText w

linter :: AstActions (State [Text]) Text
linter = astActions
{ doComment = \file comment act ->
case unFix comment of
DocWord w -> checkCommentLexeme file w
_ -> act
, doNode = \file node act ->
case unFix node of
Comment _ _ ws _ -> mapM_ (checkCommentLexeme file) ws
_ -> act

}

analyse :: (FilePath, [Node (Lexeme Text)]) -> [Text]
analyse = reverse . flip State.execState [] . traverseAst linter
35 changes: 35 additions & 0 deletions test/Tokstyle/Linter/CommentsSpec.hs
Original file line number Diff line number Diff line change
@@ -0,0 +1,35 @@
{-# LANGUAGE OverloadedStrings #-}
module Tokstyle.Linter.CommentsSpec where

import Test.Hspec (Spec, it, shouldBe)

import Tokstyle.Linter (allWarnings, analyse)
import Tokstyle.LinterSpec (mustParse)


spec :: Spec
spec = do
it "rejects gendered pronouns in plain comments" $ do
ast <- mustParse
[ "/* This is the peer himself. */"
]
analyse allWarnings ("test.c", ast)
`shouldBe`
[ "test.c:1: inappropriately gendered pronoun: himself [-Wcomments]"
]
it "rejects gendered pronouns in doxygen comments" $ do
ast <- mustParse
[ "/** @brief Checks peer goodness."
, " *"
, " * Checks a peer to see if she is good."
, " */"
]
analyse allWarnings ("test.c", ast)
`shouldBe`
[ "test.c:3: inappropriately gendered pronoun: she [-Wcomments]"
]
it "accepts gendered pronouns in code" $ do
ast <- mustParse
[ "void f(int ge, int he) { return; }"
]
analyse allWarnings ("test.c", ast) `shouldBe` []
2 changes: 2 additions & 0 deletions tokstyle.cabal
Original file line number Diff line number Diff line change
Expand Up @@ -28,6 +28,7 @@ library
, Tokstyle.Linter.Callgraph
, Tokstyle.Linter.CallocArgs
, Tokstyle.Linter.CallocType
, Tokstyle.Linter.Comments
, Tokstyle.Linter.CompoundInit
, Tokstyle.Linter.Constness
, Tokstyle.Linter.DeclaredOnce
Expand Down Expand Up @@ -133,6 +134,7 @@ test-suite testsuite
, Tokstyle.Linter.BooleanReturnSpec
, Tokstyle.Linter.CallgraphSpec
, Tokstyle.Linter.CallocTypeSpec
, Tokstyle.Linter.CommentsSpec
, Tokstyle.Linter.CompoundInitSpec
, Tokstyle.Linter.ConstnessSpec
, Tokstyle.Linter.ParensSpec
Expand Down

0 comments on commit 694640a

Please sign in to comment.