{-# LANGUAGE TemplateHaskell #-} {-# LANGUAGE MultiParamTypeClasses #-} {-# LANGUAGE FlexibleInstances #-} module Warlock.ParameterizedTypesSpec (spec) where import Test.Hspec import Warlock import qualified Witch as W import Language.Haskell.TH (varE) -- Test with polymorphic source type (Container Int <-> IntContainer) data Container a = Container { containerValue :: a , containerLabel :: String } deriving (Show, Eq) data IntContainer = IntContainer { intContainerValue :: Int , intContainerLabel :: String } deriving (Show, Eq) -- Use deriveAutomapWith (ByName for polymorphic types deriveAutomapWith (ByName datatypePrefixConfig) [t| IntContainer |] [t| Container Int |] deriveAutomapWith (ByName datatypePrefixConfig) [t| Container Int |] [t| IntContainer |] -- Test with multiple type parameters data Pair a b = Pair { pairFirst :: a , pairSecond :: b } deriving (Show, Eq) data StringIntPair = StringIntPair { stringIntPairFirst :: String , stringIntPairSecond :: Int } deriving (Show, Eq) deriveAutomapWith (ByName datatypePrefixConfig) [t| StringIntPair |] [t| Pair String Int |] deriveAutomapWith (ByName datatypePrefixConfig) [t| Pair String Int |] [t| StringIntPair |] spec :: Spec spec = do describe "Parameterized types" $ do describe "Polymorphic types (Container Int <-> IntContainer)" $ do it "maps to polymorphic Container type" $ do let intCont = IntContainer 42 "number" mapped = W.from intCont :: Container Int mapped `shouldBe` Container 42 "number" it "maps from polymorphic Container type" $ do let container = Container 99 "test" :: Container Int mapped = W.from container :: IntContainer mapped `shouldBe` IntContainer 99 "test" describe "Multiple type parameters (Pair String Int <-> StringIntPair)" $ do it "maps to polymorphic Pair type" $ do let pair = StringIntPair "hello" 123 mapped = W.from pair :: Pair String Int mapped `shouldBe` Pair "hello" 123 it "maps from polymorphic Pair type" $ do let pair = Pair "world" 456 :: Pair String Int mapped = W.from pair :: StringIntPair mapped `shouldBe` StringIntPair "world" 456 it "works bidirectionally" $ do let original = StringIntPair "test" 789 roundtrip = W.from (W.from original :: Pair String Int) :: StringIntPair roundtrip `shouldBe` original