{-# LANGUAGE CPP #-} {-# LANGUAGE DataKinds #-} {-# LANGUAGE FlexibleContexts #-} {-# LANGUAGE FlexibleInstances #-} {-# LANGUAGE MultiParamTypeClasses #-} {-# LANGUAGE RankNTypes #-} {-# LANGUAGE TypeApplications #-} {-# LANGUAGE TypeFamilies #-} {-# LANGUAGE TypeOperators #-} module Data.Diverse.ManySpec (main, spec) where import Data.Diverse import Data.Int import Data.Tagged import Data.Typeable import Test.Hspec -- `main` is here so that this module can be run from GHCi on its own. It is -- not needed for automatic spec dicovery. main :: IO () main = hspec spec -------------------------------- data Foo data Bar data Dee spec :: Spec spec = do describe "Many" $ do it "is a Typeable" $ do let x = (5 :: Int) ./ False ./ nil y = cast x :: Maybe (Many '[Int, String]) z = cast x :: Maybe (Many '[Int, Bool]) y `shouldBe` Nothing z `shouldBe` Just x #if __GLASGOW_HASKELL__ >= 802 let expected = "Many (': * Int (': * Bool ('[] *)))" #else let expected = "Many (': * Int (': * Bool '[]))" #endif (show . typeRep . (pure @Proxy) $ x) `shouldBe` expected it "is a Read and Show" $ do let s = "5 ./ False ./ 'X' ./ Just 'O' ./ nil" s' = "5 ./ False ./ 'X' ./ (Just 'O' ./ (nil))" x = read s :: Many '[Int, Bool, Char, Maybe Char] x' = read s' :: Many '[Int, Bool, Char, Maybe Char] show x `shouldBe` s show x' `shouldBe` s it "is a Eq" $ do let s = "5 ./ False ./ 'X' ./ Just 'O' ./ nil" x = read s :: Many '[Int, Bool, Char, Maybe Char] y = 5 ./ False ./ 'X' ./ Just 'O' ./ nil x `shouldBe` y it "is an Ord" $ do let s = "5 ./ False ./ 'X' ./ Just 'O' ./ nil" x = read s :: Many '[Int, Bool, Char, Maybe Char] y5o = (5 :: Int) ./ False ./ 'X' ./ Just 'O' ./ nil y4o = (4 :: Int) ./ False ./ 'X' ./ Just 'O' ./ nil y5p = (5 :: Int) ./ False ./ 'X' ./ Just 'P' ./ nil compare x y5o `shouldBe` EQ compare y4o y5o `shouldBe` LT compare y5o y4o `shouldBe` GT compare y5o y5p `shouldBe` LT compare y5p y5o `shouldBe` GT it "can converted to and from a tuple" $ do let x = (5 :: Int) ./ False ./ 'X' ./ Just 'O' ./ nil t = ((5 :: Int), False, 'X', Just 'O') x `shouldBe` toMany' t t `shouldBe` fromMany' x it "can construct using 'single', 'nil', 'prefix', 'postfix', 'append'" $ do let x = (5 :: Int) ./ False ./ 'X' ./ Just 'O' ./ nil x' = (5 :: Int) `prefix` False `prefix` 'X' `prefix` Just 'O' `prefix` nil y = single (5 :: Int) \. False \. 'X' \. Just 'O' y' = single (5 :: Int) `postfix` False `postfix` 'X' `postfix` Just 'O' a = single (5 :: Int) `postfix` False b = single 'X' `postfix` Just 'O' x `shouldBe` y x `shouldBe` x' y `shouldBe` y' a /./ b `shouldBe` x a `append` b `shouldBe` x it "can 'postfix'' a value only if that type doesn't already exist" $ do let x = (5 :: Int) ./ False ./ 'X' ./ Just 'O' ./ nil y = x `postfix'` True y `shouldBe` x it "can 'append'' the unique types from another Many" $ do let x = (5 :: Int) ./ False ./ 'X' ./ Just 'O' ./ nil y = (5 :: Int) ./ Just True ./ 'X' ./ Just False ./ Just (6 :: Int) ./ Just 'O' ./ nil (x `append'` y) `shouldBe` (5 :: Int) ./ False ./ 'X' ./ Just 'O' ./ Just True ./ Just (6 :: Int) ./ nil it "can contain multiple fields of the same type" $ do let x = (5 :: Int) ./ False ./ 'X' ./ Just 'O' ./ nil y = (5 :: Int) ./ False ./ 'X' ./ Just 'O' ./ (6 :: Int) ./ Just 'A' ./ nil (x /./ (6 :: Int) ./ Just 'A' ./ nil) `shouldBe` y it "can destruct using 'front', 'back', 'aft', 'fore'" $ do let a = (x ./ y) \. z x = 5 :: Int y = single False ./ 'X' ./ nil z = Just 'O' front a `shouldBe` x back a `shouldBe` z aft a `shouldBe` (y \. z) fore a `shouldBe` x ./ y it "has getter for unique fields using 'fetch'" $ do let x = (5 :: Int) ./ False ./ 'X' ./ Just 'O' ./ nil fetch @Int x `shouldBe` 5 fetch @Bool x `shouldBe` False fetch @Char x `shouldBe` 'X' fetch @(Maybe Char) x `shouldBe` Just 'O' it "has getter for for unique fields using 'fetchN'" $ do let x = (5 :: Int) ./ False ./ 'X' ./ Just 'O' ./ nil fetchN @0 Proxy x `shouldBe` 5 fetchN @1 Proxy x `shouldBe` False fetchN @2 Proxy x `shouldBe` 'X' fetchN @3 Proxy x `shouldBe` Just 'O' it "has getter for duplicate fields using 'fetchN'" $ do let y = (5 :: Int) ./ False ./ 'X' ./ Just 'O' ./ (6 :: Int) ./ Just 'A' ./ nil fetchN @0 Proxy y `shouldBe` 5 fetchN @1 Proxy y `shouldBe` False fetchN @2 Proxy y `shouldBe` 'X' fetchN @3 Proxy y `shouldBe` Just 'O' fetchN @4 Proxy y `shouldBe` 6 fetchN @5 Proxy y `shouldBe` Just 'A' it "with duplicate fields can still use 'fetch' for unique fields" $ do let x = (5 :: Int) ./ False ./ 'X' ./ Just 'O' ./ (6 :: Int) ./ Just 'A' ./ nil fetch @Bool x `shouldBe` False fetch @Char x `shouldBe` 'X' it "has getter for unique labels using 'fetchL'" $ do let y = (5 :: Int) ./ False ./ Tagged @Foo 'X' ./ Tagged @"Hello" (6 :: Int) ./ nil fetch @(Tagged Foo _) y `shouldBe` Tagged @Foo 'X' fetchL @Foo Proxy y `shouldBe` Tagged @Foo 'X' fetchL @"Hello" Proxy y `shouldBe` Tagged @"Hello" (6 :: Int) it "has setter for unique fields using 'replace'" $ do let x = (5 :: Int) ./ False ./ 'X' ./ Just 'O' ./ nil replace @Int x 6 `shouldBe` (6 :: Int) ./ False ./ 'X' ./ Just 'O' ./ nil replace x True `shouldBe` (5 :: Int) ./ True ./ 'X' ./ Just 'O' ./ nil replace x 'O' `shouldBe` (5 :: Int) ./ False ./ 'O' ./ Just 'O' ./ nil replace x (Just 'P') `shouldBe` (5 :: Int) ./ False ./ 'X' ./ Just 'P' ./ nil it "has polymorphic setter for unique fields using 'replace'" $ do let x = (5 :: Int) ./ False ./ 'X' ./ Just 'O' ./ nil replace' @Int Proxy x 'Z' `shouldBe` 'Z' ./ False ./ 'X' ./ Just 'O' ./ nil replace' @Bool Proxy x 'Z' `shouldBe` (5 :: Int) ./ 'Z' ./ 'X' ./ Just 'O' ./ nil replace' @(Maybe Char) Proxy x 'Z' `shouldBe` (5 :: Int) ./ False ./ 'X' ./ 'Z' ./ nil it "has setter for unique labels using 'replaceL'" $ do let y = (5 :: Int) ./ False ./ Tagged @Foo 'X' ./ Tagged @"Hello" (6 :: Int) ./ nil replace @(Tagged Foo _) y (Tagged @Foo 'Y') `shouldBe` (5 :: Int) ./ False ./ Tagged @Foo 'Y' ./ Tagged @"Hello" (6 :: Int) ./ nil replaceL @Foo Proxy y (Tagged @Foo 'Y') `shouldBe` (5 :: Int) ./ False ./ Tagged @Foo 'Y' ./ Tagged @"Hello" (6 :: Int) ./ nil replaceL @"Hello" Proxy y (Tagged @"Hello" 7) `shouldBe` (5 :: Int) ./ False ./ Tagged @Foo 'X' ./ Tagged @"Hello" (7 :: Int) ./ nil it "has polymorphic setter for unique labels using 'replaceL'" $ do let y = (5 :: Int) ./ False ./ Tagged @Foo 'X' ./ Tagged @"Hello" (6 :: Int) ./ nil replace' @(Tagged Foo Char) Proxy y (Tagged @Bar 'Y') `shouldBe` (5 :: Int) ./ False ./ Tagged @Bar 'Y' ./ Tagged @"Hello" (6 :: Int) ./ nil replaceL' @Foo Proxy y (Tagged @Bar 'Y') `shouldBe` (5 :: Int) ./ False ./ Tagged @Bar 'Y' ./ Tagged @"Hello" (6 :: Int) ./ nil replaceL' @"Hello" Proxy y (Tagged @"Hello" False) `shouldBe` (5 :: Int) ./ False ./ Tagged @Foo 'X' ./ Tagged @"Hello" False ./ nil it "has setter for unique fields using 'replaceN'" $ do let x = (5 :: Int) ./ False ./ 'X' ./ Just 'O' ./ nil replaceN @0 Proxy x (7 :: Int) `shouldBe` (7 :: Int) ./ False ./ 'X' ./ Just 'O' ./ nil replaceN @1 Proxy x True `shouldBe` (5 :: Int) ./ True ./ 'X' ./ Just 'O' ./ nil replaceN @2 Proxy x 'Y' `shouldBe` (5 :: Int) ./ False ./ 'Y' ./ Just 'O' ./ nil replaceN @3 Proxy x (Just 'P') `shouldBe` (5 :: Int) ./ False ./ 'X' ./ Just 'P' ./ nil it "has polymorphic setter using 'replaceN''" $ do let x = (5 :: Int) ./ False ./ 'X' ./ Just 'O' ./ nil replaceN' @0 Proxy x True `shouldBe` True ./ False ./ 'X' ./ Just 'O' ./ nil let y = (5 :: Int) ./ False ./ 'X' ./ Just 'O' ./ (6 :: Int) ./ Just 'A' ./ nil replaceN' @1 Proxy y 'Y' `shouldBe` (5 :: Int) ./ 'Y' ./ 'X' ./ Just 'O' ./ (6 :: Int) ./ Just 'A' ./ nil replaceN' @5 Proxy y 'Y' `shouldBe` (5 :: Int) ./ False ./ 'X' ./ Just 'O' ./ (6 :: Int) ./ 'Y' ./ nil it "has setter for duplicate fields using 'replaceN'" $ do let y = (5 :: Int) ./ False ./ 'X' ./ Just 'O' ./ (6 :: Int) ./ Just 'A' ./ nil replaceN @0 Proxy y (7 :: Int) `shouldBe` (7 :: Int) ./ False ./ 'X' ./ Just 'O' ./ (6 :: Int) ./ Just 'A' ./ nil replaceN @1 Proxy y True `shouldBe` (5 :: Int) ./ True ./ 'X' ./ Just 'O' ./ (6 :: Int) ./ Just 'A' ./ nil replaceN @2 Proxy y 'Y' `shouldBe` (5 :: Int) ./ False ./ 'Y' ./ Just 'O' ./ (6 :: Int) ./ Just 'A' ./ nil replaceN @3 Proxy y (Just 'P') `shouldBe` (5 :: Int) ./ False ./ 'X' ./ Just 'P' ./ (6 :: Int) ./ Just 'A' ./ nil replaceN @4 Proxy y (8 :: Int) `shouldBe` (5 :: Int) ./ False ./ 'X' ./ Just 'O' ./ (8 :: Int) ./ Just 'A' ./ nil replaceN @5 Proxy y (Just 'B') `shouldBe` (5 :: Int) ./ False ./ 'X' ./ Just 'O' ./ (6 :: Int) ./ Just 'B' ./ nil it "has setter for unique fields using 'replace' (even if there are other duplicate fields)" $ do let y = (5 :: Int) ./ False ./ 'X' ./ Just 'O' ./ (6 :: Int) ./ Just 'A' ./ nil replace @Bool y True `shouldBe` (5 :: Int) ./ True ./ 'X' ./ Just 'O' ./ (6 :: Int) ./ Just 'A' ./ nil replace @Char y 'Y' `shouldBe` (5 :: Int) ./ False ./ 'Y' ./ Just 'O' ./ (6 :: Int) ./ Just 'A' ./ nil it "has getter for multiple fields using 'select'" $ do let x = (5 :: Int) ./ False ./ 'X' ./ Just 'O' ./ nil select @'[Int, Maybe Char] x `shouldBe` (5 :: Int) ./ Just 'O' ./ nil it "has getter for multiple labelled fields using 'selectL'" $ do let x = False ./ Tagged @"Hi" (5 :: Int) ./ Tagged @Foo False ./ Tagged @Bar 'X' ./ Tagged @"Bye" 'O' ./ nil selectL @'[Foo, Bar] Proxy x `shouldBe` Tagged @Foo False ./ Tagged @Bar 'X' ./ nil selectL @'["Hi", "Bye"] Proxy x `shouldBe` Tagged @"Hi" (5 :: Int) ./ Tagged @"Bye" 'O' ./ nil -- below won't compile because the type of labels must match -- selectL @'["Hi", 'Foo, "Bye"] Proxy x `shouldBe` Tagged @"Hi" (5 :: Int) ./ Tagged @Foo False ./ Tagged @"Bye" 'O' ./ nil it "can reorder fields using 'select' or 'selectN'" $ do let x = (5 :: Int) ./ False ./ 'X' ./ Just 'O' ./ nil select @'[Bool, Int, Maybe Char] x `shouldBe` False ./ (5 :: Int) ./ Just 'O' ./ nil let y = (5 :: Int) ./ False ./ 'X' ./ Just 'O' ./ (6 :: Int) ./ Just 'A' ./ nil selectN (Proxy @'[5, 4, 0, 1, 3, 2]) y `shouldBe` Just 'A' ./ (6 :: Int) ./ (5 ::Int) ./ False ./ Just 'O' ./ 'X' ./ nil it "has getter for multiple fields with duplicates using 'selectN'" $ do let x = (5 :: Int) ./ False ./ 'X' ./ Just 'O' ./ (6 :: Int) ./ Just 'A' ./ nil selectN (Proxy @'[5, 4, 0]) x `shouldBe` Just 'A' ./ (6 :: Int) ./ (5 ::Int) ./ nil it "can't select into types from indistinct fields" $ do let x = (5 :: Int) ./ False ./ 'X' ./ Just 'O' ./ (6 :: Int) ./ Just 'A' ./ nil -- Compile error: Int is a duplicate -- select @[Bool, Char, Int] x `shouldBe` False ./ 'X' ./ (5 :: Int) ./ nil x `shouldBe` x it "with duplicate fields has getter for multiple unique fields 'select'" $ do let x = (5 :: Int) ./ False ./ 'X' ./ Just 'O' ./ (6 :: Int) ./ Just 'A' ./ nil select @'[Bool, Char] x `shouldBe` False ./ 'X' ./ nil it "has setter for multiple fields using 'amend'" $ do let x = (5 :: Int) ./ False ./ 'X' ./ Just 'O' ./ nil amend @'[Int, Maybe Char] x ((6 :: Int) ./ Just 'P' ./ nil) `shouldBe` (6 :: Int) ./ False ./ 'X' ./ Just 'P' ./ nil it "has polymorphc setter for multiple fields using 'amend'" $ do let x = (5 :: Int) ./ False ./ 'X' ./ Just 'O' ./ nil amend' @'[Int, Maybe Char] Proxy x ("Foo" ./ "Bar" ./ nil) `shouldBe` "Foo" ./ False ./ 'X' ./ "Bar" ./ nil it "has setter for multiple labelled fields using 'amendL'" $ do let x = False ./ Tagged @"Hi" (5 :: Int) ./ Tagged @Foo False ./ Tagged @Bar 'X' ./ Tagged @"Bye" 'O' ./ nil amendL @'[Foo, Bar] Proxy x (Tagged @Foo True ./ Tagged @Bar 'Y' ./ nil) `shouldBe` False ./ Tagged @"Hi" (5 :: Int) ./ Tagged @Foo True ./ Tagged @Bar 'Y' ./ Tagged @"Bye" 'O' ./ nil amendL @'["Hi", "Bye"] Proxy x (Tagged @"Hi" (6 :: Int) ./ Tagged @"Bye" 'P' ./ nil) `shouldBe` False ./ Tagged @"Hi" (6 :: Int) ./ Tagged @Foo False ./ Tagged @Bar 'X' ./ Tagged @"Bye" 'P' ./ nil it "has polymorphic setter for multiple labelled fields using 'amendL'" $ do let x = False ./ Tagged @"Hi" (5 :: Int) ./ Tagged @Foo False ./ Tagged @Bar 'X' ./ Tagged @"Bye" 'O' ./ nil amendL' @'[Foo, Bar] Proxy x ('Y' ./ True ./ nil) `shouldBe` False ./ Tagged @"Hi" (5 :: Int) ./ 'Y' ./ True ./ Tagged @"Bye" 'O' ./ nil amendL' @'["Hi", "Bye"] Proxy x (True ./ Tagged @"Changed" True ./ nil) `shouldBe` False ./ True ./ Tagged @Foo False ./ Tagged @Bar 'X' ./ Tagged @"Changed" True ./ nil it "has setter for multiple fields with duplicates using 'amendN'" $ do let x = (5 :: Int) ./ False ./ 'X' ./ Just 'O' ./ (6 :: Int) ./ Just 'A' ./ nil amendN (Proxy @'[5, 4, 0]) x (Just 'B' ./ (8 :: Int) ./ (4 ::Int) ./ nil) `shouldBe` (4 :: Int) ./ False ./ 'X' ./ Just 'O' ./ (8 :: Int) ./ Just 'B' ./ nil it "has polymorphic setter for multiple fields with duplicates using 'amendN''" $ do let x = (5 :: Int) ./ False ./ 'X' ./ Just 'O' ./ (6 :: Int) ./ Just 'A' ./ nil amendN' @'[5, 4, 0] Proxy x ("Foo" ./ Just 'B' ./ 'Z' ./ nil) `shouldBe` 'Z' ./ False ./ 'X' ./ Just 'O' ./ Just 'B' ./ "Foo" ./ nil it "can't amend into types from indistinct fields" $ do let x = (5 :: Int) ./ False ./ 'X' ./ Just 'O' ./ (6 :: Int) ./ Just 'A' ./ nil -- Compile error: Int is a duplicate -- amend @ '[Bool, Char, Int] x (True ./ 'B' ./ (8 :: Int) ./ nil) `shouldBe` -- (5 :: Int) ./ True ./ 'B' ./ Just 'O' ./ (8 :: Int) ./ Just 'A' ./ nil x `shouldBe` x it "with duplicate fields has setter for unique fields 'amend'" $ do let x = (5 :: Int) ./ False ./ 'X' ./ Just 'O' ./ (6 :: Int) ./ Just 'A' ./ nil amend @ '[Bool, Char] x (True ./ 'B' ./ nil) `shouldBe` (5 :: Int) ./ True ./ 'B' ./ Just 'O' ./ (6 :: Int) ./ Just 'A' ./ nil it "can be folded with 'Many' handlers using 'forMany' or 'collect'" $ do let x = (5 :: Int) ./ False ./ 'X' ./ Just 'O' ./ (6 :: Int) ./ Just 'A' ./ nil y = show @Int ./ show @Char ./ show @(Maybe Char) ./ show @Bool ./ nil ret = ["5", "False", "'X'", "Just 'O'", "6", "Just 'A'"] afoldr (:) [] (collect x (cases y)) `shouldBe` ret afoldr (:) [] (forMany (cases y) x) `shouldBe` ret afoldr (:) [] (forMany (cases y) x) `shouldBe` ret it "can be folded with polymorphic 'CaseFunc' handlers using 'forMany' or 'collect'" $ do let x = (5 :: Int) ./ False ./ 'X' ./ Just 'O' ./ (6 :: Int) ./ Just 'A' ./ nil afoldr (:) [] (forMany (CaseFunc @Typeable (show . typeRep . (pure @Proxy))) x) `shouldBe` ["Int", "Bool", "Char", "Maybe Char", "Int", "Maybe Char"] it "can be folded with 'Many' handlers in index order using 'forManyN' or 'collectN'" $ do let x = (5 :: Int) ./ False ./ 'X' ./ Just 'O' ./ (6 :: Int) ./ Just 'A' ./ nil y = show @Int ./ show @Bool ./ show @Char ./ show @(Maybe Char) ./ show @Int ./ show @(Maybe Char) ./ nil ret = ["5", "False", "'X'", "Just 'O'", "6", "Just 'A'"] afoldr (:) [] (collectN x (casesN y)) `shouldBe` ret afoldr (:) [] (forManyN (casesN y) x) `shouldBe` ret it "every item can be mapped into a different type in a Functor-like fashion with using 'afmap'" $ do let x = (5 :: Int) ./ (6 :: Int8) ./ (7 :: Int16) ./ (8 :: Int32) ./ nil y = (15 :: Int) ./ (16 :: Int8) ./ (17 :: Int16) ./ (18 :: Int32) ./ nil z = ("5" :: String) ./ ("6" :: String) ./ ("7" :: String) ./ ("8" :: String) ./ nil afmap (CaseFunc' @Num (+10)) x `shouldBe` y afmap (CaseFunc @Show @String show) x `shouldBe` z it "can be split into two 'Many's" $ do let x = (5 :: Int) ./ False ./ 'X' ./ Just True ./ Just 'A' ./ nil y = (Tagged 5 :: Tagged Foo Int) ./ False ./ Tagged @Dee 'X' ./ Just True ./ Tagged @Bar (Just 'A') ./ nil x1a = (5 :: Int) ./ False ./ nil x1b = 'X' ./ Just True ./ Just 'A' ./ nil x2a = (5 :: Int) ./ False ./ 'X' ./ nil x2b = Just True ./ Just 'A' ./ nil y1a = (Tagged 5 :: Tagged Foo Int) ./ False ./ nil y1b = Tagged @Dee 'X' ./ Just True ./ Tagged @Bar (Just 'A') ./ nil y2a = (Tagged 5 :: Tagged Foo Int) ./ False ./ Tagged @Dee 'X' ./ nil y2b = Just True ./ Tagged @Bar (Just 'A') ./ nil splitBefore (Proxy @Int) x `shouldBe` (nil, x) splitBeforeL (Proxy @Foo) y `shouldBe` (nil, y) splitBeforeN (Proxy @0) x `shouldBe` (nil, x) splitAfter (Proxy @Int) x `shouldBe` let (a, b) = viewf x in (single a, b) splitAfterL (Proxy @Foo) y `shouldBe` let (a, b) = viewf y in (single a, b) splitAfterN (Proxy @0) x `shouldBe` let (a, b) = viewf x in (single a, b) splitBefore (Proxy @(Maybe Char)) x `shouldBe` let (a, b) = viewb x in (a, single b) splitBeforeL (Proxy @Bar) y `shouldBe` let (a, b) = viewb y in (a, single b) splitBeforeN (Proxy @4) x `shouldBe` let (a, b) = viewb x in (a, single b) splitAfter (Proxy @(Maybe Char)) x `shouldBe` (x, nil) splitAfterL (Proxy @Bar) y `shouldBe` (y, nil) splitAfterN (Proxy @4) x `shouldBe` (x, nil) splitBefore (Proxy @(Char)) x `shouldBe` (x1a, x1b) splitBeforeL (Proxy @Dee) y `shouldBe` (y1a, y1b) splitBeforeN (Proxy @2) x `shouldBe` (x1a, x1b) splitAfter(Proxy @(Char)) x `shouldBe` (x2a, x2b) splitAfterL (Proxy @Dee) y `shouldBe` (y2a, y2b) splitAfterN (Proxy @2) x `shouldBe` (x2a, x2b) it "can be 'inset'ted into another 'Many'" $ do let x = (5 :: Int) ./ False ./ 'X' ./ Just True ./ Just 'A' ./ nil y = (Tagged 5 :: Tagged Foo Int) ./ False ./ Tagged @Dee 'X' ./ Just True ./ Tagged @Bar (Just 'A') ./ nil x1a = (5 :: Int) ./ False ./ nil x1b = 'X' ./ Just True ./ Just 'A' ./ nil x2a = (5 :: Int) ./ False ./ 'X' ./ nil x2b = Just True ./ Just 'A' ./ nil y1a = (Tagged 5 :: Tagged Foo Int) ./ False ./ nil y1b = Tagged @Dee 'X' ./ Just True ./ Tagged @Bar (Just 'A') ./ nil y2a = (Tagged 5 :: Tagged Foo Int) ./ False ./ Tagged @Dee 'X' ./ nil y2b = Just True ./ Tagged @Bar (Just 'A') ./ nil z = True ./ 'Y' ./ nil insetBefore (Proxy @Int) z x `shouldBe` z /./ x insetBeforeL (Proxy @Foo) z y `shouldBe` z /./ y insetBeforeN (Proxy @0) z x `shouldBe` z /./ x insetAfter (Proxy @Int) z x `shouldBe` let (a, b) = viewf x in a ./ z /./ b insetAfterL (Proxy @Foo) z y `shouldBe` let (a, b) = viewf y in a ./ z /./ b insetAfterN (Proxy @0) z x `shouldBe` let (a, b) = viewf x in a ./ z /./ b insetBefore (Proxy @(Maybe Char)) z x `shouldBe` let (a, b) = viewb x in a /./ (z \. b) insetBeforeL (Proxy @Bar) z y `shouldBe` let (a, b) = viewb y in a /./ (z \. b) insetBeforeN (Proxy @4) z x `shouldBe` let (a, b) = viewb x in a /./ (z \. b) insetAfter (Proxy @(Maybe Char)) z x `shouldBe` x /./ z insetAfterL (Proxy @Bar) z y `shouldBe` y /./ z insetAfterN (Proxy @4) z x `shouldBe` x /./ z insetBefore (Proxy @(Char)) z x `shouldBe` x1a /./ z /./ x1b insetBeforeL (Proxy @Dee) z y `shouldBe` y1a /./ z /./ y1b insetBeforeN (Proxy @2) z x `shouldBe` x1a /./ z /./ x1b insetAfter(Proxy @(Char)) z x `shouldBe` x2a /./ z /./ x2b insetAfterL (Proxy @Dee) z y `shouldBe` y2a /./ z /./ y2b insetAfterN (Proxy @2) z x `shouldBe` x2a /./ z /./ x2b #if __GLASGOW_HASKELL__ >= 802 it "can be 'insert'ted with an item at a specific place" $ do let x = (5 :: Int) ./ False ./ 'X' ./ Just True ./ Just 'A' ./ nil y = (Tagged 5 :: Tagged Foo Int) ./ False ./ Tagged @Dee 'X' ./ Just True ./ Tagged @Bar (Just 'A') ./ nil x1a = (5 :: Int) ./ False ./ nil x1b = 'X' ./ Just True ./ Just 'A' ./ nil x2a = (5 :: Int) ./ False ./ 'X' ./ nil x2b = Just True ./ Just 'A' ./ nil y1a = (Tagged 5 :: Tagged Foo Int) ./ False ./ nil y1b = Tagged @Dee 'X' ./ Just True ./ Tagged @Bar (Just 'A') ./ nil y2a = (Tagged 5 :: Tagged Foo Int) ./ False ./ Tagged @Dee 'X' ./ nil y2b = Just True ./ Tagged @Bar (Just 'A') ./ nil z = True insertBefore (Proxy @Int) z x `shouldBe` z ./ x insertBeforeL (Proxy @Foo) z y `shouldBe` z ./ y insertBeforeN (Proxy @0) z x `shouldBe` z ./ x insertAfter (Proxy @Int) z x `shouldBe` let (a, b) = viewf x in a ./ single z /./ b insertAfterL (Proxy @Foo) z y `shouldBe` let (a, b) = viewf y in a ./ single z /./ b insertAfterN (Proxy @0) z x `shouldBe` let (a, b) = viewf x in a ./ single z /./ b insertBefore (Proxy @(Maybe Char)) z x `shouldBe` let (a, b) = viewb x in a /./ (single z \. b) insertBeforeL (Proxy @Bar) z y `shouldBe` let (a, b) = viewb y in a /./ (single z \. b) insertBeforeN (Proxy @4) z x `shouldBe` let (a, b) = viewb x in a /./ (single z \. b) insertAfter (Proxy @(Maybe Char)) z x `shouldBe` x /./ single z insertAfterL (Proxy @Bar) z y `shouldBe` y /./ single z insertAfterN (Proxy @4) z x `shouldBe` x /./ single z insertBefore (Proxy @(Char)) z x `shouldBe` x1a /./ single z /./ x1b insertBeforeL (Proxy @Dee) z y `shouldBe` y1a /./ single z /./ y1b insertBeforeN (Proxy @2) z x `shouldBe` x1a /./ single z /./ x1b insertAfter(Proxy @(Char)) z x `shouldBe` x2a /./ single z /./ x2b insertAfterL (Proxy @Dee) z y `shouldBe` y2a /./ single z /./ y2b insertAfterN (Proxy @2) z x `shouldBe` x2a /./ single z /./ x2b it "can 'remove' an item at a specific place" $ do let x = (5 :: Int) ./ False ./ 'X' ./ Just True ./ Just 'A' ./ nil y = (Tagged 5 :: Tagged Foo Int) ./ False ./ Tagged @Dee 'X' ./ Just True ./ Tagged @Bar (Just 'A') ./ nil x' = (5 :: Int) ./ False ./ Just True ./ Just 'A' ./ nil y' = (Tagged 5 :: Tagged Foo Int) ./ False ./ Just True ./ Tagged @Bar (Just 'A') ./ nil remove (Proxy @Int) x `shouldBe` snd (viewf x) removeL (Proxy @Foo) y `shouldBe` snd (viewf y) removeN (Proxy @0) x `shouldBe` snd (viewf x) remove (Proxy @(Maybe Char)) x `shouldBe` fst (viewb x) removeL (Proxy @Bar) y `shouldBe` fst (viewb y) removeN (Proxy @4) x `shouldBe` fst (viewb x) remove (Proxy @(Char)) x `shouldBe` x' removeL (Proxy @Dee) y `shouldBe` y' removeN (Proxy @2) x `shouldBe` x' #endif