# Warlock Automatic type-safe mapping between Haskell data types using Template Haskell and the `witch` library. **📖 New to Warlock? Start with the [comprehensive tutorial](src/Warlock/Tutorial.hs)!** ## Features - **Compile-time type safety**: Field names and constructor names checked at compile-time using TH `Name` - **Two matching strategies**: - `ByPosition`: Structural mapping by declaration order - `ByName`: Semantic mapping with configurable rules - **Record and positional constructors**: Support for both named fields and positional arguments - **Multi-constructor ADTs**: Full support for sum types with multiple constructors - **Flexible field rules**: - Compile-time checked field names (`'fieldName`) - Virtual fields via `HasField` with `#fieldName` syntax - Computed fields combining multiple sources - Disassemble fields splitting one into many - **Type-safe constructor mapping**: - Explicit mappings: `[('OldCon, 'NewCon)]` - Helper functions: `addSuffix`, `stripSuffix`, `replaceSuffix` - Custom transformations: `Transform (++ "V2")` - **Type-safe conversions**: Uses `witch`'s `From`/`TryFrom` for nested type conversions - **Field evolution**: Handle API versioning with added/removed fields - **Common conventions built-in**: `datatypePrefixConfig`, `constructorPrefixConfig`, etc. ## Quick Start ### Simple Record Mapping ```haskell {-# LANGUAGE TemplateHaskell #-} {-# LANGUAGE MultiParamTypeClasses #-} import Warlock import qualified Witch as W data Person = Person { name :: String, age :: Int } data Employee = Employee { name :: String, age :: Int } -- Derive mapping: fields matched by name deriveAutomap (ByName defaultConfig) ''Person ''Employee -- Use it let person = Person "Alice" 30 let employee = W.from person :: Employee ``` ### Handling Naming Conventions ```haskell data Person = Person { personName :: String , personAge :: Int } data Employee = Employee { employeeName :: String , employeeAge :: Int } -- Automatically handles type-prefixed fields deriveAutomap (ByName datatypePrefixConfig) ''Person ''Employee ``` ### Positional Matching ```haskell data Point2D = Point2D Int Int data Vector2D = Vector2D Int Int -- Maps by position: 1st → 1st, 2nd → 2nd deriveAutomap ByPosition ''Point2D ''Vector2D ``` ### Multi-Constructor ADTs with Field Evolution ```haskell data PaymentV1 = CardPaymentV1 { cardNumber :: String, expiry :: String } | CashPaymentV1 { amount :: Double } data PaymentV2 = CardPaymentV2 { cardNumber :: String , expiry :: String , cvv :: String -- New field! } | CashPaymentV2 { amount :: Double, currency :: String } -- Handle field evolution with defaults and constructor mapping deriveAutomap (ByName $ defaultConfig `withConstructorMap` replaceSuffix "V1" "V2" `withDefaults` [ ('cvv, [| "000" |]) , ('currency, [| "USD" |]) ]) ''PaymentV1 ''PaymentV2 ``` ## Field References: Compile-Time Safety Warlock uses Template Haskell `Name` for compile-time checked field references: ```haskell -- ✅ Compile-time checked - typos caught at compile time! rename 'newBalance 'oldBalance defaultTo 'region [| "US" |] -- ✅ Virtual fields use #fieldName syntax (OverloadedLabels) virtualField 'empName #fullName -- ✅ Or use strings for virtual fields virtualField 'empName "fullName" ``` **Benefits:** - Typos in field names → compile errors - Refactoring tools can track field renames - IDE autocomplete works - No runtime surprises ## Field Rules ### Composable Builder Pattern ```haskell {-# LANGUAGE OverloadedLabels #-} import Warlock import Data.Function ((&)) -- Build rules step-by-step field 'balance & fromField 'balance_cents field 'region & withDefault [| "US" |] field 'empName & fromField #fullName & asVirtual -- Virtual field! field 'newBalance & fromField 'oldBalance & withDefault [| 0 |] ``` ### Pre-composed Helpers ```haskell -- For convenience rename 'balance 'balance_cents -- Real fields (TH Name) defaultTo 'region [| "US" |] virtualField 'empName #fullName -- Virtual field (OverloadedLabels) virtualField 'empName "fullName" -- Or String ignore 'internalField mapField 'name (\src dst -> [| customTransform |]) ``` ### Available Modifiers - `fromField` - Specify source field (accepts `'name` or `#name`) - `withDefault` - Provide default value when source is missing - `withExpr` - Custom TH expression - `asVirtual` - Use `HasField` to access virtual/computed fields - `withComputed` - Combine multiple source fields ## Field Manipulation Patterns ### Virtual Fields (HasField) Use runtime `HasField` instances to access computed properties: ```haskell {-# LANGUAGE DataKinds #-} {-# LANGUAGE OverloadedLabels #-} import GHC.Records (HasField(..)) data Person = Person { firstName :: String , lastName :: String , age :: Int } -- Define virtual field at runtime instance HasField "fullName" Person String where getField (Person first last _) = first ++ " " ++ last data Employee = Employee { empName :: String , empAge :: Int } -- Map from virtual field using #syntax deriveAutomap (ByName $ defaultConfig `withRules` [ virtualField 'empName #fullName , rename 'empAge 'age ]) ''Person ''Employee ``` **Characteristics:** - **Source:** 1 field via `HasField` instance - **When:** Runtime (via `getField`) - **Syntax:** `#fieldName` (OverloadedLabels) or `"fieldName"` ### Computed Fields (combineFields) Combine multiple source fields at compile-time: ```haskell deriveAutomap (ByName $ defaultConfig `withRules` [ combineFields 'fullName $ do firstName <- get 'firstName lastName <- get 'lastName pure [| $firstName ++ " " ++ $lastName |] , rename 'age 'personAge ]) ''PersonV1 ''PersonV2 ``` **Monadic FieldGetter interface:** - `get 'fieldName` - Extract field as TH expression (Q Exp) - `getName 'fieldName` - Extract field's Name (advanced) - Compile-time error if field doesn't exist - Type-safe, no manual `varE` needed **Characteristics:** - **Source:** N fields from source record - **When:** Compile-time (Template Haskell) - **Syntax:** Monadic do-notation with `get` ### Disassembled Fields (disassembleFields) Split one source field into multiple destination fields: ```haskell deriveAutomap (ByName $ defaultConfig `withRules` ( disassembleFields 'fullName [ 'firstName .= do src <- getSource pure [| case words $src of (f:_) -> f _ -> "" |] , 'lastName .= do src <- getSource pure [| case words $src of (_:l:_) -> l _ -> "" |] ] ++ [ rename 'age 'personAge ] )) ''PersonV1 ''PersonV2 ``` **Monadic DisassembleGetter interface:** - `getSource` - Get source field as TH expression (Q Exp) - `getSourceName` - Get source field as Name (advanced) - Clean syntax, no manual `varE` needed **Characteristics:** - **Source:** 1 field from source record - **Target:** N fields in destination record - **When:** Compile-time (Template Haskell) - **Syntax:** Monadic do-notation with `getSource` ## Constructor Mapping Map constructor names with compile-time safety: ### Direct Mapping (Compile-time Checked!) ```haskell -- ✅ Constructor names checked at compile time defaultConfig `withConstructorMap` [ ('CircleShape, 'CircleInfo) , ('RectangleShape, 'RectangleInfo) ] ``` ### Helper Functions ```haskell -- Add suffix: Foo → FooV2 defaultConfig `withConstructorMap` addSuffix "V2" -- Strip suffix: FooV2 → Foo defaultConfig `withConstructorMap` stripSuffix "V2" -- Replace suffix: FooV1 → FooV2 defaultConfig `withConstructorMap` replaceSuffix "V1" "V2" ``` ### Custom Transformations ```haskell -- Wrap in Transform for custom logic defaultConfig `withConstructorMap` Transform (\s -> s ++ "V2") -- Or pass function directly defaultConfig `withConstructorMap` (++ "V2") ``` ## Configuration Presets Common configurations for typical Haskell code: ```haskell -- Most common: datatype-prefixed fields (personName ↔ employeeName) deriveAutomap (ByName datatypePrefixConfig) ''Person ''Employee -- Constructor-prefixed fields deriveAutomap (ByName constructorPrefixConfig) ''Person ''Employee -- Try both conventions (datatype first, then constructor) deriveAutomap (ByName conventionalConfig) ''Person ''Employee -- snake_case ↔ camelCase (e.g., for JSON/DB interop) deriveAutomap (ByName snakeToCamelConfig) ''DbRecord ''HaskellRecord deriveAutomap (ByName camelToSnakeConfig) ''HaskellRecord ''DbRecord -- Combine configs with helpers: deriveAutomap (ByName $ datatypePrefixConfig `withDefaults` [('newField, [| defaultVal |])] `withConstructorMap` addSuffix "V2") ''OldType ''NewType ``` ## Configuration Helpers - `withDefaults :: Config -> [(Name, Q Exp)] -> Config` - Add default values - `withRenames :: Config -> [(Name, FieldRef)] -> Config` - Add field renames - `withRules :: Config -> [FieldRule] -> Config` - Add custom rules - `withConstructorMap :: Config -> ConstructorMapping -> Config` - Map constructor names - `withNormalize :: Config -> (String -> String) -> Config` - Set normalization function - `withRuleGens :: Config -> [RuleGenContext -> String -> Maybe FieldRule] -> Config` - Add rule generators ## Built-in Rule Generators - `datatypePrefixRules` - Handles type-prefixed fields (personName → employeeName) - `constructorPrefixRules` - Handles constructor-prefixed fields - `customPrefixRules` - Specify custom prefixes manually - `stripConstructorPrefix` - Remove constructor prefixes - `addConstructorPrefix` - Add constructor prefixes ## ADT Support - ✅ Single-constructor records - ✅ Multi-constructor records (sum types) - ✅ Positional constructors - ✅ Mixed ADTs (multiple constructors) - ✅ Field addition with defaults - ✅ Field removal (silently ignored) - ✅ Constructor matching by name (case-insensitive) - ✅ Compile-time constructor name checking with `DirectMapping` - ⚠️ Cannot mix record and positional in same constructor pair - ⚠️ Constructor names must be unique per module (use qualified imports if needed) ## Parameterized Types For types with type parameters, use `deriveWithType`: ```haskell data Container a = Container { value :: a } data IntContainer = IntContainer { value :: Int } -- Specify concrete type application deriveWithType (ByName defaultConfig) [t| Container Int |] [t| IntContainer |] ``` ## API Summary ### Main Derivation Functions - `derive :: MatchStrategy -> Name -> Name -> Q [Dec]` - `deriveWithType :: MatchStrategy -> Q Type -> Q Type -> Q [Dec]` - `deriveTry :: MatchStrategy -> Name -> Name -> Q [Dec]` - Generate `TryFrom` instead - `deriveBoth :: MatchStrategy -> Name -> Name -> Q [Dec]` - Generate both directions ### Match Strategies - `ByPosition` - Structural matching (by declaration order) - `ByName Config` - Semantic matching (by name with rules) ### Types - `FieldRef` - Either `RealField Name` or `VirtualField String` - `ConstructorMapping` - `Identity`, `DirectMapping [(Name, Name)]`, or `Transform (String -> String)` - `FieldRule` - Configuration for a single field mapping - `FieldGetter a` - Monad for extracting source fields in `combineFields` - `DisassembleGetter a` - Monad for accessing source field in `disassembleFields` ## Warlock.Tweak - Type Generation with Modifications The `Warlock.Tweak` module generates new data types from existing ones with field modifications, perfect for creating DTOs, API response types, and projections. Inspired by TypeScript's utility types like `Pick` and `Omit`. ### Quick Example ```haskell {-# LANGUAGE TemplateHaskell #-} import qualified Warlock.Tweak as Tweak import Warlock.Tweak (pick, omit) data User = User { userId :: Int , userName :: String , userEmail :: String , userPassword :: String -- Sensitive! , userCreatedAt :: String } -- Pick specific fields (TypeScript Pick) pick ''User "UserSummary" ['userId, 'userName] -- Omit sensitive fields (TypeScript Omit) omit ''User "UserResponse" ['userPassword] -- Generates new types + From instances automatically -- let summary = from user :: UserSummary ``` ### TypeScript-Style API **`pick`** - Select specific fields (like TypeScript's `Pick`): ```haskell -- Simple usage pick ''User "UserMinimal" ['userId, 'userName] -- With configuration pick' (defaultTweakConfig `Tweak.stripPrefix` "user") ''User "UserClean" ['userName, 'userEmail] -- Generated: UserClean { name :: String, email :: String } ``` **`omit`** - Exclude specific fields (like TypeScript's `Omit`): ```haskell -- Simple usage omit ''User "UserDTO" ['userPassword, 'userCreatedAt] -- With configuration omit' (defaultTweakConfig `Tweak.addPrefix` "dto") ''User "UserAPI" ['userPassword] -- Generated: UserAPI { dtouserId :: Int, dtouserName :: String, ... } ``` ### Composable Configuration All functions support composable configuration using helper functions: **`stripPrefix`** - Remove common prefix from fields: ```haskell pick' (defaultTweakConfig `Tweak.stripPrefix` "user") ''User "UserClean" ['userName, 'userEmail] -- userName -> name, userEmail -> email ``` **`addPrefix`** - Add prefix to all fields: ```haskell omit' (defaultTweakConfig `Tweak.addPrefix` "api") ''User "UserAPI" ['userPassword] -- userId -> apiuserId, userName -> apiuserName, etc. ``` **`replacePrefix`** - Swap one prefix for another: ```haskell pick' (defaultTweakConfig `Tweak.replacePrefix` ("product", "item")) ''Product "ItemSummary" ['productId, 'productName] -- productId -> itemId, productName -> itemName ``` **`withRenames`** - Direct field name mappings: ```haskell pick' (defaultTweakConfig `Tweak.withRenames` [('userId, mkName "id")]) ''User "UserRenamed" ['userId, 'userName] -- userId -> id, userName stays userName ``` **Chain operations** - Combine multiple transformations: ```haskell pick' (defaultTweakConfig `Tweak.stripPrefix` "user" `Tweak.addPrefix` "dto") ''User "UserDTO" ['userName, 'userEmail] -- userName -> dtoName, userEmail -> dtoEmail ``` ### Configuration Options ```haskell data TweakConfig = TweakConfig { fieldSelector :: FieldSelector -- Which fields to keep/drop , fieldRenames :: [(Name, Name)] -- Explicit field renames , prefixOps :: [PrefixOp] -- Prefix operations , autoDerive :: Bool -- Auto-generate From instances (default: True) , deriveStrategy :: Maybe MatchStrategy -- Custom Warlock strategy } -- Composable helpers: withFields :: TweakConfig -> [Name] -> TweakConfig withoutFields :: TweakConfig -> [Name] -> TweakConfig Tweak.withRenames :: TweakConfig -> [(Name, Name)] -> TweakConfig Tweak.addPrefix :: TweakConfig -> String -> TweakConfig Tweak.stripPrefix :: TweakConfig -> String -> TweakConfig Tweak.replacePrefix :: TweakConfig -> (String, String) -> TweakConfig withAutoDerive :: TweakConfig -> Bool -> TweakConfig withDeriveStrategy :: TweakConfig -> MatchStrategy -> TweakConfig ``` ### Use Cases **API Response DTOs:** ```haskell -- Omit sensitive fields for API responses omit ''User "UserResponse" ['userPassword, 'userSalt, 'userTokens] ``` **Database to Domain:** ```haskell -- Strip "db" prefix from Persistent-generated types pick' (defaultTweakConfig `Tweak.stripPrefix` "dbUser") ''DbUser "User" ['dbUserId, 'dbUserName, 'dbUserEmail] ``` **Field Projections:** ```haskell -- Create minimal type for specific use cases pick ''User "UserSummary" ['userId, 'userName] ``` **API Versioning:** ```haskell -- Add prefix for versioned types pick' (defaultTweakConfig `Tweak.addPrefix` "v2") ''User "UserV2" ['userId, 'userName, 'userEmail] ``` ### Notes - Automatically generates `From` instances between source and derived types (unless `withAutoDerive False`) - Field names are automatically lowercased after prefix operations to maintain Haskell conventions - Constructor name defaults to match type name - Single-constructor record types only (no sum types or positional constructors yet) - Module must be imported qualified to avoid name conflicts: `import qualified Warlock.Tweak as Tweak` ## Warlock.HKD - Higher-Kinded Data Generation Generate Higher-Kinded Data (HKD) versions of your types for use with libraries like `barbies`. HKD types wrap each field in a type constructor, enabling powerful patterns for validation, partial construction, and generic programming. ```haskell {-# LANGUAGE TemplateHaskell #-} {-# LANGUAGE TypeFamilies #-} import Warlock.HKD import Data.Functor.Identity import Witch (from) data Person = Person { name :: String , age :: Int , email :: String } deriving (Show, Eq) -- Generate HKD type with default config deriveHKD' ''Person -- Now you have: -- - Type family: HKD Person f -- - Concrete type: Person' f -- - From instances for Identity wrapper conversion ``` ### Type Family and Instances The `deriveHKD` function generates: 1. **A concrete HKD data type** with fields wrapped in `f`: ```haskell data Person' f = Person' { name :: f String , age :: f Int , email :: f String } ``` 2. **A type family instance** for convenient syntax: ```haskell type instance HKD Person f = Person' f ``` 3. **From instances** for Identity conversion (bidirectional): ```haskell instance From (Person' Identity) Person instance From Person (Person' Identity) ``` ### Basic Usage **Bidirectional Conversion:** ```haskell let person = Person "Alice" 30 "alice@example.com" let hkdPerson = from person :: HKD Person Identity let unwrapped = from hkdPerson :: Person ``` **Partial Construction with Maybe:** ```haskell -- Build up a Person incrementally let partial = Person' (Just "Bob") Nothing (Just "bob@example.com") :: Person' Maybe -- Validate and convert when complete validatePerson :: Person' Maybe -> Maybe Person validatePerson (Person' (Just n) (Just a) (Just e)) = Just (Person n a e) validatePerson _ = Nothing ``` **Optional Fields:** ```haskell -- Form validation where fields might be missing data UserForm f = UserForm { username :: f String , password :: f String , confirmPassword :: f String } deriveHKD' ''UserForm -- During form filling, fields are Maybe String let formInProgress = UserForm' (Just "alice") Nothing Nothing :: UserForm' Maybe ``` ### Configuration Customize field and constructor naming: **Field Prefix:** ```haskell data User = User { userName :: String , userEmail :: String } -- Fields: hkduserName, hkduserEmail deriveHKD (defaultHKDConfig `withFieldPrefix` "hkd") ''User ``` **Constructor Suffix:** ```haskell -- Constructor: PersonHKD instead of Person' deriveHKD (defaultHKDConfig `withConstructorSuffix` "HKD") ''Person ``` **Custom Transforms:** ```haskell deriveHKD (defaultHKDConfig `withFieldTransform` (\name -> "field_" ++ name) `withConstructorTransform` (\name -> name ++ "_HKD") ) ''MyType ``` **Disable From Instances:** ```haskell -- Generate only the HKD type, no From instances deriveHKD (withoutFromInstances defaultHKDConfig) ''MyType ``` ### Multi-Constructor Support HKD generation works with sum types: ```haskell data Payment = CreditCard { cardNumber :: String, cvv :: String } | Cash { amount :: Double } | Check { checkNumber :: Int } deriveHKD' ''Payment -- Generates Payment' with all constructors wrapped let payment = CreditCard "1234" "123" let hkdPayment = from payment :: HKD Payment Identity let unwrapped = from hkdPayment :: Payment ``` ### Integration with Barbies While Warlock.HKD generates the HKD types and From instances, you can use `barbies` for generic traversals by deriving the necessary instances: ```haskell {-# LANGUAGE StandaloneDeriving #-} {-# LANGUAGE DeriveGeneric #-} import GHC.Generics (Generic) import qualified Barbies as B data Person = Person { name :: String, age :: Int } deriveHKD' ''Person deriving instance Generic (Person' f) instance B.FunctorB Person' instance B.TraversableB Person' instance B.ApplicativeB Person' -- Now use barbies operations validateFields :: Person' Maybe -> Either [String] Person validateFields p = B.btraverse (maybe (Left ["missing"]) Right) p ``` ### Use Cases **Form Validation:** ```haskell -- Track validation state per field data PersonForm f = PersonForm { name :: f String , age :: f Int , email :: f String } type ValidationResult = Either String validateForm :: PersonForm Maybe -> PersonForm ValidationResult validateForm = -- validate each field -- Collect to final result collectValidation :: PersonForm (Either String) -> Either [String] Person collectValidation = B.btraverse (either (Left . pure) Right) ``` **Incremental Construction:** ```haskell -- Build complex objects step by step data Config f = Config { host :: f String , port :: f Int , timeout :: f Int } emptyConfig :: Config Maybe emptyConfig = Config Nothing Nothing Nothing addHost :: String -> Config Maybe -> Config Maybe addHost h cfg = cfg { host = Just h } ``` **Optional Fields in APIs:** ```haskell -- PATCH requests with optional updates data UserUpdate f = UserUpdate { updateName :: f String , updateEmail :: f String , updateAge :: f Int } -- Only update provided fields applyUpdate :: User -> UserUpdate Maybe -> User applyUpdate user upd = User { userName = fromMaybe (userName user) (updateName upd) , userEmail = fromMaybe (userEmail user) (updateEmail upd) , userAge = fromMaybe (userAge user) (updateAge upd) } ``` ## Learning Resources ### Warlock.Tutorial For a comprehensive guide covering all features from basic to advanced usage, see the **[Warlock.Tutorial](src/Warlock/Tutorial.hs)** module. This extensive tutorial includes: - Introduction & core concepts (ByPosition vs ByName decision tree) - Getting started with simple examples - Naming conventions (datatype prefix, constructor prefix, snake/camel case) - Advanced field manipulation (virtual fields, computed fields, disassembled fields) - Constructor mapping strategies - Type generation with Warlock.Tweak (Pick/Omit DTOs) - Higher-Kinded Data with Warlock.HKD - Real-world patterns (API versioning, database conversions, DTOs) - Advanced techniques and troubleshooting The tutorial is designed to be read sequentially and includes complete, working examples for every concept. ## License MIT