Safe Haskell | None |
---|---|
Language | Haskell2010 |
Overloaded*
language extensions as a source plugin.
Synopsis
- plugin :: Plugin
- class FromSymbol (s :: Symbol) a where
- fromSymbol :: a
- class FromNumeral (n :: Nat) a where
- fromNumeral :: a
- defaultFromNumeral :: forall n a. (KnownNat n, Integral a) => a
- class FromNatural a where
- fromNatural :: Natural -> a
- class FromChar a where
- class Nil a where
- nil :: a
- class Cons x ys zs | zs -> x ys where
- cons :: x -> ys -> zs
- class ToBool b where
- ifte :: ToBool b => b -> a -> a -> a
- class FromNatC a where
- class FromTypeSymbolC a where
- type FromTypeSymbol (s :: Symbol) :: a
Plugin
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
s.Lists
is not like built-inOverloadedLists
, but desugars explicit lists tocons
andnil
If
desugarsif
-expressions toifte
b t eLabels
works like built-inOverloadedLabels
(you should enableOverloadedLabels
so parser recognises the syntax)TypeNats
andTypeSymbols
desugar type-level literals into
andFromNat
respectively.FromTypeSymbol
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) |]
Overloaded:Symbols
class FromSymbol (s :: Symbol) a where Source #
Another way to desugar overloaded string literals using this class.
A string literal "example"
is desugared to
fromSymbol
@"example"
Enabled with:
{-# OPTIONS -fplugin=Overloaded -fplugin-opt=Overloaded:Symbols #-}
fromSymbol :: a Source #
Instances
(KnownNat y, KnownNat m, KnownNat d, ParseDay s ~ (,,) y m d) => FromSymbol s Day Source # | |
Defined in Overloaded.Symbols fromSymbol :: Day Source # | |
(KnownSymbol s, SeqList (ToList s)) => FromSymbol s ByteString Source # | |
Defined in Overloaded.Symbols | |
(KnownSymbol s, SeqList (ToList s)) => FromSymbol s ByteString Source # | |
Defined in Overloaded.Symbols | |
KnownSymbol s => FromSymbol s Text Source # | |
Defined in Overloaded.Symbols fromSymbol :: Text Source # | |
KnownSymbol s => FromSymbol s Text Source # | |
Defined in Overloaded.Symbols fromSymbol :: Text Source # | |
(KnownSymbol s, a ~ Char) => FromSymbol s [a] Source # | |
Defined in Overloaded.Symbols fromSymbol :: [a] Source # |
Overloaded:Strings
See Data.String for fromString
.
Overloaded:Numerals
class FromNumeral (n :: Nat) a where Source #
Another way to desugar numerals.
A numeric literal 123
is desugared to
fromNumeral
@123
Enabled with:
{-# OPTIONS -fplugin=Overloaded -fplugin-opt=Overloaded:Numerals #-}
One can do type-level computations with this.
fromNumeral :: a Source #
Instances
defaultFromNumeral :: forall n a. (KnownNat n, Integral a) => a Source #
Default implementation of fromNumeral
.
Usage example:
instance (KnownNat
n, ...) =>FromNumeral
n MyType wherefromNumeral
=defaultFromNumeral
@n
Overloaded:Naturals
class FromNatural a where Source #
fromNatural :: Natural -> a Source #
Instances
FromNatural Integer Source # | |
Defined in Overloaded.Naturals fromNatural :: Natural -> Integer Source # | |
FromNatural Natural Source # | |
Defined in Overloaded.Naturals fromNatural :: Natural -> Natural Source # |
Overloaded:Chars
Overloaded:Lists
Class for nil, []
See test-suite for ways to define instances for Map
.
There are at-least two-ways.
Instances
Nil IntSet Source # | Since: 0.1.2 |
Defined in Overloaded.Lists | |
Nil [a] Source # | |
Defined in Overloaded.Lists | |
Nil (Set a) Source # | Since: 0.1.2 |
Defined in Overloaded.Lists | |
n ~ Z => Nil (Vec n a) Source # | |
Defined in Overloaded.Lists | |
xs ~ ([] :: [k]) => Nil (NP f xs) Source # | |
Defined in Overloaded.Lists | |
xs ~ ([] :: [[k]]) => Nil (POP f xs) Source # | |
Defined in Overloaded.Lists |
class Cons x ys zs | zs -> x ys where Source #
Class for Cons :
.
Instances
Cons Int IntSet IntSet Source # | Since: 0.1.2 |
Ord a => Cons a (Set a) (Set a) Source # | Since: 0.1.2 |
Cons a [a] (NonEmpty a) Source # | |
Defined in Overloaded.Lists | |
Cons a [a] [a] Source # | |
Defined in Overloaded.Lists | |
Cons a (Vec n a) (Vec (S n) a) Source # | |
Cons (f x) (NP f xs) (NP f (x ': xs)) Source # | |
Cons (NP f xs) (POP f xss) (POP f (xs ': xss)) Source # | |
Overloaded:If
Overloaded:Labels
See GHC.OverloadedLabels for fromLabel
.
Overloaded:TypeNats
Overloaded:TypeSymbols
class FromTypeSymbolC a Source #
A way to overload type level Symbol
s.
A symbol type-literal "example"
is desugared to
FromTypeSymbol
"example"
Enabled with:
{-# OPTIONS -fplugin=Overloaded -fplugin-opt=Overloaded:TypeSymbols #-}
type FromTypeSymbol (s :: Symbol) :: a Source #
Instances
FromTypeSymbolC Symbol Source # | |
Defined in Overloaded.TypeSymbols type FromTypeSymbol s :: a Source # |
Overloaded:RecordFields
See GHC.Records.Compat from record-hasfield
package.