RE: Revival: PROPOSAL: Literate haskell and module file names

2014-08-16 Thread p.k.f.holzenspies
Dear Merijn,

Do you even need a separate extension or filename convention for this? Can't 
you just call it lhs and expand the definition thereof to include markdown? (I 
suggested something similar before, but objections were raised that having too 
good and too broad an unlitter might lead to the bit-rot of the flag to employ 
external unlitters. I didn't quite understand that objection, but didn't pursue 
it)

Regards,
Philip



Van: Glasgow-haskell-users  namens 
Merijn Verstraaten 
Verzonden: zaterdag 16 augustus 2014 00:40
Aan: haskell-pr...@haskell.org; glasgow-haskell-users@haskell.org
Onderwerp: Revival: PROPOSAL: Literate haskell and module file names

Ola!

I raised this proposal earlier this year and got to busy to follow up, this 
week I was suddenly reminded and decided to reraise this. To summarise the 
discussion up until this point:

There was no real opposition to the general idea, the only real objection to 
the original proposal was that “Foo.lhs.md” and “Foo.md.lhs” would collide with 
the naming scheme used by JHC on case insensitive filesystems. Alternative 
proposal raised during the discussion: "Foo+md.lhs", "Foo.lhs+md” and 
“Foo.md+lhs”.

According to MS documentation and testing the + should not be an issue on 
windows, the + doesn’t collide with any other haskell compiler (at least, not 
any I’m aware off) and since the report doesn’t specify any module name 
resolution mechanism, it does not conflict with the report either.

My personal preferences goes to either “.lhs+md” or “.md+lhs”, since GHC 
currently tries every alternative in turn, I propose to just extend this list 
to look for any file whose extension is “.lhs+*” or “.*+lhs”.

Are there any objections to this? If not, I’m just going to produce a patch + 
ticket as there were no real objections to the proposal last time.

Cheers,
Merijn

On 16 Mar 2014, at 05:56 , Merijn Verstraaten  wrote:
> Ola!
>
> I didn't know what the most appropriate venue for this proposal was so I 
> crossposted to haskell-prime and glasgow-haskell-users, if this isn't the 
> right venue I welcome advice where to take this proposal.
>
> Currently the report does not specify the mapping between filenames and 
> module names (this is an issue in itself, it essentially makes writing 
> haskell code that's interoperable between compilers impossible, as you can't 
> know what directory layout each compiler expects). I believe that a minimal 
> specification *should* go into the report (hence, haskell-prime). However, 
> this is a separate issue from this proposal, so please start a new thread 
> rather than sidetracking this one :)
>
> The report only mentions that "by convention" .hs extensions imply normal 
> haskell and .lhs literate haskell (Section 10.4). In the absence of guidance 
> from the report GHC's convention of mapping module Foo.Bar.Baz to 
> Foo/Bar/Baz.hs or Foo/Bar/Baz.lhs seems the only sort of standard that 
> exists. In general this standard is nice enough, but the mapping of literate 
> haskell is a bit inconvenient, it leaves it completelyl ambiguous what the 
> non-haskell content of said file is, which is annoying for tool authors.
>
> Pandoc has adopted the policy of checking for further file extensions for 
> literate haskell source, e.g. Foo.rst.lhs and Foo.md.lhs. Here .rst.lhs gets 
> interpreted as being reStructured Text with literate haskell and .md.lhs is 
> Markdown with literate haskell. Unfortunately GHC currently maps filenames 
> like this to the module names Foo.rst and Foo.md, breaking anything that 
> wants to import the module Foo.
>
> I would like to propose allowing an optional extra extension in the pandoc 
> style for literate haskell files, mapping Foo.rst.lhs to module name Foo. 
> This is a backwards compatible change as there is no way for Foo.rst.lhs to 
> be a valid module in the current GHC convention. Foo.rst.lhs would map to 
> module name "Foo.rst" but module name "Foo.rst" maps to filename "Foo/rst.hs" 
> which is not a valid haskell module anyway as the rst is lowercase and module 
> names have to start with an uppercase letter.
>
> Pros:
> - Tool authors can more easily determine non-haskell content of literate 
> haskell files
> - Currently valid module names will not break
> - Report doesn't specify behaviour, so GHC can do whatever it likes
>
> Cons:
> - Someone has to implement it
> - ??
>
> Discussion: 4 weeks
>
> Cheers,
> Merijn
>
___
Glasgow-haskell-users mailing list
Glasgow-haskell-users@haskell.org
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users


RE: GhcPlugin-writing and "finding things"

2014-07-24 Thread p.k.f.holzenspies
Dear Andrew,

Thanks for your suggestion. I had considered it earlier and decided against it 
for the extra dependencies. Maybe I was too picky there. I will give it another 
go. Could there possibly be a subset of hermit that plugin-writers could depend 
on, but that have fewer dependencies? I find it hard to explain to people why 
they require things like ansi-terminal if they want to use my 
parser-combinators.

I still think this isn't an unreasonable use case to take on board for future 
GHC API design, though. Also, the thing with findImportedModule still scares me.

Regards,
Philip



> -Original Message-
> From: xicheko...@gmail.com [mailto:xicheko...@gmail.com] On Behalf Of
> Andrew Farmer
> Sent: woensdag 23 juli 2014 19:22
> To: Holzenspies, P.K.F. (EWI)
> Cc: glasgow-haskell-users@haskell.org
> Subject: Re: GhcPlugin-writing and "finding things"
> 
> Have you considered using HERMIT for this? I think this is a rough
> approximation of what you are trying to do (using HERMIT):
> 
> import HERMIT.Plugin
> import HERMIT.Dictionary
> 
> plugin = hermitPlugin $ \ opts -> firstPhase $ run $ tryR $ innermostR
> $ promoteBindR compileFooBindR
> 
> compileFooBindR :: RewriteH CoreBind
> compileFooBindR = prefixFailMsg "compileFooBindR failed: " $ do
>   NonRec b rhs <- idR -- only match on non-recursive bindings
>   tcFoo <- findTyConT "Foo" -- can be fully qualified name if target
> code doesn't import directly
>   guardMsg (varType b `containsTyConAnywhere` tyFoo) "does not contain
> Foo" -- abort if binder doesn't contain Foo in type
>   return $ NonRec b $ {- magicCompileFunction -} rhs
> 
> The goal of HERMIT is to make writing these plugins easier. For
> instance, if you give a fully qualified name to findTyConT (or the
> other find functions), and HERMIT can't find the name in scope in the
> target module, it'll look in the package database for the appropriate
> interface and load it.
> 
> You can even run your compilation functions interactively and view
> their output in a REPL. To do so, change your plugin to:
> 
> plugin = hermitPlugin $ firstPhase . interactive exts
> 
> exts :: Externals
> exts = [ external "compile-foo" (promoteBindR compileFooBindR) [
> "compiles bindings involving Foo" ] ]
> 
> {- compileFooBindR as before -}
> 
> Then you can navigate around your AST and use the "compile-foo"
> command to test out your compilation.
> 
> If you want to try, I'd highly recommend using the latest from github,
> rather than what is on hackage:
> 
> https://github.com/ku-fpg/hermit
> 
> Here are a few examples of larger HERMIT plugins:
> 
> https://github.com/xich/hermit-syb/blob/master/hermit-
> syb/HERMIT/Optimization/SYB.hs#L28
> https://github.com/conal/lambda-
> ccc/blob/master/src/LambdaCCC/Reify.hs#L866
> 
> Let me know if you have questions!
> 
> Andrew
> 
> On Wed, Jul 23, 2014 at 11:06 AM,   wrote:
> > Dear GHC-ers,
> >
> > I'm working on a plugin for GHC that should help compile the library
> with which this plugin is to ship. What this plugin does is traverse the
> CoreProgram(s) to find things of types defined in my library and
> optimizes them. I have worked out how to "find" things, but I was
> wondering whether the API could be improved for plugin-writers.
> >
> > For the sake of argument, I have the following:
> >  - module Foo: library for users to import, containing functions, ADTs
> etc
> >  - module Foo.Plugin: GhcPlugin that compiles out all uses of things
> in Foo
> >
> >> module Foo where
> >>
> >> data Foo x = Foo x
> >>
> >> runFoo :: Foo x -> x
> >> runFoo (Foo x) = x
> >
> >
> > This example is trivial and I imagine GHC will have no trouble
> eliminating most cases of this, but imagine more complex stuff. Now, if
> I want to traverse the CoreProgram in my plugin, I need to find
> occurrences of these, so somewhere there's stuff like:
> >
> >> pass tcFoo _ _ (NonRec b expr)
> >>   | varType b `containsTyConAnywhere` tcFoo
> >> = {- clever stuff to compile out Foo -}
> >
> > My problem is "getting" tcFoo in this example. Below is how I do it
> now. Maybe I'm being thick, or maybe there's just no simpler way. This
> is my 'plugin' function in Foo.Plugin:
> >
> >> plugin = Plugin $ \opts todo -> do
> >>  hsc <- getHscEnv
> >>  dfs <- getDynFlags
> >>  fr  <- liftIO $ findImportedModule hsc (mkModuleName "Foo") Nothing
> >>  mod <- case fr of
> >>Found ml m -> return m
> >>_ -> panic "Failed to (unambiguously) find 'Foo' (using
> findImportedModule)"
> >>  onc <- getOrigNameCache
> >>  let nms = lookupWithDefaultModuleEnv nms (panic "No names defined
> for module 'Foo'") mod
> >>  find_ d occ fnd nm
> >>= maybe
> >>(fail $ "Failed to find " ++ d ++ " '" ++ nm ++ "'")
> >>fnd
> >>(lookupOccEnv nms $ occ nm)
> >>  tcFind = find_ "TyCon"   mkTcOcc   lookupTyCon
> >>  dcFind = find_ "DataCon" mkDataOcc lookupDataCon
> >>  idFind = find_ "Id"  mkVarOcc  lookupId
> >>  tcFoo<- tcFind "Foo

GhcPlugin-writing and "finding things"

2014-07-23 Thread p.k.f.holzenspies
Dear GHC-ers,

I'm working on a plugin for GHC that should help compile the library with which 
this plugin is to ship. What this plugin does is traverse the CoreProgram(s) to 
find things of types defined in my library and optimizes them. I have worked 
out how to "find" things, but I was wondering whether the API could be improved 
for plugin-writers.

For the sake of argument, I have the following:
 - module Foo: library for users to import, containing functions, ADTs etc
 - module Foo.Plugin: GhcPlugin that compiles out all uses of things in Foo

> module Foo where
>
> data Foo x = Foo x
>
> runFoo :: Foo x -> x
> runFoo (Foo x) = x


This example is trivial and I imagine GHC will have no trouble eliminating most 
cases of this, but imagine more complex stuff. Now, if I want to traverse the 
CoreProgram in my plugin, I need to find occurrences of these, so somewhere 
there's stuff like:

> pass tcFoo _ _ (NonRec b expr)
>   | varType b `containsTyConAnywhere` tcFoo
> = {- clever stuff to compile out Foo -}

My problem is "getting" tcFoo in this example. Below is how I do it now. Maybe 
I'm being thick, or maybe there's just no simpler way. This is my 'plugin' 
function in Foo.Plugin:

> plugin = Plugin $ \opts todo -> do
>  hsc <- getHscEnv
>  dfs <- getDynFlags
>  fr  <- liftIO $ findImportedModule hsc (mkModuleName "Foo") Nothing
>  mod <- case fr of
>Found ml m -> return m
>_ -> panic "Failed to (unambiguously) find 'Foo' (using 
> findImportedModule)"
>  onc <- getOrigNameCache
>  let nms = lookupWithDefaultModuleEnv nms (panic "No names defined for module 
> 'Foo'") mod
>  find_ d occ fnd nm
>= maybe
>(fail $ "Failed to find " ++ d ++ " '" ++ nm ++ "'")
>fnd
>(lookupOccEnv nms $ occ nm)
>  tcFind = find_ "TyCon"   mkTcOcc   lookupTyCon
>  dcFind = find_ "DataCon" mkDataOcc lookupDataCon
>  idFind = find_ "Id"  mkVarOcc  lookupId
>  tcFoo<- tcFind "Foo"
>  dcFoo<- dcFind "Foo"
>  idRunFoo <- idFind "runFoo"
>  return $ CoreDoPluginPass "Foo optimisation" (pass tcFoo dcFoo idRunFoo) : 
> todo

I have the following questions:

  1) Is this a/the right way to "find" those things in the plugin?
  2) There seems to be a lot to gain with quasi-quoting a la Template Haskell 
for people writing plugins to go with a library that they wrote. Can such QQ be 
done? Has it been considered?
  3) Is findImportedModule the right function to find my starting point to 
begin with?
  4) What is the 'Maybe FastString' argument in findImportedModule for? I've 
been trying to put in the FSs of PackageIDs, but they make the lookup fail. 
This (dumb) example really made me nervous:

>  fr  <- liftIO $ findImportedModule hsc (mkModuleName "Foo") Nothing
>  mod <- case fr of
>Found ml m -> do
>  fr' <- liftIO $ findImportedModule hsc (moduleName m) (packageIdFS $ 
> packageId m)

Here, fr' should always be a "Found ml' m'" such that ml == ml' and m == m', 
but... it consistently results in NotFound{} for me. Also, I find this 
especially round-about. Shouldn't Paths_Foo.hs (the Cabal-generated file) maybe 
contain variables for every module in the package? In my case it would thus 
contain some "modFoo :: Module"

Comments and suggestions more than welcome!

Regards,
Philip







___
Glasgow-haskell-users mailing list
Glasgow-haskell-users@haskell.org
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users


RE: Desugaring do-notation to Applicative

2013-10-02 Thread p.k.f.holzenspies
I thought the whole point of Applicative (at least, reading Connor’s paper) was 
to restore some function-application-style to the whole effects-thing, i.e. it 
was the very point *not* to resort to binds or do-notation.

That being said, I’m all for something that will promote the use of the name 
“pure” over “return”.

+1 for the Opt-In

Ph.



From: Glasgow-haskell-users [mailto:glasgow-haskell-users-boun...@haskell.org] 
On Behalf Of Iavor Diatchki


do x1 <- e1

   -- The following part is `Applicative`
   (x2,x3) <- do x2 <- e2 x1
 x3 <- e3
 pure (x2,x3)

   f x1 x2 x3
___
Glasgow-haskell-users mailing list
Glasgow-haskell-users@haskell.org
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users


RE: Question about correct GHC-API use for type checking (or zonking, or tidying)

2013-09-11 Thread p.k.f.holzenspies
Well, my tcLocalBinds seems to have a different type then yours (this is from 
my copy of 7.6.3 and it's the same in the HEAD that I just synced):

tcLocalBinds :: HsLocalBinds Name -> TcM thing -> TcM (HsLocalBinds TcId, thing)

If I want to get a GblEnv out, I can use getGblEnv, but doing this:


mkId :: Maybe FreeVars -> LHsExpr Name -> Name -> TcM Id
mkId fvs expr@(L l _) nm = do
  ((binds', gbl_env),lie) <- captureConstraints $ tcLocalBinds binds getGblEnv
  setGblEnv gbl_env (tcLookupId nm)
where
binds= HsValBinds $ ValBindsOut [(NonRecursive, unitBag fixbnd)] []
the_bind = mkTopFunBind (L l nm) [mkMatch [] expr emptyLocalBinds]
fixbnd   = L l $ maybe the_bind (\vs -> the_bind { bind_fvs = vs }) fvs


fails on the tcLookupId with a GHC internal error complaining that my name is 
"not in scope during type checking, but it passed the renamer."

Ph.




From: Simon Peyton-Jones [mailto:simo...@microsoft.com]
Sent: dinsdag 10 september 2013 14:19
To: Holzenspies, P.K.F. (EWI)
Cc: glasgow-haskell-users@haskell.org
Subject: RE: Question about correct GHC-API use for type checking (or zonking, 
or tidying)

What goes wrong if you follow my suggestion below?

tcLocalBinds takes a set of bindings, such as x=e
and returns a GblEnv whose type envt is extended with a binding for x with its 
generalised type.
This type wil indeed be closed, unless the current environment (in which 
tcLocalBinds runs) has bindings with open types. Which in your case it probably 
doesn't.

I feel that I am not being helpful but I'm not sure how to help more.

S

From: "Philip K.F. Hölzenspies" [mailto:p.k.f.holzensp...@utwente.nl]
Sent: 04 September 2013 21:25
To: Simon Peyton-Jones
Cc: glasgow-haskell-users@haskell.org
Subject: Re: Question about correct GHC-API use for type checking (or zonking, 
or tidying)

Ah, this is good to know. What I really would like is a function:

mkId :: Name -> LHsExpr Name -> TcM Id

where that Id is something I can store in my own monad (IA). The meaning of 
this, is indeed "let  = " as a top-level binding. The 
behaviour should actually be the same as that statement at the ghci-prompt. My 
IA monad implements liftTcM as something that invokes a TcM-monad, i.e.

liftTcM :: TcM b -> IA b
liftTcM thing_inside = do
hsc_env <- getSession
stored_ids <- getStoredIds :: IA [Id]-- this is the list of all Ids 
made through mkId mentioned above
ioMsgMaybe . initTcPrintErrors hsc_env iNTERACTIVE $
setInteractiveContext hsc_env (hsc_IC hsc_env) $
tcExtendGlobalValEnv stored_ids $ -- or tcExtendIdEnv??
thing_inside

In the example you give below, I'm curious which "thing_inside" you give to 
tcLocalBinds to get you the correct global environment. Also, if I do what you 
suggest, i.e.

poly_id <- setGblEnv gbl_env (tcLookupId the_id_name)

is that poly_id "self contained," in the sense that I can put it in a new 
instantiation as shown above?

Regards,
Philip









[cid:image001.jpg@01CEAEDB.407DA510]
Simon Peyton-Jones
September 4, 2013 6:00 PM
The id you are getting is a monomorphic id, with a type like a->a, not the 
polymorphic forall a. a->a.  You don't want to go round arbitrarily creating a 
new Id with the same unique but a different type. I have no idea what would 
happen then.

It's hard for me to understand just what you code is trying to do.  I think you 
are making bindig
it = 

and then you want the type of "it".  Maybe something like

   (binds', gbl_env) <- tcLocalBinds (..your bindin..)
   poly_id <- setGblEnv gbl_env (tcLooupId the_id_name)

But I'm not totally sure.

S
<>___
Glasgow-haskell-users mailing list
Glasgow-haskell-users@haskell.org
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users


RE: Question about correct GHC-API use for type checking (or zonking, or tidying)

2013-09-03 Thread p.k.f.holzenspies
Dear Simon, et al,

I had a chance to try it now. The strange thing is that when I use the lines:

zonked_id <- TcMType.zonkId id
say $ "zonked idType: " ++ pp (idType zonked_id)

that is still some unresolved type variable (i.e. prints as "b_i"). Since I 
already have the intended target-type (considering the code by which it is 
produced), is it safe to do what TcMType.zonkId does and manually set it? In 
other words, I now do this:

zonked_ty <- zonkTcType all_expr_ty
return (setIdType id zonked_ty)

Will this bite me later?

Regards,
Philip



From: Simon Peyton-Jones [mailto:simo...@microsoft.com]
Sent: maandag 2 september 2013 13:34
To: Holzenspies, P.K.F. (EWI); glasgow-haskell-users@haskell.org
Subject: RE: Question about correct GHC-API use for type checking (or zonking, 
or tidying)

Does this mean that for the idType to come out correctly I should also zonk 
(AND BIND) the Id-value I return?

Yes, zonk the type and grab the type that comes back.

S

From: p.k.f.holzensp...@utwente.nl 
[mailto:p.k.f.holzensp...@utwente.nl]
Sent: 30 August 2013 17:49
To: Simon Peyton-Jones; 
glasgow-haskell-users@haskell.org
Subject: Re: Question about correct GHC-API use for type checking (or zonking, 
or tidying)

I feel so unbelievably ignorant now. I thought with all the IORefs in the type 
checking process that zonking did this in these refs. Somehow I started 
thinking that some of these remained in SDocs, not thinking showSDoc is pure 
and results in a String, which holds no IORefs.

Does this mean that for the idType to come out correctly I should also zonk 
(AND BIND) the Id-value I return?

Ph.




Sent from Samsung Mobile



 Original message 
From: Simon Peyton-Jones mailto:simo...@microsoft.com>>
Date: 30/08/2013 18:25 (GMT+01:00)
To: "Holzenspies, P.K.F. (EWI)" 
mailto:p.k.f.holzensp...@utwente.nl>>,glasgow-haskell-users@haskell.org
Subject: RE: Question about correct GHC-API use for type checking (or zonking, 
or tidying)
Haskell is a *functional* language.  Consider

say $ "  pre-zonk:  " ++ pp all_expr_ty
zonkTcType all_expr_ty
say $ "  post-zonk: " ++ pp all_expr_ty

pp is a pure function; it is given the same input both times, so of course it 
produces the same output.

If you collect the result of zonkTcType you might have better luck, thus:

say $ "  pre-zonk:  " ++ pp all_expr_ty
zonked_expr_ty <- zonkTcType all_expr_ty
say $ "  post-zonk: " ++ pp zonked_expr_ty

Zonking walks over a type, returning a new type in which unification variables 
are replaced by the types they unified to.

Hope this helps

Simon

| -Original Message-
| From: Glasgow-haskell-users [mailto:glasgow-haskell-users-
| boun...@haskell.org] On Behalf Of 
p.k.f.holzensp...@utwente.nl
| Sent: 29 August 2013 14:42
| To: 
glasgow-haskell-users@haskell.org
| Subject: Question about correct GHC-API use for type checking (or
| zonking, or tidying)
|
| Dear GHC-ers,
|
| I'm working on building an interactive environment around the
| composition of expressions. Users can type in (i.e. give strings of)
| expressions and can then use these expressions to produce other
| expressions. I'm close to having a working GHC-API binding for this. The
| resulting types, however, still contain some things I don't quite
| understand. Any help would be appreciated.
|
| Below, I've included the function exprFromString which should parse,
| rename and typecheck strings to Id-things and give their type (although,
| ideally, the idType of said Id-thing should be the same as the type
| returned). This function lives in the IA (InterActive) monad; a monad
| that is a GhcMonad and can lift monadic computations in TcM into itself
| using liftTcM (which uses the initTcPrintErrors and
| setInteractiveContext functions similarly to TcRnDriver.tcRnExpr).
|
| Near the end of the function, debugging output is produced. This output
| confuses me slightly. Here is the output for the three inputs "map (+1)
| [1..10]", "5" and "\\x -> x":
|
|
| map (+1) [1..10]
|   pre-zonk:  forall b. (GHC.Enum.Enum b_i, GHC.Num.Num b_i) => [b_i]
|   post-zonk: forall b. (GHC.Enum.Enum b_i, GHC.Num.Num b_i) => [b_i]
|   idType:[b_c]
|   tidied:forall b. (GHC.Enum.Enum b_i, GHC.Num.Num b_i) => [b_i]
| 5
|   pre-zonk:  forall a. GHC.Num.Num a_d => t_c
|   post-zonk: forall a. GHC.Num.Num a_d => t_c
|   idType:a_b
|   tidied:forall a. GHC.Num.Num a_d => t_c
| \x -> x
|   pre-zonk:  forall t. t_e
|   post-zonk: forall t. t_e
|   idType:forall t. t -> t
|   tidied:forall t. t_e
|
|
| The zonking and tidying part of the type-checking process are still a
| bit unclear to me and I suspect the problems arise there. It looks to me
| that the type variables in the quantifications are different ones from
| those in the pi/rho-types. I ha

Re: Question about correct GHC-API use for type checking (or zonking, or tidying)

2013-08-30 Thread p.k.f.holzenspies
I feel so unbelievably ignorant now. I thought with all the IORefs in the type 
checking process that zonking did this in these refs. Somehow I started 
thinking that some of these remained in SDocs, not thinking showSDoc is pure 
and results in a String, which holds no IORefs.

Does this mean that for the idType to come out correctly I should also zonk 
(AND BIND) the Id-value I return?

Ph.




Sent from Samsung Mobile



 Original message 
From: Simon Peyton-Jones 
Date: 30/08/2013 18:25 (GMT+01:00)
To: "Holzenspies, P.K.F. (EWI)" 
,glasgow-haskell-users@haskell.org
Subject: RE: Question about correct GHC-API use for type checking (or zonking, 
or tidying)


Haskell is a *functional* language.  Consider

say $ "  pre-zonk:  " ++ pp all_expr_ty
zonkTcType all_expr_ty
say $ "  post-zonk: " ++ pp all_expr_ty

pp is a pure function; it is given the same input both times, so of course it 
produces the same output.

If you collect the result of zonkTcType you might have better luck, thus:

say $ "  pre-zonk:  " ++ pp all_expr_ty
zonked_expr_ty <- zonkTcType all_expr_ty
say $ "  post-zonk: " ++ pp zonked_expr_ty

Zonking walks over a type, returning a new type in which unification variables 
are replaced by the types they unified to.

Hope this helps

Simon

| -Original Message-
| From: Glasgow-haskell-users [mailto:glasgow-haskell-users-
| boun...@haskell.org] On Behalf Of p.k.f.holzensp...@utwente.nl
| Sent: 29 August 2013 14:42
| To: glasgow-haskell-users@haskell.org
| Subject: Question about correct GHC-API use for type checking (or
| zonking, or tidying)
|
| Dear GHC-ers,
|
| I'm working on building an interactive environment around the
| composition of expressions. Users can type in (i.e. give strings of)
| expressions and can then use these expressions to produce other
| expressions. I'm close to having a working GHC-API binding for this. The
| resulting types, however, still contain some things I don't quite
| understand. Any help would be appreciated.
|
| Below, I've included the function exprFromString which should parse,
| rename and typecheck strings to Id-things and give their type (although,
| ideally, the idType of said Id-thing should be the same as the type
| returned). This function lives in the IA (InterActive) monad; a monad
| that is a GhcMonad and can lift monadic computations in TcM into itself
| using liftTcM (which uses the initTcPrintErrors and
| setInteractiveContext functions similarly to TcRnDriver.tcRnExpr).
|
| Near the end of the function, debugging output is produced. This output
| confuses me slightly. Here is the output for the three inputs "map (+1)
| [1..10]", "5" and "\\x -> x":
|
|
| map (+1) [1..10]
|   pre-zonk:  forall b. (GHC.Enum.Enum b_i, GHC.Num.Num b_i) => [b_i]
|   post-zonk: forall b. (GHC.Enum.Enum b_i, GHC.Num.Num b_i) => [b_i]
|   idType:[b_c]
|   tidied:forall b. (GHC.Enum.Enum b_i, GHC.Num.Num b_i) => [b_i]
| 5
|   pre-zonk:  forall a. GHC.Num.Num a_d => t_c
|   post-zonk: forall a. GHC.Num.Num a_d => t_c
|   idType:a_b
|   tidied:forall a. GHC.Num.Num a_d => t_c
| \x -> x
|   pre-zonk:  forall t. t_e
|   post-zonk: forall t. t_e
|   idType:forall t. t -> t
|   tidied:forall t. t_e
|
|
| The zonking and tidying part of the type-checking process are still a
| bit unclear to me and I suspect the problems arise there. It looks to me
| that the type variables in the quantifications are different ones from
| those in the pi/rho-types. I had expected the types to only contain the
| variables over which they are quantified, so e.g. in the map-example, I
| had expected "forall b . (GHC.Enum.Enum b, GHC.Num.Num b) => [b]"
|
| Can anyone explain what I'm missing?
|
| Regards,
| Philip
|
|
|
|
|
| exprFromString :: String -> IA (Id,Type)
| exprFromString str = do
|   dfs <- getDynFlags
|   let pp  = showSDoc dfs . ppr
|   pst <- mkPState dfs buf <$> newRealSrcLoc
|
| {- Parse -}
|   (loc,rdr_expr) <- case unP parseStmt pst of
| PFailed span err -> throwOneError (mkPlainErrMsg dfs span err)
| POk pst' (Just (L l (ExprStmt rdr_expr _ _ _))) -> do
|   logWarningsReportErrors (getMessages pst')
|   return (l,rdr_expr)
| POk pst' thing -> throw $ maybe EmptyParse (const
| NonExpressionParse) thing
|   liftTcM $ do
| fresh_it <- freshName loc str
|
| {- Rename -}
| (rn_expr, fvs) <- checkNoErrs $ rnLExpr rdr_expr
|
| {- Typecheck -}
| let binds = mkBinds fresh_it rn_expr fvs
|
| (((_bnds,((_tc_expr,res_ty),id)),untch),lie) <- captureConstraints .
| captureUntouchables $
|   tcLocalBinds binds ((,) <$> tcInferRho rn_expr <*> tcLookupId
| fresh_it)
| ((qtvs, dicts, _bool, _evbinds), lie_top) <- captureConstraints $
|   simplifyInfer True False [(fresh_it, res_ty)] (untch,lie)
|
| let all_expr_ty = mkForAllTys qtvs (mkPiTypes dicts res_ty)
| say str
| say $ "  pre-zonk:  " ++ pp all_expr_ty
| zonkTcType all_expr_ty
| say $ "  post-zonk: " 

Question about correct GHC-API use for type checking (or zonking, or tidying)

2013-08-29 Thread p.k.f.holzenspies
Dear GHC-ers,

I'm working on building an interactive environment around the composition of 
expressions. Users can type in (i.e. give strings of) expressions and can then 
use these expressions to produce other expressions. I'm close to having a 
working GHC-API binding for this. The resulting types, however, still contain 
some things I don't quite understand. Any help would be appreciated.

Below, I've included the function exprFromString which should parse, rename and 
typecheck strings to Id-things and give their type (although, ideally, the 
idType of said Id-thing should be the same as the type returned). This function 
lives in the IA (InterActive) monad; a monad that is a GhcMonad and can lift 
monadic computations in TcM into itself using liftTcM (which uses the 
initTcPrintErrors and setInteractiveContext functions similarly to 
TcRnDriver.tcRnExpr).

Near the end of the function, debugging output is produced. This output 
confuses me slightly. Here is the output for the three inputs "map (+1) 
[1..10]", "5" and "\\x -> x":


map (+1) [1..10]
  pre-zonk:  forall b. (GHC.Enum.Enum b_i, GHC.Num.Num b_i) => [b_i]
  post-zonk: forall b. (GHC.Enum.Enum b_i, GHC.Num.Num b_i) => [b_i]
  idType:[b_c]
  tidied:forall b. (GHC.Enum.Enum b_i, GHC.Num.Num b_i) => [b_i]
5
  pre-zonk:  forall a. GHC.Num.Num a_d => t_c
  post-zonk: forall a. GHC.Num.Num a_d => t_c
  idType:a_b
  tidied:forall a. GHC.Num.Num a_d => t_c
\x -> x
  pre-zonk:  forall t. t_e
  post-zonk: forall t. t_e
  idType:forall t. t -> t
  tidied:forall t. t_e


The zonking and tidying part of the type-checking process are still a bit 
unclear to me and I suspect the problems arise there. It looks to me that the 
type variables in the quantifications are different ones from those in the 
pi/rho-types. I had expected the types to only contain the variables over which 
they are quantified, so e.g. in the map-example, I had expected "forall b . 
(GHC.Enum.Enum b, GHC.Num.Num b) => [b]"

Can anyone explain what I'm missing?

Regards,
Philip





exprFromString :: String -> IA (Id,Type)
exprFromString str = do
  dfs <- getDynFlags
  let pp  = showSDoc dfs . ppr
  pst <- mkPState dfs buf <$> newRealSrcLoc

{- Parse -}
  (loc,rdr_expr) <- case unP parseStmt pst of
PFailed span err -> throwOneError (mkPlainErrMsg dfs span err)
POk pst' (Just (L l (ExprStmt rdr_expr _ _ _))) -> do
  logWarningsReportErrors (getMessages pst')
  return (l,rdr_expr)
POk pst' thing -> throw $ maybe EmptyParse (const NonExpressionParse) thing
  liftTcM $ do
fresh_it <- freshName loc str

{- Rename -}
(rn_expr, fvs) <- checkNoErrs $ rnLExpr rdr_expr

{- Typecheck -}
let binds = mkBinds fresh_it rn_expr fvs

(((_bnds,((_tc_expr,res_ty),id)),untch),lie) <- captureConstraints . 
captureUntouchables $
  tcLocalBinds binds ((,) <$> tcInferRho rn_expr <*> tcLookupId fresh_it)
((qtvs, dicts, _bool, _evbinds), lie_top) <- captureConstraints $
  simplifyInfer True False [(fresh_it, res_ty)] (untch,lie)

let all_expr_ty = mkForAllTys qtvs (mkPiTypes dicts res_ty)
say str
say $ "  pre-zonk:  " ++ pp all_expr_ty
zonkTcType all_expr_ty
say $ "  post-zonk: " ++ pp all_expr_ty
say $ "  idType:" ++ pp (idType id)
say $ "  tidied:" ++ pp (tidyTopType all_expr_ty)

return (id,all_expr_ty)
  where
  say = liftIO . putStrLn
  buf = stringToStringBuffer str
  freshName loc str = (\u -> mkInternalName u name loc) <$> newUnique
where
name = mkOccNameFS varName $ fsLit $ "it" ++ show (lineOf loc)
isVarChar c = isAlphaNum c || c == '_' || c == '\''
lineOf (RealSrcSpan s) = srcSpanStartLine s
lineOf _ = -1

  mkBinds :: Name -> LHsExpr Name -> FreeVars -> HsLocalBinds Name
  mkBinds nm e@(L l _) fvs = HsValBinds $ ValBindsOut [(NonRecursive, unitBag 
the_bind)] []
where
the_bind = L l (mkTopFunBind (L l nm) [mkMatch [] e emptyLocalBinds]) { 
bind_fvs = fvs }



___
Glasgow-haskell-users mailing list
Glasgow-haskell-users@haskell.org
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users


RE: How to fix DatatypeContexts?

2013-07-18 Thread p.k.f.holzenspies
> I've also been experiencing this a lot in class instances, such as:
> 
> class Foo f where
> foo :: a -> f a
> 
> data Bar f a = Foo f => Bar {bar :: f a}
> 
> instance Foo (Bar f) where
> foo a = Bar (foo a)
> 
> Is there any way to avoid repeating the Foo f constraint in the Bar f
> instance?



Dear Harry, et al,

The problem here is that GADT-constructors simply "carry" the appropriate 
dictionaries. When you *produce* an element of a GADT where the constructor 
requires a dictionary, you must provide it there. In this case, for a variable 
f, you don't have a dictionary, so you could read the constraint and instance 
head as "if you give me a Foo-dictionary for f, then I will wrap it in a Bar."

Another way of looking at it is that the type "Bar f" only 'exists' for 'f's 
that are 'Foo's. If you don't know whether a particular 'f' is a 'Foo', you 
don't know whether Bar f exists.

In short, I think that there is no such way.

Regards,
Philip

___
Glasgow-haskell-users mailing list
Glasgow-haskell-users@haskell.org
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users


RE: Re-entrant TcRnIf

2013-06-13 Thread p.k.f.holzenspies
Dear Thomas,

Thanks for your reply. If all else fails, this could be the way to go, but if 
at all possible, I would like to get rid of the file-idea ;)

Maybe it helps if I make things slightly more concrete. Like I said, I'm 
building an interactive user interface. In this interface, users manipulate 
terms. There is a bootstrapping problem here; how do they get "terms" to begin 
with? The answer (quite unsatisfactory at the moment): They type them in. For 
the sake of the argument, lets say users give these terms names of type UIName. 
Part of the UI's state is a "Map UIName (LHsExpr Id)" which can be manipulated 
with, e.g. this function:


addExpr :: UIName -> String -> UI (Maybe ErrorMessage)


which parses its String argument, akin to how exprType works. The problem, now, 
is that if I simply restart the TcRnMonad, I'm worried uniques in one 
expression may not be unique in the entire map of expressions. Also, I will be 
looking for ways to combine these expression, e.g.


mkApplication :: UIName -> UIName -> UIName -> UI ()
mkApplication new func arg = do
  m <- gets exprMap
  f <- maybe (fail ...) return (lookup func m)
  a <- maybe (fail ...) return (lookup arg m)
  let n = L (combineLocs f a) (HsApp f a)
  checkType n
  modify (\s -> s { exprMap = insert new n m })


Again, it seems that restarting the TcRnMonad for everything breaks stuff. Then 
again, it probably doesn't help that the AST (f and a in the function above) 
contain IORefs with type-state. I was thinking that if that is problematic, I 
would always "lower" the type of 'n' from "LHsExpr Id" to "LHsExpr Name" such 
that all type information is reconstructed, but it is quite vital that the 
renaming is preserved (i.e. I can't go all the way down to "LHsExpr RdrName").

Thoughts?

Regards,
Philip


  

-Original Message-
From: Thomas Schilling [mailto:nomin...@googlemail.com] 
Sent: dinsdag 11 juni 2013 13:46
To: Holzenspies, P.K.F. (EWI)
Cc: glasgow-haskell-users@haskell.org
Subject: Re: Re-entrant TcRnIf

There are quite a lot of dependencies between different parts of the AST.

The renamer takes the whole parser output and then discovers its dependencies.  
After that you can split things into smaller units based on this dependency 
graph.

The renamer and type checker do not necessarily need to be interleaved.  Every 
Haskell file is de-facto split apart after each top-level TH splice.

If I understand you correctly you want to build some IDE functionality that 
only recompiles the parts that changed.  You can do that currently (crudely) by 
splitting the file into three parts based on the dependency graph that the 
renamer discovered:

 1. Everything upstream of the focused definition, i.e., everything that does 
not depend on the focused definition.
 2. The focused definition and everything that is in its recursive group.
 3. Everything downstream of the focused, i.e., everything that directly or 
indirectly depends on the focused definition.

You can put each part into a separate file and only recompile part 2.
Of course you also need to detect when new (renamer) dependencies are formed as 
that will change the split between parts 1, 2, and 3.

Let me know if you need more details on this approach.

 / Thomas

On 11 June 2013 11:55,   wrote:
> Dear GHC-ers,
>
> The current API *seems* to assume that all different stages of the compiler 
> pipeline are always passed successively (with the exception of the 
> interleaving of the renamer and the type checker for the sake of Template 
> Haskell), in other words, it is assumed all parsing has been done once we 
> start renaming and that when we desugar the AST, we can through out all type 
> checker state. I'm working on an interactive environment (different in many 
> ways from ghci), in which I would like to incrementally parse a statement, 
> rename it and type check it, after which I may chose to wash, rinse and 
> repeat.
>
> This is somewhat problematic in the renamer (at least; this is how far I have 
> come), at the very least with regards to the unique source and the provenance 
> of things. What I'm hoping to do is to generalize the monads in the GHC API 
> to some class, along these lines:
>
> class Generalizes m n where
>   glift :: n a -> m a
> class (GhcMonad m, Generalizes m TcRnIf, Generalizes m CoreM, ...) => 
> GHCAPI m
>
> What such a monad needs is to be able to evaluate some function in (for 
> example) the renamer monad, extract the part of the renamer state that needs 
> to persist and store that for whenever another renamer function is evaluated. 
> One such thing would be the supply of unique names.
>
> I tried simply carrying over everything in the Env, except the env_top 
> (HscEnv), but this broke things. Upon inspection of the TcGblEnv and 
> TcLclEnv, this seems logical, considering they are dependent on the HscEnv 
> (at least in terms of tcg_type_env_var, but there may be other dependencies 
> I've not spotted). The thing that seems to bite m

Re-entrant TcRnIf

2013-06-11 Thread p.k.f.holzenspies
Dear GHC-ers,

The current API *seems* to assume that all different stages of the compiler 
pipeline are always passed successively (with the exception of the interleaving 
of the renamer and the type checker for the sake of Template Haskell), in other 
words, it is assumed all parsing has been done once we start renaming and that 
when we desugar the AST, we can through out all type checker state. I'm working 
on an interactive environment (different in many ways from ghci), in which I 
would like to incrementally parse a statement, rename it and type check it, 
after which I may chose to wash, rinse and repeat.

This is somewhat problematic in the renamer (at least; this is how far I have 
come), at the very least with regards to the unique source and the provenance 
of things. What I'm hoping to do is to generalize the monads in the GHC API to 
some class, along these lines:

class Generalizes m n where
  glift :: n a -> m a
class (GhcMonad m, Generalizes m TcRnIf, Generalizes m CoreM, ...) => GHCAPI m

What such a monad needs is to be able to evaluate some function in (for 
example) the renamer monad, extract the part of the renamer state that needs to 
persist and store that for whenever another renamer function is evaluated. One 
such thing would be the supply of unique names.

I tried simply carrying over everything in the Env, except the env_top 
(HscEnv), but this broke things. Upon inspection of the TcGblEnv and TcLclEnv, 
this seems logical, considering they are dependent on the HscEnv (at least in 
terms of tcg_type_env_var, but there may be other dependencies I've not 
spotted). The thing that seems to bite me is the assumption that the top-level 
environment is assumed to be fixed [1]. In my scenario, this assumption does 
not hold.

Concretely:

1) Do ways exist to carry over the part of the TcRnMonad state that is required 
to restart the renamer / type checker / etc later on?
2) If not, what parts of the Env, TcGblEnv and TcLclEnv should I copy over to 
the new state, assuming the HscEnv changed between consecutive runs?
3) Is there a particular reason why the front-end (of the front-end) is defined 
in an overloaded monad (GhcMonad) and the later bits all take concrete monads 
(TcRnIf etc.)?

Regards,
Philip


[1] http://hackage.haskell.org/trac/ghc/wiki/Commentary/Compiler/TcRnMonad
 

___
Glasgow-haskell-users mailing list
Glasgow-haskell-users@haskell.org
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users


RE: GHC 7.8 release?

2013-02-07 Thread p.k.f.holzenspies
+1

Ph.


> -Original Message-
> From: glasgow-haskell-users-boun...@haskell.org [mailto:glasgow-haskell-
> users-boun...@haskell.org] On Behalf Of Richard Eisenberg
> Sent: donderdag 7 februari 2013 15:01
> To: Geoffrey Mainland
> Cc: parallel-hask...@googlegroups.com; glasgow-haskell-users@haskell.org;
> ghc-d...@haskell.org
> Subject: Re: GHC 7.8 release?
> 
> Geoff's reasoning seems quite sound.
> +1 for February release.
> 
> On Feb 7, 2013, at 3:50 AM, Geoffrey Mainland 
> wrote:
> 
> > In practice the versions of GHC that are widely used are those that are
> > included in the platform. Maybe we should coordinate with their next
> > release? They are targeting a May 6 release, and the release process is
> > starting March 4, so it sounds like the original GHC release plan
> > (February release) would be a good fit for the platform as it would
> > allow library writers to catch up and ensure that STABLE was tested
> > enough for inclusion in the platform. It would be a shame to miss the
> > platform release.
> >
> > Geoff
> >
> > On 02/07/2013 08:25 AM, Simon Peyton-Jones wrote:
> >> Dear GHC users,
> >>
> >> *
> >> *
> >>
> >> *Carter*: Will this RTS update make it into ghc 7.8 update thats coming
> >> up in the next monthish?
> >>
> >> *Andreas*: We are almost there - we are now trying to sort out a
> problem
> >> on mac os x. It would be helpful to know if there is a cutoff date for
> >> getting things into 7.8.
> >>
> >>
> >>
> >> Simon, Ian, and I have just been discussing 7.8, and would be interested
> >> in what you guys think.
> >>
> >>
> >> At ICFP we speculated that we'd make a release of GHC soon after
> >> Christmas to embody tons of stuff that has been included since 7.6,
> >> specifically:
> >>
> >> * major improvements in DPH (vectorisation avoidance, new
> >> vectoriser)
> >>
> >> * type holes
> >>
> >> * rebindable list syntax
> >>
> >> * major changes to the type inference engine
> >>
> >> * type level natural numbers
> >>
> >> * overlapping type families
> >>
> >> * the new code generator
> >>
> >> * support for vector (SSE/AVX) instructions
> >>
> >>
> >>
> >> Whenever it comes it would definitely be great to include Andreas &
> >> friends' work:
> >>
> >> * Scheduler changes to the RTS to improve latency
> >>
> >>
> >>
> >> The original major reason for proposing a post-Xmas release was to get
> >> DPH in a working state out into the wild.  However, making a proper
> >> release imposes costs on everyone else.  Library authors have to scurry
> >> around to make their libraries work, etc.   Some of the new stuff hasn't
> >> been in HEAD for that long, and hence has not been very thoroughly
> >> tested.   (But of course making a release unleashes a huge wave of
> >> testing that doesn't happen otherwise.)
> >>
> >>
> >>
> >> So another alternative is to leave it all as HEAD, and wait another few
> >> months before making a release.  You can still use all the new stuff by
> >> compiling HEAD, or grabbing a snapshot distribution.  And it makes it
> >> hard for the Haskell platform if GHC moves too fast. Many people are
> >> still on 7.4.
> >>
> >>
> >>
> >> There seem to be pros and cons each way.  I don't have a strong
> >> opinion.  If you have a view, let us know.
> >>
> >>
> >>
> >> Simon
> >
> >
> >
> > ___
> > Glasgow-haskell-users mailing list
> > Glasgow-haskell-users@haskell.org
> > http://www.haskell.org/mailman/listinfo/glasgow-haskell-users
> >
> 
> 
> ___
> Glasgow-haskell-users mailing list
> Glasgow-haskell-users@haskell.org
> http://www.haskell.org/mailman/listinfo/glasgow-haskell-users

___
Glasgow-haskell-users mailing list
Glasgow-haskell-users@haskell.org
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users