overloaded-0.3.1: Overloaded pragmas as a plugin
Safe HaskellNone
LanguageHaskell2010

Overloaded.Plugin

Description

Overloaded plugin, which makes magic possible.

Synopsis

Documentation

plugin :: Plugin Source #

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 to fromSymbol @sym
  • Strings works like built-in OverloadedStrings (but you can use different method than fromString)
  • Numerals desugars literal numbers to fromNumeral @nat
  • Naturals desugars literal numbers to fromNatural nat (i.e. like fromString)
  • Chars desugars literal characters to fromChars c. Note: there isn't type-level alternative: we cannot promote Chars
  • Lists is not like built-in OverloadedLists, but desugars explicit lists to cons and nil
  • If desugars if-expressions to ifte b t e
  • Unit desugars ()-expressions to nil (but you can use different method, e.g. boring from Data.Boring)
  • Labels works like built-in OverloadedLabels (you should enable OverloadedLabels so parser recognises the syntax)
  • TypeNats and TypeSymbols desugar type-level literals into FromNat and FromTypeSymbol respectively
  • Do desugar in Local Do fashion. See examples.
  • Categories change Arrows desugaring to use "correct" category classes.
  • CodeLabels desugars OverloadedLabels into Typed Template Haskell splices
  • CodeStrings desugars string literals into Typed Template Haskell splices
  • RebindableApplication changes how juxtaposition is interpreted
  • OverloadedConstructors 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:

class HasField {k} x r a | x r -> a where
    hasField :: 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 where
    fmap f (Leaf x)     = Leaf (f x)
    fmap f (Branch l r) = Branch (fmap f l) (fmap f r)

instance Traversable Tree where
    traverse 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