Skip to content

Commit

Permalink
[#578] Adds inspections for partial Scientific functions
Browse files Browse the repository at this point in the history
I added four new inspections, all relating to functions on `Scientific`
from the `scientific` package that are partial due to potentially
repeating decimals:

- STAN-0022 `fromRational :: Rational -> Scientific`
- STAN-0023 `realToFrac :: Real a => a -> Scientific`
- STAN-0024 `recip :: Scientific -> Scientific`
- STAN-0025 `(/) :: Scientific -> Scientific -> Scientific`
  • Loading branch information
jlavelle authored and tomjaguarpaw committed Dec 4, 2024
1 parent 3bbddb0 commit 386a5ef
Show file tree
Hide file tree
Showing 7 changed files with 120 additions and 10 deletions.
77 changes: 75 additions & 2 deletions src/Stan/Inspection/Partial.hs
Original file line number Diff line number Diff line change
Expand Up @@ -56,7 +56,14 @@ module Stan.Inspection.Partial
, stan0020
-- *** Partial instance for 'Natural' method 'GHC.Num.fromInteger'
, stan0021

-- *** Partial instance for 'Scientific' method 'GHC.Real.fromRational'
, stan0022
-- *** Partial 'Scientific' function 'GHC.Real.realToFrac'
, stan0023
-- *** Partial instance for 'Scientific' method 'GHC.Real.recip'
, stan0024
-- *** Partial instance for 'Scientific' method 'GHC.Real.(/)'
, stan0025
-- * List of all partial 'Inspection's
, partialInspectionsMap
) where
Expand All @@ -73,7 +80,7 @@ import Stan.NameMeta (NameMeta (..), baseNameFrom, mkBaseFoldableMeta, mkBaseLis
import Stan.Pattern.Ast (PatternAst (PatternAstName), namesToPatternAst)
import Stan.Pattern.Edsl (PatternBool (..))
import Stan.Pattern.Type (PatternType (..), integerPattern, listFunPattern, listPattern,
naturalPattern, nonEmptyPattern, (|->))
naturalPattern, nonEmptyPattern, rationalPattern, scientificPattern, (|->))
import Stan.Severity (Severity (..))

import qualified Stan.Category as Category
Expand Down Expand Up @@ -103,6 +110,10 @@ partialInspectionsMap = fromList $ fmapToFst inspectionId
, stan0019
, stan0020
, stan0021
, stan0022
, stan0023
, stan0024
, stan0025
]

-- | Smart constructor to create generic partial 'Inspection' with a given 'Pattern'.
Expand Down Expand Up @@ -314,3 +325,65 @@ stan0021 = mkPartialInspectionPattern
#endif
(integerPattern |-> naturalPattern)
""

-- | 'Inspection' — partial 'GHC.Real.fromRational' @STAN-0022@.
stan0022 :: Inspection
stan0022 = mkPartialInspectionPattern
(Id "STAN-0022")
#if __GLASGOW_HASKELL__ < 910
("fromRational" `_nameFrom` "GHC.Real")
#else
("fromRational" `_nameFrom` "GHC.Internal.Real")
#endif
(rationalPattern |-> scientificPattern)
"Scientific"
& solutionL .~
[ "Use a function like 'Data.Scientific.fromRationalRepetend' that handles repeating decimals"
, "Convert to a fractional type like 'Double'"
]

-- | 'Inspection' — partial 'GHC.Real.realToFrac' @STAN-0023@.
stan0023 :: Inspection
stan0023 = mkPartialInspectionPattern
(Id "STAN-0023")
#if __GLASGOW_HASKELL__ < 910
("realToFrac" `_nameFrom` "GHC.Real")
#else
("realToFrac" `_nameFrom` "GHC.Internal.Real")
#endif
((?) |-> scientificPattern)
"Scientific"
& solutionL .~
[ "Use 'Data.Scientific.fromFloatDigits'"
, "use a function that handles repeating decimals, e.g. 'Data.Scientific.fromRationalRepetend . toRational'"
]

-- | 'Inspection' - partial 'GHC.Real.recip' @STAN-0024@
stan0024 :: Inspection
stan0024 = mkPartialInspectionPattern
(Id "STAN-0024")
#if __GLASGOW_HASKELL__ < 910
("recip" `_nameFrom` "GHC.Real")
#else
("recip" `_nameFrom` "GHC.Internal.Real")
#endif
(scientificPattern |-> scientificPattern)
"Scientific"
& solutionL .~
[ "Convert to a fractional type like 'Double'"
]

-- | 'Inspection' - partial 'GHC.Real.(/)' @STAN-0025@
stan0025 :: Inspection
stan0025 = mkPartialInspectionPattern
(Id "STAN-0025")
#if __GLASGOW_HASKELL__ < 910
("/" `_nameFrom` "GHC.Real")
#else
("/" `_nameFrom` "GHC.Internal.Real")
#endif
(scientificPattern |-> scientificPattern |-> scientificPattern)
"Scientific"
& solutionL .~
[ "Convert to a fractional type like 'Double'"
]
20 changes: 20 additions & 0 deletions src/Stan/Pattern/Type.hs
Original file line number Diff line number Diff line change
Expand Up @@ -24,6 +24,8 @@ module Stan.Pattern.Type
, listFunPattern
, integerPattern
, naturalPattern
, rationalPattern
, scientificPattern

-- ** Textual types
, charPattern
Expand Down Expand Up @@ -158,6 +160,24 @@ naturalPattern = NameMeta

#endif

rationalPattern :: PatternType
rationalPattern =
"Rational" `_nameFrom` moduleName |:: []
where
moduleName =
#if __GLASGOW_HASKELL__ >= 910
"GHC.Internal.Real"
#else
"GHC.Real"
#endif

scientificPattern :: PatternType
scientificPattern = NameMeta
{ nameMetaName = "Scientific"
, nameMetaModuleName = "Data.Scientific"
, nameMetaPackage = "scientific"
} |:: []

charPattern :: PatternType
charPattern = primTypeMeta "Char" |:: []

Expand Down
1 change: 1 addition & 0 deletions stan.cabal
Original file line number Diff line number Diff line change
Expand Up @@ -174,6 +174,7 @@ library target
hs-source-dirs: target
build-depends: bytestring
, filepath
, scientific
, text
, unordered-containers
exposed-modules: Target.AntiPattern
Expand Down
13 changes: 13 additions & 0 deletions target/Target/Partial.hs
Original file line number Diff line number Diff line change
Expand Up @@ -8,6 +8,7 @@ import Data.List.NonEmpty (NonEmpty)
import Data.Maybe (fromJust)
import GHC.Exts (fromList)
import Numeric.Natural (Natural)
import Data.Scientific (Scientific)

import qualified Data.List.NonEmpty as NE

Expand Down Expand Up @@ -75,6 +76,18 @@ stanFromList = fromList
stanFromInteger :: Integer -> Natural
stanFromInteger = fromInteger

stanFromRational :: Rational -> Scientific
stanFromRational = fromRational

stanRealToFrac :: Real a => a -> Scientific
stanRealToFrac = realToFrac

stanRecip :: Scientific -> Scientific
stanRecip = recip

stanDivide :: Scientific -> Scientific -> Scientific
stanDivide a b = a / b

-- Other tests

stanSuccNatural :: Natural -> Natural
Expand Down
2 changes: 1 addition & 1 deletion test/Test/Stan/Analysis.hs
Original file line number Diff line number Diff line change
Expand Up @@ -57,7 +57,7 @@ analysisIgnoredObservationsSpec
:: ([Id Observation] -> Analysis) -- ^ Run analysis with ignored observations
-> Spec
analysisIgnoredObservationsSpec analyse = describe "Ignores observations" $ do
let obsId = Id "OBS-STAN-0001-pnvTKA-16:12"
let obsId = Id "OBS-STAN-0001-pnvTKA-17:12"

it "ObservationId is present when not ignored " $ do
let observationsIds = fmap observationId $ analysisObservations $ analyse []
Expand Down
15 changes: 9 additions & 6 deletions test/Test/Stan/Analysis/Partial.hs
Original file line number Diff line number Diff line change
Expand Up @@ -18,18 +18,18 @@ import qualified Stan.Inspection.Partial as Partial

analysisPartialSpec :: Analysis -> Spec
analysisPartialSpec analysis = describe "Partial functions" $ do
forM_ (zip (sortById partialInspectionsMap) [16, 19 ..]) checkObservation
forM_ (zip (sortById partialInspectionsMap) [17, 20 ..]) checkObservation

let noObservation = noObservationAssert ["Partial"] analysis

it "STAN-0010: doesn't trigger on 'succ :: Natural -> Natural'" $
noObservation Partial.stan0010 81
noObservation Partial.stan0010 94
it "STAN-0011: doesn't trigger on 'pred :: Integer -> Integer'" $
noObservation Partial.stan0011 84
noObservation Partial.stan0011 97
it "STAN-0011: triggers on polymorphic 'pred :: Enum a => a -> a'" $
checkObservationFor Partial.stan0011 87 16 20
checkObservationFor Partial.stan0011 100 16 20
it "STAN-0020: triggers on 'Data.List.NonEmpty.fromList'" $
checkObservationFor Partial.stan0020 90 18 29
checkObservationFor Partial.stan0020 103 18 29

where
checkObservation :: (Inspection, Int) -> SpecWith (Arg Expectation)
Expand All @@ -41,7 +41,10 @@ analysisPartialSpec analysis = describe "Partial functions" $ do

funLen, start, end :: Int
funLen = T.length $ nameMetaName nameMeta
start = if nameMetaName nameMeta == "!!" then funLen + 14 else funLen + 8
start = funLen + case nameMetaName nameMeta of
"!!" -> 14
"/" -> 19
_ -> 8
end = start + funLen

checkObservationFor :: Inspection -> Int -> Int -> Int -> Expectation
Expand Down
2 changes: 1 addition & 1 deletion test/Test/Stan/Number.hs
Original file line number Diff line number Diff line change
Expand Up @@ -12,7 +12,7 @@ import Stan.Hie (countLinesOfCode)
linesOfCodeSpec :: HieFile -> Spec
linesOfCodeSpec hieFile = describe "LoC tests" $
it "should count lines of code in the example file" $
countLinesOfCode hieFile `shouldBe` 90
countLinesOfCode hieFile `shouldBe` 103

modulesNumSpec :: Int -> Spec
modulesNumSpec num = describe "Modules number tests" $
Expand Down

0 comments on commit 386a5ef

Please sign in to comment.