partial-records-0.2.2.1: Template haskell utilities for constructing records with default values

Copyright(C) mniip 2019
LicenseBSD3
Maintainermniip@email.com
Stabilityexperimental
Safe HaskellNone
LanguageHaskell2010

Data.Partial.TH

Description

Template Haskell utilities for constructing records with default values.

Synopsis

Documentation

mkToPartial :: Name -> Q [Dec] Source #

Generate an instance of the Partial family and the Graded class. Takes a data constructor name. For example:

data Foo a = Foo a { fld1 :: Int, fld2 :: a }
mkToPartial ''Foo

expands to:

data instance Partial (Foo a) bs where
  Partial_Foo :: forall a b1 b2.
    Opt b1 Int -> Opt b2 a -> Partial (Foo a) '[b1, b2]
{-# INLINE mkfld1 #-}
mkfld1 :: Int -> Partial (Foo a) '[ 'True, 'False]
mkfld1 x = Partial_Foo (Has x) Hasn't
{-# INLINE mkfld2 #-}
mkfld2 :: a -> Partial (Foo a) '[ 'False, 'True]
mkfld2 x = Partial_Foo Hasn't (Has x)
instance Graded (Foo a) where
  {-# INLINE (?) #-}
  Partial_Foo x1 x2 ? Partial_Foo y1 y1
    = Partial_Foo (joinOpt x1 y1) (joinOpt x2 y2)

mkFromPartial :: String -> Q Type -> Q Exp -> Q [Dec] Source #

Generate a function that turns a Partial into a value of the actual datatype. Takes a name for the function to be defined, as well as the type the result should have (can include type variables but all of them must be quantified), as well as the "default values": a record construction specifying just those fields that you want, with their default values. For example:

data Foo a = Foo a { fld1 :: Int, fld2 :: a }
mkFromPartial "mkFoo" [t|forall a. Foo (Maybe a)|] [|Foo { fld2 = Nothing }|]

expands to:

{-# INLINE mkFoo #-}
mkFoo :: forall a b1 b2.
  ( Require "Foo" "fld1" b1
  -- ^ Assert that b1 ~ 'True but generate a nice error message if not
  )
  => Partial (Foo (Maybe a)) '[b1, b2] -> Foo (Maybe a)
mkFoo (Partial_Foo x1 x2) = Foo (unOpt x1) (fromOpt Nothing x2)

mkToPartialWith :: (String -> String) -> Name -> Q [Dec] Source #

The default procedure for generating field constructors from field names is prepending "mk". You can override this behavior by passing a custom field name generating function to this function.