Re: [Haskell-cafe] ANN: data-fix-cse -- Common subexpression elimination for EDSLs

2013-02-22 Thread Conal Elliott
On Tue, Feb 19, 2013 at 9:28 PM, Anton Kholomiov
wrote:

>
> Do you think the approach can be extended for non-regular (nested)
>> algebraic types (where the recursive data type is sometimes at a different
>> type instance)? For instance, it's very handy to use GADTs to capture
>> embedded language types in host language (Haskell) types, which leads to
>> non-regularity.
>>
>>
> I'm not sure I understand the case you are talking about. Can you write a
> simple example
> of the types like this?
>

Here's an example of a type-embedded DSEL, represented as a GADT:

> data E :: * -> * where
>   Lit :: Show a => a -> E a
>   Op  :: Op a -> E a
>   App :: E (a -> b) -> E a -> E b
>   ...
>
> data Op :: * -> * where
>   Add :: Num a => E (a -> a -> a)
>   Mul :: Num a => E (a -> a -> a)
>   Neg :: Num a => E (a -> a)
>   ...

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


Re: [Haskell-cafe] Type checking the content of a string

2013-02-22 Thread Corentin Dupont
I'm trying to load my interpreter in the Q monad:

cr :: QuasiQuoter
cr = QuasiQuoter { quoteExp = quoteRuleFunc}

quoteRuleFunc :: String -> Q TH.Exp
quoteRuleFunc s = do
   res <- runIO $ runInterpreter $ do
  setImports ["Prelude", "Language.Nomyx.Rule",
"Language.Nomyx.Expression", "Language.Nomyx.Test",
   "Language.Nomyx.Examples", "GHC.Base", "Data.Maybe"]
  interpret s (as :: RuleFunc)
   case res of
  Right _ -> [| s |]
  Left e -> fail $ show e


 However, I always obtain an error durring compilation:

...
Loading package XXX ... linking ... done.


GHCi runtime linker: fatal error: I found a duplicate definition for symbol
   __stginit_ghczm7zi4zi1_DsMeta
whilst processing object file
   /usr/lib/ghc/ghc-7.4.1/libHSghc-7.4.1.a
This could be caused by:
   * Loading two different object files which export the same symbol
   * Specifying the same object file twice on the GHCi command line
   * An incorrect `package.conf' entry, causing some object to be
 loaded twice.
GHCi cannot safely continue in this situation.  Exiting now.  Sorry.


I vaguely understand that the interpreted modules are conflicting with the
compiled ones...


On Fri, Feb 22, 2013 at 11:51 PM, Corentin Dupont  wrote:

> Great! That seems very powerful. So you can do what you want during
> compilation, readin files, send data over the network?
> Other question, in my example how can I halt the compilation if a test
> program is wrong?
>
>
> On Fri, Feb 22, 2013 at 8:30 PM, Francesco Mazzoli  wrote:
>
>> At Fri, 22 Feb 2013 19:43:51 +0100,
>> Corentin Dupont wrote:
>> > Hi Adam,
>> > that looks interresting. I'm totally new to TH and QuasiQuotes, though.
>> > Can I run IO in a QuasiQuoter? I can run my own interpreter.
>>
>> Yes, you can:
>> <
>> http://hackage.haskell.org/packages/archive/template-haskell/2.8.0.0/doc/html/Language-Haskell-TH.html#v:runIO
>> >.
>>
>> Francesco
>>
>
>
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Parsec without data declarations/AST

2013-02-22 Thread Alexander Solla
On Wed, Feb 20, 2013 at 1:09 AM, Sean Cormican wrote:

> Thanks that is exactly what I was looking for, one further question I
> might ask is how I might allow for either a integer or a string to be
> parsed. As it is now I get a complaint if I try and parse either a String
> or an Integer without creating a data declaration for say "Express"
> containing:
>
> data Express = ID String
>   | Num Integer
>
> is there a way around this without a need for a data declaration?
> As far as I know the parser will only accept (in this case) either Strings
> or Integers but not both, for example:
>
> expr8 = name
> <|> number
>
> name :: String
> number :: Integer
>
>
I don't see how expr8 type checks at all.  (<|>) is for "alternative"
functors.

In any case, I think we're using vocabulary differently.  To me, a parser
"accepts" strings and "returns" whatever value was constructed by parsing
the string.  So, if you want to "return" a value that could be a String or
an Integer, you'll have to return (Either String Integer) or (Either
Integer String) or make an algebraic data type.

Note that Either a b is an algebraic data type defined by:

> data Either a b = Left a | Right b



> will cause an error unless name and number are created using the value
> constructors ID and Num and are both the data type Express. Anybody have
> any thoughts on this ?
>
> Thanks in Advance,
> Seán
>
>
>
> On Tue, Feb 19, 2013 at 11:22 PM, Alexander Solla wrote:
>
>> Come to think of it, a parsec parser already wraps over Either, so if all
>> you want to do is check if a result is valid, you can abuse the Either
>> semantics so that your type is:
>>
>> Parser () -- the parser which returns nothing on success or an error on
>> failure.
>>
>>
>> On Tue, Feb 19, 2013 at 3:20 PM, Alexander Solla wrote:
>>
>>> If all you want to do is check that the code is valid (i.e., you aren't
>>> going to interpret the code), you can just return a Bool.  If you want to
>>> interpret it, but don't want to have a Stmt type, you can return IO ()
>>> actions.  In that case, the parser's type will be
>>>
>>> Parser (IO ())
>>>
>>> I think an algebraic AST (or even a functorial/monadic one) will help
>>> separate concerns, and will eventually help when it comes time to optimize
>>> your compiler.  It really isn't as much boilerplate as it looks like (in
>>> fact, there's hardly any boilerplate if you target free monads and
>>> interpret those in IO), and you get the type safety for which Haskell is
>>> well-known.
>>>
>>>
>>>
>>> On Tue, Feb 19, 2013 at 3:02 PM, Sean Cormican 
>>> wrote:
>>>
 I have been trying to create a parser for a functional programming
 language, but there is no need to create an AST but merely check that the
 code is valid according to the grammar.

 In the following tutorial I have been trying to take some pointers
 from, data declarations are used to create an AST for the language, There
 is, as I understand a way to parse the language without an AST.

 http://www.haskell.org/haskellwiki/Parsing_a_simple_imperative_language

 My question is what should the type signatures for example parseFile
 function instead of "Stmt" accept as input if the parser is to accept
 Strings and numerical expressions alike ?

 Thanks for any help,
 Seán

 ___
 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] Type checking the content of a string

2013-02-22 Thread Corentin Dupont
Great! That seems very powerful. So you can do what you want during
compilation, readin files, send data over the network?
Other question, in my example how can I halt the compilation if a test
program is wrong?

On Fri, Feb 22, 2013 at 8:30 PM, Francesco Mazzoli  wrote:

> At Fri, 22 Feb 2013 19:43:51 +0100,
> Corentin Dupont wrote:
> > Hi Adam,
> > that looks interresting. I'm totally new to TH and QuasiQuotes, though.
> > Can I run IO in a QuasiQuoter? I can run my own interpreter.
>
> Yes, you can:
> <
> http://hackage.haskell.org/packages/archive/template-haskell/2.8.0.0/doc/html/Language-Haskell-TH.html#v:runIO
> >.
>
> Francesco
>
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] question about: --hyperlink-source

2013-02-22 Thread Albert Y. C. Lai

On 13-02-21 05:18 AM, Doaitse Swierstra wrote:

I ran into the problem that for the packages which I install using

cabal install

The generated html does not contain links to the sources. This issue was raised 
before in:

http://stackoverflow.com/questions/1587635/haddock-for-cabal-installed-modules

I have been looking into the documentation available, but could not find a way 
to set this e.g. as a default in some .haddock file.


(I infer that you already have "documentation: True" in your 
$HOME/.cabal/config. Therefore, I will omit --enable-documentation.)


Since cabal-install 0.14: cabal install --haddock-hyperlink-source

Requires hscolour.

Unfortunately, this flag has no corresponding line in $HOME/.cabal/config.

There are several related --haddock-thisthat flags. See cabal install 
--help for more. (They are conveniently near the end.)


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


Re: [Haskell-cafe] How to input Unicode string in Haskell program?

2013-02-22 Thread Albert Y. C. Lai

On 13-02-21 04:58 AM, Semyon Kholodnov wrote:

— Windows console is locked to one specific local code page, and no
codepage contains Latin-1, Cyrillic and Kanji symbols at the same
time.


Windows console is not locked to an anti-international code page; it is 
only defaulted to.


Use CHCP 65001 to switch to the UTF-8 code page.

Unfortunately, code page and encoding is only half of the battle; the 
other half is fonts. Most Windows fonts are incomplete; all Windows 
fixed-width fonts are incomplete. (Silver lining: Arial Unicode is 
sufficiently complete.) Therefore, you may be unable to display some 
characters, but they are the correct characters.



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


Re: [Haskell-cafe] Type checking the content of a string

2013-02-22 Thread Francesco Mazzoli
At Fri, 22 Feb 2013 19:43:51 +0100,
Corentin Dupont wrote:
> Hi Adam,
> that looks interresting. I'm totally new to TH and QuasiQuotes, though.
> Can I run IO in a QuasiQuoter? I can run my own interpreter.

Yes, you can:
.

Francesco

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


Re: [Haskell-cafe] Type checking the content of a string

2013-02-22 Thread Corentin Dupont
Hi Adam,
that looks interresting. I'm totally new to TH and QuasiQuotes, though.
Can I run IO in a QuasiQuoter? I can run my own interpreter.



On Fri, Feb 22, 2013 at 7:12 PM, adam vogt  wrote:

> On Fri, Feb 22, 2013 at 12:44 PM, Corentin Dupont
>  wrote:
> > Hi all,
> > I have a program able to read another program as a string, and interpret
> it
> > (using Hint).
> > I'd like to make unit tests, so I have a file "Test.hs" containing a
> serie
> > of test programs as strings.
> > However, how could I be sure that these test program are syntactically
> > valid, at compile time?
>
> Hi Corentin,
>
> You could write the test programs like:
>
> test1 :: String
> test1 = [qq| x+1 == 3 |]
>
> Where qq is a QuasiQuoter you have to define. It could try to parse
> the string with http://hackage.haskell.org/package/haskell-src-exts,
> and if that succeeds, returns the original string.
>
> --
> Adam
>
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Type checking the content of a string

2013-02-22 Thread adam vogt
On Fri, Feb 22, 2013 at 12:44 PM, Corentin Dupont
 wrote:
> Hi all,
> I have a program able to read another program as a string, and interpret it
> (using Hint).
> I'd like to make unit tests, so I have a file "Test.hs" containing a serie
> of test programs as strings.
> However, how could I be sure that these test program are syntactically
> valid, at compile time?

Hi Corentin,

You could write the test programs like:

test1 :: String
test1 = [qq| x+1 == 3 |]

Where qq is a QuasiQuoter you have to define. It could try to parse
the string with http://hackage.haskell.org/package/haskell-src-exts,
and if that succeeds, returns the original string.

--
Adam

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


[Haskell-cafe] Type checking the content of a string

2013-02-22 Thread Corentin Dupont
Hi all,
I have a program able to read another program as a string, and interpret it
(using Hint).
I'd like to make unit tests, so I have a file "Test.hs" containing a serie
of test programs as strings.
However, how could I be sure that these test program are syntactically
valid, at compile time?
Those programs should have the type "RuleFunc".

I tried some TH:
printProg :: Q Exp -> String
printProg p = unsafePerformIO $ do
   expr <- runQ p
   return $ pprint expr

myTest = printProg [|  :: RuleFunc |]

But it's not very satisfatory yet. When pretty printing TH changes the
program quite a bit and my interpreter cannot compile it due to scoping
problems.
I'd like to have my test program copied back as is. Is it possible? Any
other solutions?

Thanks a lot!
Corentin
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] How to input Unicode string in Haskell program?

2013-02-22 Thread Semyon Kholodnov
I would like to point out again that I am talking about Windows. I
don't care about Linux—I'm sure you already threw away all those
stupid legacy one- and multibyte code pages and migrated to UTF8
completely, but that's not quite the current state of Windows. Console
still doesn't cope with Unicode quite well.

Anyway, the problem is partially solved: I patched my WinGHCi so it no
longer chokes on Unicode input, and as for compiled .exe... I'll see.

2013/2/22, Jon Fairbairn :
> Alexander V Vershilov  writes:
>
>> The problem is that Prelude.getLine uses current locale to load
>> characters:
>> for example if you have utf8 locale, then everything works out of the box:
>>
>>> $ runhaskell 1.hs
>>> résumé 履歴書 резюме
>>> résumé 履歴書 резюме
>>
>> But if you change locale you'll have error:
>>
>>> LANG="C" runhaskell 1.hs
>>> résumé 履歴書 резюме
>>> 1.hs: : hGetLine: invalid argument (invalid byte sequence)
>
> That seems to be correct behaviour: the only way to know the
> meaning of the bits input by a user is what encoding the user
> says they are in.
>
> But in general this issue is an instance of inheriting sins from
> the OS: the meaning of the bit pattern in a file should be part
> of the file, but we are stuck with OSs that use a global
> variable (which should be anathema to Haskell). So if user A has
> locale set one way and inputs a file and sends the filename to
> user B on the same system, user B might well see something
> completely different to A when looking at the file.
>
>> To force haskell use UTF8 you can load string as byte sequence
>> and convert it to UTF-8 charecters
>
> but of course, the programmer can only hope that utf-8 will work
> here. If the user is typing in KOI-8R, reading it as utf-8 is
> going to be wrong.
> --
> Jón Fairbairn jon.fairba...@cl.cam.ac.uk
>
>
> ___
> 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] package show needs upper version bound for smallcheck?

2013-02-22 Thread Johannes Waldmann

> Could the maintainers of "show"
> http://hackage.haskell.org/package/show-0.4.1.2
> please add some version bound (< 1  or similar)
> for the smallcheck dependency?

Thanks for the quick reaction.
show-0.5 now depends on smallcheck>=1.0 
This works until the next API-breaking change in smallcheck ...

I admit that I find too-detailed upper bounds on dependencies
impractical as well, because they make upgrades really painful; 
so mostly I'm too lazy to write any bounds. 
Which is a bad idea, as the above example shows.

Perhaps a dependency on a major version (only) 
could be a reasonable policy (smallcheck == 1.*)


PS: Anyway the underlying problems that these policies
try to solve (did the API "really" change? 
did the observable behaviour of the implementation change?)
can only be solved by formal specification and verification.

(e.g., you write down the full specification of a "sort" function,
then a machine can check whether some library contains some function 
that claims to fulfil this spec, and it can also check
whether the claim holds true - if the implementation comes with a proof)

(Corollary: Agda would not need a package versioning policy
because it can solve these problems at the language level :-)




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


Re: [Haskell-cafe] Is the haksell-pkg-janitors group on github alive?

2013-02-22 Thread Jan Stolarek
> Unfortunately there doesn't seem
> to be a way of getting pull request notifications.
You can get such notifications. You need to watch a repo (enabled by default if 
you have push 
permissions) and enable notifications for watching in Account settings -> 
Notification Center.

> Anyway, applied all your patches.
Thanks!

Janek

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


Re: [Haskell-cafe] Is the haksell-pkg-janitors group on github alive?

2013-02-22 Thread Erik de Castro Lopo
Jan Stolarek wrote:

> Does anyone know if haksell-pkg-janitors group on github is alive? I've 
> submitted a pull request a 
> week ago but no response so far.

I'm in the haksell-pkg-janitors group. Unfortunately there doesn't seem
to be a way of getting pull request notifications.

Anyway, applied all your patches.

Cheers,
Erik
-- 
--
Erik de Castro Lopo
http://www.mega-nerd.com/

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


[Haskell-cafe] Is the haksell-pkg-janitors group on github alive?

2013-02-22 Thread Jan Stolarek
Does anyone know if haksell-pkg-janitors group on github is alive? I've 
submitted a pull request a 
week ago but no response so far.

Janek

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


Re: [Haskell-cafe] How to input Unicode string in Haskell program?

2013-02-22 Thread Jon Fairbairn
Alexander V Vershilov  writes:

> The problem is that Prelude.getLine uses current locale to load characters:
> for example if you have utf8 locale, then everything works out of the box:
>
>> $ runhaskell 1.hs
>> résumé 履歴書 резюме
>> résumé 履歴書 резюме
>
> But if you change locale you'll have error:
>
>> LANG="C" runhaskell 1.hs
>> résumé 履歴書 резюме
>> 1.hs: : hGetLine: invalid argument (invalid byte sequence)

That seems to be correct behaviour: the only way to know the
meaning of the bits input by a user is what encoding the user
says they are in.

But in general this issue is an instance of inheriting sins from
the OS: the meaning of the bit pattern in a file should be part
of the file, but we are stuck with OSs that use a global
variable (which should be anathema to Haskell). So if user A has
locale set one way and inputs a file and sends the filename to
user B on the same system, user B might well see something
completely different to A when looking at the file.

> To force haskell use UTF8 you can load string as byte sequence
> and convert it to UTF-8 charecters

but of course, the programmer can only hope that utf-8 will work
here. If the user is typing in KOI-8R, reading it as utf-8 is
going to be wrong.
-- 
Jón Fairbairn jon.fairba...@cl.cam.ac.uk


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