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.z...@gmail.com]
Verzonden: vrijdag 25 juli 2014 13:44
Aan: Simon Peyton Jones
CC: Holzenspies, P.K.F. (EWI); ghc-devs@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.z...@gmail.com<mailto:alan.z...@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 
<simo...@microsoft.com<mailto:simo...@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.holzensp...@utwente.nl<mailto:p.k.f.holzensp...@utwente.nl>]
Sent: 24 July 2014 18:42
To: Simon Peyton Jones
Cc: ghc-devs@haskell.org<mailto:ghc-devs@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


[cid:image001.jpg@01CFA78B.7D356DE0]
Simon Peyton Jones<mailto:simo...@microsoft.com>
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-boun...@haskell.org] On Behalf Of 
p.k.f.holzensp...@utwente.nl<mailto:p.k.f.holzensp...@utwente.nl>
Sent: 24 July 2014 16:42
To: ghc-devs@haskell.org<mailto:ghc-devs@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@haskell.org<mailto:ghc-devs@haskell.org>
http://www.haskell.org/mailman/listinfo/ghc-devs



_______________________________________________
ghc-devs mailing list
ghc-devs@haskell.org
http://www.haskell.org/mailman/listinfo/ghc-devs

Reply via email to