[Haskell-cafe] mapFst and mapSnd

2013-05-28 Thread Dominique Devriese
Hi all,

I often find myself needing the following definitions:

  mapPair :: (a - b) - (c - d) - (a,c) - (b,d)
  mapPair f g (x,y) = (f x, g y)

  mapFst :: (a - b) - (a,c) - (b,c)
  mapFst f = mapPair f id

  mapSnd :: (b - c) - (a,b) - (a,c)
  mapSnd = mapPair id

But they seem missing from the prelude and Hoogle or Hayoo only turn
up versions of them in packages like scion or fgl.  Has anyone else
felt the need for these functions?  Am I missing some generalisation
of them perhaps?

Regards,
Dominique

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


Re: [Haskell-cafe] mapFst and mapSnd

2013-05-28 Thread Dominique Devriese
2013/5/28 Tikhon Jelvis tik...@jelv.is:
 These are present in Control.Arrow as (***), first and second respectively.

Right, thanks. Strange that neither Hayoo nor Hoogle turned these up..

Dominique

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


Re: [Haskell-cafe] monadic DSL for compile-time parser generator, not possible?

2013-03-13 Thread Dominique Devriese
All,

2013/3/13  o...@okmij.org:
 So, Code is almost applicative. Almost -- because we only have a
 restricted pure:
 pureR :: Lift a = a - Code a
 with a Lift constraint. Alas, this is not sufficient for realistic
 parsers, because often we have to lift functions, as in the example of
 parsing a pair of characters:

I've previously used an approach like this in the grammar-combinators
library.  See 
http://hackage.haskell.org/packages/archive/grammar-combinators/0.2.7/doc/html/Text-GrammarCombinators-Base-ProductionRule.html#t:LiftableProductionRule
and 
http://hackage.haskell.org/packages/archive/grammar-combinators/0.2.7/doc/html/Text-GrammarCombinators-Utils-LiftGrammar.html.

The approach uses a restricted pure like this:

class ProductionRule p = LiftableProductionRule p where
  epsilonL :: a - Q Exp - p aSource

and associated
  epsilonLS :: (Lift v, LiftableProductionRule p) = v - p v
  epsilonLS v = epsilonL v $ lift v

There is a function liftGrammar which lifts a grammar that uses the
type class to a list of declarations using TH.

This allowed me to start from a context-free grammar, transform it to
a non-left-recursive grammar, optimize it and then lift it using TH.
In some tests, I found that this improved performance significantly
over using the transformed grammar directly, even when I try to force
the transformation to happen before the benchmark.  I assume this is
because the lifted grammar is optimised better by the compiler.

Regards,
Dominique

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


Re: [Haskell-cafe] monadic DSL for compile-time parser generator, not possible?

2013-03-13 Thread Dominique Devriese
2013/3/13 Dominique Devriese dominique.devri...@cs.kuleuven.be:
 class ProductionRule p = LiftableProductionRule p where
   epsilonL :: a - Q Exp - p aSource

 and associated
   epsilonLS :: (Lift v, LiftableProductionRule p) = v - p v
   epsilonLS v = epsilonL v $ lift v

Note that the point of providing epsilonL as primitive and not just
epsilonLS is that I can then still lift most functions I use:

  epsilonL (,) [| (,) |]

Even though functions are not necessarily liftable. This is an
alternative to Oleg's adding of e.g. pair etc. as DSL primitives.

Dominique

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


Re: [Haskell-cafe] Parser left recursion

2013-02-26 Thread Dominique Devriese
2013/2/26 Martin Drautzburg martin.drautzb...@web.de:
 I wonder if I can enforce the nonNr property somehow, i.e. enforce the rule
 will not consider the same nonterminal again without having consumed any
 input.

You might be interested in this paper:

  Danielsson, Nils Anders. Total parser combinators. ACM Sigplan
Notices. Vol. 45. No. 9. ACM, 2010.

Regards,
Dominique

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


Re: [Haskell-cafe] Parser left recursion

2013-02-20 Thread Dominique Devriese
All,

Many (but not all) of the parsing algorithms that support left
recursion cannot be implemented in Haskell using the standard
representation of recursion in parser combinators.  The problem
can be avoided in Scala because it has imperative features like
referential identity and/or mutable references. The most practical
solution currently is probably to manually transform your grammars
to a non-left-recursive form (as suggested above) and then use a
standard parser combinator library with a top-down parsing algorithm
(I suggest uu-parsinglib).

That being said, there is active research into alternative functional
representations of recursion in grammars/parsers that support a wider
range of algorithms. If you want to read up on such research, I
suggest the following papers to get an idea of some of the approaches:

  Baars, Arthur, S. Doaitse Swierstra, and Marcos Viera. Typed
transformations of typed grammars: The left corner transform.
Electronic Notes in Theoretical Computer Science 253.7 (2010): 51-64.
  Devriese, Dominique, et al. Fixing idioms: A recursion primitive
for applicative dsls. Proceedings of the ACM SIGPLAN 2013 workshop on
Partial evaluation and program manipulation. ACM, 2013.
 Oliveira, Bruno CdS, and William R. Cook. Functional programming
with structured graphs. Proceedings of the 17th ACM SIGPLAN
international conference on Functional programming. ACM, 2012.
 Oliveira, Bruno C. D. S., and Andres Löh. Abstract syntax graphs for
domain specific languages. Proceedings of the ACM SIGPLAN 2013
workshop on Partial evaluation and program manipulation. ACM, 2013.
  DEVRIESE, DOMINIQUE, and FRANK PIESSENS. Finally tagless observable
recursion for an abstract grammar model. Journal of Functional
Programming 1.1: 1-40.

For the last one, you can check out
http://projects.haskell.org/grammar-combinators/ about the
grammar-combinators library on Hackage. It has a packrat parser that
can deal with left-recursion and a grammar transformation that
transforms it away. There is a tutorial you can checkout.

Dominique

2013/2/20 Tillmann Rendel ren...@informatik.uni-marburg.de:
 Hi,


 Roman Cheplyaka wrote:

 Another workaround is to use memoization of some sort — see e.g. GLL
 (Generalized LL) parsing.


 Is there a GLL parser combinator library for Haskell? I know about the
 gll-combinators for Scala, but havn't seen anything for Haskell.

 Bonus points for providing the graph-structured stack (for maximal sharing
 in the computation) and the shared packed parse forest (for maximal sharing
 in the results) as reusable components.

   Tillmann


 ___
 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] [Agda] How to avoid T3 fonts in pdf generated with lhs2TeX?

2012-11-01 Thread Dominique Devriese
Andreas,

2012/11/1 Andreas Abel andreas.a...@ifi.lmu.de:
 Hello,

 maybe someone has experience in publishing papers that use lhs2TeX and
 unicode characters with ACM, and has been in my situation before...

 Sheridan, who publishes for ACM, does not like T3 fonts. However, lhs2tex
 --agda does make use of T3 fonts via:

   \RequirePackage[utf8x]{inputenc}

 If I remove this, my unicode characters are garbled in the lhs2tex-generated
 code. Does anoyone know a smart workaround besides replacing all the unicode
 characters manually by some math symbols in the .tex file?

Not sure about all this, but perhaps you can try to use utf8 instead
of utf8x and manually define translations for the unicode characters
that you use,e.g.:

\DeclareUnicodeCharacter{2032}{'}
\DeclareUnicodeCharacter{2080}{_0}
\DeclareUnicodeCharacter{2081}{_1}
\DeclareUnicodeCharacter{2082}{_2}
\DeclareUnicodeCharacter{2115}{\mathbb{N}}
\DeclareUnicodeCharacter{2192}{\to}
\DeclareUnicodeCharacter{2200}{\forall\,}

Perhaps you can then somehow avoid translations that use T3 fonts (not
sure what these are though). Note: the numbers are the characters'
unicode hexadecimal representation (AFAIU), which you can find e.g.
using emacs's describe-char.

Dominique

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


Re: [Haskell-cafe] Applicative functors with branch/choice ?

2012-07-25 Thread Dominique Devriese
Евгений,

 The possible extension may look somehow like this:

 class Applicative a = Branching a where
  branch :: a (Either b c) - (a b - a d) - (a c - a d) - a d

What about the following alternative that does not require an extension?

  import Control.Applicative

  eitherA :: Applicative f = f (a - c) - f (b - c) - f (Either a b) - f c
  eitherA = liftA3 either

Note by the way that the result of this function will execute the
effects of all of its arguments (as you would expect for an
Applicative functor).

Dominique

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


Re: [Haskell-cafe] specifying using type class

2012-07-23 Thread Dominique Devriese
Patrick,

 -- Class with functional dependency
 class QUEUE_SPEC_CLASS2 a q | q - a where
newC2 :: q a -- ??
sizeC2  :: q a - Int
restC2  :: q a - Maybe (q a)
insertC2 :: q a - a - q a

The above is a reasonable type class definition for what you seem to intend.

 -- Without committing to some concrete representation such as list I do not 
 know how to specify constructor for insertC2 ?? =  ??
insertC2  newC2 a = newC2 -- wrong
isEmptyC2  :: q a - Bool
isEmptyC2 newC2  = True
 --   isEmptyC2 (insertC2 newC2 a) = False wrong

Correct me if I'm wrong, but what I understand you want to do here is
specify axioms on the behaviour of the above interface methods,
similar to how the well-known |Monad| class specifies for example m
= return === m.  You seem to want for example an axiom saying

  isEmptyC2 newC2 === True

and similar for possible other equations. With such axioms you don't
need access to actual constructors and you don't want access to them
because concrete implementations may use a different representation
that does not use such constructors. Anyway, in current Haskell, such
type class axioms can not be formally specified or proven but they are
typically formulated as part of the documentation of a type class and
implementations of the type class are required to satisfy them but
this is not automatically verified.

Dominique

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


Re: [Haskell-cafe] TLS 0.9.6, question about session resumption.

2012-07-21 Thread Dominique Devriese
Hi,

2012/7/21 C Gosch ch.go...@googlemail.com:
 I am trying to use the TLS package from hackage, and it works fine so
 far -- except when a client wants to
 do session resumption (note I am not an expert in TLS, so it might be
 something quite simple).
 In that case, I get an alert, unexpected message, during handshake.

 The handshake goes like this:
 ClientHello (with a SessionID)
 ServerHello (with the same SessionID)
 ServerHelloDone

Not an expert either, but section 7.4 of the TLS 1.2 spec (rfc 5246)
does seem to say that this ServerHelloDone should be a Finished
message instead.

 and then the server says
  (AlertLevel_Fatal,UnexpectedMessage)

Do you mean that the client says this? If so, this may obviously be
correct if the server sends the wrong message. Pehaps you can test
with a different server implementation?

 I'm not sure whether the ServerHelloDone should happen when resuming.
 Does anyone have a hint what may be going wrong?
 I am using TLS10 and the tls package with version 0.9.6.

Bye
Dominique

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


Re: [Haskell-cafe] Martin Odersky on What's wrong with Monads

2012-06-28 Thread Dominique Devriese
2012/6/27 Tillmann Rendel ren...@informatik.uni-marburg.de:
 MightyByte wrote:

 Of course every line of your program that uses a Foo will change if you
 switch
 to IO Foo instead.


 But we often have to also change lines that don't use Foo at all. For
 example, here is the type of binary trees of integers:

  data Tree = Leaf Integer | Branch (Tree Integer) (Tree Integer)

 A function to add up all integers in a tree:

  amount:: Tree - Integer
  amount (Leaf x) = x
  amount (Branch t1 t2) = amountt1 + amountt2

 All fine so far. Now, consider the following additional requirement: If the
 command-line flag --multiply is set, the function amount computes the
 product instead of the sum.

 In a language with implicit side effects, it is easy to implement this. We
 just change the third line of the amount function to check whether to call
 (+) or (*). In particular, we would not touch the other two lines.

 How would you implement this requirement in Haskell without changing the
 line amount (Leaf x) = x?

I may be missing the point here, but having worked on large code bases
with a wide variety contributors before, I find it very advantageous
that programmers are prevented from writing an amount function whose
behaviour depends on command line arguments without at least an
indication in the type. The fact that the function can not perform
stuff like that is precisely the guarantee that the Haskell type gives
me...

Dominique

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


Re: [Haskell-cafe] lhs2TeX: automatic line wrap within code blocks?

2012-04-05 Thread Dominique Devriese
David,

The easiest solution is probably to use multi-line string literals and
line-wrap manually:

\begin{code}
cyphertext = rlkmlj, zlnift ekblvke pqc elvm if pzlp gblrk, akrlomk zk zle \
  lfpiriglpke pzlp, if pzk flpojlb rcojmk cs knkfpm, morz qcobe ak pzk rcfeorp \
  cs nkjriftkpcjiu, bklnkm pzk ljdv ofekj gjkpkfmk cs jlimift jkrjoipm lfe \
  rlnlbjv
\end{code}

Dominique

Op 4 april 2012 20:14 heeft david.mihola david.mih...@gmail.com het
volgende geschreven:
 Hello,

 I am currently using lhs2TeX for the first time and have encountered a
 problem which I am unable to solve myself: Some code lines are too long to
 fit into a single line of the output (PDF) file and thus go off the right
 edge of the page.

 Consider the following example:

 -

 \documentclass{article}
 \usepackage[utf8]{inputenc}

 %include polycode.fmt
 %options ghci
 \begin{document}

 Our encrypted message:

 \begin{code}
 cyphertext = rlkmlj, zlnift ekblvke pqc elvm if pzlp gblrk, akrlomk zk zle
 lfpiriglpke pzlp, if pzk flpojlb rcojmk cs knkfpm, morz qcobe ak pzk rcfeorp
 cs nkjriftkpcjiu, bklnkm pzk ljdv ofekj gjkpkfmk cs jlimift jkrjoipm lfe
 rlnlbjv
 \end{code}

 Our decryption function:

 \begin{code}
 decrypt = id
 \end{code}

 The original message was:

 \eval{decrypt cyphertext}

 \end{document}

 -

 Converting this to .tex with lhs2TeX and to .pdf with pdflatex produces a
 PDF in which both instances of the cyphertext go off the right edge of the
 page.

 Is there any way to tell lhs2TeX to allow/force line wrap within code blocks
 and eval-statements?

 Thank you very much for any help!

 David

 P.S.: I have only found one prior discussion of my question
 (http://tex.stackexchange.com/questions/15048/how-to-typeset-a-multiline-text-in-math-environment)
 but to my understanding no real answer came out of that.

 --
 View this message in context: 
 http://haskell.1045720.n5.nabble.com/lhs2TeX-automatic-line-wrap-within-code-blocks-tp5618600p5618600.html
 Sent from the Haskell - Haskell-Cafe mailing list archive at Nabble.com.

 ___
 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] decoupling type classes

2012-01-17 Thread Dominique Devriese
2012/1/16 Yin Wang yinwa...@gmail.com:
 The typical example would be

 instance Eq a = Eq [a] where
  [] == [] = True
  (a : as) == (b : bs) = a == b  as == bs
  _ == _ = False

 It can handle this case, although it doesn't handle it as a parametric
 instance. I suspect that we don't need the concept of parameter
 instances at all. We just searches for instances recursively at the
 call site:

 That seems like it could work, but typically, one would like
 termination guarantees for this search, to avoid the type-checker
 getting stuck...

 Good point. Currently I'm guessing that we need to keep a stack of the
 traced calls. If a recursive call needs an implicit parameter X which
 is matched by one of the functions in the stack, we back up from the
 stack and resolve X to the function found on stack.

You may want to look at scala's approach for their implicit arguments.
They use a certain to conservatively detect infinite loops during the
instance search, but I don't remember the details off hand. While
talking about related work, you may also want to take a look at
Scala's implicit arguments, GHC implicit arguments and C++ concepts...


 foo x =
   let overload bar (x:Int) = x + 1
   in \() - bar x


 baz =
  in foo (1::Int)

 Even if we have only one definition of bar in the program, we should
 not resolve it to the definition of bar inside foo. Because that
 bar is not visible at the call site foo (1::int). We should report
 an error in this case. Think of bar as a typed dynamically scoped
 variable helps to justify this decision.

 So you're saying that any function that calls an overloaded function
 should always allow its own callers to provide this, even if a correct
 instance is in scope. Would that mean all instances have to be
 resolved from main? This also strikes me as strange, since I gather
 you would get something like length :: Monoid Int = [a] - Int,
 which would break if you happen to have a multiplicative monoid in
 scope at the call site?

 If you already have a correct instance in scope, then you should have
 no way defining another instance with the same name and type in the
 scope as the existing one. This is the case for Haskell.

Yes, but different ones may be in scope at different places in the code, right?

 But it may be useful to allow nested definitions (using let) to shadow
 the existing instances in the outer scope of the overloaded call.

I considered something like this for instance arguments in Agda, but
it was hard to make the instance resolution deterministic when
allowing such a form of prioritisation. The problem occurred if a
shadower and shadowee instance had slightly different types, such that
only the shadowee was actually type-valid for a certain instance
argument. However, the type information which caused the shadower to
become invalid only became available late in the type inference
process. In such a case, it is necessary to somehow ascertain that the
shadower instance is not chosen, but I did not manage to figure out
how to get this right.

Dominique

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


Re: [Haskell-cafe] decoupling type classes

2012-01-16 Thread Dominique Devriese
Yin,

2012/1/14 Yin Wang yinwa...@gmail.com:
 On Sat, Jan 14, 2012 at 2:38 PM, Dominique Devriese
 dominique.devri...@cs.kuleuven.be wrote:
 I may or may not have thought about it. Maybe you can give an example
 of parametric instances where there could be problems, so that I can
 figure out whether my system works on the example or not.

 The typical example would be

 instance Eq a = Eq [a] where
  [] == [] = True
  (a : as) == (b : bs) = a == b  as == bs
  _ == _ = False

 It can handle this case, although it doesn't handle it as a parametric
 instance. I suspect that we don't need the concept of parameter
 instances at all. We just searches for instances recursively at the
 call site:

That seems like it could work, but typically, one would like
termination guarantees for this search, to avoid the type-checker
getting stuck...

 foo x =
   let overload bar (x:Int) = x + 1
   in \() - bar x


 baz =
  in foo (1::Int)

 Even if we have only one definition of bar in the program, we should
 not resolve it to the definition of bar inside foo. Because that
 bar is not visible at the call site foo (1::int). We should report
 an error in this case. Think of bar as a typed dynamically scoped
 variable helps to justify this decision.

So you're saying that any function that calls an overloaded function
should always allow its own callers to provide this, even if a correct
instance is in scope. Would that mean all instances have to be
resolved from main? This also strikes me as strange, since I gather
you would get something like length :: Monoid Int = [a] - Int,
which would break if you happen to have a multiplicative monoid in
scope at the call site?

Dominique

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


Re: [Haskell-cafe] decoupling type classes

2012-01-12 Thread Dominique Devriese
Yin,

2012/1/12 Yin Wang yinwa...@gmail.com:
 I have an idea about type classes that I have been experimenting. It
 appears to be a generalization to Haskell’s type classes and seems to
 be doable. It seems to related the three ideas: type classes, implicit
 parameters, and (typed) dynamic scoping. But I don't know whether it
 is good or not. I hope to get some opinions before going further.

I find your ideas interesting. You may be interested in a related
design which I recently implemented for Agda [2], and an ICFP 2011
paper that presents it [1].

Also, you don't seem to have thought about the question of parametric
instances: do you allow them or not, if you do, what computational
power do they get etc.?

 I have an experimental system which “decouples” the dictionary.
 Instead of passing on a dictionary, it passes individual “implicit
 parameters around. Those implicit parameters are type inferenced and
 they can contain type parameters just as methods in a type class.
 Similarly, they are resolved by their types in the call site's scope.

I'm surprised that you propose passing all type class methods
separately. It seems to me that for many type classes, you want to
impose a certain correspondence between the types of the different
methods in a type class (for example, for the Monad class, you would
expect return to be of type (a - m a) if (=) is of type (m a - (a
- m b) - m b)). I would expect that inferencing these releations in
each function that uses either of the methods will lead to overly
general inferenced types and the need for more guidance to the type
inferencer?

By separating the methods, you would also lose the laws that associate
methods in a type class, right?

An alternative to what you suggest, is the approach I recommend for
using instance arguments: wrapping all the methods in a standard data
type (i.e. define the dictionary explicitly), and pass this around as
an implicit argument.

 The convenience of this approach compared to Haskell’s type classes is
 that we no longer require a user of a type class to define ALL the
 methods in a type class. For example, a user could just define a
 method + without defining other methods in the Num class: -, *, … He
 can use the method + independently. For example, if + is defined on
 the String type to be concatenation, we can use + in another function:

 weirdConcat x y = x + y + y

 This has a utility, because the methods in the Num class don’t “make
 sense” for Strings except +, but the current type class design
 requires us to define them. Note here that weirdConcat will not have
 the type (Num a) = a - a - a, since we no longer have the Num
 class, it is decoupled into separate methods.

For this example, one might also argue that the problem is in fact
that the Num type class is too narrow, and + should instead be defined
in a parent type class (Monoid comes to mind) together with 0 (which
also makes sense for strings, by the way)?

 There is another benefit of this decoupling: it can subsume the
 functionality of MPTC. Because the methods are no longer grouped,
 there is no “common” type parameter to the methods. Thus we can easily
 have more than one parameter in the individual methods and
 conveniently use them as MPTC methods.

Could you explain this a bit further?

 Here g is explicitly declared as “overloaded”, although my
 experimental system doesn’t need this. Any undefined variable inside
 function body automatically becomes overloaded. This may cause
 unintended overloading and it catches bugs late. That’s why we need
 the “overload” declarations.

I would definitely argue against treating undefined variables as
overloaded automatically. It seems this will lead to strange errors if
you write typo's for example.

 But the automatic overloading of the undefined may be useful in
 certain situations. For example, if we are going to use Haskell as a
 shell language. Every “command” must be evaluated when we type them.
 If we have mutually recursive definitions, the shell will report
 “undefined variables” either way we order the functions. The automatic
 overloading may solve this problem. The undefined variables will
 temporarily exist as automatic overloaded functions. Once we actually
 define a function with the same name AND satisfies the type
 constraints, they become implicit parameters to the function we
 defined before. If we call a function whose implicit parameters are
 not associated, the shell reports error very similar to Haskell’s
 “type a is not of class Num …”

The design you suggest seems to differ from Haskell's current
treatment, where functions can refer to other functions defined
further in the file, but still have them resolved statically?

 RELATIONSHIP TO DYNAMIC SCOPING

 It seems to be helpful to think of the “method calls” as referencing
 dynamically scoped variables. They are dispatched depending on the
 bindings we have in the call site's scope (and not the scope where the
 method is defined!). So it 

Re: [Haskell-cafe] Is it possible to represent such polymorphism?

2011-10-04 Thread Dominique Devriese
All,

In case anyone is interested, I just want to point out an interesting
article about the relation between Haskell type classes and C++
(overloading + concepts):

http://sms.cs.chalmers.se/publications/papers/2008-WGP.pdf

Dominique


2011/10/3 Ketil Malde ke...@malde.org:
 sdiy...@sjtu.edu.cn writes:

 This has nothing to do with OOP or being imperative. It's just about types.

 Of course, it's not necessarily linked to OOP, but OO languages - to the
 extent they have types - tend towards ad-hoc polymorphism instead of
 parametric polymorphism.  There are different trade-offs, one is the
 lack of return-type overloading in C++.

 -k
 --
 If I haven't seen further, it is by standing in the footprints of giants

 ___
 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] Smarter do notation

2011-09-04 Thread Dominique Devriese
It's not the same as what you propose, but it's related, so for
discussion, I just want to point out idiom brackets (an analog for
do-notation for Applicative functors) which have been introduced in
some Haskell-related languages. Examples are Idris
(http://www.cs.st-andrews.ac.uk/~eb/Idris/donotation.html) and SHE
(http://personal.cis.strath.ac.uk/~conor/pub/she/idiom.html).

Dominique

2011/9/4 Daniel Peebles pumpkin...@gmail.com:
 Hi all,
 I was wondering what people thought of a smarter do notation. Currently,
 there's an almost trivial desugaring of do notation into (=), (), and
 fail (grr!) which seem to naturally imply Monads (although oddly enough,
 return is never used in the desugaring). The simplicity of the desugaring is
 nice, but in many cases people write monadic code that could easily have
 been Applicative.
 For example, if I write in a do block:
 x - action1
 y - action2
 z - action3
 return (f x y z)
 that doesn't require any of the context-sensitivty that Monads give you, and
 could be processed a lot more efficiently by a clever Applicative instance
 (a parser, for instance). Furthermore, if return values are ignored, we
 could use the ($), (*), or (*) operators which could make the whole thing
 even more efficient in some instances.
 Of course, the fact that the return method is explicitly mentioned in my
 example suggests that unless we do some real voodoo, Applicative would have
 to be a superclass of Monad for this to make sense. But with the new default
 superclass instances people are talking about in GHC, that doesn't seem too
 unlikely in the near future.
 On the implementation side, it seems fairly straightforward to determine
 whether Applicative is enough for a given do block. Does anyone have any
 opinions on whether this would be a worthwhile change? The downsides seem to
 be a more complex desugaring pass (although still something most people
 could perform in their heads), and some instability with making small
 changes to the code in a do block. If you make a small change to use a
 variable before the return, you instantly jump from Applicative to Monad and
 might break types in your program. I'm not convinced that's necessary a bad
 thing, though.
 Any thoughts?
 Thanks,
 Dan
 ___
 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] SIGPLAN Programming Languages Software Award

2011-06-09 Thread Dominique Devriese
2011/6/9 Stephen Tetley stephen.tet...@gmail.com:
 On 9 June 2011 09:02, Yves Parès limestr...@gmail.com wrote:
 Were templates an original feature of C++ or did they appear in a revision
 of the langage ?
 Because C++ appeared in 1982 and Haskell in 1990.

 Templates were a later addition to C++. There is a strong tradition of
 generics in OO and related languages that seems rather unrelated to
 typed functional programming - ADA, Eiffel and particularly CLU.

Note that the more recent C++ concepts are related to (and inspired
by?) Haskell type classes. See Bernardy et al.'s interesting paper A
comparison of c++ concepts and haskell type classes:

  http://portal.acm.org/citation.cfm?id=1411324

 Congratulations to the Simon's of course, kudos _and_ escudos from the ACM!

Idem. The Simons, GHC and the associated research very much deserve this award.

Dominique

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


Re: [Haskell-cafe] Random thoughts about typeclasses

2011-05-18 Thread Dominique Devriese
Robert,

2011/5/16 Robert Clausecker fuz...@gmail.com:
 I found out, that GHC implements typeclasses as an extra argument, a
 record that stores all functions of the typeclass. So I was wondering,
 is there a way (apart from using newtype) to pass a custom record as the
 typeclass record, to modify the behavior of the typeclass? I thought
 about something like this:

You may be interested in Agda's upcoming instance arguments
(inspired upon Scala implicits and Agda's implicit arguments). These
will be available in Agda 2.2.12 (you may find references to an older
name non-canonical implicit arguments). The new type of function
arguments are automatically inferred from call-site scope unless they
are explicitly provided. Type classes are directly (not just under the
hood) modelled as records, and you can do what you suggest. You can
also define local instances, and there are other advantages. We have
chosen a more limited-power instance search though. More discussion
online.

  
http://wiki.portal.chalmers.se/agda/pmwiki.php?n=ReferenceManual.InstanceArguments
  http://people.cs.kuleuven.be/~dominique.devriese/agda-instance-arguments/

I believe a similar Haskell extension (perhaps with a less principled
instance search) would improve and simplify Haskell's type class
system.

By the way, Kahl and Scheffczyk proposed extending Haskell with named
instances in 2001 which allowed something like this to a limited
extent. Look for Named instances for Haskell Type Classes in Google
Scholar.

Dominique

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


Re: [Haskell-cafe] Robert Harper on monads and laziness

2011-05-03 Thread Dominique Devriese
2011/5/3 Manuel M T Chakravarty c...@cse.unsw.edu.au:
 Interestingly, today (at least the academic fraction of) the Haskell
 community appears to hold the purity of the language in higher
 regard than its laziness.

I find Greg Morissett's comment on Lennart Augustsson's article pro
lazy evaluation very interesting:

  
http://augustss.blogspot.com/2011/05/more-points-for-lazy-evaluation-in.html#c7969361694724090315

What I find interesting is that he considers (non-)termination an
effect, which Haskell does not manage to control like it does other
types of effects. Dependently typed purely functional languages like
Coq (or Agda if you prefer ;)) do manage to control this (at the cost
of replacing general recursion with structural recursion) and require
you to model non-termination in a monad (or Applicative functor) like
in YNot or Agda's partiality monad (written _⊥) which models just
non-termination.

I have the impression that this separation of the partiality effect
provides a certain independence of evaluation order which neither ML
(because of side-effects) nor Haskell (because of non-strict
semantics) manage to provide. Such an independence seems very useful
for optimization and parallel purposes.

Dominique

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


Re: [Haskell-cafe] Robert Harper on monads and laziness

2011-05-02 Thread Dominique Devriese
2011/5/2 Ketil Malde ke...@malde.org:
  There is a particular reason why monads had to arise in Haskell,
   though, which is to defeat the scourge of laziness.

 My own view is/was that monads were so successful in Haskell since it
 allowed writing flexible programs with imperative features, without
 sacrificing referential transparency.  [...]

 Laziness does require referential transparency (or at least, it is
 easier to get away with the lack of RT in a strict language), so I can
 see that he is indirectly correct, but RT is a goal in itself.  Thus, I
 wonder if there are any other rationale for a statement like that?

I agree with your analysis. Throughout his different articles, I think
Harper partly has a point when he says that laziness brings certain
disadvantages (like e.g. complex memory and CPU behaviour) to Haskell
(although I disagree with some of his other  arguments here). However,
like you say, he misses the ball by amalgamating laziness with
referential transparency, where the first probably requires the second
but not vice versa. This allows him to simply dismiss both, which is
convenient for his apparent conclusion that ML is strictly better
than Haskell, since referential transparency and purity are (in my
view) one of the things ML lacks most when compared to Haskell. His
only other argument against referential transparency and purity seems
to be his mentioning of benign effects, which is weak for two
reasons: first, benign effects are clearly not what typical ML
programs use non-purity for and second, benign effects can be
supported much more conservatively using Haskell's unsafePerformIO.

Dominique

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


Re: [Haskell-cafe] Proving correctness

2011-02-11 Thread Dominique Devriese
Kashyap,

2011/2/11 C K Kashyap ckkash...@gmail.com:
 I've come across this a few times - In Haskell, once can prove the
 correctness of the code - Is this true?
 I know that static typing and strong typing of Haskell eliminate a whole
 class of problems - is that related to the proving correctness?
 Is it about Quickcheck - if so, how is it different from having test sutites
 in projects using mainstream languages?

You may be confusing Haskell with dependently typed programming languages such
as Coq or Agda, where formal proofs of correctness properties of
programs can be verified by the type checker.

Dominique

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


Re: [Haskell-cafe] [Haskell] Problems with (projects|community).haskell.org

2011-02-10 Thread Dominique Devriese
Also, is there any news yet on a procedure for community members with
accounts on projects.haskell.org to get access to them again? My ssh
publickey login is no longer being accepted. I had an account mainly
for hosting the darcs repo and the website for my project
grammar-combinators. The website has been down for a couple of weeks
now.

Dominique

P.S.: This is not a complaint, I'm just hoping for a status update.
P.P.S.: Thanks to the people working on fixing this..

2011/2/9 Erik de Castro Lopo mle...@mega-nerd.com:
 Hi all,

 Still a couple of problems with these servers.

 Firstly, community.haskell.org shows the default Apache It works
 page. It would be nice to have something better there.

 Secondly the mailman web interface on projects.haskell.org [0] is
 giving a Service Temporarily Unavailable message (and has been
 for a couple of days).

 Cheers,
 Erik

 [0] http://projects.haskell.org/cgi-bin/mailman/admindb/haskell-llvm
 --
 --
 Erik de Castro Lopo
 http://www.mega-nerd.com/

 ___
 Haskell mailing list
 hask...@haskell.org
 http://www.haskell.org/mailman/listinfo/haskell


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


Re: [Haskell-cafe] Haskell for children? Any experience?

2011-01-27 Thread Dominique Devriese
Hi,

I'm also curious about this. Is a pure programming style like
Haskell's less or more natural than an imperative mutable-state based
one to kids without experience. I intuitively expect that for kids
with a high-school background in mathematics would find the first more
natural, but this is not based on any teaching experience. Does anyone
have real-life experience with this or know of any related literature?

Thanks
Dominique

2011/1/27 Vo Minh Thu not...@gmail.com:
 Hi,

 You said Haskell's immutability is good for mathematics but doing anything 
 else
 takes a great deal of up-front patience and perseverance[...]

 I guess it is true for imperative programmers... but are you saying
 that about kids that just know how to use a calculator?

 Cheers,
 Thu

 2011/1/27 aditya siram aditya.si...@gmail.com:
 Ye gods! A B  D [1] language for kids? At least give them a fighting
 chance [2] at becoming future developers.

 Haskell's immutability is good for mathematics but doing anything else
 takes a great deal of up-front patience and perseverance, two very
 rare qualities in that demographic if my own childhood is any
 indication.

 BTW I want to be wrong so if you do succeed with this I will feast on
 crow with gusto.

 -deech

 [1] http://c2.com/cgi/wiki?BondageAndDisciplineLanguage
 [2] http://scratch.mit.edu/

 On Thu, Jan 27, 2011 at 9:04 AM, Chris Smith cdsm...@gmail.com wrote:
 So I find myself being asked to plan Haskell programming classes for one
 hour, once a week, from September through May this coming school year.
 The students will be ages 11 to 13.  I'm wondering if anyone has
 experience in anything similar that they might share with me.  I'm
 trying to decide if this is feasible, or it I should try to do something
 different.

 To be honest, as much as I love Haskell, I tried to push the idea of
 learning a different language; perhaps Python.  So far, the kids will
 have none of it!  This year, I've been teaching a once-a-week
 exploratory mathematics sort of thing, and we've made heavy use of
 GHCi... and they now insist on learning Haskell.

 (By the way, GHCi is truly amazing for exploratory mathematics.  We
 really ought to promote the idea of Haskell for elementary / junior-high
 level math teachers!  It's so easy to just try stuff; and there are so
 many patterns you can just discover and then say Huh, why do you think
 that happens?  Can you write it down precisely? ...)

 --
 Chris Smith


 ___
 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


 ___
 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] Template Haskell a Permanent solution?

2011-01-04 Thread Dominique Devriese
All,

2010/12/27 Jonathan Geddes geddes.jonat...@gmail.com:
 I see TH used most for the following tasks:

 #1 Parse a string at compile-time so that a custom syntax for
 representing data can be used. At the extreme, this data might even
 be an EDSL.
 #2 Provide instances automatically.

Just a note that TH is also sometimes used in its generality: as a
general compile time meta-programming facility. For example, in my
experimental grammar-combinators parsing library [1], I am using it to
perform grammar transformations at compile time by simply generating
the definition for the transformed grammar using TH. This could be
extended in the future to provide a low-cost parser generator that
works from within TH, which can reuse the library's infrastructure.

Dominique

[1] http://projects.haskell.org/grammar-combinators/

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


[Haskell-cafe] Decoupling type classes (e.g. Applicative)?

2010-10-29 Thread Dominique Devriese
Hi all,

I have a problem with the design of the Applicative type class, and
I'm interested to know people's opinion about this.

Currently, the Functor and Applicative type class are defined like this:

  class  Functor f  where
  fmap:: (a - b) - f a - f b

  class Functor f = Applicative f where
pure :: a - f a
(*) :: f (a - b) - f a - f b

My problem is that in the grammar-combinators library [1], the pure
combinator is too general for me. I would propose a hierarchy like
the following:

  class  Pointed f  where
  pure :: a - f a

  class  ApplicativeC f where
(*) :: f (a - b) - f a - f b

The original type class Applicative can then be recovered as follows,
and the applicative laws can be specified informally in this class's
definition.

  class  (Pointed f, ApplicativeC f, Functor f) = Applicative f where

This would allow me to restrict injected values to stuff I can lift
into Template Haskell later on:

  class  LiftablyPointed f where
  pureL :: (Lift a) - a - f a
  pureL' :: a - Q Exp - f a

  class  (LiftablyPointed f, ApplicativeC) = LiftablyApplicative f where

This problem currently makes it impossible for me to use the (*)
combinator and I have to redefine it under a different name (I
currently use ()). To me the problem seems similar to the well
known example of the inclusion of the fail primitive in the monad
class, where the general opinion seems to be that it was a bad idea to
include fail in the Monad class (see
e.g. the article on the haskell wiki about handling failure [2]).

I've been thinking about the following type class design principles:

* Only include two functions in the same design class if both can be
  implemented in terms of each other.

* Only introduce a dependency from type class A to type class B if all
  functions in type class B can be implemented in terms of the
  functions in type class A or if type class A is empty.

(Disclaimer: I currently do not follow these principles myself ;))

I would like to know people's opinions about this. Are there any
issues with this advice that I don't see? Have other people
encountered similar problems? Any interesting references?

Thanks,
Dominique

Footnotes:
[1]  http://projects.haskell.org/grammar-combinators/
[2]  http://www.haskell.org/haskellwiki/Failure
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] Re: [Haskell] Specification and prover for Haskell

2010-10-25 Thread Dominique Devriese
Romain,

2010/10/25 Romain Demeyer r...@info.fundp.ac.be:
 I'm working on static verification in Haskell, and I search for existing
 works on specification of Haskell programs (such as pre/post conditions, for
 example) or any other functional language. It would be great if there exists
 a prover based on this kind of specifications. I already found the
 ESC/Haskell. Do you know some other works which could be interesting?

I found the paper Verifying Haskell using constructive type theory
[1] interesting...

Dominique

Footnotes:
[1] http://www.mimuw.edu.pl/~ben/Papers/monadic.pdf
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] pointers for EDSL design

2010-10-12 Thread Dominique Devriese
2010/10/12  o...@okmij.org:
 An alternative approach to model sharing at the object level is the
 technique I use for modelling context-free grammars in my PADL 2011
 paper Explicitly Recursive Grammar Combinators...  Using ideas from
 the Multirec generic programming library and some recent Haskell type
 system extensions (most importantly GADTs and type families), you can
 do this in a well-typed way for sets of mutually recursive
 object-level expressions.

 I guess you are using what I call `the initial embedding' of an object
 language. Somehow I prefer the final embedding.

No. In the library, I use both embedding styles for different
purposes, but what I was referring to here (the construction of
production rules) is actually implemented using what you call a typed
tagless-final embedding. I see the technique as an encoding of
*recursion* in a typed tagless final object language in such a way
that the recursion is observable in the host language.

Suppose you have the following (logically inconsistent ;)) code (in
Haskell notation):
  term1 :: Int
  term1 = if term2 then 1 else 2
  term2 :: Bool
  term2 = term1 == 2

and you want to model it in the typed tagless final encoding of simply
typed lambda calculus from the examples in your online typed tagless
final lecture notes [1] extended with implicit arbitrary recursion.
Then you could do

  data Term1
  data Term2

  data TermDomain ix where
   Term1 :: TermDomain Term1
   Term2 :: TermDomain Term2

  data family TermVal ix
  newtype instance TermVal Term1 = TV1 {unTV1 :: Int}
  newtype instance TermVal Term2 = TV2 {unTV2 :: Bool}

  class ExtraSymantics repr where
if_ :: repr h Bool - repr h a - repr h a - repr h a
eq_int :: repr h Int - repr h Int - repr h Bool

  class RecSymantics repr phi | repr - phi where
ref :: phi ix - repr h (TermVal ix)

  terms :: (Functor (repr h), Symantics repr, ExtraSymantics repr,
RecSymantics repr TermDomain) = TermDomain ix - repr h
(TermVal ix)
  terms Term1 = fmap TV1 $ if_ (fmap unTV2 (ref Term2)) (int 1) (int 2)
  terms Term2 = fmap TV2 $ eq_int (fmap unTV1 (ref Term1)) (int 2)

In this way, the embedding models the object language recursion in
such a way that the recursion remains observable in the host language
because you can implement it the way you want in your RecSymantics
instance. Possible needs for this observable recursion could be that
you want to do some form of recursion depth-bounded evaluation or some
form of static analysis or whatever... Such modifications are
fundamentally impossible if you model object language recursion
naively using direct host language recursion.

For my parsing library, I need these techniques to get a good view on
the recursion in the grammar. This allows me perform grammar
transformations and analysis.

Dominique

Footnotes:
[1]  http://okmij.org/ftp/tagless-final/course/#infin1
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] pointers for EDSL design

2010-10-11 Thread Dominique Devriese
John, Oleg,

2010/10/9  o...@okmij.org:
 So here's a very simple expression:

 t1 = let v = sigGen (cnst 1) in outs v v

 which is what led to my question.  I'm binding the sigGen to 'v' to
 introduce sharing at the meta-level.  Would it be better to introduce
 support for this in the dsl?

 Often this is not a question of preference but that of
 necessity. Sharing at the meta-level may help the generator, but it
 does _not_ translate into the sharing at the object level. In the
 generated code, the code for 'sigGen (cnst 1)' shall be
 duplicated. It could be that two csound blocks must share the same
 signal source, to receive samples in parallel. Meta-level sharing
 (Haskell's let) would not do. We need a construct for an object-level
 let, for example

  t1 = let_ (SigGen (cnst 1)) (\v - outs v v)

An alternative approach to model sharing at the object level is the
technique I use for modelling context-free grammars in my PADL 2011
paper Explicitly Recursive Grammar Combinators [1] (just got
acceptance notification this morning!). The idea is basically that you make the
sharing in the object-level expression explicit by modelling all
your terms as the results of one big recursive function and then
opening up the recursion. Using ideas from the Multirec generic
programming library and some recent Haskell type system extensions
(most importantly GADTs and type families), you can do this in a
well-typed way for sets of mutually recursive object-level
expressions.

In this case, you would get something like the following (written
without any understanding of your problem domain, so sorry if I
interpret stuff wrong here ;) ):

data I1
data T1
data CircuitNode ix where
   I1 :: CircuitNode I1
   T1 :: CircuitNode T1

myCircuit self I1 = sigGen (cnst 1)
myCircuit self T1 = outs (self I1) (self I1)

With a type class such as RecProductionRule in my paper, you can then
even get rid of the self argument and get something like this:

myCircuit I1 = sigGen (cnst 1)
myCircuit T1 = outs (ref I1) (ref I1)

The main advantage is that this approach extends to circuits with
mutually recursive nodes, but contrary to simple meta-level sharing,
allows you to observe and manipulate the recursive structure of the
circuit. Oh, and it stays properly typed. More info in the paper and
the accompanying technical report [2].

cheers
Dominique

Footnotes:
[1]  
http://people.cs.kuleuven.be/~dominique.devriese/permanent/cfgc-submitted-PADL.pdf
[2]  http://www.cs.kuleuven.be/publicaties/rapporten/cw/CW594.abs.html
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] [Off-topic]Functional parsing theory

2010-10-06 Thread Dominique Devriese
Mauricio,

2010/10/6 Maurí­cio CA mauricio.antu...@gmail.com:
 I've been working in a tool that reads a grammar with associated
 actions and act on input based on that grammar. I would like to
 rewrite it in a functional style, but I've not been able to find a
 theory that would handle any possible grammar with cyclicity and
 empty productions, and flexibility is more important for this tool
 than performance.

 Do you have a suggestion on that? What I'm using now is this
 (non-functional) article on Earley method:

I'm not sure what you're looking for exactly, but my
grammar-combinators library [1] might be interesting for you. It is
not yet industry-proof at the moment, but might benefit from some more
real-world use and comments. It is a novel functional parsing library
using an explicit representation of recursion which allows it to
support many different parsing algorithms and grammar transformations.

Anyway, in the functional world, parsing algorithms used are often LL
parsing algorithms, often used with parser combinators. Other
algorithms can sometimes be emulated in a functional style using a
top-down parsing algorithm on a transformed grammar (e.g. left-corner
transform, but I also suspect you can emulate LR parsing using what I
call the uniform Paull transformation). My library automates two such
important transformations (supporting for example left-recursion).

Dominique

Footnotes:
[1] http://projects.haskell.org/grammar-combinators/
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Re: Suggestions for improvement

2010-10-05 Thread Dominique Devriese
2010/10/5 N. Raghavendra ra...@mri.ernet.in:
 At 2010-10-03T22:45:30+02:00, Dominique Devriese wrote:

 comma :: (a - b) - (a - c) - a - (b,c)
 comma f g x = (f x, g x)

 comma = liftA2 (,)

 blowup = (uncurry (++)) . liftA2 (,) (blowup . allButLast) lastToTheLength

 I tried both of them, but they don't seem to work:

    -- Pointfree blowup.
    blowup1 :: String - String
    blowup1 = (uncurry (++)) . comma1 (blowup1 . allButLast) lastToTheLength

Sorry, I didn't look in detail at your solution in my answer, just
focused on the solution, and only checked that it compiled. Your
problem is that both your blowup functions recurse infinitely on the
empty string (blowup{1,2} [] will always call blowup{1,2} [] again).
Instead of fixing it, I recommend you study one of the other solutions
proposed in this thread, since they are superior in many ways
(shorter, more elegant, more lazy, probably more efficient).

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


Re: [Haskell-cafe] Suggestions for improvement

2010-10-03 Thread Dominique Devriese
 One question I have is whether I can eliminate points in the above
 definition of blowup, and write something like

blowup = (++) . (blowup . allButLast, lastToTheLength)

 thinking of (++) as a function String x String - String.

Actually (++) is of type String - String - String. When you want
something of the type you mean (you normally write that as (String,
String) - String in Haskell, then you can use (uncurry (++)).

Additionally, you can't combine the functions (blowup . allButLast)
and lastToTheLength into a function that returns a pair like you seem
to attempt. You need a function like the following for that:

comma :: (a - b) - (a - c) - a - (b,c)
comma f g x = (f x, g x)

Then you could say:

blowup = (uncurry (++)) . comma (blowup . allButLast) lastToTheLength

Ignore this if you haven't read about Applicative or type classes yet,
but using the Applicative instance for arrow types (-) a, you can
also write

comma = liftA2 (,)

or

blowup = (uncurry (++)) . liftA2 (,) (blowup . allButLast) lastToTheLength

 Also, I can't
 figure out whether it is possible to get a shorter solution using fold.
 I have tried Hlint on my file, but it gave no suggestions.

 I am sure there are better ways, and would like some pointers and any
 general suggestions for improvement.

By the way, shorter is not always better. Trying to recognize
abstraction patterns in your code is never a bad thing though.

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


Re: [Haskell-cafe] Suggestions for improvement

2010-10-03 Thread Dominique Devriese
Gregory,

2010/10/3 Gregory Crosswhite gcr...@phys.washington.edu:
  On 10/3/10 1:45 PM, Dominique Devriese wrote:

 Additionally, you can't combine the functions (blowup . allButLast)
 and lastToTheLength into a function that returns a pair like you seem
 to attempt. You need a function like the following for that:

 comma :: (a -  b) -  (a -  c) -  a -  (b,c)
 comma f g x = (f x, g x)

 Then you could say:

 blowup = (uncurry (++)) . comma (blowup . allButLast) lastToTheLength

 It is worth noting that such a function already exists in the standard
 libraries;  it is the  operator in Control.Arrow:

    blowup = uncurry (++) . (blowup . allButLast  lastToTheLength)

Or you can write it as (liftA2 (,)) as I noted a few lines further in my mail ;)

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


Re: [Haskell-cafe] Fwd: Type families - how to resolve ambiguities?

2010-09-12 Thread Dominique Devriese
Paolo,

 The problem with mult is that k is not specified unambiguously. You either
 need v to determine k (which is probably not what you want, at a guess), mult
 to take a dummy argument that determines what k is:
 [...]
 or, to make Tensor a data family instead of a type family.
 What is the difference making it work?
The problem is that in your definition of mult
  mult :: Tensor k v v - v
you seem to expect the type v to be determined by the type of Tensor
you apply it to. However, since Tensor is not an injective type
functor, it does not uniquely determine the type v. It is possible
that there is a completely unrelated type instance for Tensor, for
different types k and v that is also equal to the type you apply mult
to.

If you make Tensor a data family, then the types k and v are uniquely
determined, because then it is an injective type functor.

 However, it would make more sense to have it be a type family, without
 the overhead of data (both in space and in typing).

You can make Tensor a data family and use newtype instances. As I
understand these, there should not be a space overhead. The only
overhead I would expect this to introduce is the extra newtype
constructor.

 Is there a non-
 hacky approach, without dummies and without making Tensor a data
 family without a semantic need?

Without thinking about your problem domain, I have the impression that
you do have a semantic need, because you seem to expect your Tensor
type to uniquely determine at least the type v. If this is not the
case, you need a different solution.

Anyway, the below compiles fine with the following result:
*Main mult $ Tensor $ (V [(T [1] [2],3)] :: Vect Integer (TensorBasis
[Int] [Int]))
V [([1,2],3)]

{-# LANGUAGE MultiParamTypeClasses, TypeFamilies #-}
{-# LANGUAGE FlexibleInstances, TypeSynonymInstances #-}

data Vect k b = V [(b,k)] deriving (Eq,Show)

data TensorBasis a b = T a b deriving (Eq, Ord, Show)

data family Tensor k u v :: *

newtype instance Tensor k (Vect k a) (Vect k b) = Tensor (Vect k
(TensorBasis a b))

class Algebra k v where -- v is a k-algebra
   unit :: k - v
   mult :: Tensor k v v - v

instance Algebra Integer (Vect Integer [Int]) where
   unit 0 = V []
   unit x = V [([],x)]
   mult (Tensor (V ts)) = V [(g++h,x) | (T g h, x) - ts]
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] ANNOUNCE: grammar-combinators 0.1 (initial release): A parsing library of context-free grammar combinators

2010-09-08 Thread Dominique Devriese
The grammar-combinators library is a parsing library employing a novel
grammar representation with explicit recursion. The library features
much of the power of a parser generator like Happy or ANTLR, but with
the library approach and most of the benefits of a parser combinator
library. Grammars and grammar algorithms are defined in a
functional style. The library currently has the following features:

* Grammar specified completely in Haskell using an elegant syntax
* Grammar algorithms implemented in a functional style (no fresh
 identifiers), with elegant and meaningful types.
* Multi-backend: use the same grammar with a Packrat, Parsec or
 UUParse parser
* Grammar transformations: use left-recursive grammars directly thanks
 to a powerful grammar transformation library, featuring the
 left-corner left-recursion removal transform, a uniform version of
 the classic Paull left-recursion removal, and various smaller
 transformations (dead-branch removal, dead non-terminal removal,
 consecutive epsilon combination, selective unfolding etc.).
* Grammar utility functions: printing of grammars, FIRST-set
 calculation, reachability analysis of non-terminals, etc.
* Compile-time transformations (using Template Haskell), given a
 suitable definition of the grammar. This is currently limited to a
 certain set of transformations.

The library is currently not intended for mainstream use. Its API is
relatively stable, but performance needs to be looked at further.

We are submitting a paper about the ideas behind this library to PADL
2011. A draft is linked on the project's website.

More information:

* Project website: http://projects.haskell.org/grammar-combinators/
* Tutorial: http://projects.haskell.org/grammar-combinators/tutorial.html
* Hackage: http://hackage.haskell.org/package/grammar-combinators

All comments welcome!

Dominique

PS. The documentation on hackage currently doesn't build because of
(seemingly) a Hackage dependency problem during the build [1].
Compiling and generating the documentation locally should work fine. A
version of the docs is available on the project's webpage as a
temporary replacement [2].

Footnotes:
[1]  http://www.haskell.org/pipermail/libraries/2010-September/014168.html
[2]  http://projects.haskell.org/grammar-combinators/docs/index.html
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] Re: ANNOUNCE: grammar-combinators 0.1 (initial release): A parsing library of context-free grammar combinators

2010-09-08 Thread Dominique Devriese
Some snippets from the Tutorial [1] to give an idea of the
grammar-combinator library's approach, its functional style and its
additional power (e.g. the transformations used):

Defining a simple expresssions grammar:
  grammarArith :: ExtendedContextFreeGrammar ArithDomain Char
  grammarArith Line =
LineF $ ref Expr * endOfInput
  grammarArith Expr =
SubtractionF $  ref Expr * token '-'  ref Term
||| SumF $  ref Expr * token '+'  ref Term
||| SingleTermF $   ref Term
  grammarArith Term =
SingleFactorF $ ref Factor
||| QuotientF $ ref Term * token '/'  ref Factor
||| ProductF $  ref Term * token '*'  ref Factor
  grammarArith Factor =
NumberF $   many1Ref Digit
||| ParenthesizedF $*   token '('  ref Expr * token ')'
  grammarArith Digit =
DigitF $tokenRange ['0' .. '9']

A semantic processor:
  data family ArithValue ix
  newtype instance ArithValue Line   = ArithValueL Int deriving (Show)
  newtype instance ArithValue Expr   = ArithValueE Int deriving (Show)
  newtype instance ArithValue Term   = ArithValueT Int deriving (Show)
  newtype instance ArithValue Factor = ArithValueF Int deriving (Show)
  newtype instance ArithValue Digit  = ArithValueD Char deriving (Show)

  calcArith :: Processor ArithDomain ArithValue
  calcArith Line   (LineF (ArithValueE e))= ArithValueL e
  calcArith Expr   (SumF (ArithValueE e) (ArithValueT t)) =
ArithValueE $ e + t
  calcArith Expr   (SingleTermF (ArithValueT t))  = ArithValueE t
  calcArith Term   (ProductF (ArithValueT e) (ArithValueF t)) =
ArithValueT $ e * t
  calcArith Term   (SingleFactorF (ArithValueF t))= ArithValueT t
  calcArith Factor (ParenthesizedF (ArithValueE e))   = ArithValueF e
  calcArith Factor (NumberF ds)   =
ArithValueF $ read $ map unArithValueD ds
  calcArith Digit  (DigitF c) = ArithValueD c

  unArithValueD :: ArithValue Digit - Char
  unArithValueD (ArithValueD c) = c

Transforming the grammar:
  calcGrammarArith :: ProcessingExtendedContextFreeGrammar ArithDomain
Char ArithValue
  calcGrammarArith = applyProcessorE grammarArith calcArith
  calcGrammarArithTP :: ProcessingExtendedContextFreeGrammar (UPDomain
ArithDomain) Char (UPValue ArithValue)
  calcGrammarArithTP = transformUniformPaullE calcGrammarArith
  calcGrammarArithTPF :: ProcessingExtendedContextFreeGrammar
(UPDomain ArithDomain) Char (UPValue ArithValue)
  calcGrammarArithTPF = filterDiesE (unfoldDeadE calcGrammarArithTP)
  calcGrammarArithTPFF :: ProcessingContextFreeGrammar
(FoldLoopsDomain (UPDomain ArithDomain)) Char (FoldLoopsValue (UPValue
ArithValue))
  calcGrammarArithTPFF = foldAndProcessLoops calcGrammarArithTPF

Parsing:
  *Main parsePackrat calcGrammarArithTPFF (FLBase (UPBase Line)) 123
  Parsed FLBV {unFLBV = UPBV {unUPBV = ArithValueL 123}} _
  *Main parsePackrat calcGrammarArithTPFF (FLBase (UPBase Line)) 123+
  NoParse
  *Main parsePackrat calcGrammarArithTPFF (FLBase (UPBase Line)) 123+12
  Parsed FLBV {unFLBV = UPBV {unUPBV = ArithValueL 135}} _
  *Main parseParsec calcGrammarArithTPFF (FLBase (UPBase Line))  123+12
  Right (FLBV {unFLBV = UPBV {unUPBV = ArithValueL 135}})
  *Main parseUU calcGrammarArithTPFF (FLBase (UPBase Line)) 123+12
  FLBV {unFLBV = UPBV {unUPBV = ArithValueL 135}}

Dominique

Footnotes:
[1]  http://projects.haskell.org/grammar-combinators/tutorial.html
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Re: ANNOUNCE: grammar-combinators 0.1 (initial release): A parsing library of context-free grammar combinators

2010-09-08 Thread Dominique Devriese
Johannes,

(sorry for the double mail)

I will give some short answers below, but you can find more details in
the paper we are submitting to PADL 2011 [1].

2010/9/8 Johannes Waldmann waldm...@imn.htwk-leipzig.de:
 .. grammar-combinator library's approach ..
 am I reading this correctly: in the traditional combinator approach,
 a grammer (a parser) is a Haskell value,
 while in your approach, the grammar is a Haskell (GAD)type?

Not completely. A grammar-combinators grammar is a Haskell value with
a different (more complicated) type than a traditional parser
combinator value. It is actually a function that returns the
production rules for a given non-terminal. Because the non-terminals
are modelled using a GADT and do not have the same type, the grammar's
production rules' types can depend on the non-terminal in question.

 then you'll get more static guarantees (e.g., context-freeness)
 but you need extra (type-level, or even syntax-level) machinery
 to handle grammars. Convince me that it's worth it ...

The advantage of the grammar-combinators approach is that grammar
algorithms have a lot more power, because they can reason explicitly
about the recursion in the grammar, whereas the recursion is not
observable in the traditional parser combinators approach. The Parser
combinator model is in fact so limited that something simple as
pretty-printing a BNF representation of the grammar is fundamentally
impossible. More details in the PADL-submitted draft.

As James says below, a grammar algorithm using grammar-combinators
grammars can observe the recursion in the grammar and can therefore do
stuff for which you would otherwise have to use a parser generator.

 I guess the proper solution (TM) is to blur the distiction
 between types and values by switching to dependent types altogether...

There is actually some very interesting work about dependently typed
parser combinator libraries, I discuss this in the related work
section of the PADL paper.

Dominique

Footnotes:
[1]  http://projects.haskell.org/grammar-combinators/#background
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Re: ANNOUNCE: grammar-combinators 0.1 (initial release): A parsing library of context-free grammar combinators

2010-09-08 Thread Dominique Devriese
Johannes,

2010/9/8 Johannes Waldmann waldm...@imn.htwk-leipzig.de:

 That compilation process is highly nonlocal
 and would never be possible with, e.g., the Parsec approach.

 Pipe dream: attach such a grammar object to every Parsec parser,
 and include the compiler with the combinators,
 and have them run at (Haskell) compile time (in ghc's specializer).

You can actually use a grammar-combinators parser with Parsec
(although the current implementation will use backtracking on every
branch), keeping the original grammar around for other purposes.

About the compile-time stuff, there is code in the library doing
compile-time transformations using Template-Haskell (but requiring a
grammar with embedded TH splices for injected values). You could also
do a similar compilation to a PDA parser in TH if you want, again
keeping the full grammar available for other stuff.

Additionally, I have noted that passing certain GHC inlining flags as
has been suggested for generic code [1] produces spectacular
(execution time/16) optimizations for a test grammar, but I have not
investigated what resulting code GHC actually produces in this case.
This is also related to what you talk about, since the compiler does
part of the transformation from abstract grammar at compile time.

 Should work for some subset (e.g., just let, not letrec, use
 proper combinators instead) and with some future ghc version ...

 When I teach parsing (in Compiler Construction), for lack of time
 it's either traditional (CFG - PDA) or combinator (not both),
 and I'm not happy with that, since both are important concepts.
 But then, semantics is more important than syntax ...

I actually think of the grammar-combinators approach as an attempt to
bring the power available in parser combinator libraries to the level
of what can be done in parser generators.

Dominique

Footnotes:
[1] http://www.cs.uu.nl/research/techreps/repo/CS-2009/2009-022.pdf
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Which Mail editor or mail chain do you use ?

2010-08-17 Thread Dominique Devriese
2010/8/17 Luc TAESCH luc.tae...@googlemail.com:
 May I ask you how you redact your answers and which toolchain you are using?

You can use footnote-mode [1] for easily producing the
footnotes/references if you're an emacs user.

Dominique

Footnotes:
[1]  http://www.emacswiki.org/emacs/FootnoteMode
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] datatype contexts

2010-07-26 Thread Dominique Devriese
2010/7/26 Ryan Ingram ryani.s...@gmail.com:
 There are two types of datatype contexts; haskell'98 contexts (which I
 think are terrible), and GHC existential contexts (which I like):

See also GADT-style data type declarations [1] and full GADT's [2],
which both behave like GHC existential contexts mentioned above: pattern
matching on them makes available the context constraint.

Dominique

Footnotes:
[1]  
http://www.haskell.org/ghc/docs/6.12.2/html/users_guide/data-type-extensions.html#gadt-style
[2]  
http://www.haskell.org/ghc/docs/6.12.2/html/users_guide/data-type-extensions.html#gadt
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] DpH/repa cache locality

2010-07-13 Thread Dominique Devriese
Hi,

2010/7/13 Gregory Crosswhite gcr...@phys.washington.edu:
 Just out of curiosity, what work is being done in the data parallel
 haskell / repa projects regarding cache locality?
Hi,

I'm not knowledgeable at all about this, but for a technical
introduction to DPH, I found the following excellent. Locality
is a recurring theme in the talk, IIRC. (Sorry for the double reply)

http://www.youtube.com/watch?v=NWSZ4c9yqW8

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