| Safe Haskell | Safe-Inferred |
|---|---|
| Language | Haskell2010 |
Data.Record.Plugin
Contents
Description
Support for scalable large records
Usage
{-# OPTIONS_GHC -fplugin=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.
Dependencies
In addition to the dependency on large-records, you will also need to add
dependencies on
Language extensions
The plugin depends on a number of language extensions. If you are using GHC2021, you will need enable:
{-# LANGUAGE DataKinds #-}
{-# LANGUAGE TypeFamilies #-}
{-# LANGUAGE UndecidableInstances #-}If you are using Haskell2010, you need to enable:
{-# LANGUAGE ConstraintKinds #-}
{-# LANGUAGE DataKinds #-}
{-# LANGUAGE FlexibleInstances #-}
{-# LANGUAGE GADTs #-}
{-# LANGUAGE MultiParamTypeClasses #-}
{-# LANGUAGE ScopedTypeVariables #-}
{-# LANGUAGE TypeFamilies #-}
{-# LANGUAGE TypeOperators #-}
{-# LANGUAGE UndecidableInstances #-}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 | |
Fields | |