summaryrefslogtreecommitdiff
path: root/compiler/basicTypes/Id.hs
diff options
context:
space:
mode:
authorMatthew Pickering <matthewtpickering@gmail.com>2015-10-19 21:17:29 +0100
committerBen Gamari <ben@smart-cactus.org>2015-10-29 12:24:21 +0100
commit2a74a64e8329ab9e0c74bec47198cb492d25affb (patch)
tree2f0ac8dc3f1d372062eba5a4945fad55580cf9f0 /compiler/basicTypes/Id.hs
parenta0517889383127848faf82b32919d3f742a59278 (diff)
downloadhaskell-2a74a64e8329ab9e0c74bec47198cb492d25affb.tar.gz
Record pattern synonyms
This patch implements an extension to pattern synonyms which allows user to specify pattern synonyms using record syntax. Doing so generates appropriate selectors and update functions. === Interaction with Duplicate Record Fields === The implementation given here isn't quite as general as it could be with respect to the recently-introduced `DuplicateRecordFields` extension. Consider the following module: {-# LANGUAGE DuplicateRecordFields #-} {-# LANGUAGE PatternSynonyms #-} module Main where pattern S{a, b} = (a, b) pattern T{a} = Just a main = do print S{ a = "fst", b = "snd" } print T{ a = "a" } In principle, this ought to work, because there is no ambiguity. But at the moment it leads to a "multiple declarations of a" error. The problem is that pattern synonym record selectors don't do the same name mangling as normal datatypes when DuplicateRecordFields is enabled. They could, but this would require some work to track the field label and selector name separately. In particular, we currently represent datatype selectors in the third component of AvailTC, but pattern synonym selectors are just represented as Avails (because they don't have a corresponding type constructor). Moreover, the GlobalRdrElt for a selector currently requires it to have a parent tycon. (example due to Adam Gundry) === Updating Explicitly Bidirectional Pattern Synonyms === Consider the following ``` pattern Silly{a} <- [a] where Silly a = [a, a] f1 = a [5] -- 5 f2 = [5] {a = 6} -- currently [6,6] ``` === Fixing Polymorphic Updates === They were fixed by adding these two lines in `dsExpr`. This might break record updates but will be easy to fix. ``` + ; let req_wrap = mkWpTyApps (mkTyVarTys univ_tvs) - , pat_wrap = idHsWrapper } +, pat_wrap = req_wrap } ``` === Mixed selectors error === Note [Mixed Record Field Updates] ~~~~~~~~~~~~~~~~~~~~~~~~~~~~ Consider the following pattern synonym. data MyRec = MyRec { foo :: Int, qux :: String } pattern HisRec{f1, f2} = MyRec{foo = f1, qux=f2} This allows updates such as the following updater :: MyRec -> MyRec updater a = a {f1 = 1 } It would also make sense to allow the following update (which we reject). updater a = a {f1 = 1, qux = "two" } ==? MyRec 1 "two" This leads to confusing behaviour when the selectors in fact refer the same field. updater a = a {f1 = 1, foo = 2} ==? ??? For this reason, we reject a mixture of pattern synonym and normal record selectors in the same update block. Although of course we still allow the following. updater a = (a {f1 = 1}) {foo = 2} > updater (MyRec 0 "str") MyRec 2 "str"
Diffstat (limited to 'compiler/basicTypes/Id.hs')
-rw-r--r--compiler/basicTypes/Id.hs31
1 files changed, 26 insertions, 5 deletions
diff --git a/compiler/basicTypes/Id.hs b/compiler/basicTypes/Id.hs
index 7b54baae15..e22a77c07c 100644
--- a/compiler/basicTypes/Id.hs
+++ b/compiler/basicTypes/Id.hs
@@ -54,11 +54,13 @@ module Id (
isStrictId,
isExportedId, isLocalId, isGlobalId,
isRecordSelector, isNaughtyRecordSelector,
+ isPatSynRecordSelector,
+ isDataConRecordSelector,
isClassOpId_maybe, isDFunId,
isPrimOpId, isPrimOpId_maybe,
isFCallId, isFCallId_maybe,
isDataConWorkId, isDataConWorkId_maybe, isDataConId_maybe, idDataCon,
- isConLikeId, isBottomingId, idIsFrom,
+ idConLike, isConLikeId, isBottomingId, idIsFrom,
hasNoBinding,
-- ** Evidence variables
@@ -114,7 +116,6 @@ import Var( Id, DictId,
isId, isLocalId, isGlobalId, isExportedId )
import qualified Var
-import TyCon
import Type
import TysPrim
import DataCon
@@ -132,6 +133,7 @@ import UniqSupply
import FastString
import Util
import StaticFlags
+import {-# SOURCE #-} ConLike ( ConLike(..) )
-- infixl so you can say (id `set` a `set` b)
infixl 1 `setIdUnfoldingLazily`,
@@ -354,14 +356,17 @@ That is what is happening in, say tidy_insts in TidyPgm.
-}
-- | If the 'Id' is that for a record selector, extract the 'sel_tycon'. Panic otherwise.
-recordSelectorTyCon :: Id -> TyCon
+recordSelectorTyCon :: Id -> RecSelParent
recordSelectorTyCon id
= case Var.idDetails id of
- RecSelId { sel_tycon = tycon } -> tycon
+ RecSelId { sel_tycon = parent } -> parent
_ -> panic "recordSelectorTyCon"
+
isRecordSelector :: Id -> Bool
isNaughtyRecordSelector :: Id -> Bool
+isPatSynRecordSelector :: Id -> Bool
+isDataConRecordSelector :: Id -> Bool
isPrimOpId :: Id -> Bool
isFCallId :: Id -> Bool
isDataConWorkId :: Id -> Bool
@@ -373,7 +378,15 @@ isFCallId_maybe :: Id -> Maybe ForeignCall
isDataConWorkId_maybe :: Id -> Maybe DataCon
isRecordSelector id = case Var.idDetails id of
- RecSelId {} -> True
+ RecSelId {} -> True
+ _ -> False
+
+isDataConRecordSelector id = case Var.idDetails id of
+ RecSelId {sel_tycon = RecSelData _} -> True
+ _ -> False
+
+isPatSynRecordSelector id = case Var.idDetails id of
+ RecSelId {sel_tycon = RecSelPatSyn _} -> True
_ -> False
isNaughtyRecordSelector id = case Var.idDetails id of
@@ -424,6 +437,14 @@ idDataCon :: Id -> DataCon
-- INVARIANT: @idDataCon (dataConWrapId d) = d@: remember, 'dataConWrapId' can return either the wrapper or the worker
idDataCon id = isDataConId_maybe id `orElse` pprPanic "idDataCon" (ppr id)
+idConLike :: Id -> ConLike
+idConLike id =
+ case Var.idDetails id of
+ DataConWorkId con -> RealDataCon con
+ DataConWrapId con -> RealDataCon con
+ PatSynBuilderId ps -> PatSynCon ps
+ _ -> pprPanic "idConLike" (ppr id)
+
hasNoBinding :: Id -> Bool
-- ^ Returns @True@ of an 'Id' which may not have a
-- binding, even though it is defined in this module.