large-records-0.1.0.0: Efficient compilation for large records, linear in the size of the record
Safe HaskellNone
LanguageHaskell2010

Data.Record.TH

Synopsis

Documentation

lr :: QuasiQuoter Source #

Construct or match on large-records-style records

Example construction usage:

inOrder :: R Bool
inOrder = [lr| MkR { x = 1234, y = [True] } |]

or:

constructorApp :: R Bool
constructorApp = [lr| MkR |] 1234 [True]

Example matching usage:

projectOne :: T Bool -> Int
projectOne [lr| MkT { x = a } |] = a

data Options Source #

Tweak the output of the generator

In the explanations of the various options below, we will use the following record as our running example:

data T a b = MkT {
      tWord  :: Word
    , tBool  :: Bool
    , tChar  :: Char
    , tA     :: a
    , tListB :: [b]
    }
  deriving (Eq, Show)

Constructors

Options 

Fields

  • generatePatternSynonym :: Bool

    Generate a pattern synonym for the record

    pattern MkT :: Word -> Bool -> Char -> a -> [b] -> T a b
    pattern MkT{tInt, tBool, tChar, tA, tListB} <- ..
      where
        MkT tInt' tBool' tChar' tA' tListB' = ..

    The pattern synonym makes it possible to construct or pattern match on T values as if it had been defined like a normal record.

    We do not do this by default, however, because unfortunately when we define a record pattern synonym in ghc, ghc also (unnecessarily but currently unavoidably) introduces field accessors for all fields in the record, and we're back to code that is quadratic in size.

    Avoid if possible.

  • generateConstructorFn :: Bool

    Generate a "constructor function" for the record

    _construct_MkT :: Word -> Bool -> Char -> a -> [b] -> T a b
    _construct_MkT = ..

    This function can be used directly, but it is also used by the lr quasi-quoter, so if this function is not generated, lr will not work.

  • generateHasFieldInstances :: Bool

    Generate HasField instances

    instance HasField "tInt" (T a b) Word where
      hasField = ..

    These are required by the record-dot-preprocessor.

  • generateFieldAccessors :: Bool

    Generate field accessors

    tInt :: T a b -> Word
    tInt = ..

    If field accessors are not generated, the only way to access fields is through the HasField instances.

    Disabling this option is primarily useful if you need overloading: if you have multiple records with a field of the same name, then generating field accessors would result in name clashes. Without the accessors, overloading is resolved through HasField.

  • allFieldsStrict :: Bool

    Make all fields strict

    This should be used when using the StrictData or Strict language extension.

defaultPureScript :: Options Source #

Default options for "Purescript style" records

That is:

  • All fields are strict
  • We do not generate field accessors: fields must be accessed and updated through the HasField instances (e.g., record-dot-preprocessor syntax).

We do not introduce a pattern synonym by default:

  • Introducing a pattern synonym reintroduces code that is quadratic in size.
  • Perhaps more importantly, it would make it impossible to define two records with the same field names in a single module, as the field accessors (unnecessarily but currently unavoidably) introduced by the pattern synonym would clash.

NOTE: The record-dot-preprocessor enables DuplicateRecordFields by default. Since the records that we produce are not visible to ghc, large-records is not compatible with DRF-style overloading. However, as long as all overloading is resolved through HasField instead (which is what record-dot-preprocessor encourages anyway), all is fine.

largeRecord :: Options -> Q [Dec] -> Q [Dec] Source #

Declare a large record

Example usage:

largeRecord defaultPureScript [d|
    data R a = MkR { x :: Int, y :: [a] } deriving (Eq, Show)
    data S a = S   { x :: Int, y :: [a] } deriving (Eq, Show)
  |]