Skip to content

Commit

Permalink
Use Choice for askDebug
Browse files Browse the repository at this point in the history
  • Loading branch information
brandonchinn178 committed Jun 2, 2024
1 parent 626712f commit a2a2f40
Show file tree
Hide file tree
Showing 7 changed files with 24 additions and 9 deletions.
1 change: 1 addition & 0 deletions ormolu.cabal
Original file line number Diff line number Diff line change
Expand Up @@ -176,6 +176,7 @@ test-suite tests
Cabal-syntax >=3.12 && <3.13,
QuickCheck >=2.14,
base >=4.14 && <5,
choice >= 0.1 && < 0.3,
containers >=0.5 && <0.8,
directory ^>=1.3,
filepath >=1.2 && <1.6,
Expand Down
7 changes: 5 additions & 2 deletions src/Ormolu/Fixity/Internal.hs
Original file line number Diff line number Diff line change
@@ -1,3 +1,4 @@
{-# LANGUAGE DataKinds #-}
{-# LANGUAGE DeriveAnyClass #-}
{-# LANGUAGE DerivingStrategies #-}
{-# LANGUAGE OverloadedStrings #-}
Expand Down Expand Up @@ -33,6 +34,8 @@ import Control.DeepSeq (NFData)
import Data.Binary (Binary)
import Data.ByteString.Short (ShortByteString)
import Data.ByteString.Short qualified as SBS
import Data.Choice (Choice)
import Data.Choice qualified as Choice
import Data.List.NonEmpty (NonEmpty (..))
import Data.List.NonEmpty qualified as NE
import Data.Map.Strict (Map)
Expand Down Expand Up @@ -259,15 +262,15 @@ data FixityQualification
-- | Get a 'FixityApproximation' of an operator.
inferFixity ::
-- | Whether to print debug info regarding fixity inference
Bool ->
Choice "debug" ->
-- | Operator name
RdrName ->
-- | Module fixity map
ModuleFixityMap ->
-- | The resulting fixity approximation
FixityApproximation
inferFixity debug rdrName (ModuleFixityMap m) =
if debug
if Choice.toBool debug
then
trace
(renderFixityJustification opName moduleName m result)
Expand Down
7 changes: 5 additions & 2 deletions src/Ormolu/Printer/Internal.hs
Original file line number Diff line number Diff line change
@@ -1,3 +1,4 @@
{-# LANGUAGE DataKinds #-}
{-# LANGUAGE LambdaCase #-}
{-# LANGUAGE OverloadedStrings #-}

Expand Down Expand Up @@ -59,6 +60,8 @@ import Control.Monad
import Control.Monad.Reader
import Control.Monad.State.Strict
import Data.Bool (bool)
import Data.Choice (Choice)
import Data.Choice qualified as Choice
import Data.Coerce
import Data.Functor ((<&>))
import Data.List (find)
Expand Down Expand Up @@ -393,8 +396,8 @@ askModuleFixityMap = R (asks rcModuleFixityMap)

-- | Retrieve whether we should print out certain debug information while
-- printing.
askDebug :: R Bool
askDebug = R (asks rcDebug)
askDebug :: R (Choice "debug")
askDebug = R (asks (Choice.fromBool . rcDebug))

inciBy :: Int -> R () -> R ()
inciBy step (R m) = R (local modRC m)
Expand Down
6 changes: 4 additions & 2 deletions src/Ormolu/Printer/Operators.hs
Original file line number Diff line number Diff line change
@@ -1,3 +1,4 @@
{-# LANGUAGE DataKinds #-}
{-# LANGUAGE MultiWayIf #-}
{-# LANGUAGE PatternSynonyms #-}

Expand All @@ -13,6 +14,7 @@ module Ormolu.Printer.Operators
)
where

import Data.Choice (Choice)
import Data.List.NonEmpty (NonEmpty (..))
import Data.List.NonEmpty qualified as NE
import GHC.Parser.Annotation
Expand Down Expand Up @@ -92,7 +94,7 @@ opTreeLoc (OpBranches exprs _) =
-- re-associate it using this function before printing.
reassociateOpTree ::
-- | Whether to print debug info regarding fixity inference
Bool ->
Choice "debug" ->
-- | How to get name of an operator
(op -> Maybe RdrName) ->
-- | Fixity Map
Expand All @@ -110,7 +112,7 @@ reassociateOpTree debug getOpName modFixityMap =
-- about its fixity (extracted from the specified fixity map).
addFixityInfo ::
-- | Whether to print debug info regarding fixity inference
Bool ->
Choice "debug" ->
-- | Fixity map for operators
ModuleFixityMap ->
-- | How to get the name of an operator
Expand Down
2 changes: 1 addition & 1 deletion tests/Ormolu/CabalInfoSpec.hs
Original file line number Diff line number Diff line change
Expand Up @@ -44,7 +44,7 @@ spec = do
mentioned `shouldBe` True
unPackageName ciPackageName `shouldBe` "ormolu"
ciDynOpts `shouldBe` [DynOption "-XGHC2021"]
Set.map unPackageName ciDependencies `shouldBe` Set.fromList ["Cabal-syntax", "QuickCheck", "base", "containers", "directory", "filepath", "ghc-lib-parser", "hspec", "hspec-megaparsec", "megaparsec", "ormolu", "path", "path-io", "temporary", "text"]
Set.map unPackageName ciDependencies `shouldBe` Set.fromList ["Cabal-syntax", "QuickCheck", "base", "choice", "containers", "directory", "filepath", "ghc-lib-parser", "hspec", "hspec-megaparsec", "megaparsec", "ormolu", "path", "path-io", "temporary", "text"]
ciCabalFilePath `shouldSatisfy` isAbsolute
makeRelativeToCurrentDirectory ciCabalFilePath `shouldReturn` "ormolu.cabal"
it "handles correctly files that are not mentioned in ormolu.cabal" $ do
Expand Down
5 changes: 4 additions & 1 deletion tests/Ormolu/FixitySpec.hs
Original file line number Diff line number Diff line change
@@ -1,8 +1,11 @@
{-# LANGUAGE OverloadedLabels #-}
{-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE PatternSynonyms #-}
{-# OPTIONS_GHC -fno-warn-orphans #-}

module Ormolu.FixitySpec (spec) where

import Data.Choice (pattern Without)
import Data.Function ((&))
import Data.List.NonEmpty (NonEmpty (..))
import Data.Map.Strict qualified as Map
Expand Down Expand Up @@ -261,7 +264,7 @@ checkFixities dependencies fixityImports expectedResult =
where
actualResult =
fmap
(\(k, _) -> (k, inferFixity False k resultMap))
(\(k, _) -> (k, inferFixity (Without #debug) k resultMap))
expectedResult
resultMap =
moduleFixityMap
Expand Down
5 changes: 4 additions & 1 deletion tests/Ormolu/OpTreeSpec.hs
Original file line number Diff line number Diff line change
@@ -1,8 +1,11 @@
{-# LANGUAGE OverloadedLabels #-}
{-# LANGUAGE OverloadedLists #-}
{-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE PatternSynonyms #-}

module Ormolu.OpTreeSpec (spec) where

import Data.Choice (pattern Without)
import Data.Map.Strict qualified as Map
import Data.Text (Text)
import Data.Text qualified as T
Expand Down Expand Up @@ -31,7 +34,7 @@ checkReassociate fixities inputTree expectedOutputTree =
removeOpInfo (OpNode x) = OpNode x
removeOpInfo (OpBranches exprs ops) =
OpBranches (removeOpInfo <$> exprs) (opiOp <$> ops)
actualOutputTree = reassociateOpTree False convertName modFixityMap inputTree
actualOutputTree = reassociateOpTree (Without #debug) convertName modFixityMap inputTree
modFixityMap = ModuleFixityMap (Map.map Given (Map.fromList fixities))
convertName = Just . mkRdrUnqual . mkOccName varName . T.unpack . unOpName

Expand Down

0 comments on commit a2a2f40

Please sign in to comment.