[GHC] #12001: RFC: Add pattern synonyms to base
GHC
ghc-devs at haskell.org
Tue Apr 18 21:41:52 UTC 2017
#12001: RFC: Add pattern synonyms to base
-------------------------------------+-------------------------------------
Reporter: Iceland_jack | Owner: (none)
Type: feature request | Status: new
Priority: normal | Milestone:
Component: libraries/base | Version: 7.10.3
Resolution: | Keywords:
Operating System: Unknown/Multiple | Architecture:
| Unknown/Multiple
Type of failure: None/Unknown | Test Case:
Blocked By: | Blocking:
Related Tickets: | Differential Rev(s):
Wiki Page: |
-------------------------------------+-------------------------------------
Description changed by Iceland_jack:
@@ -46,0 +46,3 @@
+ import Data.Complex (Complex, conjugate, polar, mkPolar)
+ import qualified Data.Complex as C
+
@@ -56,2 +59,2 @@
- pattern Real r <- r :+ _
- where Real r = r :+ 0
+ pattern Real r <- r C.:+ _
+ where Real r = r C.:+ 0
@@ -60,2 +63,2 @@
- pattern Imaginary i <- _ :+ i
- where Imaginary i = 0 :+ i
+ pattern Imaginary i <- _ C.:+ i
+ where Imaginary i = 0 C.:+ i
@@ -63,0 +66,2 @@
+ pattern (:+) :: a -> a -> Complex a
+ pattern (:+) { realPart, imagPart } = realPart C.:+ imagPart
New description:
Since we have pattern synonyms it's worth considering if some belong in
base:
[https://hackage.haskell.org/package/lens-4.14/docs/Data-Complex-Lens.html
Data.Complex.Lens] contains patterns that could be defined in base, here
are some more suggestions:
=== Data.Array ===
{{{#!hs
pattern ArrayIx :: Ix i => (i, i) -> [(i, e)] -> Array i e
pattern ArrayIx low'high xs <- ((\arr -> (bounds arr, assocs arr)) ->
(low'high, xs))
where ArrayIx low'high xs = array low'high xs
}}}
=== Data.Bits ===
{{{#!hs
pattern ZeroBits :: (Eq a, Bits a) => a
pattern ZeroBits <- ((== zeroBits) -> True)
where ZeroBits = zeroBits
pattern BitSize :: Bits a => Int -> a
pattern BitSize n <- (bitSizeMaybe -> Just n)
pattern Signed :: Bits a => a
pattern Signed <- (isSigned -> True)
pattern Unsigned :: Bits a => a
pattern Unsigned <- (isSigned -> False)
pattern PopCount :: Bits a => Int -> a
pattern PopCount n <- (popCount -> n)
}}}
=== Data.Char ===
{{{#!hs
pattern ControlChar :: Char
pattern ControlChar <- (isControl -> True)
pattern SpaceChar :: Char
pattern SpaceChar <- (isSpace -> True)
}}}
=== Data.Complex ===
{{{#!hs
import Data.Complex (Complex, conjugate, polar, mkPolar)
import qualified Data.Complex as C
pattern Conjugate :: Num a => Complex a -> Complex a
pattern Conjugate a <- (conjugate -> a)
where Conjugate a = conjugate a
pattern Polar :: RealFloat a => a -> a -> Complex a
pattern Polar m theta <- (polar -> (m, theta))
where Polar m theta = mkPolar m theta
-- See https://github.com/ekmett/lens/issues/653
pattern Real :: Num a => a -> Complex a
pattern Real r <- r C.:+ _
where Real r = r C.:+ 0
pattern Imaginary :: Num a => a -> Complex a
pattern Imaginary i <- _ C.:+ i
where Imaginary i = 0 C.:+ i
pattern (:+) :: a -> a -> Complex a
pattern (:+) { realPart, imagPart } = realPart C.:+ imagPart
}}}
=== GHC.Float ===
{{{#!hs
pattern NegativeZero :: RealFloat a => a
pattern NegativeZero <- (isNegativeZero -> True)
where NegativeZero = -0
pattern Denormalized :: RealFloat a => a
pattern Denormalized <- (isDenormalized -> True)
pattern NaN :: RealFloat a => a
pattern NaN <- (isNaN -> True)
where NaN = 0 / 0
-- How ever negative infinity is handled
pattern Infinity :: RealFloat a => a
pattern Infinity <- ((== 1 / 0) -> True)
where Infinity = 1 / 0
}}}
--
--
Ticket URL: <http://ghc.haskell.org/trac/ghc/ticket/12001#comment:12>
GHC <http://www.haskell.org/ghc/>
The Glasgow Haskell Compiler
More information about the ghc-tickets
mailing list