{-# LANGUAGE TemplateHaskell #-} {-# LANGUAGE MultiParamTypeClasses #-} module Warlock.AutoSpec (spec) where import Test.Hspec import qualified Witch as W import Warlock -- Test types for basic field mapping data Foobert = Foobert { foobertName :: String , foobertAge :: Int } deriving (Show, Eq) data Barfoo = Barfoo { barfooName :: String , barfooAge :: Int } deriving (Show, Eq) deriveAutomap (ByName datatypePrefixConfig) ''Foobert ''Barfoo deriveAutomap (ByName datatypePrefixConfig) ''Barfoo ''Foobert -- Test types for constructor prefix rules data Person = Person { personFirstName :: String , personLastName :: String , personAge :: Int } deriving (Show, Eq) data Employee = Employee { empFirstName :: String , empLastName :: String , empAge :: Int } deriving (Show, Eq) deriveAutomap ( ByName $ defaultConfig { ruleGens = [customPrefixRules "emp" "person"] } ) ''Person ''Employee -- Test types for positional constructors data Point2D = Point2D Int Int deriving (Show, Eq) data Vector2D = Vector2D Int Int deriving (Show, Eq) deriveAutomap (ByName defaultConfig) ''Point2D ''Vector2D spec :: Spec spec = do describe "Basic AutoMap functionality" $ do it "maps between records with datatype prefix rules" $ do let foobert = Foobert "Alice" 30 let barfoo = W.from foobert :: Barfoo barfoo `shouldBe` Barfoo "Alice" 30 it "maps between records with constructor prefix rules" $ do let person = Person "Bob" "Smith" 25 let employee = W.from person :: Employee employee `shouldBe` Employee "Bob" "Smith" 25 it "maps between positional constructors" $ do let point = Point2D 3 4 let vector = W.from point :: Vector2D vector `shouldBe` Vector2D 3 4 describe "Bidirectional mapping" $ do it "can map back and forth" $ do let original = Foobert "Test" 42 let converted = W.from original :: Barfoo let back = W.from converted :: Foobert back `shouldBe` original