{-# LANGUAGE TemplateHaskell #-} {-# LANGUAGE MultiParamTypeClasses #-} module Warlock.ComputedFieldsSpec (spec) where import Test.Hspec import qualified Witch as W import Warlock -- Combining multiple source fields into one destination field data PersonV1 = PersonV1 { firstName :: String , lastName :: String , age :: Int } deriving (Show, Eq) data PersonV2 = PersonV2 { fullName :: String , personAge :: Int } deriving (Show, Eq) deriveAutomap ( ByName $ defaultConfig `withRules` [ combineFields 'fullName $ do firstName <- get 'firstName lastName <- get 'lastName pure [| $firstName ++ " " ++ $lastName |] , rename 'personAge 'age ] ) ''PersonV1 ''PersonV2 -- Multiple computed fields data ProductV1 = ProductV1 { itemName :: String , unitPrice :: Double , quantity :: Int } deriving (Show, Eq) data ProductV2 = ProductV2 { description :: String , totalCost :: Double } deriving (Show, Eq) deriveAutomap ( ByName $ defaultConfig { staticRules = [ combineFields 'description $ do itemName <- get 'itemName quantity <- get 'quantity pure [| $itemName ++ " (qty: " ++ show $quantity ++ ")" |] , combineFields 'totalCost $ do unitPrice <- get 'unitPrice quantity <- get 'quantity pure [| $unitPrice * fromIntegral $quantity |] ] } ) ''ProductV1 ''ProductV2 -- Splitting fields (reverse operation) data PersonV3 = PersonV3 { fullNameV3 :: String , ageV3 :: Int } deriving (Show, Eq) data PersonV4 = PersonV4 { firstNameV4 :: String , lastNameV4 :: String , ageV4 :: Int } deriving (Show, Eq) splitFullName :: String -> (String, String) splitFullName s = case words s of [] -> ("", "") [w] -> (w, "") (w:ws) -> (w, unwords ws) deriveAutomap ( ByName $ defaultConfig `withRules` [ combineFields 'firstNameV4 $ do fullNameV3 <- get 'fullNameV3 pure [| fst (splitFullName $fullNameV3) |] , combineFields 'lastNameV4 $ do fullNameV3 <- get 'fullNameV3 pure [| snd (splitFullName $fullNameV3) |] , rename 'ageV4 'ageV3 ] ) ''PersonV3 ''PersonV4 spec :: Spec spec = do describe "Computed destination fields" $ do it "combines multiple source fields into one destination field" $ do let personV1 = PersonV1 "Alice" "Smith" 30 let personV2 = W.from personV1 :: PersonV2 fullName personV2 `shouldBe` "Alice Smith" personAge personV2 `shouldBe` 30 it "computes multiple destination fields from the same sources" $ do let productV1 = ProductV1 "Widget" 9.99 5 let productV2 = W.from productV1 :: ProductV2 description productV2 `shouldBe` "Widget (qty: 5)" totalCost productV2 `shouldBe` 49.95 it "can split a field into multiple fields" $ do let personV3 = PersonV3 "Bob Jones" 25 let personV4 = W.from personV3 :: PersonV4 firstNameV4 personV4 `shouldBe` "Bob" lastNameV4 personV4 `shouldBe` "Jones" ageV4 personV4 `shouldBe` 25