Skip to content

Commit

Permalink
Enable doctest
Browse files Browse the repository at this point in the history
  • Loading branch information
newhoggy committed Dec 10, 2019
1 parent e69d76c commit 9b6efaa
Show file tree
Hide file tree
Showing 5 changed files with 48 additions and 21 deletions.
12 changes: 12 additions & 0 deletions doctest/DoctestDriver.hs
Original file line number Diff line number Diff line change
@@ -0,0 +1,12 @@
{-# LANGUAGE CPP #-}

#if MIN_VERSION_GLASGOW_HASKELL(8,4,4,0)
{-# OPTIONS_GHC -F -pgmF doctest-discover #-}
#else
module Main where

import qualified System.IO as IO

main :: IO ()
main = IO.putStrLn "WARNING: doctest will not run on GHC versions earlier than 8.4.4"
#endif
33 changes: 24 additions & 9 deletions hw-fingertree.cabal
Original file line number Diff line number Diff line change
Expand Up @@ -31,19 +31,22 @@ source-repository head
type: git
location: https://github.com/haskell-works/hw-fingertree

common base { build-depends: base >= 4 && < 5 }
common base { build-depends: base >= 4 && < 5 }

common deepseq { build-depends: deepseq >= 1.4 && < 1.5 }
common hedgehog { build-depends: hedgehog >= 0.6 && < 1.1 }
common hspec { build-depends: hspec >= 2.4 && < 3.0 }
common hw-hspec-hedgehog { build-depends: hw-hspec-hedgehog >= 0.1 && < 0.2 }
common hw-prim { build-depends: hw-prim >= 0.6.2.25 && < 0.7 }
common deepseq { build-depends: deepseq >= 1.4 && < 1.5 }
common doctest { build-depends: doctest >= 0.16.2 && < 0.17 }
common doctest-discover { build-depends: doctest-discover >= 0.2 && < 0.3 }
common hedgehog { build-depends: hedgehog >= 0.6 && < 1.1 }
common hspec { build-depends: hspec >= 2.4 && < 3.0 }
common hw-hspec-hedgehog { build-depends: hw-hspec-hedgehog >= 0.1 && < 0.2 }
common hw-prim { build-depends: hw-prim >= 0.6.2.25 && < 0.7 }

common config
default-language: Haskell2010
default-language: Haskell2010
ghc-options: -Wall

common hw-fingertree
build-depends: hw-fingertree
build-depends: hw-fingertree

library
import: base, config
Expand All @@ -61,8 +64,8 @@ test-suite hw-fingertree-tests
, deepseq
, hedgehog
, hspec
, hw-fingertree
, hw-hspec-hedgehog
build-depends: hw-fingertree
type: exitcode-stdio-1.0
main-is: Spec.hs
hs-source-dirs: tests
Expand All @@ -71,3 +74,15 @@ test-suite hw-fingertree-tests
other-modules: HaskellWorks.Data.FingerTree.Gen
HaskellWorks.Data.FingerTreeSpec
Paths_hw_fingertree

test-suite doctest
import: base, config
, doctest
, doctest-discover
, hw-fingertree
default-language: Haskell2010
type: exitcode-stdio-1.0
ghc-options: -threaded
main-is: DoctestDriver.hs
HS-Source-Dirs: doctest
build-tool-depends: doctest-discover:doctest-discover
4 changes: 2 additions & 2 deletions src/HaskellWorks/Data/IntervalMap/FingerTree.hs
Original file line number Diff line number Diff line change
Expand Up @@ -51,10 +51,10 @@ module HaskellWorks.Data.IntervalMap.FingerTree
import Control.Applicative ((<$>))
import Control.DeepSeq
import Data.Foldable (Foldable (foldMap))
import Data.Monoid
import Data.Monoid (Monoid (..))
import Data.Traversable (Traversable (traverse))
import GHC.Generics
import HaskellWorks.Data.FingerTree (FingerTree, Measured (..), ViewL (..), (<|), (><), (|>))
import HaskellWorks.Data.FingerTree (FingerTree, Measured (..), ViewL (..), (<|), (><))

import qualified Data.Semigroup as S
import qualified HaskellWorks.Data.FingerTree as FT
Expand Down
16 changes: 8 additions & 8 deletions tests/HaskellWorks/Data/FingerTree/Gen.hs
Original file line number Diff line number Diff line change
Expand Up @@ -26,8 +26,8 @@ shrinkFingerTree (Deep _ pr m sf) =
[deep pr' m sf | pr' <- shrinkDigit pr] ++
[deep pr m' sf | m' <- shrinkFingerTree m ] ++
[deep pr m sf' | sf' <- shrinkDigit sf]
shrinkFingerTree (Single x) = []
shrinkFingerTree Empty = []
shrinkFingerTree (Single _) = []
shrinkFingerTree Empty = []

fingerTree :: (MonadGen m, Measured v a) => m a -> m (FingerTree v a)
fingerTree gen = G.sized $ \size -> genSizedFingerTree size gen
Expand All @@ -36,10 +36,10 @@ genSizedFingerTree :: (MonadGen m, Measured v a) => Size -> m a -> m (FingerTree
genSizedFingerTree n gen = G.shrink shrinkFingerTree $ case n of
0 -> return Empty
1 -> Single <$> gen
n -> deep <$> (One <$> gen) <*> genSizedFingerTree (n `div` 2) (genSizedNode (n `div` 2) gen) <*> (One <$> gen)
o -> deep <$> (One <$> gen) <*> genSizedFingerTree (o `div` 2) (genSizedNode (o `div` 2) gen) <*> (One <$> gen)

shrinkNode :: Measured v a => Node v a -> [Node v a]
shrinkNode (Node2 _ a b) = []
shrinkNode (Node2 _ _ _ ) = []
shrinkNode (Node3 _ a b c) = [node2 a b, node2 a c, node2 b c]

genSizedNode :: (MonadGen m, Measured v a) => Size -> m a -> m (Node v a)
Expand All @@ -49,7 +49,7 @@ genSizedNode n gen = G.shrink shrinkNode $ G.choice
]

shrinkDigit :: Digit a -> [Digit a]
shrinkDigit (One a) = []
shrinkDigit (Two a b) = [One a, One b]
shrinkDigit (Three a b c) = [Two a b, Two a c, Two b c]
shrinkDigit (Four a b c d) = [Three a b c, Three a b d, Three a c d, Three b c d]
shrinkDigit (One _ ) = []
shrinkDigit (Two a b ) = [One a, One b]
shrinkDigit (Three a b c ) = [Two a b, Two a c, Two b c]
shrinkDigit (Four a b c d) = [Three a b c, Three a b d, Three a c d, Three b c d]
4 changes: 2 additions & 2 deletions tests/HaskellWorks/Data/FingerTreeSpec.hs
Original file line number Diff line number Diff line change
Expand Up @@ -118,9 +118,9 @@ spec = do
toList' (evalM (traverse' f xs)) ~== evalM (traverse f (toList xs))
it "traverseWithPos" $ require $ property $ do
xs <- forAll (G.fingerTree (G.int R.constantBounded))
let f xs y = do
let f ys y = do
n <- step
return (xs, n, y)
return (ys, n, y)
let xs_list = toList xs
toList' (evalM (traverseWithPos f xs)) ~== evalM (traverse (uncurry f) (zip (inits xs_list) xs_list))

Expand Down

0 comments on commit 9b6efaa

Please sign in to comment.