[Haskell-cafe] Proposal: Hackage's packages should be seperated by buildable

2013-08-25 Thread He-chien Tsai
I'm sick for checking whether package is obsolete or not.
I think packages build failed long time ago should be collected and moved
to another page until someone fix them, or hackage pages should have a
filter for checking obsolete packages.
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] reasons why Template Haskell does not propose something similar to Python exec() or eval()

2013-08-25 Thread TP
Tobias Dammers wrote:

 IIRC you can use haskell-src-exts to parse a string into TH AST
 structures. There might even be a quasi-quoter for that; I don't have a
 real computer at hand right more, so you'll need to do some research of
 your own.

Thanks Tobias, it led me to the right path. There is indeed a solution in 
Language.Haskell.Meta:

$ ghci
 :m Language.Haskell.Meta
 parseDecs s=s+1
Right [ValD (VarP s) (NormalB (UInfixE (VarE s) (VarE +) (LitE (IntegerL 
1 []]
 parseExp x+1
Right (UInfixE (VarE x) (VarE +) (LitE (IntegerL 1)))
 :i parseDecs
parseDecs ::
  String - Either String [Language.Haskell.TH.Syntax.Dec]
-- Defined in `Language.Haskell.Meta.Parse'
 :i parseExp 
parseExp :: String - Either String Language.Haskell.TH.Syntax.Exp
-- Defined in `Language.Haskell.Meta.Parse'

Thanks,

TP


___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Proposal: Hackage's packages should be seperated by buildable

2013-08-25 Thread Rogan Creswick
On Sun, Aug 25, 2013 at 12:48 AM, He-chien Tsai depot...@gmail.com wrote:

 I'm sick for checking whether package is obsolete or not.
 I think packages build failed long time ago should be collected and moved
 to another page until someone fix them, or hackage pages should have a
 filter for checking obsolete packages.


I don't believe hackage can (currently) do this with a sufficient level of
precision.

*Many* packages fail to build on hackage because they depend on c-libraries
that need to be installed externally from cabal. There are some mitigations
for this in the works (although, it's been that way for some time now...).

Hackage 2 should have some community-involvement features (such as ratings,
tags, etc..) that can enable better rankings of packages, and there is a
hackage reverse-dependencies database that can also be used as a rough
indicator of stability.

That said, I do firmly believe that we should have multiple instances of
hackage at various levels of stability (and at corresponding levels of
scrutiny). At the moment, we have the Haskell Platform on one end of this
continuum of stability, and hackage at the other.  It would be useful to
have something in the middle.

--Rogan






 ___
 Haskell-Cafe mailing list
 Haskell-Cafe@haskell.org
 http://www.haskell.org/mailman/listinfo/haskell-cafe


___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] reasons why Template Haskell does not propose something similar to Python exec() or eval()

2013-08-25 Thread Dag Odenhall
There's a 
proposalhttp://ghc.haskell.org/trac/ghc/blog/Template%20Haskell%20Proposal#PartD:quasiquotationfor
adding a proper Haskell
QuasiQuoter as part of template-haskell. Until then, as others have noted
your best option is the haskell-src-meta package, but be aware that this
uses a separate parser.


On Sat, Aug 24, 2013 at 11:36 AM, TP paratribulati...@free.fr wrote:

 Hi everybody,

 I continue to learn and test Template Haskell (one more time thanks to John
 Lato for his post at:

 http://www.mail-archive.com/haskell-cafe@haskell.org/msg106696.html

 that made me understand a lot of things).

 I have a question about the way Template Haskell is working. Why Template
 Haskell does not propose something similar to Python (or bash) exec() or
 eval(), i.e. does not offer the possibility to take a (quoted) string in
 input, to make abstract syntax in output (to be executed later in a splice
 $()).
 For example, in Python, to make an affectation 'a=a' programatically, I
 can simply do (at runtime; even if I am here only concerned with what
 Template Haskell could do, i.e. at compile time):
  def f(s): return '%s = \'%s\'' % (s,s)
  exec(f(a))
  a
 'a'

 With Template Haskell, I am compelled to make a function returning the
 abstract syntax corresponding to variable declaration:

 ValD (VarP $ mkName s) (NormalB $ LitE $ StringL s)

 (see complete example in Post Scriptum).
 This works fine, but it is less direct. I am sure that the Template Haskell
 approach has many advantages, but I am unable to list them. I think it is
 important to have the reasons in mind. Could you help me?

 Thanks in advance,

 TP


 PS: the complete Haskell example:

 ---
 module MakeVard where
 import Language.Haskell.TH

 makeVard :: Monad m = String - m [Dec]
 -- Equivalent to %s = \%s\
 makeVard s = return [ ValD (VarP $ mkName s) (NormalB $ LitE $ StringL s)
 []
 ]
 ---

 tested by

 ---
 {-# LANGUAGE TemplateHaskell #-}
 import MakeVard

 $(makeVard a)

 main = do

 print a
 ---

 resulting in
 $ runghc -ddump-splices test.hs
 test_makeVar.hs:1:1: Splicing declarations
 makeVard a
   ==
 test_makeVar.hs:4:3-14
 a = a
 a


 ___
 Haskell-Cafe mailing list
 Haskell-Cafe@haskell.org
 http://www.haskell.org/mailman/listinfo/haskell-cafe

___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Renumbered mailing list posts

2013-08-25 Thread Niklas Hambüchen
Austin: Do you have any update on this?

On 11/08/13 04:48, Austin Seipp wrote:
 Henning,
 
 Thanks for the report. I'm currently investigating this, and think it
 should be possible to keep all of the old URLs intact.
 
 On Sat, Aug 10, 2013 at 11:01 AM, Niklas Hambüchen m...@nh2.me wrote:
 On 11/08/13 00:50, Brandon Allbery wrote:
 Those at least are recoverable, just replace hpaste.org
 http://hpaste.org with lpaste.net http://lpaste.net (content is
 still there). But still.

 Unfortunately I cannot amend emails that I have sent.

 Could we not just have kept the domain and set a CNAME entry to the new one?


___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Template Haskell: let statement in a splice put in the main = do part of a program?

2013-08-25 Thread adam vogt
On Sat, Aug 24, 2013 at 11:00 AM, TP paratribulati...@free.fr wrote:
 that has type Stmt, in an ExpQ that seems to be the only thing that we can
 put in a splice. I have found that it can only be done by doE (or DoE) and
 compE (or CompE) according to

 http://www.haskell.org/ghc/docs/latest/html/libraries/template-haskell-2.8.0.0/Language-Haskell-TH.html#v:doE

 But doE is not a solution as we have seen above, and compE is to construct
 list comprehensions, which is a different thing.

 So, is there any solution to my problem?

Hi TP,

TH quotes limited as you've noticed. One way to generate similar code
is to note that:

do
  let x = y
  z

is the same as let x = y in do z. You can generate the latter with
something like the following file, but the `a' isn't in scope for the
second argument to makeLetStatement. The uglier $(dyn a) works,
though I suppose it's more verbose than manually in-lining the
variable a.

{-# LANGUAGE TemplateHaskell #-}
import Language.Haskell.TH

main = $(let

makeLetStatement :: String - ExpQ - ExpQ
makeLetStatement s rest = letE [ valD (varP (mkName s))
(normalB $ stringE s) []]
rest

in makeLetStatement a [| print $(dyn a) |] )


--
Adam

___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe