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
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)
Known limitations
- Doesn't desugar inside patterns
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
(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.
class Cons x ys zs | zs -> x ys where Source #
Class for Cons :
.
Overloaded:If
Overloaded:Labels
See GHC.OverloadedLabels for fromLabel
.
generic-lens example!