[commit: ghc] master: Implement pattern synonyms (4f8369b)

git at git.haskell.org git at git.haskell.org
Mon Jan 20 20:58:23 UTC 2014


Repository : ssh://git@git.haskell.org/ghc

On branch  : master
Link       : http://ghc.haskell.org/trac/ghc/changeset/4f8369bf47d27b11415db251e816ef1a2e1eb3d8/ghc

>---------------------------------------------------------------

commit 4f8369bf47d27b11415db251e816ef1a2e1eb3d8
Author: Dr. ERDI Gergo <gergo at erdi.hu>
Date:   Mon Jan 13 20:12:34 2014 +0800

    Implement pattern synonyms
    
    This patch implements Pattern Synonyms (enabled by -XPatternSynonyms),
    allowing y ou to assign names to a pattern and abstract over it.
    
    The rundown is this:
    
      * Named patterns are introduced by the new 'pattern' keyword, and can
        be either *unidirectional* or *bidirectional*. A unidirectional
        pattern is, in the simplest sense, simply an 'alias' for a pattern,
        where the LHS may mention variables to occur in the RHS. A
        bidirectional pattern synonym occurs when a pattern may also be used
        in expression context.
    
      * Unidirectional patterns are declared like thus:
    
            pattern P x <- x:_
    
        The synonym 'P' may only occur in a pattern context:
    
            foo :: [Int] -> Maybe Int
            foo (P x) = Just x
            foo _     = Nothing
    
      * Bidirectional patterns are declared like thus:
    
            pattern P x y = [x, y]
    
        Here, P may not only occur as a pattern, but also as an expression
        when given values for 'x' and 'y', i.e.
    
            bar :: Int -> [Int]
            bar x = P x 10
    
      * Patterns can't yet have their own type signatures; signatures are inferred.
    
      * Pattern synonyms may not be recursive, c.f. type synonyms.
    
      * Pattern synonyms are also exported/imported using the 'pattern'
        keyword in an import/export decl, i.e.
    
            module Foo (pattern Bar) where ...
    
        Note that pattern synonyms share the namespace of constructors, so
        this disambiguation is required as a there may also be a 'Bar'
        type in scope as well as the 'Bar' pattern.
    
      * The semantics of a pattern synonym differ slightly from a typical
        pattern: when using a synonym, the pattern itself is matched,
        followed by all the arguments. This means that the strictness
        differs slightly:
    
            pattern P x y <- [x, y]
    
            f (P True True) = True
            f _             = False
    
            g [True, True] = True
            g _            = False
    
        In the example, while `g (False:undefined)` evaluates to False,
        `f (False:undefined)` results in undefined as both `x` and `y`
        arguments are matched to `True`.
    
    For more information, see the wiki:
    
        https://ghc.haskell.org/trac/ghc/wiki/PatternSynonyms
        https://ghc.haskell.org/trac/ghc/wiki/PatternSynonyms/Implementation
    
    Reviewed-by: Simon Peyton Jones <simonpj at microsoft.com>
    Signed-off-by: Austin Seipp <austin at well-typed.com>


>---------------------------------------------------------------

4f8369bf47d27b11415db251e816ef1a2e1eb3d8
 compiler/basicTypes/BasicTypes.lhs                 |   20 ++
 compiler/basicTypes/ConLike.lhs                    |   82 +++++
 compiler/basicTypes/DataCon.lhs-boot               |    9 +-
 compiler/basicTypes/OccName.lhs                    |    5 +-
 compiler/basicTypes/PatSyn.lhs                     |  225 ++++++++++++++
 compiler/basicTypes/PatSyn.lhs-boot                |   19 ++
 compiler/deSugar/Check.lhs                         |   52 +++-
 compiler/deSugar/Coverage.lhs                      |    9 +-
 compiler/deSugar/Desugar.lhs                       |   17 +-
 compiler/deSugar/DsBinds.lhs                       |   12 +-
 compiler/deSugar/DsExpr.lhs                        |   13 +-
 compiler/deSugar/DsMeta.hs                         |    4 +-
 compiler/deSugar/DsMonad.lhs                       |   18 +-
 compiler/deSugar/DsUtils.lhs                       |  236 ++++++++------
 compiler/deSugar/Match.lhs                         |   28 +-
 compiler/deSugar/MatchCon.lhs                      |   59 +++-
 compiler/ghc.cabal.in                              |    3 +
 compiler/ghc.mk                                    |    2 +
 compiler/hsSyn/Convert.lhs                         |    8 +-
 compiler/hsSyn/HsBinds.lhs                         |  100 +++++-
 compiler/hsSyn/HsExpr.lhs                          |    4 +
 compiler/hsSyn/HsPat.lhs                           |   22 +-
 compiler/hsSyn/HsPat.lhs-boot                      |    2 +
 compiler/hsSyn/HsTypes.lhs                         |   12 +-
 compiler/hsSyn/HsUtils.lhs                         |   28 +-
 compiler/iface/BinIface.hs                         |    3 +-
 compiler/iface/BuildTyCl.lhs                       |   69 +++++
 compiler/iface/IfaceSyn.lhs                        |   72 ++++-
 compiler/iface/MkIface.lhs                         |   30 +-
 compiler/iface/TcIface.lhs                         |   48 ++-
 compiler/main/DynFlags.hs                          |    4 +-
 compiler/main/HscMain.hs                           |    1 +
 compiler/main/HscStats.hs                          |   63 ++--
 compiler/main/HscTypes.lhs                         |   58 +++-
 compiler/main/PprTyThing.hs                        |   29 +-
 compiler/main/TidyPgm.lhs                          |   11 +-
 compiler/parser/Lexer.x                            |   13 +-
 compiler/parser/Parser.y.pp                        |   18 ++
 compiler/parser/RdrHsSyn.lhs                       |    8 +-
 compiler/prelude/TysWiredIn.lhs                    |    7 +-
 compiler/rename/RnBinds.lhs                        |  152 +++++++--
 compiler/rename/RnEnv.lhs                          |    7 +-
 compiler/rename/RnNames.lhs                        |   18 ++
 compiler/rename/RnPat.lhs                          |   26 +-
 compiler/rename/RnSource.lhs                       |   25 +-
 compiler/typecheck/TcBinds.lhs                     |  172 +++++++----
 compiler/typecheck/TcClassDcl.lhs                  |   18 +-
 compiler/typecheck/TcDeriv.lhs                     |    3 +-
 compiler/typecheck/TcEnv.lhs                       |   16 +-
 compiler/typecheck/TcExpr.lhs                      |   12 +-
 compiler/typecheck/TcForeign.lhs                   |    3 +-
 compiler/typecheck/TcGenDeriv.lhs                  |   50 +--
 compiler/typecheck/TcGenGenerics.lhs               |    6 +-
 compiler/typecheck/TcHsSyn.lhs                     |   40 ++-
 compiler/typecheck/TcHsType.lhs                    |    3 +-
 compiler/typecheck/TcInstDcls.lhs                  |   28 +-
 compiler/typecheck/TcPat.lhs                       |  130 ++++++--
 compiler/typecheck/TcPatSyn.lhs                    |  324 ++++++++++++++++++++
 compiler/typecheck/TcPatSyn.lhs-boot               |   16 +
 compiler/typecheck/TcRnDriver.lhs                  |   15 +-
 compiler/typecheck/TcRnMonad.lhs                   |    8 +-
 compiler/typecheck/TcRnTypes.lhs                   |   33 +-
 compiler/typecheck/TcSplice.lhs                    |    3 +-
 compiler/typecheck/TcTyClsDecls.lhs                |    2 +-
 compiler/types/TypeRep.lhs                         |   10 +-
 compiler/utils/UniqFM.lhs                          |   13 +
 compiler/utils/UniqSet.lhs                         |    1 +
 ghc/GhciTags.hs                                    |   10 +-
 testsuite/tests/driver/T4437.hs                    |    3 +-
 testsuite/tests/ghc-api/T6145.hs                   |   10 +-
 testsuite/tests/{annotations => patsyn}/Makefile   |    0
 testsuite/tests/patsyn/should_compile/.gitignore   |    9 +
 .../should_compile/Makefile                        |    0
 testsuite/tests/patsyn/should_compile/all.T        |    9 +
 testsuite/tests/patsyn/should_compile/bidir.hs     |    6 +
 testsuite/tests/patsyn/should_compile/ex-num.hs    |    9 +
 testsuite/tests/patsyn/should_compile/ex-prov.hs   |   12 +
 testsuite/tests/patsyn/should_compile/ex-view.hs   |   12 +
 testsuite/tests/patsyn/should_compile/ex.hs        |   13 +
 .../tests/patsyn/should_compile/incomplete.hs      |   11 +
 testsuite/tests/patsyn/should_compile/num.hs       |    6 +
 testsuite/tests/patsyn/should_compile/overlap.hs   |    9 +
 testsuite/tests/patsyn/should_compile/univ.hs      |   11 +
 .../should_compile => patsyn/should_fail}/Makefile |    0
 testsuite/tests/patsyn/should_fail/all.T           |    3 +
 testsuite/tests/patsyn/should_fail/mono.hs         |    7 +
 testsuite/tests/patsyn/should_fail/mono.stderr     |   12 +
 testsuite/tests/patsyn/should_fail/unidir.hs       |    4 +
 testsuite/tests/patsyn/should_fail/unidir.stderr   |    4 +
 testsuite/tests/patsyn/should_run/.gitignore       |    7 +
 .../should_compile => patsyn/should_run}/Makefile  |    0
 testsuite/tests/patsyn/should_run/all.T            |    3 +
 testsuite/tests/patsyn/should_run/eval.hs          |   22 ++
 testsuite/tests/patsyn/should_run/eval.stdout      |    7 +
 testsuite/tests/patsyn/should_run/ex-prov-run.hs   |   21 ++
 .../should_run/ex-prov-run.stdout}                 |    0
 testsuite/tests/patsyn/should_run/match.hs         |   21 ++
 testsuite/tests/patsyn/should_run/match.stdout     |    5 +
 utils/ghctags/Main.hs                              |    5 +-
 99 files changed, 2324 insertions(+), 484 deletions(-)

Diff suppressed because of size. To see it, use:

    git diff-tree --root --patch-with-stat --no-color --find-copies-harder --ignore-space-at-eol --cc 4f8369bf47d27b11415db251e816ef1a2e1eb3d8


More information about the ghc-commits mailing list