[GHC] #12001: RFC: Add pattern synonyms to base
GHC
ghc-devs at haskell.org
Sun May 1 09:34:26 UTC 2016
#12001: RFC: Add pattern synonyms to base
-------------------------------------+-------------------------------------
Reporter: Iceland_jack | Owner:
Type: feature | Status: new
request |
Priority: normal | Milestone:
Component: | Version: 7.10.3
libraries/base |
Keywords: | Operating System: Unknown/Multiple
Architecture: | Type of failure: None/Unknown
Unknown/Multiple |
Test Case: | Blocked By:
Blocking: | Related Tickets:
Differential Rev(s): | Wiki Page:
-------------------------------------+-------------------------------------
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
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 :+ _
where Real r = r :+ 0
pattern Imaginary :: Num a => a -> Complex a
pattern Imaginary i <- _ :+ i
where Imaginary i = 0 :+ i
}}}
=== 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>
GHC <http://www.haskell.org/ghc/>
The Glasgow Haskell Compiler
More information about the ghc-tickets
mailing list