{-# LANGUAGE AllowAmbiguousTypes #-} {-# LANGUAGE ConstraintKinds #-} {-# LANGUAGE RankNTypes #-} {-# LANGUAGE ScopedTypeVariables #-} {-# LANGUAGE TypeApplications #-} module ElasticSpec where import Control.Applicative (ZipList) import Control.Functor.Compactable (Compactable (compact, mapThese), separate) import Control.Functor.Elastic (Elastic) import Control.Functor.Expansive (Expansive (emapThese, expand, unite)) import Data.Functor.Product (Product) import Data.IntMap (IntMap) import Data.Map (Map) import Data.Sequence (Seq) import Data.These (These) import Data.Vector (Vector) import Core (Case') import Test.QuickCheck (Testable (property), applyFun) import Test.Syd (SpecWith, describe, it, parallel) type Case f = (Case' Compactable Functor f, Elastic f) dual :: forall f. Case f => SpecWith () dual = describe "Elastic" $ do it "compact . expand = id" . property $ \(x :: f Int) -> compact (expand x) == x it "separate . uncurry unite = id" . property $ \(xy :: (f Int, f Int)) -> separate (uncurry unite xy) == xy it "uncurry (emapThese id) . mapThese id = id" . property $ \(xs :: f (These String Int)) -> uncurry (emapThese id) (mapThese id xs) == xs spec :: SpecWith () spec = describe "Elastic" $ do describe "Maybe" $ dual @Maybe describe "IntMap" $ dual @IntMap describe "Map String" $ dual @(Map String)