Safe Haskell | None |
---|---|
Language | Haskell2010 |
Overloaded plugin, which makes magic possible.
Documentation
Overloaded
plugin.
To enable plugin put the following at top of the module:
{-# OPTIONS -fplugin=Overloaded -fplugin-opt=Overloaded:Symbols #-}
At least one option is required, multiple can given
either using multiple -fplugin-opt
options, or by separating options
with colon:
{-# OPTIONS -fplugin=Overloaded -fplugin-opt=Overloaded:Symbols:Numerals #-}
Options also take optional desugaring names, for example
{-# OPTIONS -fplugin=Overloaded -fplugin-opt=Overloaded:Labels=Data.Generics.ProductFields.field #-}
to desugar OverloadedLabels
directly into field
from generics-lens
(no need to import orphan instance!)
Supported options
Symbols
desugars literal strings tofromSymbol
@symStrings
works like built-inOverloadedStrings
(but you can use different method thanfromString
)Numerals
desugars literal numbers tofromNumeral
@natNaturals
desugars literal numbers to
(i.e. likefromNatural
natfromString
)Chars
desugars literal characters to
. Note: there isn't type-level alternative: we cannot promotefromChars
cChar
sLists
is not like built-inOverloadedLists
, but desugars explicit lists tocons
andnil
If
desugarsif
-expressions toifte
b t eUnit
desugars()
-expressions to
(but you can use different method, e.g.nil
boring
from Data.Boring)Labels
works like built-inOverloadedLabels
(you should enableOverloadedLabels
so parser recognises the syntax)TypeNats
andTypeSymbols
desugar type-level literals into
andFromNat
respectivelyFromTypeSymbol
Do
desugar in Local Do fashion. See examples.Categories
changeArrows
desugaring to use "correct" category classes.CodeLabels
desugarsOverloadedLabels
into Typed Template Haskell splicesCodeStrings
desugars string literals into Typed Template Haskell splicesRebindableApplication
changes how juxtaposition is interpretedOverloadedConstructors
allows you to use overloaded constructor names!
Known limitations
- Doesn't desugar inside patterns
RecordFields
WARNING the type-checker plugin is experimental, it's adviced to use
{-# OPTIONS_GHC -ddump-simpl #-}
to avoid surprising segfaults.
Usage
{-# OPTIONS -fplugin=Overloaded -fplugin-opt=Overloaded:RecordFields #-}
Implementation bits
See Note [HasField instances] in ClsInst, the behavior of this plugin is similar.
The HasField
class is defined in GHC.Records.Compat module of record-hasfield
package:
classHasField
{k} x r a | x r -> a wherehasField
:: r -> (a -> r, a)
Suppose we have
data R y = MkR { foo :: [y] }
and foo
in scope. We will solve constraints like
HasField "foo" (R Int) a
by emitting a new wanted constraint
[Int] ~# a
and building a HasField
dictionary out of selector foo
appropriately cast.
Idiom brackets from TemplateHaskellQuotes
{-# LANGUAGE TemplateHaskellQuotes #-} {-# OPTIONS_GHC -fplugin=Overloaded -fplugin-opt=Overloaded:IdiomBrackets #-} data Tree a = Leaf a | Branch (Tree a) (Tree a) deriving (Show) instance Functor Tree wherefmap
f (Leaf x) = Leaf (f x)fmap
f (Branch l r) = Branch (fmap
f l) (fmap
f r) instance Traversable Tree wheretraverse
f (Leaf x) = [| Leaf (f x) |]traverse
f (Branch l r) = [| Branch (traverse
f l) (traverse
f r) |]
RebindableApplication
Converts all f x
applications into (f $ x)
with whatever $
is in scope.
{-# OPTIONS -fplugin=Overloaded -fplugin-opt=Overloaded:RebindableApplication #-}
let f = pure ((+) :: Int -> Int -> Int)
x = Just 1
y = Just 2
z = let ($) = (<*>
) in f x y
in z