{-# LANGUAGE TemplateHaskell #-} {-# LANGUAGE MultiParamTypeClasses #-} module Warlock.ComposableRulesSpec (spec) where import Data.Function ((&)) import Test.Hspec import Warlock import qualified Witch as W -- Test the new composable field rule API data Source = Source { srcBalance :: Int , srcName :: String , srcStatus :: String } deriving (Show, Eq) data Dest = Dest { balance :: Int , displayName :: String , status :: String , region :: String } deriving (Show, Eq) -- Demonstrate composable field rules deriveAutomap ( ByName $ defaultConfig `withRules` [ field 'balance & fromField 'srcBalance , field 'displayName & fromField 'srcName , field 'status & fromField 'srcStatus , field 'region & withDefault [| "US" |] ] ) ''Source ''Dest -- Test combining modifiers data ComplexSource = ComplexSource { oldBalance :: Int , oldName :: String } deriving (Show, Eq) data ComplexDest = ComplexDest { newBalance :: Int , newName :: String } deriving (Show, Eq) deriveAutomap ( ByName $ defaultConfig `withRules` [ field 'newBalance & fromField 'oldBalance & withDefault [| 0 |] , field 'newName & fromField 'oldName & withDefault [| "Unknown" |] ] ) ''ComplexSource ''ComplexDest spec :: Spec spec = do describe "Composable Field Rules" $ do describe "Basic composition" $ do it "allows chaining 'from' modifier" $ do let src = Source 100 "Alice" "active" dst = W.from src :: Dest dst `shouldBe` Dest 100 "Alice" "active" "US" it "supports withDefault modifier" $ do let src = Source 50 "Bob" "inactive" dst = W.from src :: Dest region dst `shouldBe` "US" describe "Combined modifiers" $ do it "allows chaining from and withDefault" $ do let src = ComplexSource 200 "Charlie" dst = W.from src :: ComplexDest dst `shouldBe` ComplexDest 200 "Charlie" it "uses default when combining modifiers" $ do let src = ComplexSource 0 "" dst = W.from src :: ComplexDest newBalance dst `shouldBe` 0 newName dst `shouldBe` "" describe "Mixing composable and pre-composed styles" $ do it "both styles work together" $ do let src = Source 300 "David" "pending" dst = W.from src :: Dest balance dst `shouldBe` 300 displayName dst `shouldBe` "David" status dst `shouldBe` "pending" region dst `shouldBe` "US"