Re: [Haskell-cafe] GADT and instance deriving

2013-05-26 Thread TP
Hi Tillmann and Richard,

Thanks for your answers.

I have tried to analyze the code snippets you proposed.
I've tried to transpose your examples to what I need, but it is not easy.

The problem I see with putting the list of independent variables (*) at the 
type level is that at some time in my code I want for instance to perform 
formal mathematical operations, for example I want a function deriv that 
takes f(x(t),y(t),z(t)) as input, and returns

df/dt = ∂f/∂x*dx/dt + ∂f/∂y*dy/dt + ∂f/∂z*dz/dt

If the list of dependencies is encoded at the type level, I don't see how to 
produce the previous output from the knowledge of f(x(t),y(t),z(t)). You 
understand that what I want to do is some type of basic Computer Algebra 
System library.

Moreover, I want overloading for infix functions as '*', '/', '⋅' (scalar 
product), × (vector product) etc., that is why I have used typeclasses (see 
the code I showed in my previous post). For example, for the time being I 
will restrict myself to scalar product between vector and vector, vector and 
dyadic, dyadic and vector (a dyadic is a tensor of order 2, a matrix if you 
prefer). So I have three instances for scalar product '⋅'. I don't see how 
to combine this idea of overloading or derivation function with what you 
proposed. But I have perhaps missed something.

Thanks,

TP

(*): That is to say the list of tensors of which one tensor depends, e.g. 
[t,r] for E(t,r), or simply [x,y,z] for f(x(t),y(t),z(t)) where x, y, and z 
themselves are scalars depending on a scalar t). In the test file of my 
library, my code currently looks like:

-
type Scalar = Tensor Zero
type Vector = Tensor One
[...]
let s = (t s []) :: Scalar
let v = (t v [i s]) :: Vector
let c1 = v + v
let c2 = s + v⋅v
-

t is a smart constructor taking a string str and a list of independent 
variables, and makes a (Tensor order) of name str.

So in the example above, s is a scalar that depends on nothing (thus it is 
an independent variable), v is a vector that depends on s (i is a smart 
constructor that wraps s into a Box constructor, such that I can put all 
independent variables in an heterogeneous list).
c1 is the sum of v and v, i.e. is equal to 2*v.
c2 is the sum of s and v scalar v.
If I try to write:

let c3 = s + v

I will obtain a compilation error, because adding a scalar and a vector has 
no meaning.

Is there some way to avoid typeable in my case?

Moreover, if I wanted to avoid the String in the first argument of my smart 
constructor t, such that

let s = (t []) :: Scalar

constructs an independent Scalar of name s, googling on the topic seems to 
indicated that I am compelled to use Template Haskell (I don't know it at 
all, and this is not my priority).
Thus, in a general way, it seems to me that I am compelled to use some 
meta features as typeable or Template Haskell to obtain exactly the result 
I need while taking benefit from a maximum amount of static type checking.


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


[Haskell-cafe] ghc release schedule

2013-05-26 Thread Rustom Mody
I give ghc release schedule to google and get at/near the top:

http://hackage.haskell.org/trac/ghc/wiki/Status/Releases

whose title is Release plans for ghc 6.12
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Cabal config file Guide

2013-05-26 Thread Albert Y. C. Lai

On 13-05-25 04:52 PM, Daniel Díaz Casanueva wrote:

As you already know, cabal-install is configured in the file config.
It has a lot of fields, but I didn't find a single place where each
field is explained with detail.


There is none, but my new and timely

http://www.vex.net/~trebla/haskell/cabal-cabal.xhtml

talks about a few, and one of them is a real surprise.


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


[Haskell-cafe] Fwd: Cabal config file Guide

2013-05-26 Thread Daniel Díaz Casanueva
Thank you, Albert, what you wrote is very useful.

Why the Cabal Guide is lacking this kind of information? Maybe I should
start gathering information in one place myself!

Thank you,
Daniel Díaz.
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] ANNOUNCE: new bridge! (prelude-prime)

2013-05-26 Thread Alexander Solla
On Thu, May 23, 2013 at 6:13 AM, Roman Cheplyaka r...@ro-che.info wrote:

 * Manuel Gómez tar...@gmail.com [2013-05-23 08:33:15-0430]
  On Thu, May 23, 2013 at 3:07 AM, Roman Cheplyaka r...@ro-che.info
 wrote:
   Pull requests are welcome, but let's stick to widely agreed changes
   (like the Foldable/Traversable one). I think one of the reasons why
   other Preludes haven't been adopted is because they were too radical.
  
   * Andreas Abel andreas.a...@ifi.lmu.de [2013-05-20 13:26:05+0200]
   Maybe instead of fiddling with the current Prelude (which might break
   backwards compatibility), we should design a new prelude which is not
   automatically loaded but contains roughly the current prelude (with
   the list functions generalized to collections) plus the modern type
   class stack: Functor, Applicative, Monad, Foldable, Traversable,
   Monoid etc.
 
  Is this strategy adequate for attacking the issue of the type class
  stack, though?  Defining, say, a new Monad class with the desired
  Functor constraint wouldn’t be of much use, as everything else on
  Hackage (and on the GHC libraries!) would still use the “real” Monad.

 No, it definitely isn't.


I think that there is enough interest in fixing the functor typeclass
hierarchy that we should probably get the ball rolling on making it a part
of the next Haskell language standard.

Yes, it would break code.  Probably a lot of code.  Which is exactly why it
should be a part of the language standard, instead of an ad hoc compiler
change.  Ideally, the change would be synchronized with the release of a
new Haskell Platform, as well, like the Haskell Platform 2010.2 (I think --
the first one tied to GHC 7.*)

In particular, it would be very nice if we could just change Cabal files to
explicitly use the haskell98 and haskell2010 packages to get the old
interface back.  Presumably, those packages would eventually be deprecated.

Also, we might want the language standard to reserve the module namespace
Haskell.* for modules like IO, instead of just plain IO.  (So that we'd
have Haskell.System.IO instead of IO /AND/ System.IO)  I don't remember the
details, but these module names are the only reason my code won't work with
haskell98/2010 packages.
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe