Add instances for containers

This commit is contained in:
Taylor Fausak 2021-04-18 14:50:39 +00:00 committed by GitHub
parent 9ccfc80ede
commit 65b8a0db0a
3 changed files with 148 additions and 22 deletions

View File

@ -10,23 +10,21 @@ module Witch.Instances where
import qualified Data.Bits as Bits
import qualified Data.Complex as Complex
import qualified Data.Fixed as Fixed
import qualified Data.Foldable as Foldable
import qualified Data.Int as Int
import qualified Data.IntMap as IntMap
import qualified Data.IntSet as IntSet
import qualified Data.List.NonEmpty as NonEmpty
import qualified Data.Map as Map
import qualified Data.Ratio as Ratio
import qualified Data.Sequence as Seq
import qualified Data.Set as Set
import qualified Data.Word as Word
import qualified Numeric.Natural as Natural
import qualified Witch.Cast as Cast
import qualified Witch.TryCast as TryCast
import qualified Witch.TryCastException as TryCastException
-- NonEmpty
instance TryCast.TryCast [a] (NonEmpty.NonEmpty a) where
tryCast = maybeTryCast NonEmpty.nonEmpty
instance Cast.Cast (NonEmpty.NonEmpty a) [a] where
cast = NonEmpty.toList
-- Int8
instance Cast.Cast Int.Int8 Int.Int16 where
@ -678,6 +676,54 @@ instance (Eq a, Num a) => TryCast.TryCast (Complex.Complex a) a where
tryCast = maybeTryCast $ \s ->
if Complex.imagPart s == 0 then Just $ Complex.realPart s else Nothing
-- NonEmpty
instance TryCast.TryCast [a] (NonEmpty.NonEmpty a) where
tryCast = maybeTryCast NonEmpty.nonEmpty
instance Cast.Cast (NonEmpty.NonEmpty a) [a] where
cast = NonEmpty.toList
-- Set
instance Ord a => Cast.Cast [a] (Set.Set a) where
cast = Set.fromList
instance Cast.Cast (Set.Set a) [a] where
cast = Set.toAscList
-- IntSet
instance Cast.Cast [Int] IntSet.IntSet where
cast = IntSet.fromList
instance Cast.Cast IntSet.IntSet [Int] where
cast = IntSet.toAscList
-- Map
instance Ord k => Cast.Cast [(k, v)] (Map.Map k v) where
cast = Map.fromList
instance Cast.Cast (Map.Map k v) [(k, v)] where
cast = Map.toAscList
-- IntMap
instance Cast.Cast [(Int, v)] (IntMap.IntMap v) where
cast = IntMap.fromList
instance Cast.Cast (IntMap.IntMap v) [(Int, v)] where
cast = IntMap.toAscList
-- Seq
instance Cast.Cast [a] (Seq.Seq a) where
cast = Seq.fromList
instance Cast.Cast (Seq.Seq a) [a] where
cast = Foldable.toList
fromNonNegativeIntegral :: (Integral s, Num t) => s -> Maybe t
fromNonNegativeIntegral x = if x < 0 then Nothing else Just $ fromIntegral x

View File

@ -9,8 +9,13 @@ import qualified Data.Complex as Complex
import qualified Data.Either as Either
import qualified Data.Fixed as Fixed
import qualified Data.Int as Int
import qualified Data.IntMap as IntMap
import qualified Data.IntSet as IntSet
import qualified Data.List.NonEmpty as NonEmpty
import qualified Data.Map as Map
import qualified Data.Ratio as Ratio
import qualified Data.Sequence as Seq
import qualified Data.Set as Set
import qualified Data.Word as Word
import qualified Numeric.Natural as Natural
import qualified Test.Hspec as Hspec
@ -1355,19 +1360,6 @@ main = Hspec.hspec . Hspec.describe "Witch" $ do
test $ f 0.5 `Hspec.shouldBe` 0.5
test $ f (-0.5) `Hspec.shouldBe` (-0.5)
-- NonEmpty
Hspec.describe "TryCast [a] (NonEmpty a)" $ do
let f = Witch.tryCast @[Int] @(NonEmpty.NonEmpty Int)
test $ f [] `Hspec.shouldSatisfy` Either.isLeft
test $ f [1] `Hspec.shouldBe` Right (1 NonEmpty.:| [])
test $ f [1, 2] `Hspec.shouldBe` Right (1 NonEmpty.:| [2])
Hspec.describe "Cast (NonEmpty a) [a]" $ do
let f = Witch.cast @(NonEmpty.NonEmpty Int) @[Int]
test $ f (1 NonEmpty.:| []) `Hspec.shouldBe` [1]
test $ f (1 NonEmpty.:| [2]) `Hspec.shouldBe` [1, 2]
-- Ratio
Hspec.describe "Cast a (Ratio a)" $ do
@ -1420,6 +1412,92 @@ main = Hspec.hspec . Hspec.describe "Witch" $ do
test $ f 1 `Hspec.shouldBe` Right 1
test $ f (0 Complex.:+ 1) `Hspec.shouldSatisfy` Either.isLeft
-- NonEmpty
Hspec.describe "TryCast [a] (NonEmpty a)" $ do
let f = Witch.tryCast @[Int] @(NonEmpty.NonEmpty Int)
test $ f [] `Hspec.shouldSatisfy` Either.isLeft
test $ f [1] `Hspec.shouldBe` Right (1 NonEmpty.:| [])
test $ f [1, 2] `Hspec.shouldBe` Right (1 NonEmpty.:| [2])
Hspec.describe "Cast (NonEmpty a) [a]" $ do
let f = Witch.cast @(NonEmpty.NonEmpty Int) @[Int]
test $ f (1 NonEmpty.:| []) `Hspec.shouldBe` [1]
test $ f (1 NonEmpty.:| [2]) `Hspec.shouldBe` [1, 2]
-- Set
Hspec.describe "Cast [a] (Set a)" $ do
let f = Witch.cast @[Char] @(Set.Set Char)
test $ f [] `Hspec.shouldBe` Set.fromList []
test $ f ['a'] `Hspec.shouldBe` Set.fromList ['a']
test $ f ['a', 'b'] `Hspec.shouldBe` Set.fromList ['a', 'b']
test $ f ['a', 'a'] `Hspec.shouldBe` Set.fromList ['a']
Hspec.describe "Cast (Set a) [a]" $ do
let f = Witch.cast @(Set.Set Char) @[Char]
test $ f (Set.fromList []) `Hspec.shouldBe` []
test $ f (Set.fromList ['a']) `Hspec.shouldBe` ['a']
test $ f (Set.fromList ['a', 'b']) `Hspec.shouldBe` ['a', 'b']
-- IntSet
Hspec.describe "Cast [Int] IntSet" $ do
let f = Witch.cast @[Int] @IntSet.IntSet
test $ f [] `Hspec.shouldBe` IntSet.fromList []
test $ f [1] `Hspec.shouldBe` IntSet.fromList [1]
test $ f [1, 2] `Hspec.shouldBe` IntSet.fromList [1, 2]
Hspec.describe "Cast IntSet [Int]" $ do
let f = Witch.cast @IntSet.IntSet @[Int]
test $ f (IntSet.fromList []) `Hspec.shouldBe` []
test $ f (IntSet.fromList [1]) `Hspec.shouldBe` [1]
test $ f (IntSet.fromList [1, 2]) `Hspec.shouldBe` [1, 2]
-- Map
Hspec.describe "Cast [(k, v)] (Map k v)" $ do
let f = Witch.cast @[(Char, Int)] @(Map.Map Char Int)
test $ f [] `Hspec.shouldBe` Map.fromList []
test $ f [('a', 1)] `Hspec.shouldBe` Map.fromList [('a', 1)]
test $ f [('a', 1), ('b', 2)] `Hspec.shouldBe` Map.fromList [('a', 1), ('b', 2)]
test $ f [('a', 1), ('a', 2)] `Hspec.shouldBe` Map.fromList [('a', 2)]
Hspec.describe "Cast (Map k v) [(k, v)]" $ do
let f = Witch.cast @(Map.Map Char Int) @[(Char, Int)]
test $ f (Map.fromList []) `Hspec.shouldBe` []
test $ f (Map.fromList [('a', 1)]) `Hspec.shouldBe` [('a', 1)]
test $ f (Map.fromList [('a', 1), ('b', 2)]) `Hspec.shouldBe` [('a', 1), ('b', 2)]
-- IntMap
Hspec.describe "Cast [(Int, v)] (IntMap v)" $ do
let f = Witch.cast @[(Int, Char)] @(IntMap.IntMap Char)
test $ f [] `Hspec.shouldBe` IntMap.fromList []
test $ f [(1, 'a')] `Hspec.shouldBe` IntMap.fromList [(1, 'a')]
test $ f [(1, 'a'), (2, 'b')] `Hspec.shouldBe` IntMap.fromList [(1, 'a'), (2, 'b')]
test $ f [(1, 'a'), (1, 'b')] `Hspec.shouldBe` IntMap.fromList [(1, 'b')]
Hspec.describe "Cast (IntMap v) [(Int, v)]" $ do
let f = Witch.cast @(IntMap.IntMap Char) @[(Int, Char)]
test $ f (IntMap.fromList []) `Hspec.shouldBe` []
test $ f (IntMap.fromList [(1, 'a')]) `Hspec.shouldBe` [(1, 'a')]
test $ f (IntMap.fromList [(1, 'a'), (2, 'b')]) `Hspec.shouldBe` [(1, 'a'), (2, 'b')]
-- Seq
Hspec.describe "Cast [a] (Seq a)" $ do
let f = Witch.cast @[Int] @(Seq.Seq Int)
test $ f [] `Hspec.shouldBe` Seq.fromList []
test $ f [1] `Hspec.shouldBe` Seq.fromList [1]
test $ f [1, 2] `Hspec.shouldBe` Seq.fromList [1, 2]
Hspec.describe "Cast (Seq a) [a]" $ do
let f = Witch.cast @(Seq.Seq Int) @[Int]
test $ f (Seq.fromList []) `Hspec.shouldBe` []
test $ f (Seq.fromList [1]) `Hspec.shouldBe` [1]
test $ f (Seq.fromList [1, 2]) `Hspec.shouldBe` [1, 2]
test :: Hspec.Example a => a -> Hspec.SpecWith (Hspec.Arg a)
test = Hspec.it ""

View File

@ -17,7 +17,9 @@ source-repository head
type: git
common basics
build-depends: base >= 4.13.0 && < 4.16
build-depends:
, base >= 4.13.0 && < 4.16
, containers >= 0.6.2 && < 0.7
default-language: Haskell2010
ghc-options:
-Weverything