Broken Data.Data instances

Richard Eisenberg eir at cis.upenn.edu
Mon Jul 28 01:49:42 UTC 2014


What if there is a good reason for a missing/broken Data.Data instance? I'm specifically thinking of GADTs. There are few currently, but I, for one, have toyed with the idea of adding more. My recollection is that Data.Data doesn't work with GADTs. As a concrete, existent example, see CoAxiom.BranchList, which allows for type-level reification of singleton lists as distinct from other, not-necessarily-singleton lists.

I would very much like to support API usage that would benefit from working Data.Data instances, but I also want to be sure we're not eliminating other possible futures without due discussion.

Richard

On Jul 27, 2014, at 2:04 PM, "Alan & Kim Zimmerman" <alan.zimm at gmail.com> wrote:

> Philip
> 
> How would you like to take this forward? From my side I would appreciate all guidance/help to get it resolved, it is a huge hindrance for HaRe.
> 
> Alan
> 
> 
> On Sun, Jul 27, 2014 at 7:27 PM, Edward Kmett <ekmett at gmail.com> wrote:
> Philip, Alan, 
> 
> If you need a hand, I'm happy to pitch in guidance. 
> 
> I've had to mangle a bunch of hand-written Data instances and push out patches to a dozen packages that used to be built this way before I convinced the authors to switch to safer versions of Data. Using virtual smart constructors like we do now in containers and Text where needed can be used to preserve internal invariants, etc.
> 
> This works far better for users of the API than just randomly throwing them a live hand grenade. As I recall, these little grenades in generic programming over the GHC API have been a constant source of pain for libraries like haddock.
> 
> Simon,
> 
> It seems to me that regarding circular data structures, nothing prevents you from walking a circular data structure with Data.Data. You can generate a new one productively that looks just like the old with the contents swapped out, it is indistinguishable to an observer if the fixed point is lost, and a clever observer can use observable sharing to get it back, supposing that they are allowed to try.
> 
> Alternately, we could use the 'virtual constructor' trick there to break the cycle and reintroduce it, but I'm less enthusiastic about that idea, even if it is simpler in many ways.
> 
> -Edward
> 
> 
> On Sun, Jul 27, 2014 at 10:17 AM, <p.k.f.holzenspies at utwente.nl> wrote:
> Alan,
> 
> In that case, let's have a short feedback-loop between the two of us. It seems many of these files (Name.lhs, for example) are really stable through the repo-history. It would be nice to have one bigger refactoring all in one go (some of the code could use a polish, a lot of code seems removable).
> 
> Regards,
> Philip
> 
> Van: Alan & Kim Zimmerman [alan.zimm at gmail.com]
> Verzonden: vrijdag 25 juli 2014 13:44
> Aan: Simon Peyton Jones
> CC: Holzenspies, P.K.F. (EWI); ghc-devs at haskell.org
> Onderwerp: Re: Broken Data.Data instances
> 
> By the way, I would be happy to attempt this task, if the concept is viable.
> 
> 
> On Thu, Jul 24, 2014 at 11:23 PM, Alan & Kim Zimmerman <alan.zimm at gmail.com> wrote:
> While we are talking about fixing traversals, how about getting rid of the phase specific panic initialisers for placeHolderType, placeHolderKind and friends?
> 
> In order to safely traverse with SYB, the following needs to be inserted into all the SYB schemes (see 
> https://github.com/alanz/HaRe/blob/master/src/Language/Haskell/Refact/Utils/GhcUtils.hs)
> 
> -- Check the Typeable items
> checkItemStage1 :: (Typeable a) => SYB.Stage -> a -> Bool
> checkItemStage1 stage x = (const False `SYB.extQ` postTcType `SYB.extQ` fixity `SYB.extQ` nameSet) x
>   where nameSet     = const (stage `elem` [SYB.Parser,SYB.TypeChecker]) :: GHC.NameSet       -> Bool
>         postTcType  = const (stage < SYB.TypeChecker                  ) :: GHC.PostTcType    -> Bool
>         fixity      = const (stage < SYB.Renamer                      ) :: GHC.Fixity        -> Bool
> 
> And in addition HsCmdTop and ParStmtBlock are initialised with explicit 'undefined values.
> 
> Perhaps use an initialiser that can have its panic turned off when called via the GHC API?
> 
> Regards
>   Alan
> 
> 
> 
> On Thu, Jul 24, 2014 at 11:06 PM, Simon Peyton Jones <simonpj at microsoft.com> wrote:
> So... does anyone object to me changing these "broken" instances with the ones given by DeriveDataTypeable?
> 
> 
> That’s fine with me provided (a) the default behaviour is not immediate divergence (which it might well be), and (b) the pitfalls are documented.
> 
>  
> 
> Simon
> 
>  
> 
> From: "Philip K.F. Hölzenspies" [mailto:p.k.f.holzenspies at utwente.nl] 
> Sent: 24 July 2014 18:42
> To: Simon Peyton Jones
> Cc: ghc-devs at haskell.org
> Subject: Re: Broken Data.Data instances
> 
>  
> 
> Dear Simon, et al,
> 
> These are very good points to make for people writing such traversals and queries. I would be more than happy to write a page on the pitfalls etc. on the wiki, but in my experience so far, exploring the innards of GHC is tremendously helped by trying small things out and showing (bits of) the intermediate structures. For me, personally, this has always been hindered by the absence of good instances of Data and/or Show (not having to bring DynFlags and not just visualising with the pretty printer are very helpful).
> 
> So... does anyone object to me changing these "broken" instances with the ones given by DeriveDataTypeable?
> 
> Also, many of these internal data structures could be provided with useful lenses to improve such traversals further. Anyone ever go at that? Would be people be interested?
> 
> Regards,
> Philip
> 
> 
> 
> <image001.jpg>
> 
> Simon Peyton Jones
> 
> 24 Jul 2014 18:22
> 
> GHC’s data structures are often mutually recursive. e.g.
> 
> ·        The TyCon for Maybe contains the DataCon for Just
> 
> ·        The DataCon For just contains Just’s type
> 
> ·        Just’s type contains the TyCon for Maybe
> 
>  
> 
> So any attempt to recursively walk over all these structures, as you would a tree, will fail. 
> 
>  
> 
> Also there’s a lot of sharing.  For example, every occurrence of ‘map’ is a Var, and inside that Var is map’s type, its strictness, its rewrite RULE, etc etc.  In walking over a term you may not want to walk over all that stuff at every occurrence of map.
> 
>  
> 
> Maybe that’s it; I’m not certain since I did not write the Data instances for any of GHC’s types
> 
>  
> 
> Simon
> 
>  
> 
> From: ghc-devs [mailto:ghc-devs-bounces at haskell.org] On Behalf Of p.k.f.holzenspies at utwente.nl
> Sent: 24 July 2014 16:42
> To: ghc-devs at haskell.org
> Subject: Broken Data.Data instances
> 
>  
> 
> Dear GHC-ers,
> 
>  
> 
> Is there a reason for explicitly broken Data.Data instances? Case in point:
> 
>  
> 
> > instance Data Var where
> 
> >   -- don't traverse?
> 
> >   toConstr _   = abstractConstr "Var"
> 
> >   gunfold _ _  = error "gunfold"
> 
> >   dataTypeOf _ = mkNoRepType "Var"
> 
>  
> 
> I understand (vaguely) arguments about abstract data types, but this also excludes convenient queries that can, e.g. extract all types from a CoreExpr. I had hoped to do stuff like this:
> 
>  
> 
> > collect :: (Typeable b, Data a, MonadPlus m) => a -> m b
> 
> > collect = everything mplus $ mkQ mzero return
> 
> > 
> 
> > allTypes :: CoreExpr -> [Type]
> 
> > allTypes = collect
> 
>  
> 
> Especially when still exploring (parts of) the GHC API, being able to extract things in this fashion is very helpful. SYB’s “everything” being broken by these instances, not so much.
> 
>  
> 
> Would a patch “fixing” these instances be acceptable?
> 
>  
> 
> Regards,
> 
> Philip
> 
>  
> 
>  
> 
> 
> _______________________________________________
> ghc-devs mailing list
> ghc-devs at haskell.org
> http://www.haskell.org/mailman/listinfo/ghc-devs
> 
> 
> 
> 
> _______________________________________________
> ghc-devs mailing list
> ghc-devs at haskell.org
> http://www.haskell.org/mailman/listinfo/ghc-devs
> 
> 
> 
> _______________________________________________
> ghc-devs mailing list
> ghc-devs at haskell.org
> http://www.haskell.org/mailman/listinfo/ghc-devs

-------------- next part --------------
An HTML attachment was scrubbed...
URL: <http://www.haskell.org/pipermail/ghc-devs/attachments/20140727/f49da648/attachment.html>


More information about the ghc-devs mailing list