large-records-0.4: Efficient compilation for large records, linear in the size of the record
Safe HaskellSafe-Inferred
LanguageHaskell2010

Data.Record.Plugin

Description

Support for scalable large records

Usage

{-# OPTIONS_GHC -fplugin=Data.Record.Plugin #-}

import Data.Record.Plugin

{-# ANN type B largeRecord #-}
data B a = B {a :: a, b :: String}
  deriving stock (Show, Eq, Ord)

See LargeRecordOptions for the list of all possible annotations.

Usage with record-dot-preprocessor

The easiest way to use both plugins together is to do

{-# OPTIONS_GHC -fplugin=Data.Record.Plugin.WithRDP #-}

You can also load them separately, but if you do, you need to be careful with the order. Unfortunately, the correct order is different in different ghc versions. Prior to ghc 9.4, the plugins must be loaded like this:

{-# OPTIONS_GHC -fplugin=RecordDotPreprocessor -fplugin=Data.Record.Plugin #-}

From ghc 9.4 and up, they need to be loaded in the opposite order:

{-# OPTIONS_GHC -fplugin=Data.Record.Plugin -fplugin=RecordDotPreprocessor #-}
Synopsis

Annotations

data LargeRecordOptions Source #

A type specifying how a record should be treated by large-records.

The default for Haskell code should probably be:

{-# ANN type T largeRecord #-}
data T = ..

To see the definitions generated by large-records:

{-# ANN type T largeRecord {debugLargeRecords = True} #-}
data T = ..

Constructors

LargeRecordOptions 

Instances

Instances details
Data LargeRecordOptions Source # 
Instance details

Defined in Data.Record.Internal.Plugin.Options

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> LargeRecordOptions -> c LargeRecordOptions #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c LargeRecordOptions #

toConstr :: LargeRecordOptions -> Constr #

dataTypeOf :: LargeRecordOptions -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c LargeRecordOptions) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c LargeRecordOptions) #

gmapT :: (forall b. Data b => b -> b) -> LargeRecordOptions -> LargeRecordOptions #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> LargeRecordOptions -> r #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> LargeRecordOptions -> r #

gmapQ :: (forall d. Data d => d -> u) -> LargeRecordOptions -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> LargeRecordOptions -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> LargeRecordOptions -> m LargeRecordOptions #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> LargeRecordOptions -> m LargeRecordOptions #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> LargeRecordOptions -> m LargeRecordOptions #

HasField "debugLargeRecords" LargeRecordOptions Bool Source # 
Instance details

Defined in Data.Record.Internal.Plugin.Options

For use by ghc