Skip to content

Commit

Permalink
Fix doctests for GHC9.4
Browse files Browse the repository at this point in the history
I don't know what am I doing really. But doctests now work
  • Loading branch information
Shimuuar committed Aug 28, 2023
1 parent 92a28fd commit 624c0ab
Show file tree
Hide file tree
Showing 3 changed files with 42 additions and 6 deletions.
3 changes: 2 additions & 1 deletion vector/src/Data/Vector/Storable.hs
Original file line number Diff line number Diff line change
Expand Up @@ -1029,7 +1029,8 @@ izipWith6 = G.izipWith6
-- | Checks whether two values are the same vector: they have same length
-- and share the same buffer.
--
-- >>> let xs = fromList [0/0::Double] in isSameVector xs xs
-- >>> import qualified Data.Vector.Storable as VS
-- >>> let xs = VS.fromList [0/0::Double] in VS.isSameVector xs xs
-- True
isSameVector :: (Storable a) => Vector a -> Vector a -> Bool
{-# INLINE isSameVector #-}
Expand Down
9 changes: 5 additions & 4 deletions vector/src/Data/Vector/Unboxed/Base.hs
Original file line number Diff line number Diff line change
Expand Up @@ -304,6 +304,7 @@ idU = id
-- >>> :set -XTypeFamilies -XStandaloneDeriving -XDerivingVia
-- >>> :set -XMultiParamTypeClasses -XTypeOperators -XFlexibleInstances
-- >>> import qualified Data.Vector.Unboxed as VU
-- >>> import qualified Data.Vector.Unboxed.Mutable as MVU
-- >>> import qualified Data.Vector.Generic as VG
-- >>> import qualified Data.Vector.Generic.Mutable as VGM
-- >>> :{
Expand All @@ -316,17 +317,17 @@ idU = id
-- {-# INLINE fromURepr #-}
-- newtype instance VU.MVector s (Foo a) = MV_Foo (VU.MVector s (Int, a))
-- newtype instance VU.Vector (Foo a) = V_Foo (VU.Vector (Int, a))
-- deriving via (Foo a `VU.As` (Int, a)) instance VU.Unbox a => VGM.MVector MVector (Foo a)
-- deriving via (Foo a `VU.As` (Int, a)) instance VU.Unbox a => VG.Vector Vector (Foo a)
-- deriving via (Foo a `VU.As` (Int, a)) instance VU.Unbox a => VGM.MVector MVU.MVector (Foo a)
-- deriving via (Foo a `VU.As` (Int, a)) instance VU.Unbox a => VG.Vector VU.Vector (Foo a)
-- instance VU.Unbox a => VU.Unbox (Foo a)
-- :}
--
--
-- It's also possible to use generic-based instance for 'IsoUnbox'
-- which should work for all product types.
--
-- >>> :set -XTypeFamilies -XStandaloneDeriving -XDerivingVia -XDeriveGeneric
-- >>> :set -XMultiParamTypeClasses -XTypeOperators -XFlexibleInstances
-- >>> :set -XMultiParamTypeClasses -XTypeOperators -XFlexibleInstances -XDeriveGeneric
-- >>> :set -XDerivingVia
-- >>> import qualified Data.Vector.Unboxed as VU
-- >>> import qualified Data.Vector.Generic as VG
-- >>> import qualified Data.Vector.Generic.Mutable as VGM
Expand Down
36 changes: 35 additions & 1 deletion vector/tests/doctests.hs
Original file line number Diff line number Diff line change
@@ -1,4 +1,38 @@
import Test.DocTest (doctest)

-- Doctests are weirdly fragile. For example running tests for module
-- A (D.V.Unboxed.Base) could cause tests in unrelated woudle B
-- (D.V.Storable) to start failing with weird errors.
--
-- In order to avoid this one would want to run doctests with
-- per-module granularity but this cause another sort of problems!
-- When we load only single module and use import doctests then some
-- data types may come from built library and some from ghci session.
--
-- This could be remedied by running doctests for groups of modules.
-- This _is_ convoluted setup but doctests now works for GHC9.4
main :: IO ()
main = doctest [ "-Iinclude" , "-Iinternal" , "-XHaskell2010" , "src/Data" ]
main = mapM_ run modGroups
where
run mods = do
mapM_ putStrLn mods
doctest $ ["-Iinclude", "-Iinternal", "-XHaskell2010"] ++ mods
--
modGroups =
[ [ "src/Data/Vector/Storable/Mutable.hs"
, "src/Data/Vector/Storable.hs"
]
, [ "src/Data/Vector.hs"
, "src/Data/Vector/Mutable.hs"
]
, [ "src/Data/Vector/Generic.hs"
, "src/Data/Vector/Generic/Mutable.hs"
]
, [ "src/Data/Vector/Primitive.hs"
, "src/Data/Vector/Primitive/Mutable.hs"
]
, [ "src/Data/Vector/Unboxed.hs"
, "src/Data/Vector/Unboxed/Mutable.hs"
, "src/Data/Vector/Unboxed/Base.hs"
]
]

0 comments on commit 624c0ab

Please sign in to comment.