[ghc-steering-committee] Proposal #270: Support pun-free code. Recommendation: accept

Adam Gundry adam at well-typed.com
Mon Dec 12 20:00:38 UTC 2022


(Simon, I'm guessing this message should have gone to the committee 
list, so I'm including the full text below.)


On 12/12/2022 13:04, Simon Peyton Jones wrote:
>
>     The nested use is already possible with ExplicitNamespaces.
>     Currently it
>
>
> Wow. I had no idea.  The user manual is entirely silent on this point 
> <https://ghc.gitlab.haskell.org/ghc/doc/users_guide/exts/explicit_namespaces.html?highlight=explicitnamespace#explicit-namespaces-in-import-export>.  
> Is there some proposal that specifies this behaviour, which the user 
> manual is failing to document?  Or is the implementation doing 
> something that is nowhere specified?
>
>     I'm trying to understand what `import M type (MkT)` does
>
>
> Well the proposal says
> # With |type| specified in the import, only identifiers belonging to the 
> type namespace will be brought into the scope.
> I took this saying "behave exactly as now, but post-filter the imports 
> to take only the ones from the type namespace".  Today `import M( MkT 
> )` will be rejected; so I assume it'll still be rejected.
>
> I agree that this point could be more clearly articulated.
>
> Simon
>
> On Mon, 12 Dec 2022 at 12:22, Adam Gundry <adam at well-typed.com> wrote:
>
>     On 12/12/2022 11:39, Simon Peyton Jones wrote:
>     >         {-# LANGUAGE ExplicitNamespaces #-}
>     >         module N where
>     >           import M (T(type MkT)) -- NB "type" import of a data
>     constructor
>     >           v = MkT                -- usage at term level
>     >
>     >
>     > Crumbs.  I had not realised the proposal is to allow *nested*
>     uses of
>     > 'type' in import lists, as you show above.
>
>     The nested use is already possible with ExplicitNamespaces.
>     Currently it
>     allows
>
>          import M (T(type MkT))
>          import M (type MkT)
>          import M (pattern MkT)
>
>     whereas the proposal extends it to add the possibility to write
>
>          import M type (MkT)
>          import M data (MkT)
>          import M (data MkT)
>
>
>     >     In general, I don't feel the extensions to
>     ExplicitNamespaces included
>     >     in the proposal are very clearly specified.
>     >
>     >
>     > Actually isn't the proposal pretty clear on this, namely the first
>     > bullet of proposed change spec
>     >
>     <https://github.com/hithroc/ghc-proposals/blob/master/proposals/0000-support-pun-free-code.md#2-proposed-change-specification>.
>     It only covers
>     > import M *type *
>     > import M *data *as MD
>     > where I have emboldened the new bits.  Nothing about the
>     contents of
>     > import lists.   Why did you think your example is covered by the
>     proposal?
>
>     I'm trying to understand what
>
>          import M type (MkT)
>
>     means where MkT is a data constructor (or if it raises some kind of
>     error). This was by analogy to the existing
>
>          import M (T(type MkT))
>
>     which means something today, albeit not necessarily a very sensible
>     thing (per https://gitlab.haskell.org/ghc/ghc/-/issues/22581).
>
>     I don't see a clear specification of the proposed (extended)
>     semantics
>     of ExplicitNamespaces in the proposal, but perhaps I've missed
>     something?
>
>     Cheers,
>
>     Adam
>
>
>     > On Mon, 12 Dec 2022 at 09:15, Adam Gundry <adam at well-typed.com
>     > <mailto:adam at well-typed.com>> wrote:
>     >
>     >     Actually, reading
>     https://gitlab.haskell.org/ghc/ghc/-/issues/22581
>     >     <https://gitlab.haskell.org/ghc/ghc/-/issues/22581> I
>     >     realised I'm unclear how the proposed extensions to
>     ExplicitNamespaces
>     >     are supposed to work. The existing situation is apparently
>     that for a
>     >     (non-punned) data constructor, it is possible to use either a
>     >     pattern or
>     >     type qualifier in an import list (presumably because
>     DataKinds means
>     >     the
>     >     constructor is in scope at both the term and type levels),
>     and the
>     >     imported constructor is then usable in both contexts.
>     >
>     >     For example, the following is accepted at present:
>     >
>     >          module M where
>     >            data T = MkT
>     >
>     >         {-# LANGUAGE ExplicitNamespaces #-}
>     >         module N where
>     >           import M (T(type MkT)) -- NB "type" import of a data
>     constructor
>     >           v = MkT                -- usage at term level
>     >
>     >     The present proposal says "With type specified in the
>     import, only
>     >     identifiers belonging to the type namespace will be brought
>     into the
>     >     scope." I'm not exactly sure how to interpret this, does it
>     mean the
>     >     following alternative will be accepted or rejected?
>     >
>     >         module N where
>     >           import M type (MkT)
>     >           v = MkT
>     >
>     >     I'm worried we will end up with a situation where
>     ExplicitNamespaces
>     >     does subtly different things depending on the position of
>     the keyword.
>     >
>     >     In general, I don't feel the extensions to
>     ExplicitNamespaces included
>     >     in the proposal are very clearly specified. Given the
>     discussion about
>     >     exactly which parts belong to
>     ExplicitNamespaces/PatternSynonyms versus
>     >     separate extensions, perhaps we should accept the parts
>     relating to
>     >     -Wpuns/-Wpun-bindings, but ask for the ExplicitNamespaces
>     changes to be
>     >     proposed separately?
>     >
>     >     Cheers,
>     >
>     >     Adam
>     >
>     >
>     >     On 09/12/2022 11:11, Adam Gundry wrote:
>     >      > I'm broadly in favour of accepting the proposal. I
>     realise the
>     >     history
>     >      > is complex here, so I don't think we should ask anyone to
>     rewrite
>     >     things
>     >      > further, though in general it would be nicer to have separate
>     >     proposals
>     >      > for -Wpuns/-Wpun-bindings (which is unambiguously fine)
>     and for the
>     >      > changes to imports (which as Joachim points out raise
>     issues).
>     >      >
>     >      > I'm a bit concerned that the proposal does not motivate
>     or specify
>     >      > -Wpattern-namespace-qualified very well.
>     >      >
>     >      >
>     >      > On 08/12/2022 08:33, Joachim Breitner wrote:
>     >      >> ...
>     >      >>
>     >      >> This gives us (at least) these options:
>     >      >>
>     >      >> 1. Leave ExplicitNamespaces alone, add ExplicitNamespaces to
>     >     GHC2023,
>     >      >>     introduce one or two new extensions for the newer
>     changes.
>     >      >> 2. Extend ExplicitNamespaces, and don’t add it already
>     to GHC2023,
>     >      >>     disregarding issue #551.
>     >      >> 3. Add ExplicitNamespaces to GHC2023, and still add it
>     to GHC2023,
>     >      >>     arguing that GHC20xx allows more liberal
>     (backward-compatibile)
>     >      >>     changes than, say, Haskell2010 would allow.
>     >      >>
>     >      >> Certainly 1 is the least bold move. I am not sure what
>     the best way
>     >      >> forwards is, and welcome other opinions.
>     >      >
>     >      > I would prefer a variant of 1: allow "data" as a keyword in
>     >     import lists
>     >      > under ExplicitNamespaces, but make the other changes
>     under other
>     >      > extensions.
>     >      >
>     >      > As I've said previously, I have a general preference for
>     multiple
>     >     small,
>     >      > orthogonal extensions rather than changing existing
>     extensions to
>     >     add
>     >      > unrelated features that happen to be in similar
>     territory. I realise
>     >      > this is controversial, of course.
>     >      >
>     >      > Cheers,
>     >      >
>     >      > Adam
>

-- 
Adam Gundry, Haskell Consultant
Well-Typed LLP,https://www.well-typed.com/

Registered in England & Wales, OC335890
27 Old Gloucester Street, London WC1N 3AX, England
-------------- next part --------------
An HTML attachment was scrubbed...
URL: <http://mail.haskell.org/pipermail/ghc-steering-committee/attachments/20221212/522ed80e/attachment.html>


More information about the ghc-steering-committee mailing list