[GHC] #12001: RFC: Add pattern synonyms to base

#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

#12001: RFC: Add pattern synonyms to base -------------------------------------+------------------------------------- Reporter: Iceland_jack | Owner: 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: | -------------------------------------+------------------------------------- Comment (by Iceland_jack): {{{#!hs pattern II :: Int -> Int# pattern II i <- (I# -> i) where II (I# i) = i pattern FF :: Float -> Float# pattern FF f <- (F# -> f) where FF (F# f) = f }}} also if GHC allowed unlifted types in pattern synonyms, should that be a ticket? {{{ tImB.hs:6:22-25: error: … • Expecting a lifted type, but ‘Int#’ is unlifted • In the type ‘Int#’ tImB.hs:10:22-27: error: … • Expecting a lifted type, but ‘Float#’ is unlifted • In the type ‘Float#’ Compilation failed. }}} -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/12001#comment:1 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#12001: RFC: Add pattern synonyms to base -------------------------------------+------------------------------------- Reporter: Iceland_jack | Owner: 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: | -------------------------------------+------------------------------------- Comment (by Iceland_jack): Some random ideas, === Data.Functor.Const === {{{#!hs pattern K :: forall a (b :: k). a -> Const a b pattern K a = Const a pattern K' :: forall a (b :: k). a -> Constant a b pattern K' a = Constant a }}} === GHC.Generics === {{{#!hs isAssociative :: Associativity -> Bool isAssociative LeftAssociative = True isAssociative RightAssociative = True isAssociative NotAssociative = False pattern Associative :: Associative pattern Associative <- (isAssociative -> True) }}} === Data.Ratio === {{{#!hs pattern Denominator :: a -> Ratio a pattern Denominator a <- (denominator -> a) pattern Numerator :: a -> Ratio a pattern Numerator a <- (numerator -> a) pattern (:%) :: Integral a => a -> a -> Ratio a pattern num :% den <- ((\r -> (numerator r, denominator r)) -> (num, den)) where num :% den = num % den }}} === System.Exit === {{{#!hs exitCode :: ExitCode -> Int exitCode = \case ExitSuccess -> 0 ExitFailure n -> n pattern ExitCode :: Int -> ExitCode pattern ExitCode n <- (exitCode -> n) where ExitCode 0 = ExitSuccess ExitCode n = ExitFailure n }}} === Data.Maybe === {{{#!hs pattern Some :: a -> Maybe a pattern Some a = Just a pattern None :: a -> Maybe a pattern None = Nothing }}} === Data.Functor.Identity === {{{#!hs pattern I :: a -> Identity pattern I a = Identity a }}} === Data.Ord === {{{#!hs pattern :: Ordering pattern Less = LT pattern :: Ordering pattern Equal = EQ pattern :: Ordering pattern Greater = GT }}} === Data.Foldable === {{{#!hs pattern Null :: Foldable f => f a pattern Null <- (null -> True) }}} === Data.Bool === {{{#!hs pattern T :: Bool pattern T = True pattern F :: Bool pattern F = False }}} It's fine if these don't get accepted, just throwing them into the universe -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/12001#comment:2 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#12001: RFC: Add pattern synonyms to base -------------------------------------+------------------------------------- Reporter: Iceland_jack | Owner: 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: | -------------------------------------+------------------------------------- Comment (by nomeata): I am very sceptical. Pattern synonyms are still relatively new, and I would say that best practices around them have not evolved yet (e.g.: should they be used for non-injective convenience patterns like `Popcount` at all? Should they be used for anything else but compatible or alternative views on data types?) Also, they clutter the namespace. Therefore, I would prefer if less central libraries would be first to take up pattern synonym and explore usage patterns, until it becomes apparent with which intensity pattern synonym make most sense. More concretely, of your list above, I’d give a +1 only to `Polar`. This is a genuine, self-descriptive constructor-like view on a data type. A bit fishy around 0, but that’s inherent in the general concept and not an issue with the constructor. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/12001#comment:3 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#12001: RFC: Add pattern synonyms to base -------------------------------------+------------------------------------- Reporter: Iceland_jack | Owner: 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: | -------------------------------------+------------------------------------- Comment (by ekmett): I'm pretty much in the same camp as Joachim: The only one of these that I think really passes muster as a pattern that models a constructor is `Polar`. It doesn't destroy information when you pattern match with it and then reconstruct. (It does, however, destroy the phase information if the magnitude is 0 if you construct then deconstruct). The rest seem all better managed as view patterns, using existing combinators so that their lossy nature is much more clear. It is worthy of discussion to explore whether we're ready to start incorporating patterns into the bulk of `base`, but I personally think I'd like to see them endure a couple of releases without the sorts of major overhauls they have going on with how to put signatures on them, etc. before they started taking a more prominent role in a place where they'd be as hard to dislodge as `base`. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/12001#comment:4 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#12001: RFC: Add pattern synonyms to base -------------------------------------+------------------------------------- Reporter: Iceland_jack | Owner: 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: | -------------------------------------+------------------------------------- Comment (by Iceland_jack): Great responses, there are obviously no best practices yet for this extension. As the dust settles, will we only accept ''constructor-like'' patterns? Are non-constructor-like patterns wholly undesirable or are there examples where they are worth it? I personally use all of these to good effect, let's wait until we understand them better. Let's identify and categorise some of these examples: === Literal synonyms === Bidirectional patterns, nothing fancy {{{#!hs pattern I a = Identity a pattern K a = Const a pattern Less = LT }}} === ‘Getter’ patterns === Unidirectional patterns, these are essentially ‘Getter’s {{{#!hs pattern Real r <- r :+ _ pattern Imaginary i <- _ :+ i }}} === Constructor-Like Patterns === (Implicitly) bidirectional patterns that don't lose information {{{#!hs pattern Real, Imaginary :: (Num a, Eq a) => a -> Complex pattern Real r = r :+ 0 (Implicitly) pattern Imaginary i = 0 :+ i }}} In this case this is the identity function on complex numbers: {{{#!hs f :: (Num a, Eq a) => Complex a -> Complex a f (Real r) = Real r f complex = complex }}} @ekmett argues for this property [https://github.com/ekmett/lens/issues/653 here]. === Non-Constructor-Like Patterns === Explicitly bidirectional patterns that do lose information {{{#!hs pattern Real, Imaginary :: Num a => a -> Complex a pattern Real r <- r :+ _ where Real r = r :+ 0 pattern Imaginary i <- _ :+ i where Imaginary i = 0 :+ i }}} We lose the constructor property, but matching never fails so it's closer to the lens `_realPart`. ---- We can keep this ticket open until the extension and understanding matures, same as #11349 where [https://github.com/RyanGlScott/proxied/blob/master/src/Data/Proxyless.hs Data.Proxyless] was created in response. It has been said of me that I embrace pattern synonyms to “almost an absurd level” so someone needs to show restraint `:--)` tickets such as #11977 show that this extension still isn't even fully understood and I look forward to seeing how it evolves -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/12001#comment:5 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#12001: RFC: Add pattern synonyms to base -------------------------------------+------------------------------------- Reporter: Iceland_jack | Owner: 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: | -------------------------------------+------------------------------------- Comment (by Iceland_jack): Since `Polar` was the pick of the litter, it's worth mentioning that with record syntax: {{{#!hs pattern Polar :: RealFloat a => a -> a -> Complex a pattern Polar {m, theta} <- (polar -> (m, theta)) where Polar m theta = mkPolar m theta }}} we can write {{{ ghci> (3 :+ 1) { m = 2 } 1.8973665961010275 :+ 0.6324555320336759 ghci> ghci> set (_polar._1) 2 (3 :+ 1) 1.8973665961010275 :+ 0.6324555320336759 }}} -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/12001#comment:6 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#12001: RFC: Add pattern synonyms to base -------------------------------------+------------------------------------- Reporter: Iceland_jack | Owner: 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: | -------------------------------------+------------------------------------- Comment (by Iceland_jack): === GHC.Generics === {{{#!hs pattern From :: Generic a => (Rep a) x -> a pattern From rep <- (from → rep) where From rep = to rep pattern From1 :: Generic1 f => (Rep1 f) a -> f a pattern From1 rep <- (from1 → rep) where From1 rep = to1 rep }}} or corresponding `To`, `To1` patterns. === Text.Read === {{{#!hs pattern Read :: Read a => a -> String pattern Read a <- (readMaybe -> Just a) }}} with the caveat that they parse different types, {{{#!hs foo :: String -> String foo (Read 42) = "answer" foo (Read n) = "some other number " ++ show n foo _ = "can't parse" }}} {{{ ghci> foo "()" "some other number ()" }}} If the types are made explicit with #11350 {{{#!hs foo :: String -> String foo (Read @Integer 42) = "answer" foo (Read @() n) = "some other number " ++ show n foo _ = "can't parse" }}} it is a common action and pattern (search for `pattern` and `readMaybe -> Just`), and is often use to pattern match on numbers. Artificially restricting the type avoids it matching `()` {{{#!hs pattern ReadNumber :: (Num a, Read a) => a -> String }}} This is cool {{{ ghci> [ n | ReadNumber n <- words "from 2010 ... 2016 they were 4" ] [2010,2016,4] }}} -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/12001#comment:7 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#12001: RFC: Add pattern synonyms to base -------------------------------------+------------------------------------- Reporter: Iceland_jack | Owner: 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: | -------------------------------------+------------------------------------- Comment (by Iceland_jack): Not sure if makes sense === Control.DeepSeq === {{{#!hs pattern Force :: NFData a => a -> a pattern Force a <- !(force -> a) }}} -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/12001#comment:8 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#12001: RFC: Add pattern synonyms to base -------------------------------------+------------------------------------- Reporter: Iceland_jack | Owner: 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: | -------------------------------------+------------------------------------- Comment (by Iceland_jack): With `UnboxedSums` {{{#!hs pattern Left# :: a -> (# a | b #) pattern Left# a = (# a | #) pattern Right# :: b -> (# a | b #) pattern Right# b = (# | b #) }}} -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/12001#comment:9 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#12001: RFC: Add pattern synonyms to base -------------------------------------+------------------------------------- Reporter: Iceland_jack | Owner: 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: | -------------------------------------+------------------------------------- Comment (by Iceland_jack): See #12767: {{{#!hs pattern Cont :: ((a -> r) -> r) -> Cont r a pattern Cont a <- (runCont -> a) where Cont a = cont a pattern Writer :: (a, w) -> Writer w a pattern Writer a <- (runWriter -> a) where Writer a = WriterT (Identity a) pattern Reader :: (r -> a) -> Reader r a pattern Reader a <- (runReader -> a) where Reader a = reader a pattern State :: (s -> (a, s)) -> State s a pattern State a <- (runState -> a) where State a = state a }}} -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/12001#comment:10 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#12001: RFC: Add pattern synonyms to base -------------------------------------+------------------------------------- Reporter: Iceland_jack | Owner: 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: | -------------------------------------+------------------------------------- Comment (by Iceland_jack): For [https://hackage.haskell.org/package/base-4.9.0.0/docs/Data-List- NonEmpty.html Data.List.NonEmpty] {{{#!hs pattern NonEmpty :: NonEmpty a -> [a] pattern NonEmpty xs <- (nonEmpty -> Just xs) where NonEmpty xs = toList xs {-# COMPLETE [], NonEmpty #-} }}} using PatternSynonyms/CompleteSigs. == Uses == The pattern of destructing a `NonEmpty` value only to reassemble it pop up when using `NonEmpty` {{{#!hs f [] = ... f (x:xs) = ... (x:|xs) }}} An example is {{{#!hs -- match_groups :: [[(PatGroup,EquationInfo)]] -> DsM (NonEmpty MatchResult) -- match_groups [] = matchEmpty v ty -- match_groups (g:gs) = mapM match_group (g:|gs) match_groups :: [[(PatGroup,EquationInfo)]] -> DsM (NonEmpty MatchResult) match_groups [] = matchEmpty v ty match_groups (NonEmpty gs) = mapM match_group gs }}} Which can be abstracted into this rather useful eliminator: {{{#!hs -- match_groups = neElim (matchEmpty v ty) (mapM match_group) neElim :: c -> (NonEmpty a -> c) -> [a] -> c neElim c _ [] = c neElim _ f (NonEmpty xs) = f xs }}} -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/12001#comment:11 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#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

#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: | -------------------------------------+------------------------------------- Comment (by Iceland_jack): Examples added to [https://gist.github.com/Icelandjack/dc50599550545cb53857bcb6622cf270 gist]. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/12001#comment:13 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#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: Old 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 }}}
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 <- (isInfinite -> True) where Infinity = 1 / 0 }}} Used [https://github.com/cchalmers/optical/blob/a85484ad23a7f4d6b5da1dcb78781ea9c4... here] -- -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/12001#comment:14 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#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: Old 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 <- (isInfinite -> True) where Infinity = 1 / 0 }}}
Used [https://github.com/cchalmers/optical/blob/a85484ad23a7f4d6b5da1dcb78781ea9c4... here]
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 <- (isInfinite -> True) where Infinity = 1 / 0 === Foreign.Ptr === {{{#!hs pattern NullPtr :: Ptr a pattern NullPtr <- ((==) nullPtr -> True) where NullPtr = nullPtr }}} Used [https://github.com/cchalmers/optical/blob/a85484ad23a7f4d6b5da1dcb78781ea9c4... here] -- -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/12001#comment:15 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#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: Old 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 <- (isInfinite -> True) where Infinity = 1 / 0
=== Foreign.Ptr === {{{#!hs pattern NullPtr :: Ptr a pattern NullPtr <- ((==) nullPtr -> True) where NullPtr = nullPtr }}}
Used [https://github.com/cchalmers/optical/blob/a85484ad23a7f4d6b5da1dcb78781ea9c4... here]
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 <- (isInfinite -> True) where Infinity = 1 / 0 }}} === Foreign.Ptr === {{{#!hs pattern NullPtr :: Ptr a pattern NullPtr <- ((==) nullPtr -> True) where NullPtr = nullPtr }}} Used [https://github.com/cchalmers/optical/blob/a85484ad23a7f4d6b5da1dcb78781ea9c4... here] -- -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/12001#comment:16 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler
participants (1)
-
GHC