Re: [Haskell-cafe] reifying typeclasses

2013-09-16 Thread Emil Axelsson

2013-09-15 11:16, o...@okmij.org skrev:

Evan Laforge wrote:

I have a typeclass which is instantiated across a closed set of 3
types.  It has an ad-hoc set of methods, and I'm not too happy with
them because being a typeclass forces them to all be defined in one
place, breaking modularity.  A sum type, of course, wouldn't have that
problem.  But in other places I want the type-safety that separate
types provide, and packing everything into a sum type would destroy
that.  So, expression problem-like, I guess.

It seems to me like I should be able to replace a typeclass with
arbitrary methods with just two, to reify the type and back.  This
seems to work when the typeclass dispatches on an argument, but not on
a return value.  E.g.:


If the universe (the set of types of interest to instantiate the type
class to) is closed, GADTs spring to mind immediately. See, for
example, the enclosed code. It is totally unproblematic (one should
remember to always write type signatures when programming with
GADTs. Weird error messages otherwise ensue.)

One of the most notable differences between GADT and type-class--based
programming is that GADTs are closed and type classes are open (that
is, new instances can be added at will). In fact, a less popular
technique of implementing type classes (which has been used in some Haskell
systems -- but not GHC)) is intensional type analysis, or typecase.
It is quite similar to the GADT solution.


I've been toying with using Data Types à la Carte to get type 
representations, a `Typeable` class and dynamic types parameterized by a 
possibly open universe:


  https://github.com/emilaxelsson/dsl-factory/blob/master/TypeReify.hs

Using this module (which depends on the syntactic package), Evan's 
problem can be solved easily without setting up any new classes or data 
types, as shown below.


/ Emil



import Language.Syntactic
import TypeReify

type Universe = IntType :+: CharType

argument :: forall a . Typeable Universe a = a - Int
argument a
| Just IntType  - prj t = a
| Just CharType - prj t = fromEnum a
-- Note: All cases are covered, since `Universe` is closed
  where
TypeRep t = typeRep :: TypeRep Universe a

result :: forall a . Typeable Universe a = Int - a
result a
| Just IntType  - prj t = a
| Just CharType - prj t = toEnum a
-- Note: All cases are covered, since `Universe` is closed
  where
TypeRep t = typeRep :: TypeRep Universe a

-- Note that we do not have to use a closed universe. Here's an alternative,
-- open version of `argument`:
argument' :: forall u a . (IntType :: u, CharType :: u) =
 Typeable u a = a - Int
argument' a
| Just IntType  - prj t = a
| Just CharType - prj t = fromEnum a
| otherwise  = 0  -- or whatever :)
  where
TypeRep t = typeRep :: TypeRep u a

___
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 Emil Axelsson

`mapPair` also exists as `tup2` in patch-combinators:

  http://hackage.haskell.org/package/patch-combinators

/ Emil

2013-05-28 16:01, Andreas Abel skrev:

See Agda.Utils.Tuple :-)

-- | Bifunctoriality for pairs.
(-*-) :: (a - c) - (b - d) - (a,b) - (c,d)
(f -*- g) ~(x,y) = (f x, g y)

-- | @mapFst f = f -*- id@
mapFst :: (a - c) - (a,b) - (c,b)
mapFst f ~(x,y) = (f x, y)

-- | @mapSnd g = id -*- g@
mapSnd :: (b - d) - (a,b) - (a,d)
mapSnd g ~(x,y) = (x, g y)

I think mapPair, mapFst, and mapSnd are canonical names that could be
added to Data.Tuple.  But if you suggest this on librar...@haskell.org,
you get probably turned down, see e.g.

   http://comments.gmane.org/gmane.comp.lang.haskell.libraries/17411

Cheers,
Andreas

On 28.05.2013 15:34, Petr Pudlák wrote:

Dne 28.5.2013 10:54, Dominique Devriese napsal(a):

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?

Apart from Arrows, there is also package bifunctors that defines this
functionality for (,), Either and a few others:
http://hackage.haskell.org/packages/archive/bifunctors/3.2.0.1/doc/html/Data-Bifunctor.html



Petr Pudlak


___
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] Why were datatype contexts removed instead of fixing them?

2013-04-25 Thread Emil Axelsson

2013-04-26 04:31, wren ng thornton skrev:

On 4/25/13 9:49 PM, Dan Doel wrote:

I don't really think they're worth saving in general, though. I haven't
missed them, at least.


The thing I've missed them for (and what I believe they were originally
designed for) is adding constraints to derived instances. That is, if I
have:

 data Bar a = Foo a = ... deriving Baz

Then this is equivalent to:

 data Foo a = ...
 instance Bar a = Baz (Foo a) where ...

where the second ellipsis is filled in by the compiler. Now that these
constraints have been removed from the language, I've had to either (a)
allow instances of derived classes which do not enforce sanity
constraints, or (b) implement the instances by hand even though they're
entirely boilerplate.


I think standalone deriving solves this:

deriving instance Bar a = Baz (Foo a)

/ Emil

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


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

2013-02-21 Thread Emil Axelsson

This should be possible using higher-order terms, as in

http://hackage.haskell.org/packages/archive/compdata/latest/doc/html/Data-Comp-Multi-Term.html

The only complication I see is that the Dag nodes would get 
heterogeneous types requiring existential quantification with a 
`Typeable` constraint. A better representation might be typed ASGs [1]


Syntactic has typed ASTs and it has a module that does something similar 
to data-fix-cse (uses a combination of stable names and hashing), but it 
needs some fixing up.


/ Emil

[1]: http://dl.acm.org/citation.cfm?id=2426909


2013-02-20 01:58, Conal Elliott skrev:

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.



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


Re: [Haskell-cafe] adding recursion to a DSL

2013-02-19 Thread Emil Axelsson
You probably don't need recursion in the DSL for this (that would 
require a way to detect cycles in the expressions). For this example, it 
looks like all you need is to add something like `map` as a DSL construct.


Your example could perhaps be expressed as

  forEach (1,1000) (\n - out (matrixMult, A, n, row, matrix-row))

For this you need a way to reify functions in the DSL. For an example of 
how to do this, see the `While` and `Arr` constructs in this paper:


  http://www.cse.chalmers.se/~emax/documents/svenningsson2013combining.pdf

I'm not familiar with your particular DSL though, so I might have missed 
something.


/ Emil

2013-02-17 23:53, frit...@joerg.cc skrev:

I have a tiny DSL that actually works quite well. When I say

import language.CWMWL

main = runCWMWL $ do
 out (matrixMult, A, 1, row, matrix-row)

then runCWMWL is a function that is exported by language.CWMWL. This parses the 
experession and takes some action.

Now, A is the name of the matrix and the third tuple element would represent the numbe of 
the row. For example 1 to 1. I want to achieve some sort of elegant 
(means readable code, a good representation) recursion that would let me do something like
sequence [ out (matrixMult, A, n, row, matrix-row) | n - [1..1000] ]
but in a nicer manner an without expending this to 1 lines of code at 
compile time.

How can I best introduce recursion into my DSL or borrow this from the host language 
Haskell effectively?

--Joerg



___
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] ANN: data-fix-cse -- Common subexpression elimination for EDSLs

2013-02-19 Thread Emil Axelsson

2013-02-19 12:10, Anton Kholomiov skrev:

I'm glad to announce the package for Commonsubexpression elimination [1].
It's an implementation of the hashconsig algorithm as described in the
paper
'Implementing Explicit and Finding Implicit Sharing in EDSLs' by Oleg
Kiselyov.

Main point of the library is to define this algorithm in the most
generic way.
You can define the AST for your DSL as fixpoint type[2]. And then all
you need
to use the library is to define the instance for type class `Traversable`.


One way to make the library even more useful would have been to base it 
on compdata instead of data-fix. Compdata has support for composable 
types and lots of extra functionality. On the other hand, it's easy 
enough to translate from compdata terms to your `Fix`...





One side-note form my experience: Fixpoint types can be very flexible.
It's easy to compose them. If suddenly we need to add some extra data
to all cases from the example above we can easily do it with just another
Functor:

Imagine that we want to use a SampleRate value with all signals.
Then we can do it like this:

type E = Fix SampledExp

data SampledExp a = SampledExp SampleRate (Exp a)

then we should define an instance of the type class Traversable
for our new type SampleRate. The Exp doesn't change.


Very useful indeed! A more principled way to extend data types in this 
way is Data Types à la Carte:


  http://dx.doi.org/10.1017/S0956796808006758

(Implemented in compdata.)

/ Emil


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


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

2013-02-19 Thread Emil Axelsson
Fully understandable! Compdata would be quite a heavy dependency for 
your library.


I'm just generally fond of the idea of collecting all DSL implementation 
tricks under one umbrella. That requires using the same term representation.


/ Emil

2013-02-19 14:12, Anton Kholomiov skrev:

There are several packages that already define fixpoints (another one is
about unification), but all packages that I'm aware of define a lot of
functionality
that I don't need (and actually don't understand, packages with fixpoint
types
tend to be rather dense with math). I'd like it to be simple and
lightweight.
Just fixpoints, just folds and unfolds.


2013/2/19 Emil Axelsson e...@chalmers.se mailto:e...@chalmers.se

2013-02-19 12:10, Anton Kholomiov skrev:

I'm glad to announce the package for Commonsubexpression
elimination [1].

It's an implementation of the hashconsig algorithm as described
in the
paper
'Implementing Explicit and Finding Implicit Sharing in EDSLs' by
Oleg
Kiselyov.

Main point of the library is to define this algorithm in the most
generic way.
You can define the AST for your DSL as fixpoint type[2]. And
then all
you need
to use the library is to define the instance for type class
`Traversable`.


One way to make the library even more useful would have been to base
it on compdata instead of data-fix. Compdata has support for
composable types and lots of extra functionality. On the other hand,
it's easy enough to translate from compdata terms to your `Fix`...




One side-note form my experience: Fixpoint types can be very
flexible.
It's easy to compose them. If suddenly we need to add some extra
data
to all cases from the example above we can easily do it with
just another
Functor:

Imagine that we want to use a SampleRate value with all signals.
Then we can do it like this:

type E = Fix SampledExp

data SampledExp a = SampledExp SampleRate (Exp a)

then we should define an instance of the type class Traversable
for our new type SampleRate. The Exp doesn't change.


Very useful indeed! A more principled way to extend data types in
this way is Data Types à la Carte:

http://dx.doi.org/10.1017/__S0956796808006758
http://dx.doi.org/10.1017/S0956796808006758

(Implemented in compdata.)

/ Emil




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


Re: [Haskell-cafe] catamorphisms and attribute grammars

2013-01-28 Thread Emil Axelsson
Patrick Bahr does something very similar in Modular Tree Automata [1], 
also noting the relation to attribute grammars. It's implemented in the 
compdata package [2].


[1] Patrick Bahr, Modular Tree Automata (MPC 2012), 
http://dx.doi.org/10.1007/978-3-642-31113-0_14

[2] http://hackage.haskell.org/package/compdata

/ Emil

2013-01-26 23:03, Petr P skrev:

   Dear Haskellers,

I read some stuff about attribute grammars recently [1] and how UUAGC
[2] can be used for code generation. I felt like this should be possible
inside Haskell too so I did some experiments and I realized that indeed
catamorphisms can be represented in such a way that they can be combined
together and all run in a single pass over a data structure. In fact,
they form an applicative functor.

[1] http://www.haskell.org/haskellwiki/Attribute_grammar
[2] Utrecht University Attribute Grammar Compiler

To give an example, let's say we want to compute the average value of a
binary tree. If we compute a sum first and then count the elements, the
whole tree is retained in memory (and moreover, deforestation won't
happen). So it's desirable to compute both values at once during a
single pass:

-- Count nodes in a tree.
count' :: (Num i) = CataBase (BinTree a) i
count' = ...

-- Sums all nodes in a tree.
sum' :: (Num n) = CataBase (BinTree n) n
sum' = ...

-- Computes the average value of a tree.
avg' :: (Fractional b) = CataBase (BinTree b) b
avg' = (/) $ sum' * count'

Then we can compute the average in a single pass like

runHylo avg' treeAnamorphism seed

My experiments together with the example are available
at https://github.com/ppetr/recursion-attributes

I wonder, is there an existing library that expresses this idea?

   Best regards,
   Petr Pudlak



___
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] sequential logic

2012-12-05 Thread Emil Axelsson

2012-12-06 01:16, Christopher Howard skrev:

Hi. I was wondering what the various (and especially most simple)
approaches one could take for working with (simulating or calculating)
sequential logic in Haskell. By sequential logic, I mean like wikipedia
describes, where a system is made up of logic gates, whose output is
dependent not only on the logic operation of the gate, but on the
previous state of the gate. (Like in electronics where the system can be
driven by a clock signal or have memory.)

Does one have to get into FRP for that sort of thing? Or use some kind
of FSM framework? Or is there some kind of fancy state monad suitable
for that? Or...?

I'm no electronic or digital engineer, but for learning purposes I've
been trying to see if I could build an (extremely simple) virtual
processor or calculator in Haskell, using only the Bool type and a few
of the boolean operators (and functions composed of the aforementioned),
reproducing things like half adders and full adders as functions in the
program. Of course, I quickly ran into the stateful aspect of the
problem, in subjects like clock signal and flip flops.


If you just want to simulate your design, this is actually very easy. 
Signals can be represented as a stream of bits (an old idea dating at 
least from Sheeran's µFP, 1984):


 type Bit= Bool
 type Signal = [Bit]

Constant signals are defined using `repeat`:

 low, high :: Signal
 low  = repeat False
 high = repeat True

Basic gates are implemented using `map` and `zipWith` over the streams:

 inv :: Signal - Signal
 inv = map not

 () :: Signal - Signal - Signal
 () = zipWith ()

 (|) :: Signal - Signal - Signal
 (|) = zipWith (||)

And flip-flops are defined by just shifting the stream one step:

 delay :: Bool - Signal - Signal
 delay init sig = init : sig

(Note that the clock is implicit.)

Here is a simple oscillator

 osc :: Signal
 osc = let out = delay False (inv out) in out

which we can simulate as follows:

  *Main take 10 osc
  [False,True,False,True,False,True,False,True,False,True]

If you want a more full-blown system with the possibility of also 
generating VHDL, check out Lava:


  http://hackage.haskell.org/package/chalmers-lava2000

or

  https://github.com/ku-fpg/kansas-lava (The Hackage version doesn't 
compile on GHC 7.6.)


The two versions are based on the same ideas. The former is a bit 
simpler, but less useful for practical stuff.


The oscillator looks almost the same in Lava (Kansas):

 osc :: Seq Bool
 osc = let out = register False (bitNot out) in out

  *Main takeS 10 osc
  low | high | low | high | low | high | low | high | low | high | ? .

/ Emil


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


Re: [Haskell-cafe] AST Rewriting

2012-11-21 Thread Emil Axelsson
This is one of the problem Syntactic aims to solve, but it requires you 
to use a different representation of expressions (for good or bad). If 
you want to keep your existing representation, then you have to use a 
generic programming library that supports GADTs. I know at least the 
Spine approach supports GADTs, but the library on Hackage seems too 
incomplete to be useful:


  http://hackage.haskell.org/package/spine

I don't know if there are other libraries that support GADTs.

You can also have a look at CompData:

  http://hackage.haskell.org/package/compdata

It is similar to Syntactic (i.e. requires a different representation), 
but it has a richer library of generic traversals.


/ Emil


2012-11-21 04:20, Alexander Solla skrev:

Have you read Data types a la carte?  The 'syntactic' package
implements the ideas, but it was a little dense for my purposes when I
looked (I just wanted data types, a la carte; it focuses on manipulating
ASTs defined a la carte).  It might be what you need, or you can roll
your own based on the paper.


On Tue, Nov 20, 2012 at 3:21 PM, Steve Severance
ssevera...@alphaheavy.com mailto:ssevera...@alphaheavy.com wrote:

Hi Everyone,

I am trying to build a function to rewrite and AST. I have and AST
which is designed to represent a computation graph. I will present a
simplified version here designed to illustrate the problem. I have
tried numerous ways of rewriting it including uniplate, recursion
and Edward Kmett's implementation of plate in his lens package.

My AST is defined using GADTs as follows:

class (ReflectDescriptor a, Typeable a, Wire a) = ProtoBuf a

data Expression a b where
   OpenTable :: (ProtoBuf b) = Int - Table - Expression () b
   OpenFile :: (ProtoBuf b) = Int - String - Expression () b
   WriteFile :: (Typeable a, ProtoBuf b) = Int - String -
Expression a b - Expression b ()
   WriteTable :: (Typeable a, ProtoBuf b) = Int - Table -
Expression a b - Expression b ()
   Map :: (ProtoBuf a, ProtoBuf b, ProtoBuf c) = Int - (a - b) -
Expression c a - Expression a b
   LocalMerge :: (ProtoBuf a) = Int - [Expression c a] -
Expression c a

The user can create code inside a Monad Transformer like so:

q - query $ do
  table - openTable myTable
  transform - map someFunc table
  writeTable otherTable transform

As part of this language the compiler I am building would need to
for instance transform OpenTable into a series OpenFile nodes with a
LocalMerge to merge the results together.

So uniplate cannot work over GADTs if I recall correctly.

I exchanged emails with Edward and he explained that for the lens
case I would need something like an indexed lens family from his
indexed package which is not implemented yet but which may be in the
future.

The issue with recursion is that as you recurse through the AST the
a b on the Expression change and GHC cannot compile it because it
wants the a b to be the same on each recursive call.

My question to the Haskell community is how might one develop AST
rewriting functionality. One possible solution is stripping the
types away from GHC and doing all the type checking myself. That
doesn't seem very good.

Another possibility that I have looked at was using hoopl. It seems
very compatible given that it is built for describing and optimizing
data flow which I am doing however the learning curve looks quite
steep. I have been reluctant so far to invest the time in it.

Has anyone developed something similar? What recommendations do you
have?

Thanks.

Steve

___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org mailto: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] Parameterized constraints

2012-07-06 Thread Emil Axelsson

Hi!

The `constraints` package provides ways to manipulate objects of kind 
`Constraint`. I need the same kind of manipulation, except that I need 
to work with objects of kind `* - Constraint`. I.e. I need 
parameterized constraints that can be applied to different types.


BTW, is there a standard term for things of kind `* - Constraint`?

I have a type family

  type family Constr (f :: * - *) :: * - Constraint

which returns a parameterized constraint with the property that any 
value of type `f a` fulfills the constraint `Constr f a`. Since the 
constraint can be stronger than needed, I need something similar to `:-` 
from `constraints`, except it should operate on parameterized constraints.


I have implemented the stuff I need (see below), but my question is if 
it's possible to do this with the `constraints` package directly (e.g. 
using `Forall`). I'm afraid I can't see how.


Here is what I've come up with so far:

  -- Instead of (c1,c2)
  class(c1 a, c2 a) = (c1 :/\: c2) a
  instance (c1 a, c2 a) = (c1 :/\: c2) a

  -- Instead of (:-)
  type sub : sup = forall a . Dict (sup a) - Dict (sub a)

  -- Instead of weaken1
  weak1 :: c1 : (c1 :/\: c2)
  weak1 Dict = Dict

  weak2 :: c2 : (c1 :/\: c2)
  weak2 Dict = Dict

Thanks!

--
/ Emil


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


Re: [Haskell-cafe] Using syntactic to implement the lambda calculus

2012-07-05 Thread Emil Axelsson

Hi Alex!

2012-07-03 20:18, Alex Rozenshteyn skrev:

I'm trying to implement the lambda calculus (with CBV evaluation) using
the syntactic package, in such a way that a simple extension is also
simple to implement.

I am stuck on the fact that it seems that the Value type needs to be
parametrized over the Expr type and I can't seem to figure out how to do it.


The trick is to see that your `Expr` and `Value` can be merged to a 
single type:


  data Expr group
where
  Var :: Ident - Expr NONVAL
  Lam :: Ident - Expr any - Expr VAL
  App :: Expr any1 - Expr any2 - Expr NONVAL

  data VAL
  data NONVAL

  type Value = Expr VAL

  eval :: Expr any - Value
  ...

(Here I'm using polymorphic constructors to emulate that `Value` is a 
sub-type of `Expr`. I could have made a more direct translation with two 
lambda constructors. Then all constructors would have been monomorphic.)


Once this is done, the conversion to Syntactic is easy:

  data Var :: * - * where Var :: Ident - Var (Full NONVAL)
  data Lam :: * - * where Lam :: Ident - Lam (any :- Full VAL)
  data App :: * - * where App :: App (any1 :- any2 :- Full NONVAL)

  type Expr group = ASTF (Lam :+: Var :+: App) group
  type Value  = ASTF (Lam :+: Var :+: App) VAL

  eval :: Expr any - Value
  eval var
  | Just (Var _) - prj var = error not closed
  eval e@(lam :$ _)
  | Just (Lam _) - prj lam = e
  eval (app :$ e1 :$ e2)
  | Just App - prj app = case eval e1 of
  (lam :$ e) | Just (Lam i) - prj lam   - subst e (eval e2) i
  _ - error illegal application

  subst :: Expr any - Value - Ident - Value
  subst = undefined

Of course, you need to generalize the types of `eval` and `subst` in 
order to make them extensible. For more details, see this paper:


  http://www.cse.chalmers.se/~emax/documents/axelsson2012generic.pdf

(The paper refers to syntactic-1.0 which hasn't been uploaded yet, so 
there are some small differences.)


/ Emil


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


Re: [Haskell-cafe] Using Data Types a la Carte

2012-04-19 Thread Emil Axelsson

2012-04-19 22:31, Alex Rozenshteyn skrev:

I'm trying to implement a set of languages with a large overlap between them.

 From what I understand, there are 3 main ways to do this: Finally
Tagless, Data Types a la Carte, or manually.

I'm currently leaning toward DTalaC, but not strongly.

There seem to be two packages which implement the DTalaC style:
syntactic and compdata. Alternatively, I can write the common code
myself.

Does anyone have recommendations for which one to use, and any
materials for learning to use them?


I can only give useful comments on Syntactic. The core part has been 
described in my draft ICFP submission:



http://www.cse.chalmers.se/~emax/documents/astModel-icfp2012-submitted.pdf

For more advanced usage (of defining embedded languages), see 
NanoFeldspar, which is included in the Syntactic package.


Syntactic doesn't really support mutually recursive data types, but they 
can be encoded using the technique described here:


  http://www.haskell.org/pipermail/haskell-cafe/2011-May/091770.html

This seems to be similar to how CompData handles mutually recursive types.

HTH

/ Emil


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


Re: [Haskell-cafe] partial type annotations

2012-01-19 Thread Emil Axelsson
In the spirit of Oleg's hack, but with nicer combinator support, you can 
use the patch combinators I just uploaded to Hackage (prompted by this 
thread):


  http://hackage.haskell.org/package/patch-combinators

Your example then becomes:

  my_code_block = do
  x - instruction1 -:: tCon (tCon tInteger)
  y - instruction2 (x + x)

The signature `tCon (tCon tInteger)` should be read as the type `_ (_ 
Integer)`.


Alternatively, with ViewPatterns, you can write:

  my_code_block2 = do
  (tCon tInteger - x) - instruction1
  y - instruction2 (x + x)
  return y

/ Emil


2012-01-19 21:37, Nicholas Tung skrev:

Dear all,

 I wanted to voice support for a partial type annotations. Here's my
usage scenario: I have a monad for an imperative EDSL, which has an
associated expression data type,

class (Monad m, Expression (ExprTyp m)) = MyDSLMonad m where
 data ExprTyp m :: * - *

 and you write imperative EDSL code like so,

my_code_block = do
 x - instruction1
 y - instruction2 (x + x)
 ...

 I want the user to be able to annotate x is an Integer. However,
to do that now, one has to now add a type signature for my_code_block
like so, so that the $m$ variable is in scope,

my_code_block :: forall m. MyDSLMonad m = m ()
my_code_block = do
 x :: ExprTyp m Integer - instruction1
 ...

 If such a feature were available, one could write a nice type
synonym Expr and use it like so,

type Expr a = ExprTyp _ a

my_code_block = do
 x :: Expr Integer - instruction1

 Suggestions for workarounds are appreciated. I created an
`asExprTypeOf`, similar to Prelude's `asExprTyp`, but I don't like the
syntax as much.

 Some previous discussion
* http://www.haskell.org/pipermail/haskell/2002-April/009409.html
* (a reply) http://www.haskell.org/pipermail/haskell/2002-April/009413.html
* http://hackage.haskell.org/trac/haskell-prime/wiki/PartialTypeAnnotations

cheers,
Nicholas — https://ntung.com — 4432-nstung


___
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] Patch combinators

2012-01-16 Thread Emil Axelsson

Hi all!

Based on ideas by Koen Claessen, I have made a small module for what 
might be called patch combinators:


  http://hpaste.org/56501

Examples are found as comments.

Before I push this to Hackage, I just wanted to check if there is any 
package that already provides this sort of functionality.


(We're planning to use this module for expressing compile-time 
constraints on Feldspar functions.)


Thanks for any feedback!

/ Emil

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


Re: [Haskell-cafe] Disjunctive patterns

2011-12-08 Thread Emil Axelsson

Instead of pattern guards you can use ViewPatterns:

  http://hackage.haskell.org/trac/ghc/wiki/ViewPatterns

This reduces some of the noise.


{-# LANGUAGE ViewPatterns #-}

data T = Foo Int | Bar Int | Baz

fooBar (Foo a) = Just a
fooBar (Bar a) = Just a
fooBar _   = Nothing

foo :: T - T - Int
foo x y = case (x,y) of
  (fooBar - Just a, fooBar - Just b) - a + b
  (Bar a, Baz) - -a
  (Foo a, Baz) - a
  _ - 0


/ Emil


2011-12-08 11:13, Asger Feldthaus skrev:

Haskell doesn't seem to support disjunctive patterns, and I'm having a
difficult time writing good Haskell code in situations that would
otherwise call for that type of pattern.

Suppose for an example I have this data type:

data T = Foo Int | Bar Int | Baz

In OCaml I can write something like:

(* foo : T - T - int *)
fun foo x y = match (x,y) with
   | (Foo a | Bar a, Foo b | Bar b) - a + b
   | (Baz, Foo a)
   | (Bar a, Baz) - -a
   | (Baz, Bar a)
   | (Foo a, Baz) - a
   | _ - 0

In Haskell I can't find any equivalent to the disjunctive pattern. If
expanded naively, my Haskell version would look like this:

foo :: T - T - Int
foo x y = case (x,y) of
   (Foo a, Foo b) - a + b
   (Foo a, Bar b) - a + b
   (Bar a, Foo b) - a + b
   (Bar a, Bar b) - a + b
   (Baz, Foo a) - -a
   (Bar a, Baz) - -a
   (Baz, Bar a) - a
   (Foo a, Baz) - a
   _ - 0

While my example is still managable in size, this quickly goes out of
hand in practice. I've tried using pattern guards but with limited
success. For example:

foo2 :: T - T - Int
foo2 x y = case (x,y) of
   (x,y) | Just a - open x,
   Just b - open y -
 a+b
   (Baz, Foo a) - -a
   (Bar a, Baz) - -a
   (Baz, Bar a) - a
   (Foo a, Baz) - a
   _ - 0
   where
 open (Foo x) = Just x
 open (Bar x) = Just x
 open Baz = Nothing

I admit it doesn't look that bad in my crafted example, but this
approach doesn't seem to well work for me in practice. In any case, it's
still far more verbose than the disjunctive pattern version.

Nesting the case expressions instead of tuple-matching can reduce some
code duplication, but in general it becomes really verbose, and it is
easy to make mistakes when you have partially overlapped patterns in the
disjunctive-pattern version. Here's the example with nested cases:

foo3 :: T - T - Int
foo3 x y = case x of
   Foo a - case y of
 Foo b - a+b
 Bar b - a+b
 Baz - a
   Bar a - case y of
 Foo b - a+b
 Bar b - a+b
 Baz - -a
   Baz - case y of
 Foo b - -b
 Bar b - b
 Baz - 0

What do people do in this situation - is there a good trick I've
overlooked? And is there some reason why Haskell does not support
disjunctive patterns?

Thanks,
Asger


___
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] Putting constraints on internal type variables in GADTs

2011-11-08 Thread Emil Axelsson

2011-11-08 14:59, Felipe Almeida Lessa skrev:

On Tue, Nov 8, 2011 at 11:49 AM, Anupam Jainajn...@gmail.com  wrote:

I can work around this by changing my data type declaration to include Show
constraints but I don't want to restrict my data type to only Showable
things just so I could have a Show instance for debugging -

Only ∷ Show o ⇒ o → T o
TT ∷ (Show o1, Show o2) ⇒ T o1 → (o1 → o2) → T o2

What else can I do to declare a Show instance for my datatype?


[...]


I think you may do something more complicated with the new
ConstraintKinds extesions, something like

   data T c o where
 Only :: o -  T o
 TT :: c o1 =  T o1 -  (o1 -  o2) -  T o2

   instance Show o =  Show (T Show o) where
 ...

This is completely untested.  And even if it works, I don't know if it
is useful =).


If you don't have the development version of GHC, this can be done 
without ConstraintKinds using the Sat class available in Syntactic 
(cabal install syntactic). I attach such a solution where the GADT is 
defined as follows:


  data T ctx o where
Only :: Sat ctx o  = o - T ctx o
TT   :: Sat ctx o1 = T ctx o1 - (o1 - o2) - T ctx o2

Whether this solution is too complicated is up to you to decide :)

/ Emil

{-# LANGUAGE FlexibleContexts #-}
{-# LANGUAGE FlexibleInstances #-}
{-# LANGUAGE GADTs #-}
{-# LANGUAGE MultiParamTypeClasses #-}
{-# LANGUAGE ScopedTypeVariables #-}
{-# LANGUAGE TypeFamilies #-}

import Language.Syntactic

data T ctx o where
  Only :: Sat ctx o  = o - T ctx o
  TT   :: Sat ctx o1 = T ctx o1 - (o1 - o2) - T ctx o2

-- | Representation of a 'Show' constraint
data ShowCtx

instance Show a = Sat ShowCtx a
  where
data Witness ShowCtx a = Show a = ShowWit
witness = ShowWit

show' :: forall a . Sat ShowCtx a = a - String
show' a = case witness :: Witness ShowCtx a of
ShowWit - show a

instance Show (T ShowCtx o) where
  show (Only o)  = Only  ++ (show' o)
  show (TT t1 f) = TT ( ++ (show' t1) ++ )

t :: Sat ctx Int = T ctx Bool
t = TT (Only (3 :: Int)) even

test = show (t :: T ShowCtx Bool)

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


Re: [Haskell-cafe] library on common sub-expression elimination?

2011-08-15 Thread Emil Axelsson

2011-08-13 05:40, Levent Erkok skrev:

On 8/12/2011 10:30 AM, Conal Elliott wrote:

Note that data-reify will only find *some* common/equal sub-expressions,
namely the pointer-equal ones. In all of my code-generating (deep)
DSLs, it's been very important for efficiency to also pull out
equal-but-pointer-unequal expressions.

 - Conal


data-reify-cse (http://hackage.haskell.org/package/data-reify-cse) by
Sebastiaan Visser performs cse for graphs generated by Andy's data-reify.

-Levent.


I just wanted to point out that syntactic

  http://hackage.haskell.org/package/syntactic

also has the functionality provided by data-reify and data-reify-cse. 
See Examples/NanoFeldspar/Test.hs for a demonstration. The reification 
part is more or less copied from data-reify, so it's conceptually doing 
the same thing.


When it comes to graph reification, syntactic doesn't really offer 
anything more than what data-reify(-cse) does. But in the future, 
syntactic will also rebuild an expression with let binding from the graph.


/ Emil

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


Re: [Haskell-cafe] Haskell syntax highlighting in a public blog

2011-08-15 Thread Emil Axelsson

2011-08-09 03:54, Oscar Picasso skrev:

Hi,

Is there a public blog that that allow syntax highlighting of Haskell code?


One option is to write the post in Markdown and use Pandoc (with syntax 
highlighting) to convert to HTML. The process (for Blogger) is described 
here:


http://flygdynamikern.blogspot.com/2009/03/blogging-with-pandoc-literate-haskell.html

/ Emil


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


[Haskell-cafe] ANN: syntactic-0.5

2011-07-28 Thread Emil Axelsson

I've just uploaded a new version of syntactic:

  http://hackage.haskell.org/package/syntactic

The most important change is that I've added observable sharing based on 
StableNames. The implementation and interface are conceptually quite 
similar to Andy Gill's data-reify.


The library offers both referentially transparent common sub-expression 
elimination (that uses a combination of hashing and observable sharing 
under the hood), as well as direct observation of sharing. The 
difference between the two flavors is demonstrated in the accompanied file:


  Examples/NanoFeldspar/Test.hs

(See test7_X.)

Still missing a way to rebuild an expression with let bindings from the 
syntax graphs. This is ongoing work.


/ Emil


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


Re: [Haskell-cafe] How unique is Unique

2011-05-30 Thread Emil Axelsson

2011-05-28 11:35, Heinrich Apfelmus skrev:

Emil Axelsson wrote:

Hello!

Lacking a proper blog, I've written some notes about Data.Unique here:

   http://community.haskell.org/~emax/darcs/MoreUnique/

This describes a real problem that makes Data.Unique unsuitable for
implementing observable sharing.

The document also proposes a solution that uses time stamps to generate
symbols that are more unique.

Does anyone have any comments on the proposed solution? Are there any
alternatives available?


I don't know how Data.Unique is implemented. For observable sharing, I
usually implement my own variant of Data.Unique with a global
variable/counter.


This is how Data.Unique is implemented too. Would your implementation 
pass the test I posted at the link above?





Since every module of my DSL depends on the same
global variable, only two things should happen:

* Reloading a module does not reload the global counter. Everything is fine.
* Reloading a module does reload the global counter. This forces *all*
modules to be reloaded, which removes all expressions that have used the
old variable from scope.


But Simon Marlow just said that CAFs are reset upon reload. So the first 
situation should never occur(?). And as my example shows, resetting the 
counter does not force all dependent modules to get reloaded.





However, note that the problem is not so much with Data.Unique; the real
problem is that you can't say I want this to be unique, you have to
say I want this to be unique within this or that *context*. Imagine
that I give you two expressions with some  Uniques  inside, some of them
equal, some of them not. How do you know that two equal Uniques denote
the same subexpressions? For that, you have to know that I created them
in the same context, in the same *environment*.

Using Data.Unique assumes that the environment is one program run. It is
clear that reloading modules in GHCi leads to different environments.


OK, so I guess you could say that my solution makes the context explicit 
by associating it with a time stamp. Of course, this is just an 
approximation, because it's not impossible for two different contexts to 
get the same time stamp, especially in a parallel setting. However, it 
seems that this somewhat ugly trick might actually be what makes this 
approach to observable sharing work in practice.





Concerning observable sharing, I very much like the approach from

Andy Gill. Type safe observable sharing.
http://www.ittc.ku.edu/csdl/fpg/sites/default/files/Gill-09-TypeSafeReification.pdf

which uses  StablePointers . Unfortunately, it forces Typeable
contraints on polymorphic combinators.


As far as I've heard, the semantics of stable pointers is not always 
well-defined either (but I could be wrong). But I should look into 
whether this technique could be used with the syntactic library. It 
would be nice to be able to gather several techniques under a common 
interface.


/ Emil

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


[Haskell-cafe] How unique is Unique

2011-05-27 Thread Emil Axelsson

Hello!

Lacking a proper blog, I've written some notes about Data.Unique here:

  http://community.haskell.org/~emax/darcs/MoreUnique/

This describes a real problem that makes Data.Unique unsuitable for 
implementing observable sharing.


The document also proposes a solution that uses time stamps to generate 
symbols that are more unique.


Does anyone have any comments on the proposed solution? Are there any 
alternatives available?


Thanks!

/ Emil


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


Re: [Haskell-cafe] How unique is Unique

2011-05-27 Thread Emil Axelsson

2011-05-27 10:44, David Virebayre skrev:

2011/5/27 Emil Axelssone...@chalmers.se:


Does anyone have any comments on the proposed solution? Are there any
alternatives available?


It might be unsuitable where an administrator can change the system's
time while the program is running.


Agreed! However, it should be extremely hard to cause a clash in this 
way. So unless there are even safer solutions, I think this is a risk 
I'm willing to take.


/ Emil

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


Re: [Haskell-cafe] How unique is Unique

2011-05-27 Thread Emil Axelsson

2011-05-27 13:12, Simon Marlow skrev:

On 27/05/2011 08:35, Emil Axelsson wrote:

Hello!

Lacking a proper blog, I've written some notes about Data.Unique here:

http://community.haskell.org/~emax/darcs/MoreUnique/

This describes a real problem that makes Data.Unique unsuitable for
implementing observable sharing.

The document also proposes a solution that uses time stamps to generate
symbols that are more unique.

Does anyone have any comments on the proposed solution? Are there any
alternatives available?


This has nothing to do with Unique, you are simply using unsafePerformIO
in an unsafe way.  It is called unsafePerformIO for a reason :-)


Right, I wasn't suggesting this is a bug in Data.Unique. It's just that 
I need something different. I've added a note about this on the post.


Note that I am planning to wrap all this in a safe interface. So using 
unsafePerformIO should be fine in this case, as long as Unique symbols 
survive GHCi reloads.


/ Emil

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


[Haskell-cafe] Cabal upload failure

2011-05-24 Thread Emil Axelsson

Hello!

I'm trying to upload a new version of syntactic, but Hackage gives the 
error:


500 Internal Server Error
stdin: hWaitForInput: invalid argument (Invalid or incomplete 
multibyte or wide character)


In fact, I get the same error if I use the Check functionality on the 
earlier version that is already on Hackage.


Any idea what causes this?

/ Emil


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


Re: [Haskell-cafe] Cabal upload failure

2011-05-24 Thread Emil Axelsson

2011-05-24 12:05, Niklas Broberg skrev:

On 24 May 2011 19:48, Emil Axelsson e...@chalmers.se
mailto:e...@chalmers.se wrote:
  Hello!
 
  I'm trying to upload a new version of syntactic, but Hackage gives the
  error:
 
  500 Internal Server Error
  stdin: hWaitForInput: invalid argument (Invalid or incomplete
multibyte or
  wide character)
 
  In fact, I get the same error if I use the Check functionality on the
  earlier version that is already on Hackage.
 
  Any idea what causes this?

I have the exact same issue, I mailed about it some 10 minutes before
you.


Aha, so maybe it's a local problem :)




So I believe this is Hackage's fault.


Yes, and as I said, it gives the same error for a tarball that was 
already accepted by Hackage, namely:


http://hackage.haskell.org/packages/archive/syntactic/0.2.0.1/syntactic-0.2.0.1.tar.gz



2011-05-24 12:00, Ivan Lazar Miljenovic skrev:
 Do you have any comments or something somewhere that are in a 
non-UTF8 encoding?


No, not conciously at least...

/ Emil


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


[Haskell-cafe] Impossible class instance?

2011-05-16 Thread Emil Axelsson

Hello!

At the end of this message is a program with a simple expression type, 
and a class `ToExpr` that generalizes expressions to arbitrary Haskell 
types. Every node in `Expr` is annotated with some abstract information. 
The program raises the following type error:


test.hs:13:5:
Couldn't match type `(,) a' with `(,) (a, a)'
Inaccessible code in the instance declaration
In the instance declaration for `ToExpr (a, b)'

It seems that the mere existence of the constraint

  info (a,b) ~ (info a, info b)

causes this error. I was hoping that this constraint would make it 
possible to construct the value (ia,ib) in the class instance, which is 
otherwise not allowed.


Note: I don't want to make `info` an associated type. The idea is to 
make this work with any type function `info` that fulfills the above 
constraint.


Is there any way to make this work?

/ Emil




{-# LANGUAGE UndecidableInstances #-}

data Expr info a
  where
Int  :: info a - Int - Expr info a
Pair :: info (a,b) - Expr info a - Expr info b - Expr info (a,b)

getInfo :: Expr info a - info a
getInfo (Int info _)= info
getInfo (Pair info _ _) = info

class ToExpr a
  where
type Internal a
toExpr :: a - Expr info (Internal a)

instance
( ToExpr a
, ToExpr b
, info (a,b) ~ (info a, info b)
) =
  ToExpr (a,b)
  where
type Internal (a,b) = (Internal a, Internal b)
toExpr (a,b) = Pair (ia,ib) (toExpr a) (toExpr b)
  where
ia = getInfo a
ib = getInfo b



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


Re: [Haskell-cafe] Impossible class instance?

2011-05-16 Thread Emil Axelsson
Ahh, never mind... I just realized there's no way to relate the `info` 
in the instance to the `info` in the class definition.


Alright, I'll keep trying to make this work. Sorry for the noise!

/ Emil


2011-05-16 12:19, Emil Axelsson skrev:

Hello!

At the end of this message is a program with a simple expression type,
and a class `ToExpr` that generalizes expressions to arbitrary Haskell
types. Every node in `Expr` is annotated with some abstract information.
The program raises the following type error:

test.hs:13:5:
  Couldn't match type `(,) a' with `(,) (a, a)'
  Inaccessible code in the instance declaration
  In the instance declaration for `ToExpr (a, b)'

It seems that the mere existence of the constraint

info (a,b) ~ (info a, info b)

causes this error. I was hoping that this constraint would make it
possible to construct the value (ia,ib) in the class instance, which is
otherwise not allowed.

Note: I don't want to make `info` an associated type. The idea is to
make this work with any type function `info` that fulfills the above
constraint.

Is there any way to make this work?

/ Emil




{-# LANGUAGE UndecidableInstances #-}

data Expr info a
where
  Int  :: info a -  Int -  Expr info a
  Pair :: info (a,b) -  Expr info a -  Expr info b -  Expr info (a,b)

getInfo :: Expr info a -  info a
getInfo (Int info _)= info
getInfo (Pair info _ _) = info

class ToExpr a
where
  type Internal a
  toExpr :: a -  Expr info (Internal a)

instance
  ( ToExpr a
  , ToExpr b
  , info (a,b) ~ (info a, info b)
  ) =
ToExpr (a,b)
where
  type Internal (a,b) = (Internal a, Internal b)
  toExpr (a,b) = Pair (ia,ib) (toExpr a) (toExpr b)
where
  ia = getInfo a
  ib = getInfo b



___
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] [Haskell] ANN: syntactic-0.1

2011-05-10 Thread Emil Axelsson

2011-05-10 15:31, Heinrich Apfelmus skrev:

I'm also unhappy about some of the boilerplate. For instance, have a
look at the function  goE  in  compileAccumB  (line 210), it's just a
generic applicative traversal through the data type.


Most likely, this boilerplate could be simplified using syntactic.


Hm, does the boilerplate get removed or only simplified? I was hoping
that one could use a completely generic traversal; but is that actually
the case?


I was using careful wording :) I think the traversal can be completely 
generic. But syntactic brings its own (constant) overhead, so I felt the 
word remove might be too strong.





On closer inspection, I'm discovering another issue, namely the need for
the  Typeable  class. This is quite unfortunate, because it would mean
that I won't be able to make an API built on type classes like Functor
or Applicative. Some discussion on that can be found at the end of

http://apfelmus.nfshost.com/blog/2011/04/24-frp-push-driven-sharing.html


Hm... The only reason (afair) for having Typeable constraints in the 
tree was that my code motion transform (not yet released) needs to move 
around nodes in a way that the type checker is not happy with. But as 
long as my algorithm is correct, the type casts will actually always 
succeed. So it might be possible to use unsafeCoerce directly and get 
rid of Typeable. There might also be ways to make Typeable optional...


I will look into this.




So, it looks like I can't make use of  syntactic  at the moment. Then
again, my library is probably one of the strongest tests of expressivity
for  endeavors like  syntactic , so that's fine. Another example of
similar difficulty would be D. Swierstra's recent parser/grammar
combinators that can handle left-recursive grammars. Once  syntactic
can deal with those, you're the king! :)


Thanks for the tip! It would be interesting to try out these libraries 
for real, if only for the sake of getting to know the practical limits 
of syntactic. But my focus is currently on the Feldspar implementation, 
so I probably won't have time for things like this in a (long) while.


/ Emil

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


[Haskell-cafe] ANN: syntactic-0.1

2011-05-06 Thread Emil Axelsson

I'm happy to announce the first release of syntactic:

  http://hackage.haskell.org/package/syntactic

providing generic abstract syntax and utilities for embedded languages.

To get an idea of what it's about, check out the tiny(!) implementation 
of (simplified) Feldspar in the Examples directory:


  http://projects.haskell.org/syntactic/Examples/MuFeldspar

The library is intended to provide a growing set of utilities for 
embedded languages. In particular, I hope to be able to provide safe 
interfaces to various unsafe techniques for speeding things up.


Comments, patches and clients are welcome!

/ Emil


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


[Haskell-cafe] ANNOUNCE: New version Feldspar

2011-04-27 Thread Emil Axelsson
On behalf of the Feldspar team, I'm happy to announce version 0.4.0.2 of 
feldspar-language and feldspar-compiler:


  http://hackage.haskell.org/package/feldspar-language
  http://hackage.haskell.org/package/feldspar-compiler

Feldspar is an embedded domain-specific language for generating code for 
embedded applications, in particular for digital signal processing. For 
more information, see our web pages:


  http://feldspar.inf.elte.hu/feldspar/
  http://feldspar.inf.elte.hu/

A brief list of changes since the last version:

  * Support for GHC 7.
  * Including a fresh tutorial for new users.
  * Improved C code generation (efficiency and readability).
- Efficient vector append.
- More unified representation of arrays in the C code.
- Etc.
  * A new sequential construct for unfolding vectors using an 
accumulating parameter.

  * Support for structs.
  * New optimization: common sub-expression elimination.
  * Lots of restructuring under the hood.
  * Bugfixes.

/ Emil


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


[Haskell-cafe] Why does Cabal not choose the latest package?

2011-04-26 Thread Emil Axelsson

Hello!

I've had some of the usual problems with packages depending on multiple 
versions of another package. It seems the root of the hole problem was 
that I once attempted to run


  cabal install cabal-install

This brought in a number of older packages (Cabal-1.8.0.6, 
containers-0.3.0.0, directory-1.0.1.2, filepath-1.1.0.4, 
process-1.0.1.5) to my local package DB, which led to inconsistencies 
when trying to install new packages.


However, if I run

  cabal install cabal-install-0.10.2

things work just fine. So the problem is that it wants to install an 
older version of cabal-install. A session demonstrating the problem is 
found below.


Why doesn't cabal always install the latest packages?

Thanks!

/ Emil


[emax@laptop:~] ghc --version
The Glorious Glasgow Haskell Compilation System, version 7.0.2

[emax@laptop:~] cabal --version
cabal-install version 0.10.2
using version 1.10.1.0 of the Cabal library

[emax@laptop:~] cabal install cabal-install
Resolving dependencies...
Downloading containers-0.3.0.0...
...

[emax@laptop:~] cabal install cabal-install-0.10.2
Resolving dependencies...
Configuring cabal-install-0.10.2...
Preprocessing executables for cabal-install-0.10.2...
Building cabal-install-0.10.2...
...


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


Re: [Haskell-cafe] ANN: unordered-containers - a new, faster hashing-based containers library

2011-02-23 Thread Emil Axelsson

2011-02-23 13:56, Victor Nazarov skrev:

Also I think that value of hash functions is obviously a Monoid and it
will be convenient to have Monoid instance

 newtype Hash = Hash Int
 instance Monoid Hash where
   mempty = Hash 0
   Hash a `mappend` Hash b = Hash (a `combine` b)

 class Eq a =  Hashable a where
 hash :: a -  Hash
 hashWithSalt :: Hash -  a -  Hash

 hashWithSalt salt x = salt `mappend` hash x


Monoid would be a good idea if combine was associative :)

  Prelude Data.Hashable let a = hash a
  Prelude Data.Hashable let b = hash b
  Prelude Data.Hashable let c = hash c
  Prelude Data.Hashable (a `combine` b) `combine` c
  198573605
  Prelude Data.Hashable a `combine` (b `combine` c)
  177445

/ Emil


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


Re: [Haskell-cafe] Is let special?

2010-11-02 Thread Emil Axelsson

Fundera på vad parentesen innebär.

/ Emil


2010-11-02 10:20, Max Bolingbroke skrev:

To recover this sharing, you either need some sort of observable
sharing, or some common subexpression elimination (which risks
introducing space leaks if your DSL has lazy semantics).

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


Re: [Haskell-cafe] Is let special?

2010-11-02 Thread Emil Axelsson

Sorry, that was a mental note to myself :)

/ Emil


2010-11-02 12:41, Emil Axelsson skrev:

Fundera på vad parentesen innebär.

/ Emil


2010-11-02 10:20, Max Bolingbroke skrev:

To recover this sharing, you either need some sort of observable
sharing, or some common subexpression elimination (which risks
introducing space leaks if your DSL has lazy semantics).

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


Re: [Haskell-cafe] Re: Map constructor in a DSL

2010-10-28 Thread Emil Axelsson

2010-10-28 12:09, Dupont Corentin skrev:

I'm also looking at the Atom's DSL to get inspiration.
Something I don't understand in it is that it has two languages, on typed:

data  E  a  where
   VRef ::  V  a  -  E  a
   Const::  a  -  E  a
   Cast ::  (NumE  a,  NumE  b)  =  E  a  -  E  b
   Add  ::  NumE  a  =  E  a  -  E  a  -  E  a

etc.

And, along with it, an untyped counterpart:

-- | An untyped term.
data  UE

   =  UVRef  UV
   |  UConst  Const

   |  UCast   Type  UE
   |  UAddUE  UE

etc.

What that for? What's the use of having beautiful GADT if you have to maintain 
an untyped ADT aside??


The general reason for this (I can't speak for Atom specifically) is 
that the typed representation can be quite hard to work with when you 
want to transform the expressions. But you can still often limit the use 
of the untyped representation to the last stages in the backend, which 
means that you can enjoy the typed representation in the initial stages.


In the development version of Feldspar, we use a typed representation 
combined with type-safe casting using Data.Typeable. Although not ideal, 
this seems to be better than having two different representations.


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


Re: [Haskell-cafe] EDSL for Makefile

2010-09-30 Thread Emil Axelsson

How about:

  execute (gcc -c  ++ dependencyList ++  -o  ++ target r1)

/ Emil


2010-09-30 10:41, C K Kashyap skrev:

Also, I wanted some idea
on how(in the current approach) I could make the target name and the
dependency available to the action writer - as shown below.

r1 = Rule {
target = file1,
dependsOn = [file2],
action = do
execute (gcc -c  ++ dependencyList ++  -o  ++ 
target)
}



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


[Haskell-cafe] Re: [fp-embedded] Which Haskell DSL for writing C? (Was ANN: Copilot 0.22 -- A stream DSL for writing embedded C.)

2010-09-21 Thread Emil Axelsson

2010-09-21 22:32, Lee Pike skrev:

Oh, one thing I should mention is that there are a few Haskell DSLs for 
generating embedded C now:

  * Atom http://hackage.haskell.org/package/atom
  * Feldspar http://hackage.haskell.org/package/feldspar-language
  * cmonad http://hackage.haskell.org/package/cmonad
  * Copilot http://hackage.haskell.org/package/copilot
  * Others?


From a quick browse of the cmonad package, it seems that it does not 
generate C code, but is only intended for interpretation in Haskell.





I know less about Feldspar, but I think the language has higher-level 
data-structures (e.g., vectors and matrices) and is focused more on DSP than 
periodic, constant-time/constant-space C code generation.


Yes, at the moment, Feldspar can only describe pure functions. The next 
step is to add data flow (and other forms of coordination) on top of the 
pure language.


/ Emil

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


[Haskell-cafe] ANNOUNCE: feldspar 0.3

2010-07-17 Thread Emil Axelsson
On behalf of the Feldspar team, I'm happy to announce a new release of 
the embedded language Feldspar and its C code generator:


  http://hackage.haskell.org/package/feldspar-language
  http://hackage.haskell.org/package/feldspar-compiler

The main changes in 0.3 are:

  * Signed/unsigned integers of different bit widths (8, 16 and 32).
  * Fixed-point numbers.
  * Slight change of the vector library interface: All intermediate
vectors are guaranteed to be removed.
  * A new Stream data type.
  * Support for user-defined types.
  * Tracing functions.
  * Limited support for code generations for the TMS320C64x chip family.
  * Bugfixes.

For more information, see:

  http://feldspar.inf.elte.hu/feldspar/

/ Emil

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


Re: [Haskell-cafe] Build problems on Hackage server

2010-07-08 Thread Emil Axelsson

2010-07-08 09:01, Ross Paterson skrev:

On Wed, Jul 07, 2010 at 10:22:25AM +0200, Emil Axelsson wrote:

Last week I uploaded new versions of feldspar-language and
feldspar-compiler. Both packages build just fine on our local
machines with GHC 6.10 and 6.12.

But Hackage reports the following build failure:


cabal: dependencies conflict: ghc-6.12.2 requires array ==0.3.0.1 however
array-0.3.0.1 was excluded because ghc-6.12.2 requires array ==0.3.0.0


Any idea of what might be causing this?


I think the problem was that containers-0.3.0.0 had been rebuilt
(using array-0.3.0.1, which released at the same time as GHC 6.12.3).
Upgrading to GHC 6.12.3 has fixed this (until the next GHC release).


Cool, thanks!

/ Emil

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


[Haskell-cafe] Build problems on Hackage server

2010-07-07 Thread Emil Axelsson

Hello

Last week I uploaded new versions of feldspar-language and 
feldspar-compiler. Both packages build just fine on our local machines 
with GHC 6.10 and 6.12.


But Hackage reports the following build failure:


cabal: dependencies conflict: ghc-6.12.2 requires array ==0.3.0.1 however
array-0.3.0.1 was excluded because ghc-6.12.2 requires array ==0.3.0.0


Any idea of what might be causing this?

Thanks!

/ Emil

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


Re: [Haskell-cafe] How to use unsafePerformIO properly (safely?)

2010-03-31 Thread Emil Axelsson

In Feldspar's module for observable sharing [1] I use the following

{-# OPTIONS_GHC -O0 #-}

which I assumed would take care of the steps required for 
unsafePerformIO. Could someone please tell if this assumption is correct?


(Of course, observable sharing is not safe regardless, but that's beside 
the point :) )


/ Emil

[1] 
http://hackage.haskell.org/packages/archive/feldspar-language/0.2/doc/html/src/Feldspar-Core-Ref.html




Ivan Miljenovic skrev:

I use the dreaded unsafePerformIO for a few functions in my graphviz
library ( 
http://hackage.haskell.org/packages/archive/graphviz/2999.8.0.0/doc/html/src/Data-GraphViz.html
).  However, a few months ago someone informed me that the
documentation for unsafePerformIO had some steps that should be
followed whenever it's used:
http://www.haskell.org/ghc/docs/latest/html/libraries/base-4.2.0.0/System-IO-Unsafe.html
.

Looking through this documentation, I'm unsure on how to deal with the
last two bullet points (adding NOINLINE pragmas is easy).  The code
doesn't combine IO actions, etc. and I don't deal with mutable
variables, so do I have to worry about them?


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


[Haskell-cafe] ANNOUNCE: feldspar-language-0.2, feldspar-compiler-0.2

2010-03-16 Thread Emil Axelsson

We are happy to announce the new release of Feldspar and its compiler!

  http://feldspar.sourceforge.net/

Feldspar is an embedded domain-specific language for digital signal 
processing. It is developed as a joint project with Ericsson, ELTE 
university and Chalmers university.


This is an intermediate release to make some of our ongoing work 
available. The most user-visible change from the previous version is 
that the vector types have got much simpler, leading to much simpler 
programs. There have also been some substantial changes under the hood: 
Most notably, the compiler has a completely new structure which allows 
defining various optimizations as plugins.


The examples available are still very limited. We hope to make a new 
release quite soon with a reworked tutorial and many more examples.


/ Emil

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


Re: [Haskell-cafe] Non-termination due to context

2010-01-25 Thread Emil Axelsson
OK, I'll try to get to the SYB3 paper at some point. For now I'll just 
add to my knowledge that UndecidableInstances allows you to create 
non-terminating dictionaries in addition to the well-known risk of 
making the type checker loop.


Thanks!

/ Emil


Simon Peyton-Jones skrev:
It's a feature! 


You have
 * B is a superclass of A
 * Eq is a superclass of B

So every A dictionary has a B dictionary inside it, and every B dictionary has 
an Eq dictionary inside it.

Now, your instance declaration 
	instance (A a, Eq a) = B a

says if you give me an A dictionary and an Eq dictionary, I'll make you a B 
dictionary.

Now, 'test' needs a (B Int) dictionary.  To get one, we need an (A Int) dictionary and an (Eq Int) dictionary.  But 

	when solving these sub-problems, GHC assumes that you 
	have in hand a solution to the original problem, this case (B Int)


Why? Read the SYB3 paper.

OK so now you see the problem: we can solve the (A Int) and (Eq Int) 
sub-problems by selection from the (B Int) dictionary.


Still, I confess that I have not fully grokked the relationship between the 
SYB3-style recursion stuff and the question of superclasses.   So I will think 
about your example some more, thank you.

Meanwhile, it's clear that you are on thin ice.

Simon


| -Original Message-
| From: haskell-cafe-boun...@haskell.org 
[mailto:haskell-cafe-boun...@haskell.org] On
| Behalf Of Emil Axelsson
| Sent: 22 January 2010 11:25
| To: Haskell Cafe
| Subject: [Haskell-cafe] Non-termination due to context
| 
| Hello all!
| 
| Consider the following program:
| 
|  {-# LANGUAGE FlexibleInstances, OverlappingInstances, UndecidableInstances #-}

| 
|  class B a = A a
| 
|  instance A Int
| 
|  class Eq a = B a
| 
|  instance (A a, Eq a) = B a
| 
|  eq :: B a = a - a - Bool
|  eq = (==)
| 
|  test = 1 `eq` (2::Int)
| 
| (This is a condensed version of a much larger program that I've been

| debugging.)
| 
| It compiles just fine, but `test` doesn't terminate (GHCi 6.10.4). If I

| change the context `B a` to `Eq a` for the function `eq`, it terminates.
| 
| Although I don't know all the details of the class system, it seems

| unintuitive that I can make a program non-terminating just by changing
| the context of a function (regardless of UndecidableInstances etc.).
| 
| Is this a bug or a feature?
| 
| / Emil
| 
| ___

| 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] Non-termination due to context

2010-01-22 Thread Emil Axelsson

Hello all!

Consider the following program:


{-# LANGUAGE FlexibleInstances, OverlappingInstances, UndecidableInstances #-}

class B a = A a

instance A Int

class Eq a = B a

instance (A a, Eq a) = B a

eq :: B a = a - a - Bool
eq = (==)

test = 1 `eq` (2::Int)


(This is a condensed version of a much larger program that I've been 
debugging.)


It compiles just fine, but `test` doesn't terminate (GHCi 6.10.4). If I 
change the context `B a` to `Eq a` for the function `eq`, it terminates.


Although I don't know all the details of the class system, it seems 
unintuitive that I can make a program non-terminating just by changing 
the context of a function (regardless of UndecidableInstances etc.).


Is this a bug or a feature?

/ Emil

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


Re: [Haskell-cafe] Non-termination due to context

2010-01-22 Thread Emil Axelsson

Ross Paterson skrev:

On Fri, Jan 22, 2010 at 12:24:37PM +0100, Emil Axelsson wrote:

Consider the following program:


{-# LANGUAGE FlexibleInstances, OverlappingInstances, UndecidableInstances #-}
class B a = A a

instance A Int

class Eq a = B a

instance (A a, Eq a) = B a

[...]
Although I don't know all the details of the class system, it seems
unintuitive that I can make a program non-terminating just by
changing the context of a function (regardless of
UndecidableInstances etc.).

Is this a bug or a feature?


I'm afraid you voided the warranty when you used UndecidableInstances.

You really do have a circularity between A and B here, so it's not
surprising that you get a loop.  By changing the context, you demanded
more instances, undecidable ones in fact.


But still, I've always heard that undecidable instances can cause the 
type checker to loop, but if the compiler terminates, you're fine. Here 
the loop happens at run time, so undecidable instances must be a little 
more evil than I thought...


/ Emil


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


Re: [Haskell-cafe] Re: FASTER primes

2010-01-05 Thread Emil Axelsson

Will Ness skrev:

Emil Axelsson emax at chalmers.se writes:

For me, a real smart compiler is one that would take in e.g. (sum $ 
take n $ 
cycle $ [1..m]) and spill out a straight up math formula, inside a few ifs 
maybe (just an aside). 

(Also an aside, I couldn't resist...)

Then I'm sure you'd say that Feldspar [1] has a smart compiler :)



but it didn't produce

f n m = if n  m then n*(n+1)/2 else
let (q,r)=quotRem n m
in q*(m*(m+1)/2) + r*(r+1)/2

:)


Ah, I see... Yes, that would be a very smart compiler :)

/ Emil


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


Re: [Haskell-cafe] Re: FASTER primes

2010-01-04 Thread Emil Axelsson
For me, a real smart compiler is one that would take in e.g. (sum $ take n $ 
cycle $ [1..m]) and spill out a straight up math formula, inside a few ifs 
maybe (just an aside). 


(Also an aside, I couldn't resist...)

Then I'm sure you'd say that Feldspar [1] has a smart compiler :)

The above expression written in Feldspar and the resulting C code can be 
found here:


  http://hpaste.org/fastcgi/hpaste.fcgi/view?id=15592#a15593

The C code is somewhat complicated by the fact that Feldspar doesn't 
have infinite vectors.


Feldspar usually works well on small examples like this one, but we're 
very much lacking bigger examples, so I can't advise you to use it for 
prime numbers just yet.


/ Emil


[1] http://feldspar.sourceforge.net/


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


Re: [Haskell-cafe] writing graphs with do-notation

2009-12-15 Thread Emil Axelsson
Yes, that's probably close to what I want. It would of course be nice to 
also have a monadic/applicative interface for building the graphs. In 
libraries like Wired where you're in a monad anyway, this would get rid 
of the need for IO.


Koen Claessen has made a sketch of a generic graph library that we were 
planning to use as a basis for the EDSLs at Chalmers. But as far as I 
remember it looked a lot like the graph in data-reify, so maybe we 
should just use that instead.


/ Emil



Levent Erkok skrev:
Andy Gill wrote a very nice recent paper on this topic which can serve  
as the basis for a generic implementation:


http://www.ittc.ku.edu/~andygill/paper.php?label=DSLExtract09

As long as you do your reification in the IO monad, Andy's library  
gives you the graph conversion for (almost-) free.


-Levent.

On Dec 13, 2009, at 10:48 PM, Emil Axelsson wrote:

Hi!

This technique has been used to define netlists in hardware  
description languages. The original Lava [1] used a monad, but later  
switched to using observable sharing [2]. Wired [3] uses a monad  
similar to yours (but more complicated).


I think it would be nice to have a single library for defining such  
graphs (or maybe there is one already?). The graph structure in  
Wired could probably be divided into a purely structural part and a  
hardware-specific part.


[1] http://citeseerx.ist.psu.edu/viewdoc/summary?doi=10.1.1.46.5221
[2] http://www.cs.chalmers.se/~dave/papers/observable-sharing.pdf
[3] http://hackage.haskell.org/package/Wired

/ Emil



Soenke Hahn skrev:

Hi!
Some time ago, i needed to write down graphs in Haskell. I wanted  
to be able to write them down without to much noise, to make them  
easily maintainable. I came up with a way to define graphs using  
monads and the do notation. I thought this might be interesting to  
someone, so i wrote a small script to illustrate the idea. Here's  
an example:

example :: Graph String
example = buildGraph $ do
   a - mkNode A []
   b - mkNode B [a]
   mkNode C [a, b]
In this graph there are three nodes identified by [A, B, C]  
and three edges ([(A, B), (A, C), (B, C)]). Think of  
the variables a and b as outputs of the nodes A and B. Note  
that each node identifier needs to be mentioned only once. Also the  
definition of edges (references to other nodes via the outputs) can  
be checked at compile time.
The attachment is a little script that defines a Graph-type  
(nothing elaborate), the buildGraph function and an example graph  
that is a little more complex than the above. The main function of  
the script prints the example graph to stdout to be read by dot (or  
similar).
By the way, it is possible to define cyclic graphs using mdo  
(RecursiveDo).
I haven't come across something similar, so i thought, i'd share  
it. What do you think?

Sönke

___
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] writing graphs with do-notation

2009-12-13 Thread Emil Axelsson

Hi!

This technique has been used to define netlists in hardware description 
languages. The original Lava [1] used a monad, but later switched to 
using observable sharing [2]. Wired [3] uses a monad similar to yours 
(but more complicated).


I think it would be nice to have a single library for defining such 
graphs (or maybe there is one already?). The graph structure in Wired 
could probably be divided into a purely structural part and a 
hardware-specific part.


[1] http://citeseerx.ist.psu.edu/viewdoc/summary?doi=10.1.1.46.5221
[2] http://www.cs.chalmers.se/~dave/papers/observable-sharing.pdf
[3] http://hackage.haskell.org/package/Wired

/ Emil



Soenke Hahn skrev:

Hi!

Some time ago, i needed to write down graphs in Haskell. I wanted to be able 
to write them down without to much noise, to make them easily maintainable. I 
came up with a way to define graphs using monads and the do notation. I thought 
this might be interesting to someone, so i wrote a small script to illustrate 
the idea. Here's an example:


example :: Graph String
example = buildGraph $ do
a - mkNode A []
b - mkNode B [a]
mkNode C [a, b]

In this graph there are three nodes identified by [A, B, C] and three 
edges ([(A, B), (A, C), (B, C)]). Think of the variables a and b 
as outputs of the nodes A and B. Note that each node identifier needs to be 
mentioned only once. Also the definition of edges (references to other nodes 
via the outputs) can be checked at compile time.


The attachment is a little script that defines a Graph-type (nothing 
elaborate), the buildGraph function and an example graph that is a little 
more complex than the above. The main function of the script prints the 
example graph to stdout to be read by dot (or similar).


By the way, it is possible to define cyclic graphs using mdo (RecursiveDo).

I haven't come across something similar, so i thought, i'd share it. What do 
you think?


Sönke


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


Re: [Haskell-cafe] ANNOUNCE: feldspar-language

2009-11-25 Thread Emil Axelsson

(In response to Tom Hawkins' posting of an IIR filter in Atom)

We're still experimenting with how to best describe streaming 
computations with feedback in Feldspar. But for completeness, here one 
possible implementation of an IIR filter:



iir :: forall m n o a . (NaturalT m, NaturalT n, NaturalT o, Num a , Primitive a) 
=
VectorP m a - VectorP n a - VectorP o a - VectorP o a

iir as bs = feedback f
  where
f :: VectorP o a - VectorP o a - Data a
f inPrev outPrev = dotProd as (resize inPrev) - dotProd bs (resize outPrev)



(Please don't mind the type clutter -- we hope to get rid of most of it 
in the future.)


The local function `f` computes a single output, and the `feedback` 
combinator applies `f` across the input stream. You can find the 
resulting C code attached. As you can see, the generated C has lots of 
room for optimization, but the time complexity is right (one top-level 
loop with two inner loops in sequence). We plan to tackle the more 
small-scale optimizations in the future.


The dot product is defined in standard Haskell style:


dotProd :: (Num a, Primitive a) = VectorP n a - VectorP n a - Data a
dotProd as bs = fold (+) 0 (zipWith (*) as bs)


Interestingly, `feedback` is also defined within Feldspar:


feedback :: forall n a . (NaturalT n, Storable a) =
(VectorP n a - VectorP n a - Data a) - VectorP n a - VectorP n a

feedback f inp = unfreezeVector (length inp) outArr'
  where
outArr :: Data (n : a)
outArr = array []

outArr' = for 0 (length inp - 1) outArr $ \i arr -
  let prevInps  = reverse $ take (i+1) inp
  prevOutps = reverse $ take i $ unfreezeVector i arr
  a = f prevInps prevOutps
   in setIx arr i a


This definition uses low-level data structures and loops, and this is 
not something that ordinary Feldspar users should write. It is our hope 
that a few combinators like this one can be defined once and for all, 
and then reused for a wide range of DSP applications.


It turns out that FIR filters are much nicer :)


fir :: (NaturalT m, Num a , Primitive a) =
VectorP m a - VectorP n a - VectorP n a

fir coeffs = map (dotProd coeffs . resize . reverse) . inits


C code attached.

/ Emil


#include feldspar.h

void fir( signed int var0_0_0, signed int var0_0_1[10], signed int var0_1_0, signed int var0_1_1[100], signed int *out_0, signed int out_1[100] )
{
signed int var23[100];

{
int var1;
for( var1 = 0; var1  var0_1_0; var1 += 1)
{
signed int var7;
int var8;
signed int var9;
int var10;
signed int var11;
signed int var12;
signed int var17;
signed int var22_0;

var7 = (var1 + 1);
var8 = (var0_1_0 = var7);
if(var8)
{

var9 = var0_1_0;
}
else
{

var9 = var7;
}
var10 = (var0_0_0 = var9);
if(var10)
{

var11 = var0_0_0;
}
else
{

var11 = var9;
}
var12 = (var11 - 1);
var17 = (var9 - 1);
var22_0 = 0;
var23[var1] = 0;
{
int var13;

var13 = (var22_0 = var12);
while(var13)
{

var23[var1] = (var23[var1] + (var0_0_1[var22_0] * var0_1_1[(var17 - var22_0)]));
var22_0 = (var22_0 + 1);
var13 = (var22_0 = var12);
}
}
}
}
*out_0 = var0_1_0;
copy_arrayOf_signed_int((var23[0]), 100, (out_1[0]));
}

#include feldspar.h

void iir( signed int var0_0_0, signed int var0_0_1[10], signed int var0_1_0, signed int var0_1_1[10], signed int var0_2_0, signed int var0_2_1[100], signed int *out_0, signed int out_1[100] )
{
signed int var3;
signed int var51_0;
signed int var51_1[100];
signed int var53[100];

var3 = (var0_2_0 - 1);
var51_0 = 0;
copy_arrayOf_signed_int(({}[0]), 100, (var51_1[0]));
{
int var4;

var4 = (var51_0 = var3);
while(var4)
{
signed int var12;
int var13;
signed int var14;
int var15;
signed int var16;
signed int var17;
signed int var22;
signed int var27_0;
signed int var27_1;
int var33;
signed int var34;
int var35;
signed int var36;
signed int var37;
signed int var42;
signed int var47_0;
signed int var47_1;
signed int var49[100];

var12 = (var51_0 + 1);
var13 = (var0_2_0 = var12);
if(var13)
{

var14 = var0_2_0;
}
else
{

var14 = var12;
 

Re: [Haskell-cafe] ANNOUNCE: feldspar-language

2009-11-09 Thread Emil Axelsson

Tom Hawkins skrev:

On Fri, Nov 6, 2009 at 6:28 AM, Emil Axelsson e...@chalmers.se wrote:


I'm trying to get realtime signal processing with Haskell for long. I make
progress, but slowly. Has Ericsson ever thought about using Haskell itself
for signal processing? (But I think they already have Erlang?)

No, using Haskell directly is not an option (at least with current compiler
technology). Their performance requirements are very high, and the signal
processors have quite limited memory, so putting a Haskell RTS on them
wouldn't work.


Atom may be another option.  Though it is not intended for high
performance DSP, we do use it for basic signal processing.  Here is an
IIR filter that is used is some fault detection logic on our
application:

-- | IIR filter implemented using direct form 2.
iirFilter :: Name - Float - [(Float, Float)] - E Float - Atom (E Float)
iirFilter name b0 coeffs x = do
  -- Create the filter taps.
  vs - mapM (\ i - float (name ++ show i) 0) [1 .. length coeffs]
  -- Cascade the filter taps together.
  mapM_ (\ (vA, vB) - vA == value vB) $ zip (tail vs) vs
  -- Calculate the input to the chain of taps.
  let w0 = sum ( x :  [ (value v) * Const (-a) | (v, (a, _)) - zip vs coeffs ])
  bs = b0 : (snd $ unzip coeffs)
  ws = w0 : map value vs
  us = [ w * Const b | (w, b) - zip ws bs ]
  head vs == w0
  -- Return the output.
  return $ sum us

http://hackage.haskell.org/package/atom


Nice!

One of our project members has been looking at Atom, not for numerical 
computations, but for real-time scheduling (which Feldspar should deal 
with eventually).


What kind of code (in terms of efficiency) does the above description 
compile to?


/ Emil

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


Re: [Haskell-cafe] ANNOUNCE: feldspar-language

2009-11-04 Thread Emil Axelsson
One thing I forgot to make clear in the announcement is that the 
language is still highly experimental, and some obvious things, such as 
complex numbers, are currently missing. So this first release should 
probably not be used for real applications.


However, while I don't know how autotuning works, I don't see why you 
shouldn't be able to code it in Feldspar a few releases from now. I 
don't know if it will be easy though :)


/ Emil



Warren Henning skrev:

I see that section 4.1 of the user guide -
http://feldspar.sourceforge.net/documents/language/FeldsparLanguage.html#htoc23
- includes an example involving autocorrelation.

Does this mean I could use Feldspare to easily build my own Autotune
program? I love T-Pain and Autotune the News!

Warren

On Tue, Nov 3, 2009 at 7:39 PM, Emil Axelsson e...@chalmers.se wrote:

I'm happy to announce the first release of Feldspar, which is an embedded
domain-specific language with associated code generator mainly targeting DSP
algorithms. The language is developed in cooperation by Ericsson, Chalmers
University and Eötvös Loránd University.

Feldspar stands for *F*unctional *E*mbedded *L*anguage for *DSP* and
*PAR*allelism.

The language front-end is available on Hackage:

 http://hackage.haskell.org/package/feldspar-language

The back-end C code generator will be uploaded and announced shortly. For
more information, see:

 http://feldspar.sourceforge.net/

/ Emil

___
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] ANNOUNCE: feldspar-language

2009-11-03 Thread Emil Axelsson
I'm happy to announce the first release of Feldspar, which is an 
embedded domain-specific language with associated code generator mainly 
targeting DSP algorithms. The language is developed in cooperation by 
Ericsson, Chalmers University and Eötvös Loránd University.


Feldspar stands for *F*unctional *E*mbedded *L*anguage for *DSP* and 
*PAR*allelism.


The language front-end is available on Hackage:

  http://hackage.haskell.org/package/feldspar-language

The back-end C code generator will be uploaded and announced shortly. 
For more information, see:


  http://feldspar.sourceforge.net/

/ Emil

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


Re: [Haskell-cafe] What *is* a DSL?

2009-10-07 Thread Emil Axelsson

Hi,

A DSL is just a domain-specific language. It doesn't imply any specific 
implementation technique.


An *embedded* DSL is a library implemented in a more general language, 
which has been designed to give the feeling of a stand-alone language. 
Still nothing about implementation.


A *shallow embedding* of a DSL is when the evaluation is done 
immediately by the functions and combinators of the DSL. I don't think 
it's possible to draw a line between a combinator library and a 
shallowly embedded DSL.


A *deep embedding* is when interpretation is done on an intermediate 
data structure.


/ Emil



Günther Schmidt skrev:

Hi all,


for people that have followed my posts on the DSL subject this question 
probably will seem strange, especially asking it now.


I have read quite a lot lately on the subject, most of it written by the 
great old ones, (come on guys you know whom I mean :)).


What I could gather from their papers was, that a DSL is basically 
something entirely abstract as such, ie. it allows you build and combine 
expressions in a language which is specific for your problem domain.
Irregardless of further details on how to do that, and there are quite a 
few, the crux as such is that they are abstract of meaning.


The meaning depends how you *evaluate* the expression, which can be in 
more than merely one way, which is where, as far as I understand it, the 
true power lies.



So, you might wonder, since I figured it out this far, why ask what a 
DSL is?


Because out there I see quite a lot of stuff that is labeled as DSL, I 
mean for example packages on hackage, quite useuful ones too, where I 
don't see the split of assembling an expression tree from evaluating it, 
to me that seems more like combinator libraries.


Thus:

What is a DSL?


Günther


___
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] Re: What *is* a DSL?

2009-10-07 Thread Emil Axelsson

Ben Franksen skrev:

minh thu wrote:

2009/10/7 Günther Schmidt gue.schm...@web.de:

I've informally argued that a true DSL -- separate from a good API --
should have semantic characteristics of a language: binding forms,
control structures, abstraction, composition. Some have type systems.


That is one requirement that confuses me, abstraction.

I thought of DSLs as special purpose languages, ie. you give your DSL
everything it needs for that purpose.

Why would it also need the ability to express even further abstractions,
it is supposed to *be* the abstraction.

Programming abstractions at the DSL level, not to further abstract
what the DSL covers.

Functions, for instance, are typical abstraction means offered by
programming languages. Even if your language is specific to some
domain, being able to create your own functions, and not only rely on
those provided by the DSL implementation, is important.

Imagine a (E)DSL for 3D programming (e.g. shading language): the
language is designed to fit well the problem (e.g. in this case, 3D
linear algebra, color operations, ...) but you'll agree it would be a
shame to not be able to provide your own functions.


But isn't one of the advantages of an _E_DSL that we can use the host
language (Haskell) as a meta or macro language for the DSL? I would think
that this greatly reduces the need to provide abstraction
facilities /inside/ the DSL. In fact most existing (and often cited
examples of) EDSLs in Haskell do not provide abstraction.


I would say that the DSL is what the user sees. In this view, I think 
it's correct to say that many (or most) DSLs need function abstraction. 
Whether or not the internal data structure has function abstraction is 
an implementation detail.


/ Emil


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


Re: [Haskell-cafe] QuickCheck Questions

2009-09-28 Thread Emil Axelsson
Not sure this is what you want, but I thought I'd mention Formal 
Specifications for Free:


  http://www.erlang.org/euc/08/1005Hughes2.pdf

(I wasn't able to find a better link. That talk is for Erlang, but 
people are working on this for Haskell QuickCheck.)


/ Emil



Yusaku Hashimoto skrev:

After a few more investigations, I can say

QuickCheck does:
- make easy to finding couter-cases and refactoring codes
- make easy to test some functions if they have good mathematical properties
- generate random test cases

But QuickCheck does *not*:
- help us to find good properties

So what I want to know is how to find good properties. Please let me
know how do you find QuickCheck properties. There are so many
tutorials or papers for using QuickCheck, but when I try to apply them
to my programming, I often miss properties in my codes.

Cheers
-nwn
___
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] QuickCheck Questions

2009-09-28 Thread Emil Axelsson

Pasqualino Titto Assini skrev:

Fantastic.

If I understand correctly it inductively derives equations that hold
for a set of examples.


AFAIU, it enumerates a set of terms and uses random testing to 
approximate an equivalence relation for these. The real trick, 
apparently, is in filtering out the interesting equations.



I am looking forward to see it in Haskell, who is working on the port?


John Hughes, Koen Claessen and Nick Smallbone. (At least.)

/ Emil

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


[Haskell-cafe] Strange type error (tfp package + GADTs)

2009-09-09 Thread Emil Axelsson

Hi Café,

Can anyone explain why `add1` is rejected in the code below (which uses 
the tfp package):




import Types.Data.Num

data A n
  where
A :: NaturalT n = Int - A n

getA :: A n - Int
getA (A n) = n

add1 :: NaturalT (m:+:n) = A m - A n - A (m:+:n)
add1 (A a) (A b) = A (a+b)

add2 :: NaturalT (m:+:n) = A m - A n - A (m:+:n)
add2 a b = A (getA a + getA b)

add3 :: NaturalT (m:+:n) = A m - A n - A (m:+:n)
add3 (A a) _ = A a



`add2` and `add3` are accepted. As far as I can see, `add2` is 
equivalent to `add1` except that it delegates the pattern matching to 
the function `getA`. If I only pattern match on one of the arguments, as 
in `add3`, things are also fine.


Thanks!

/ Emil


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


Re: [Haskell-cafe] Strange type error (tfp package + GADTs)

2009-09-09 Thread Emil Axelsson

I forgot to say that I'm using GHC 6.10.1.

Also, the code requires

{-# LANGUAGE FlexibleContexts, GADTs, TypeOperators #-}

/ Emil



Emil Axelsson skrev:

Hi Café,

Can anyone explain why `add1` is rejected in the code below (which uses 
the tfp package):




import Types.Data.Num

data A n
  where
A :: NaturalT n = Int - A n

getA :: A n - Int
getA (A n) = n

add1 :: NaturalT (m:+:n) = A m - A n - A (m:+:n)
add1 (A a) (A b) = A (a+b)

add2 :: NaturalT (m:+:n) = A m - A n - A (m:+:n)
add2 a b = A (getA a + getA b)

add3 :: NaturalT (m:+:n) = A m - A n - A (m:+:n)
add3 (A a) _ = A a



`add2` and `add3` are accepted. As far as I can see, `add2` is 
equivalent to `add1` except that it delegates the pattern matching to 
the function `getA`. If I only pattern match on one of the arguments, as 
in `add3`, things are also fine.


Thanks!

/ Emil


___
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] Nested Lists

2009-06-04 Thread Emil Axelsson

Hi Paul,

I don't have time to solve your actual problem, but I think it's doable 
using associated type families. I attach a module which I'm using in my 
current project that does things quite similar to what you're asking for.


For example:

  *Main replicateArray (3 : IntArr) 4
  [4,4,4]

  *Main replicateArray (4 : 3 : IntArr) 4
  [[4,4,4],[4,4,4],[4,4,4],[4,4,4]]

Hope it helps!

/ Emil



Paul Keir skrev:

Hi all,

If I have a list, and I'd like to convert it to a list of lists,
each of length n, I can use a function like bunch:

bunch _ [] = []
bunch n as = let (c,cs) = splitAt n as in c:bunch n cs

  bunch 8 [1..16]
[[1,2,3,4,5,6,7,8],[9,10,11,12,13,14,15,16]]

If I now want to do the same for the nested lists, I can compose
an application involving both map and bunch:

  map (bunch 4) . bunch 8 $ [1..16]
[[[1,2,3,4],[5,6,7,8]],[[9,10,11,12],[13,14,15,16]]]

and I can bunch the new length 4 lists again:

  map (map (bunch 2)) . map (bunch 4) . bunch 8 $ [1..16]
1,2],[3,4]],[[5,6],[7,8]]],[[[9,10],[11,12]],[[13,14],[15,16

Clearly there is a pattern here involving the bunch function and
latterly, three Int parameters; 2, 4 and 8. My question is, can I
create a function that will take such parameters as a list, and
give the same result, for example:

  f [2,4,8] [1..16]
1,2],[3,4]],[[5,6],[7,8]]],[[[9,10],[11,12]],[[13,14],[15,16

or perhaps:

  f [bunch 2, bunch 4, bunch 8] [1..16]
1,2],[3,4]],[[5,6],[7,8]]],[[[9,10],[11,12]],[[13,14],[15,16

I think it may not be possible because the type signature of f would
depend on the length of its list parameter; but I'm not sure.

-Paul




___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe
{-# LANGUAGE TypeFamilies #-}

class Storable a
  where
data Dimension a
type Element a

listDimensions :: Dimension a - [Int]
replicateArray :: Dimension a - Element a - a
makeSquare :: Dimension a - Element a - a - a

instance Storable Bool
  where
data Dimension Bool = BoolArr
type Element   Bool = Bool

listDimensions BoolArr   = []
replicateArray BoolArr e = e
makeSquare BoolArr _ = id

instance Storable Int
  where
data Dimension Int = IntArr
type Element   Int = Int

listDimensions IntArr   = []
replicateArray IntArr e = e
makeSquare IntArr _ = id

instance Storable a = Storable [a]
  where
data Dimension [a] = Int : Dimension a
type Element   [a] = Element a

listDimensions (n : ns)   = n : listDimensions ns
replicateArray (n : ns) a = replicate n (replicateArray ns a)
makeSquare (n : ns) a as  = as' ++ replicateArray (diff : ns) a
  where
as'  = take n (map (makeSquare ns a) as)
diff = n - length as'

infixr 5 :

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


[Haskell-cafe] ANN: Bookshelf

2009-05-13 Thread Emil Axelsson
This is the first release of Bookshelf, a simple document organizer with 
some wiki functionality. Documents in a directory tree are displayed as 
a set of HTML pages. Documents in Markdown format are converted to HTML 
automatically using Pandoc. The manual


  http://www.cs.chalmers.se/~emax/bookshelf/Manual.shelf.html

describes the full functionality.

Bookshelf is available on Hackage:

  http://hackage.haskell.org/cgi-bin/hackage-scripts/package/Bookshelf

or through its Darcs repository:

  http://www.cs.chalmers.se/~emax/darcs/Bookshelf/

I'm not aware of any bugs.

I hope it works on Windows, but I haven't tested.

Cheers,

/ Emil

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


Re: [Haskell-cafe] ANN: Bookshelf

2009-05-13 Thread Emil Axelsson
I've added a missing source file (and the documentation files) to 
Hackage. Hope it works now...


Also, if anyone tries it on Windows, please let me know if it works. If 
not, patches are welcome.


/ Emil



Emil Axelsson skrev:
This is the first release of Bookshelf, a simple document organizer with 
some wiki functionality. Documents in a directory tree are displayed as 
a set of HTML pages. Documents in Markdown format are converted to HTML 
automatically using Pandoc. The manual


  http://www.cs.chalmers.se/~emax/bookshelf/Manual.shelf.html

describes the full functionality.

Bookshelf is available on Hackage:

  http://hackage.haskell.org/cgi-bin/hackage-scripts/package/Bookshelf

or through its Darcs repository:

  http://www.cs.chalmers.se/~emax/darcs/Bookshelf/

I'm not aware of any bugs.

I hope it works on Windows, but I haven't tested.

Cheers,

/ Emil

___
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] Re: ANN: Bookshelf

2009-05-13 Thread Emil Axelsson

m...@justinbogner.com skrev:

Emil Axelsson e...@chalmers.se writes:

This is the first release of Bookshelf, a simple document organizer
with some wiki functionality. Documents in a directory tree are
displayed as a set of HTML pages. Documents in Markdown format are
converted to HTML automatically using Pandoc. The manual

  http://www.cs.chalmers.se/~emax/bookshelf/Manual.shelf.html

describes the full functionality.


It would probably be a good idea to include the markdown functionality
in your demonstration, since it's one of the more interesting
features. This looks pretty neat though, good work!


But did you see that the manual itself was generated from markdown? At 
the top of the page, there's a link to the source:


  http://www.cs.chalmers.se/~emax/bookshelf/Manual.shelf

Anyway, I added some minimal markdown demonstration to the file 
Documentation/Test/Notes.shelf. If you have any suggestions, let me know.


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


Re: [Haskell-cafe] Code Golf

2009-04-15 Thread Emil Axelsson

Sorry, I misread the task :)

/ Emil



Emil Axelsson skrev:

Why not:

  diag = [(x, sum-x) | sum - [2..], x - [1 .. sum-1]]

/ Emil



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


Re: [Haskell-cafe] Code Golf

2009-04-15 Thread Emil Axelsson

Why not:

  diag = [(x, sum-x) | sum - [2..], x - [1 .. sum-1]]

/ Emil



MigMit skrev:

If I understand the problem correctly...

Prelude let diag = concat . diags where diags ((x:xs):xss) = [x] : 
zipWith (:) xs (diags xss)

Prelude take 10 $ diag [[ (m,n) | n - [1..]] | m - [1..]]
[(1,1),(1,2),(2,1),(1,3),(2,2),(3,1),(1,4),(2,3),(3,2),(4,1)]

Sebastian Fischer wrote on 15.04.2009 14:32:

Fancy some Codegolf?

I wrote the following function for list diagonalization:

  diag l = foldr (.) id ((sel l . flip sel) ((:[]).(:))) []
   where
sel = foldr (\a b c - id : mrg (a c) (b c)) (const []) . map 
(flip id)

 
mrg [] ys = ys
mrg xs [] = xs
mrg (x:xs) (y:ys) = (x.y) : mrg xs ys

Self explanatory, isn't it? Here is a test case:

*Main take 10 $ diag [[ (m,n) | n - [1..]] | m - [1..]]
[(1,1),(1,2),(2,1),(1,3),(2,2),(3,1),(1,4),(2,3),(3,2),(4,1)]

I was trying to golf it down [^1] but my brain explodes. If you 
succeed in reducing keystrokes, I'd be happy to know!


Cheers,
Sebastian

[^1]: http://codegolf.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

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


[Haskell-cafe] Haskell tutorial for pseudo users?

2009-02-02 Thread Emil Axelsson

Hello,

Are there any Haskell tutorials suitable for people who don't (and 
possibly don't want to) know Haskell, but just want to use an embedded 
language that happens to be in Haskell?


Such a tutorial would focus on using libraries rather than defining 
them. For example, it might explain how to interpret a type signature 
involving type classes, but not how to write one's own type class.


Thanks,

/ Emil

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


Re: [Haskell-cafe] Haskell tutorial for pseudo users?

2009-02-02 Thread Emil Axelsson

Hi Deniz,

Deniz Dogan skrev:

I don't think it's a good idea (or even possible) to use a Haskell
library without knowing anything about Haskell or functional
programming. However, it shouldn't take too long to learn the very


Well, I guess I was asking for a tutorial which covers everything except
the parts that are not normally relevant for a DSEL user. For example, I
would expect the following to be left out:

  * Definition of data types and classes
  * Laziness
  * Monad internals
  * IO
  * etc.

Things that I think should be covered:

  * Polymorphism
  * Higher-order functions
  * Lists
  * Recursion
  * Monadic combinators
  * etc.

Of course, the requirements may vary from case to case, but you get the
idea.


Take some the time to
read the parts that are relevant to you in e.g. Learn You a Haskell
for Great Good (http://learnyouahaskell.com/)


Seems like a nice and gentle tutorial, somewhat like what I imagined.
However, it also seems a bit too high school-oriented for the audience
I currently have in mind :)

/ Emil (who may try to write this tutorial himself at some point)


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


Re: [Haskell-cafe] Haskell tutorial for pseudo users?

2009-02-02 Thread Emil Axelsson
Ah, that's nice! I never actually looked at your Cheat Sheet before 
(thought it would be much shorter and not very useful :) ).


I will definitely forward this to the people in our project.

Still on the lookout for a DSEL tutorial though...

/ Emil



Justin Bailey skrev:

It's not a tutorial but it covers all the relvant portions you asked
about. Download the package, unzip it and you'll find my Haskell
Cheat Sheet PDF inside:

http://hackage.haskell.org/cgi-bin/hackage-scripts/package/CheatSheet



On Mon, Feb 2, 2009 at 6:35 AM, Emil Axelsson e...@chalmers.se wrote:

Hello,

Are there any Haskell tutorials suitable for people who don't (and possibly
don't want to) know Haskell, but just want to use an embedded language that
happens to be in Haskell?

Such a tutorial would focus on using libraries rather than defining them.
For example, it might explain how to interpret a type signature involving
type classes, but not how to write one's own type class.

Thanks,

/ Emil

___
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] ANN: Wired 0.2

2009-01-26 Thread Emil Axelsson

There is now a new release of Wired available:

  http://hackage.haskell.org/cgi-bin/hackage-scripts/package/Wired

The most important news in this release is that it now contains a 45nm
cell library, which means that you can use Wired to create and analyze
modern VLSI designs[*] today!

However...

Wired is still in the experimentation phase, but is slowly stabilizing.
The current status is further explained in the package text. There's
very little documentation (basically only a few examples), so I expect
it to be quite hard to use if you haven't seen it before. I hope to
improve the documentation in the future. Feel free to mail me questions
meanwhile.

/ Emil


[*] Unfortunately, while the 45nm library is realistic, it's not based
on any actual process that can be fabricated. Contact me if you have
access to any real cell library and are interested in using it with Wired.


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


Re: [Haskell-cafe] about the concatenation on a tree

2008-12-31 Thread Emil Axelsson

I'm not working, but still checking mail.

If you don't care about balancing the tree or the order of elements, you can 
just use


  Branch :: Tree a - Tree a - Tree a

as a concatenation operator. Check with GHCi to see that the Branch constructor 
actually has the above type.


/ Emil



Max cs skrev:
hi all, not sure if there is someone still working during holiday like 
me : )
 
I got a little problem in implementing some operations on tree.
 
suppose we have a tree date type defined:
 
data Tree a = Leaf a | Branch (Tree a) (Tree a)
 
I want to do a concatenation on these tree just like the concat on list.

Anyone has idea on it? or there are some existing implementation?
 
Thank you and Happy New Year!
 
regards,

Max




___
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] How to think about this? (profiling)

2008-12-16 Thread Emil Axelsson
This is actually a perfect case for lazy immutable arrays, if you use a circular 
program:



import Data.Array

foo' :: Array Int Int - Int - Int
foo' arr 0 = 0
foo' arr 1 = 1
foo' arr 2 = 2
foo' arr n = arr!(n-1) + arr!(n-2) + arr!(n-3)

foo :: Int - Int
foo n = arr ! n
  where
assocs = [(i, foo' arr i) | i - [0..n]]
arr= array (0,n) assocs


But I haven't checked its performance against your version, so I don't know how 
good it is.


/ Emil



Magnus Therning skrev:

On Tue, Dec 16, 2008 at 12:14 PM, Lemmih lem...@gmail.com wrote:

You could use a Map or a mutable array. However, this kind of problem
comes up a lot less often than you'd think.


Well, I happen to have  a problem just like it right now, hence my
interest :-)  In order to better understand the different options I
thought I'd look at solving simpler problems with similar shape.

Thanks for pointing me in the direction of mutable arrays, I haven't
explored those before.

/M



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


[Haskell-cafe] Exact parsing of decimal numbers

2008-12-09 Thread Emil Axelsson

Hello,

I don't know enough about the RealFrac class to answer this myself:

Can I be sure that

  Numeric.readFloat :: ReadS Rational

never exhibits any rounding errors?

Thanks,

/ Emil

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


Re: [Haskell-cafe] Combining licences

2008-12-01 Thread Emil Axelsson

Henning Thielemann skrev:

On Mon, 1 Dec 2008, Emil Axelsson wrote:

Or perhaps it's better to put the cell library in its own package? I'm 
a bit reluctant to do this, because it means that Wired will be 
essentially useless on its own.


It's more the question, whether a Haskell wrapper to the cell library is 
useful on its own. I assume yes, and thus it sounds like a good idea to 
make separate package for a cell library wrapper.


Well, not really. It's not a Haskell wrapper in the normal sense where you 
make a Haskell API around some code in another language. A cell library is a 
bunch of cell models in various formats. For example, a VHDL file gives the 
logical models, and another file contains tables with timing data. Wired has its 
own way of modeling cells (a number of classes), and what I've done is to 
translate the cell library data to Wired's model. So if I make it a separate 
package, it would have to depend on Wired.


Of course, it still makes sense to have cell libraries as separate packages (I 
don't want to include every future cell lib in Wired). But I would like at least 
one cell lib to be shipped together with Wired.


/ Emil

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


[Haskell-cafe] Combining licences

2008-11-30 Thread Emil Axelsson

Hello,

I know very little about licensing, so I'm hoping to get some advice from you 
guys.

In the next release of Wired, I plan to include an open-source standard cell 
library (or rather data derived from it). This cell library has a custom license 
(found at the bottom of http://www.nangate.com/openlibrary). It appears to be 
very permissive, but it states that the license text must be included in all 
copies of the Library, in whole or in part, and all derivative works of the 
Library. Wired itself is BSD3-licensed.


How do I arrange this in the package? Can I still have a BSD3 license for Wired? 
Where do I put the respective license texts? Any other things I should have in mind?


Or perhaps it's better to put the cell library in its own package? I'm a bit 
reluctant to do this, because it means that Wired will be essentially useless on 
its own.


Thanks,

/ Emil

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


[Haskell-cafe] FFI and GHCi

2008-10-21 Thread Emil Axelsson

Hi,

I'm making my first attempt at using some C code in my Haskell program. I need 
it because I have a large amount of small constant tables, and GHC takes ages to 
compile the if I use ordinary lists (and the object file gets huge). If there's 
any way of achieving this without going to C, I'd be interested to know.


My question is about how to compile a library that contains C code. At the end 
of this message is a simple example of an 'increase' function. To compile, I run


  ghc Increase.hs --make -o increase increase.c

and everything works as expected. But then when I want to load the example in 
GHCi, I need to give the object file at the command line


  ghci Increase increase.o

or I get unknown symbol `increase' when I try to run main. It feels a bit 
awkward to have to list the object files every time I want to run GHCi. Is there 
any way of avoiding that? There must be, because if I install the files as a 
Cabal library, I can fire up GHCi without mentioning any object files. But I 
don't want to go through cabal every time I want test some part of my code.


Thanks for any help,

/ Emil





increase.h:

  int increase(int x);



increase.c:

  #include increase.h

  int increase(int x) {
return x+1;
  }



Increase.hs:

  {-# INCLUDE increase.h #-}
  {-# LANGUAGE ForeignFunctionInterface #-}

  import Foreign.C

  foreign import ccall increase.h increase inc :: CInt - CInt

  main = print (inc 2, inc 20)




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


Re: [Haskell-cafe] FFI and GHCi

2008-10-21 Thread Emil Axelsson
I thought so too, but didn't find anything that seemed to work. One thing that 
perhaps could work would be to set the -l flag from the .ghci file. But when I 
tried giving -lincrease on the command line, apparently GHC expects to find a 
file named libincrease.so, which apparently is not the same as the existing 
increase.o (I tried renaming it :) ).


/ Emil



Corey O'Connor skrev:

I would think there is a command you can embed in the .ghci file that
would automate the loading of the object files. But I didn't see one
on a quick scan of the manual:
http://www.haskell.org/ghc/docs/latest/html/users_guide/ghci-dot-files.html

-Corey O'Connor



On Tue, Oct 21, 2008 at 9:10 AM, Emil Axelsson [EMAIL PROTECTED] wrote:

Hi,

I'm making my first attempt at using some C code in my Haskell program. I
need it because I have a large amount of small constant tables, and GHC
takes ages to compile the if I use ordinary lists (and the object file gets
huge). If there's any way of achieving this without going to C, I'd be
interested to know.

My question is about how to compile a library that contains C code. At the
end of this message is a simple example of an 'increase' function. To
compile, I run

 ghc Increase.hs --make -o increase increase.c

and everything works as expected. But then when I want to load the example
in GHCi, I need to give the object file at the command line

 ghci Increase increase.o

or I get unknown symbol `increase' when I try to run main. It feels a bit
awkward to have to list the object files every time I want to run GHCi. Is
there any way of avoiding that? There must be, because if I install the
files as a Cabal library, I can fire up GHCi without mentioning any object
files. But I don't want to go through cabal every time I want test some part
of my code.

Thanks for any help,

/ Emil





increase.h:

 int increase(int x);



increase.c:

 #include increase.h

 int increase(int x) {
   return x+1;
 }



Increase.hs:

 {-# INCLUDE increase.h #-}
 {-# LANGUAGE ForeignFunctionInterface #-}

 import Foreign.C

 foreign import ccall increase.h increase inc :: CInt - CInt

 main = print (inc 2, inc 20)




___
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] Functional dependencies and incoherent instances

2008-10-08 Thread Emil Axelsson

I think the technique described at

  http://haskell.org/haskellwiki/GHC/AdvancedOverlap

may give you what you want. I've never tried it myself though.

/ Emil



Tobias Bexelius skrev:

Yeah, I realized that.

But heres where I would like the undecidable incoherent instances to kick in, 
i.e. as long as I haven't got any NumVec instances GHC should be able to choose 
only one of the Mult instances. Or do I have too much faith in the 
-fallow-incoherent-instances flag now? :/

I would like to be able to write something like

instance (Vec a x, -Num (a x)) = Mult (a x) (a x) x where (*.) = dot

where -Num (a x) means that (a x) must not be an instance of Num. Can I express 
this in some way?

Regards
Tobias


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


Re: [Haskell-cafe] Hackage Build Failures

2008-10-01 Thread Emil Axelsson

Hi Cetin!

Glad to see at least one person trying my package :)

The error comes from using QuickCheck 2, which happens to also use the operator 
(). I can see two ways to solve the problem:


(1) Add  2 after QuickCheck in the Wired.cabal file.

(2) Add hiding (()) after import Test.QuickCheck in 
Data/Hardware/Internal.hs

I guess this means you can't use cabal-install...?

Does anybody know the best way to avoid this problem without manual 
intervention? Or should I just require people to use QuickCheck 2?


PS. Cetin, please let me know if you have any questions regarding Wired. I'm 
slowly working on enhancing the library, and I'll soon upload a version with 
timing analysis and a DEF backend in.


/ Emil



Cetin Sert skrev:

Hi,

what is the best action to take if a package from hackage fails to 
build? Is there a recommended/established common way to deal with build 
failures/runtime bugs etc.?


For example:

[EMAIL PROTECTED]:~/Links/Elite/ac cabal install wired
Resolving dependencies...
Downloading Wired-0.1.1...
Configuring Wired-0.1.1...
Preprocessing library Wired-0.1.1...
Building Wired-0.1.1...
[ 1 of 21] Compiling Data.Hardware.Internal ( Data/Hardware/Internal.hs, 
dist/build/Data/Hardware/Internal.o )


Data/Hardware/Internal.hs:198:15:
Ambiguous occurrence `'
It could refer to either `Data.Hardware.Internal.', defined at 
Data/Hardware/Internal.hs:129:4
  or `Test.QuickCheck.', imported from 
Test.QuickCheck at Data/Hardware/Internal.hs:11:0-21

cabal: Error: some packages failed to install:
Wired-0.1.1 failed during the building phase. The exception was:
exit: ExitFailure 1

Regards,
CS




___
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] Hackage Build Failures

2008-10-01 Thread Emil Axelsson

Stephan Friedrichs skrev:

Emil Axelsson wrote:

[...]

The error comes from using QuickCheck 2, which happens to also use the 
operator (). I can see two ways to solve the problem:


(1) Add  2 after QuickCheck in the Wired.cabal file.

(2) Add hiding (()) after import Test.QuickCheck in 
Data/Hardware/Internal.hs


Emil,

my suggestion is: Please use alternative (2), at least if there are no 
further problems with quickcheck 2! Otherwise, depending on quickcheck 
2 just introduces unnecessary package incompatibilities.


Hi Stephan,

Option (1) was only meant as a temporary solution for Cetin. It just occurred 
that the obvious solution to make both QC1 and QC2 users happy is to have an 
explicit import list rather than hiding () (there are no further problems with 
QC2). I'll do this until QC2 is standard in GHC.


/ Emil


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


[Haskell-cafe] ANNOUNCE: Wired 0.1.1

2008-08-27 Thread Emil Axelsson

Hello,

This is to announce the first release of the hardware description library Wired. 
Wired can be seen as an extension to Lava that targets (not exclusively) 
semi-custom VLSI design. A particular aim of Wired is to give the designer more 
control over the routing wires' effects on performance.


The only working backends in this version are simulation and verification 
(through Lava), and generation of postscript layouts. Soon, there will also be 
static timing analysis and DEF file generation. The DEF format is accepted by 
most tools for physical design.


Wired is available from Hackage:

  http://hackage.haskell.org/cgi-bin/hackage-scripts/package/Wired

or using Darcs:

  darcs get http://www.cs.chalmers.se/~emax/darcs/Wired/

There is also a homepage at:

  http://www.cs.chalmers.se/~emax/wired/index.html

Comments, questions, patches are welcome.

Cheers,

/ Emil

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


Re: [Haskell-cafe] Why doesn't this work?

2008-08-24 Thread Emil Axelsson

BTW, this is a case where it may be more convenient to use forM:

 forM ps $ \pix - do
   particle - read_grid g pix
   return $ fn particle

(untested...)

forM is just another way of saying (flip mapM).

/ Emil



Andrew Coppin skrev:

colour_grid :: (Particle - IO ()) - Grid ph - IO ()
colour_grid fn g = sequence_ $ runST $ do
 ps - grid_coords g

 mapM
   (\pix - do
 particle - read_grid g pix
 return $ fn particle
   )
   ps

When I attempt to run this, GHCi just gives me a very cryptic type 
checker error. I can't figure out what's wrong here. As far as I can 
tell, this should run...


___
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] Help with associated types

2008-04-21 Thread Emil Axelsson
Thanks for the explanation! I didn't realize associate data types were different 
in that respect, but it makes sense to me now.


I think associated data types seem too heavy-weight for my application. And 
anyway, just thinking about this made me simplify my previous solution to a 
three-parameter class, which makes things a lot nicer.


/ Emil



On 2008-04-19 14:57, Niklas Broberg wrote:

Hi Emil,

On 4/17/08, Emil Axelsson [EMAIL PROTECTED] wrote:

Hello!

 I'm trying to rewrite some FD classes to use associated types instead. The
Port class is for type structures whose leaves have the same type:

  class Port p
where
  type Leaf   p
  type Struct p
  toList   :: p - [Leaf p]
  fromList :: [Leaf p] - p

 (Leaf p) gives the leaf type, and (Struct p) gives a canonical
representation of the structure regardless of leaf type. Here we just
instantiate two leaf types:

  instance Port Int
where
  type Leaf   Int = Int
  type Struct Int = ()
  toList   a  = [a]
  fromList [a]= a

  instance Port Bool
where
  type Leaf   Bool = Bool
  type Struct Bool = ()
  toList   a   = [a]
  fromList [a] = a

 There's also a function for mapping over ports:

  mapPort ::
  ( Port pa
  , Port pb
  , Struct pa ~ Struct pb
  ) =
(Leaf pa - Leaf pb) - (pa - pb)

  mapPort f = fromList . map f . toList

 The equality constraint makes sure that we're mapping between equal
structures. When I try to run this, I get:

  *Main mapPort even (5::Int)

  interactive:1:8:
  No instance for (Integral (Leaf Int))
  ...



the problem here is that Leaf p doesn't determine p, e.g. there can be
many different types p for which Leaf p = Int. It has nothing to do
with the Struct type.


 What's the easiest way to encode that pb can be inferred from (Struct pb)
and (Leaf pb)?


If you want the dependency Leaf p - p then Leaf needs to be
injective, i.e. you need to use an accociated datatype rather than
just a type. Here's a sketch that shows this:

 class Port p
  where
data Leaf  p  -- note the use of data here
type Struct p
toList   :: p - [Leaf p]
fromList :: [Leaf p] - p

 instance Port Int
  where
newtype Leaf Int = IntLeaf Int
type Struct Int = ()
toList   a  = [IntLeaf a]
fromList [IntLeaf a]= a

 instance Port Bool
  where
newtype Leaf Bool = BoolLeaf Bool
type Struct Bool = ()
toList   a   = [BoolLeaf a]
fromList [BoolLeaf a] = a

mapPort ::
( Port pa
, Port pb
, Struct pa ~ Struct pb
) =
  (Leaf pa - Leaf pb) - (pa - pb)

 mapPort f = fromList . map f . toList

The problem now is of course that the arguments to f will now be a lot
more complex, since the Leaf type is more complex. So to call this you
would have to say

*Port let f (IntLeaf n) = BoolLeaf (even n) in mapPort f 1
False

Not very pretty, but that's the way it goes if you want that
dependency. So in the general case,


If I have a class with some dependencies, say

 a - ..., b c - ...

Is it possible to encode this using associated types without having all of a, b
and c as class parameters?


Yes it can be done, if you use associated *datatypes* instead of
associated types. But as you can see, it introduces extra overhead.

Cheers,

/Niklas

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


Re: [Haskell-cafe] Help with associated types

2008-04-18 Thread Emil Axelsson

After some thinking I think I can put my question much simpler:

If I have a class with some dependencies, say

  a - ..., b c - ...

Is it possible to encode this using associated types without having all of a, b 
and c as class parameters?


It seems to me that it's not possible. And if so, I'll simply drop this idea 
(was hoping that ATs would allow me to have fewer class parameters).


Thanks,

/ Emil


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


[Haskell-cafe] Help with associated types

2008-04-17 Thread Emil Axelsson

Hello!

I'm trying to rewrite some FD classes to use associated types instead. The Port 
class is for type structures whose leaves have the same type:


  class Port p
where
  type Leaf   p
  type Struct p
  toList   :: p - [Leaf p]
  fromList :: [Leaf p] - p

(Leaf p) gives the leaf type, and (Struct p) gives a canonical representation of 
the structure regardless of leaf type. Here we just instantiate two leaf types:


  instance Port Int
where
  type Leaf   Int = Int
  type Struct Int = ()
  toList   a  = [a]
  fromList [a]= a

  instance Port Bool
where
  type Leaf   Bool = Bool
  type Struct Bool = ()
  toList   a   = [a]
  fromList [a] = a

There's also a function for mapping over ports:

  mapPort ::
  ( Port pa
  , Port pb
  , Struct pa ~ Struct pb
  ) =
(Leaf pa - Leaf pb) - (pa - pb)

  mapPort f = fromList . map f . toList

The equality constraint makes sure that we're mapping between equal structures. 
When I try to run this, I get:


  *Main mapPort even (5::Int)

  interactive:1:8:
  No instance for (Integral (Leaf Int))
  ...

because as it stands, mapPort is not able to infer (pb = Bool) from (Struct pb = 
()) and (Leaf pb = Bool).


What's the easiest way to encode that pb can be inferred from (Struct pb) and 
(Leaf pb)?


Thanks,

/ Emil




PS.

I used to have a class

  class SameStruct pa a pb b | pa - a, pa b - pb, pb - b, pb a - pa

In the example above, we'd have pa=Int and b==Bool, so the second dependeny 
would infer pb=Bool.



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


[Haskell-cafe] Template Haskell -- when are things evaluated?

2008-03-13 Thread Emil Axelsson

Hello all!

Up until yesterday I thought I understood the basics of Template Haskell, but 
now I'm a little confused. Consider the following code


module A
  where
a1 = [| (2::Int) + 2 |]

a2 = let x = (2::Int) + 2 in [| x |]

a3 = [| y |]
  where
y = (2::Int) + 2

z = (2::Int) + 2

a4 = [| z |]

module B
  where
import A

a1S = $a1
a2S = $a2
a3S = $a3
a4S = $a4

I'd have thought that in all four cases the addition was evaluated at 
compile-time, but compiling with -ddump-splices reveals that this is only the 
case for a2 and a3. Is there a general reliable rule for when things are evaluated?


Thanks,

/ Emil

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


Re: [Haskell-cafe] Template Haskell -- when are things evaluated?

2008-03-13 Thread Emil Axelsson
Aha, I guess I thought for a while that [|x|] and  lift x  where the same thing. 
Having thought too much about partial evaluation lately, I forgot that the main 
purpose of quoting is to get the unevaluated AST.


I'll just use lift in the future then (for partial evalutation).

Thanks, Alfonso!

/ Emil



On 2008-03-13 09:49, Alfonso Acosta wrote:

Hi Emil,

Your  problem is related to how are things evaluated not when. The
short answer is: if you want to make sure an expression is evaluated
before you lift it, don't use quasiquotes, call
Language.Haskell.TH.lift

On Thu, Mar 13, 2008 at 9:00 AM, Emil Axelsson [EMAIL PROTECTED] wrote:

 a1 = [| (2::Int) + 2 |]


You are lifting the expression AST, not its evaluation. a1 = lift
((2::Int) + 2) would work as you want.



 a2 = let x = (2::Int) + 2 in [| x |]


here you are enclosing a local variable in quasiquotes and, thus, [| x
|] is equivalent to lift x


 a3 = [| y |]
   where
 y = (2::Int) + 2


Same as in a2, y is local. Therefore [| y |] is equivalent to lift y


 z = (2::Int) + 2

 a4 = [| z |]


z is a global variable and [| z |] is lifted to a variable expression
(i.e. a4 is equivalent to varE 'z  )

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


Re: [Haskell-cafe] Template Haskell -- when are things evaluated?

2008-03-13 Thread Emil Axelsson

I'm reading the following rule from your answer:

[|exp|] normally returns the unevaluated AST of exp. However, if exp contains 
local variables, these are lifted using Language.Haskell.TH.lift (i.e. evaluated 
before lifting).


Is that correct?

/ Emil



On 2008-03-13 09:49, Alfonso Acosta wrote:

Hi Emil,

Your  problem is related to how are things evaluated not when. The
short answer is: if you want to make sure an expression is evaluated
before you lift it, don't use quasiquotes, call
Language.Haskell.TH.lift

On Thu, Mar 13, 2008 at 9:00 AM, Emil Axelsson [EMAIL PROTECTED] wrote:

 a1 = [| (2::Int) + 2 |]


You are lifting the expression AST, not its evaluation. a1 = lift
((2::Int) + 2) would work as you want.



 a2 = let x = (2::Int) + 2 in [| x |]


here you are enclosing a local variable in quasiquotes and, thus, [| x
|] is equivalent to lift x


 a3 = [| y |]
   where
 y = (2::Int) + 2


Same as in a2, y is local. Therefore [| y |] is equivalent to lift y


 z = (2::Int) + 2

 a4 = [| z |]


z is a global variable and [| z |] is lifted to a variable expression
(i.e. a4 is equivalent to varE 'z  )

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


Re: [Haskell-cafe] I love purity, but it's killing me.

2008-02-07 Thread Emil Axelsson

I know of a few of ways to express sharing in a pure language:

1) Observable sharing, which, in general, is unsafe.

  http://www.cs.chalmers.se/~koen/pubs/entry-asian99-lava.html

2) Using Template Haskell

  http://www.dcs.gla.ac.uk/publications/PAPERS/7524/EmbedHDLinTH.ps

3) Matthew Naylor has done some work on expressible sharing, which has 
advantages over both methods above. I don't have any reference though...


4) Use a monad (but I'm sure this is what you're trying to avoid).

/ Emil



On 2008-02-08 07:33, Tom Hawkins wrote:

I've been programming with Haskell for a few years and love it.  One
of my favorite applications of Haskell is using for domain specific
languages.  However, after designing a handful of DSLs, I continue to
hit what appears to be a fundamental hurdle -- or at least I have yet
to find an adequate solution.

My DSLs invariably define a datatype to capture expressions; something
like this:

data Expression
  = Add Expression Expression
  | Sub Expression Expression
  | Variable String
  | Constant Int
  deriving Eq

Using the datatype Expression, it is easy to mass a collections of
functions to help assemble complex expressions, which leads to very
concise programs in the DSL.

The problem comes when I want to generate efficient code from an
Expression (ie. to C or some other target language).  The method I use
invovles converting the tree of subexpressions into an acyclic graphic
to eliminate common subexpressions.  The nodes are then topologically
ordered and assigned an instruction, or statement for each node.  For
example:

let a = Add (Constant 10) (Variable i1)
b = Sub (Variable i2) (Constant 2)
c = Add a b

would compile to a C program that may look like this:

  a = 10 + i1;
  b = i2 - 2;
  c = a + b;

The process of converting an expression tree to a graph uses either Eq
or Ord (either derived or a custom instance) to search and build a set
of unique nodes to be ordered for execution.  In this case a, then
b, then c.  The problem is expressions often have shared,
equivalent subnodes, which dramatically grows the size of the tree.
For example:

let d = Add c c
e = Add d d-- e now as 16 leaf nodes.

As these trees grow in size, the equality comparison in graph
construction quickly becomes the bottleneck for DSL compilation.
What's worse, the phase transition from tractable to intractable is
very sharp.  In one of my DSL programs, I made a seemingly small
change, and compilation time went from milliseconds to
not-in-a-million-years.

Prior to Haskell, I wrote a few DSLs in OCaml.  I didn't have this
problem in OCaml because each let expression was mutable, and I
could use the physical equality operator to perform fast comparisons.
Unfortunately, I have grown to love Haskell's type system and its lack
of side effects, and could never go back.

Is there anything that can be done to dramatically speed up
comparisons, or is there a better approach I can take to extract
common subexpressions?  I should point out I have an opportunity to
get Haskell on a real industrial application.  But if I can't solve
this problem, I may have to resort to far less eloquent languages.
:-(

Thanks for any and all help.

-Tom
___
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] Show instances for error messages (Was: Refactoring status)

2008-01-09 Thread Emil Axelsson

I think partial type signatures

  http://hackage.haskell.org/trac/haskell-prime/wiki/PartialTypeAnnotations

would allow that kind of tunneling. Is there any ongoing work on that?

/ Emil



Henning Thielemann skrev:

On Mon, 7 Jan 2008, Emil Axelsson wrote:


One approach to programming in Haskell, which I use all the time, is to write
the type signature before the function body. This means that if I'm trying to do
something strange, I will often be warned by the type checker even before I've
written the strange code.

But I've also been bitten by the problem of having to change a lot of type
signatures just because I want to e.g. show an overloaded variable.


... which is especially annoying if you need the Show instance for an
'error'.  Since 'error' denotes a programming error it should never be
evaluated and thus the Show instance is only for cases which must not
happen. Paradoxical. It would be interesting if it is possible to tunnel
Show class dictionaries through to an 'error' like IO is tunneled to
'trace'.
___
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] Refactoring status

2008-01-07 Thread Emil Axelsson
One approach to programming in Haskell, which I use all the time, is to write 
the type signature before the function body. This means that if I'm trying to do 
something strange, I will often be warned by the type checker even before I've 
written the strange code.


But I've also been bitten by the problem of having to change a lot of type 
signatures just because I want to e.g. show an overloaded variable.


/ Emil



On 2008-01-04 19:19, Peter Verswyvelen wrote:

Yes, sometimes it is neccerary to give an explicit type. But in so many
cases, type inference works fine no? What I usually do, is use the GHCi t:
command, copy/paste that in my code, and then make the type signature more
specific if it has to be. It's often funny to see how generic the code
really is :) 


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


Re: [Haskell-cafe] Show instances for error messages (Was: Refactoring status)

2008-01-07 Thread Emil Axelsson

The only possible definition of such a function is something like

  unsafeShow :: (forall a . Show a = a) - String
  unsafeShow a = show (a :: Bool)

right?

And you'd also need to coerce the argument type in order to use it:

  putStrLn $ unsafeShow $ unsafeCoerce True

Right?

Then a nicer definition might be

  unsafeShow :: Show a = a - b - String
  unsafeShow a b = show (unsafeCoerce b `asTypeOf` a)

Here is an example of how to use it to show an overloaded variable without 
changing the type signature:


  test :: Eq a = a - IO ()
  test a = putStrLn $ unsafeShow (undefined :: Int) a

Of course, this only works safely if a is an Int:

  *Main test (5 :: Int)
  5
  *Main test (5 :: Double)
  0



/ Emil



On 2008-01-07 12:56, Lutz Donnerhacke wrote:

* Henning Thielemann wrote:

happen. Paradoxical. It would be interesting if it is possible to tunnel
Show class dictionaries through to an 'error' like IO is tunneled to
'trace'.


unsafeShow :: (forall a . Show a = a) - String
___
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] Class deriving in GHC 6.8

2007-12-20 Thread Emil Axelsson

Hello all!

How come in GHC 6.6 I could to write


{-# OPTIONS_GHC -fglasgow-exts -fallow-undecidable-instances #-}
data Foo   = Foo deriving Show
data Bar c = Bar (c Foo) deriving Show


but in GHC 6.8.2 I get the error


No instance for (Show (c Foo))
  arising from the 'deriving' clause of a data type declaration
   at Ert.hs:3:0-37
Possible fix: add an instance declaration for (Show (c Foo))
When deriving the instance for (Show (Bar c))




Thanks,

/ Emil

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


Re: [Haskell-cafe] Class deriving in GHC 6.8

2007-12-20 Thread Emil Axelsson

After looking more closely at user's manual, I just found that the following 
works:


{-# OPTIONS_GHC -fglasgow-exts -fallow-undecidable-instances #-}
data Foo   = Foo deriving Show
data Bar c = Bar (c Foo)   


deriving instance Show (c Foo) = Show (Bar c)


/ Emil



On 2007-12-20 11:18, Emil Axelsson wrote:

Hello all!

How come in GHC 6.6 I could to write


{-# OPTIONS_GHC -fglasgow-exts -fallow-undecidable-instances #-}
data Foo   = Foo deriving Show
data Bar c = Bar (c Foo) deriving Show


but in GHC 6.8.2 I get the error


No instance for (Show (c Foo))
  arising from the 'deriving' clause of a data type declaration
   at Ert.hs:3:0-37
Possible fix: add an instance declaration for (Show (c Foo))
When deriving the instance for (Show (Bar c))




Thanks,

/ Emil

___
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] unification would give infinite type

2007-12-05 Thread Emil Axelsson
You usually don't need to worry about it. Just keep in mind that if you happen 
to get a strange type error concerning an (overloaded) function *without type 
signature*, it sometimes helps to add a signature.


/ Emil



On 2007-12-04 15:52, Rafael wrote:

I don't know about monomorphis restriction

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


Re: [Haskell-cafe] unification would give infinite type

2007-12-04 Thread Emil Axelsson

Hi,

Depending on what you want, you should either remove 'return' or change to 
'foldM' (from Control.Monad). If you choose the latter, you also need to add a 
type signature to f (because of the monomorphism restriction).


/ Emil



On 2007-12-04 14:43, Rafael wrote:

Hi... I give this error using hugs for the code:

---
f = foldl (\x y - add x y) 0 [1,2,3]
add x y = return (x + y)
---
I try:

f = foldl (\x y - counter x y) (return 0) [1,2,3]

but it dont solve,  and with ghci:


Occurs check: cannot construct the infinite type: b = m b
  Expected type: b
  Inferred type: m b
In the expression: add x y
In a lambda abstraction: \ x y - add x y


thnks.

att
Rafael
___
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] Re: FP design

2007-11-07 Thread Emil Axelsson

You mean:

  Jonh Hughes. The Design of a Pretty-printing Library.

:)

/ Emil



On 2007-11-07 05:16, apfelmus wrote:

  Paul Hudak. The Design of a Pretty-printing Library.



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


Re: [Haskell-cafe] Strictness leak

2007-10-30 Thread Emil Axelsson

You mean for the IO monad, right?

  take 10 $ execWriter $ sequence $ repeat $ tell ([3]::[Int])

/ Emil



On 10/30/2007 02:04 PM, Jeff Polakow wrote:


Hello,

   countIO :: String - String - Int - [a] - IO [a]
   countIO msg post step xs = sequence $ map unsafeInterleaveIO
  ((blank  outmsg (0::Int)  c):cs)
  where (c:cs) = ct 0 xs
output   = hPutStr stderr
blank= output ('\r':take 70 (repeat ' '))
outmsg x = output ('\r':msg++show x)  hFlush stderr
ct s ys = let (a,b) = splitAt (step-1) ys
  next  = s+step
  in case b of [b1] - map return a ++ [outmsg
  (s+step)  hPutStr stderr post  return b1]
   []   - map return (init a) ++
  [outmsg (s+length a)  hPutStr stderr post  return (last a)]
   _ - map return a ++ [outmsg s 
  return (head b)] ++ ct next (tail b)
 
  It wraps a list with IO operations, so that progress can be reported
  while evaluating the list elements.  Unfortunately, there seems to be
  a stricness leak here - and consequently, it does not work on an
  infinite list.
 
Besides anything else, sequence will diverge on an infinite list. This 
can be seen directly from the type:


sequence :: Monad m = [m a] - m [a]

It is necessary to compute all of the computations in the list before 
returning any of the pure resulting list.


-Jeff

---

This e-mail may contain confidential and/or privileged information. If you
are not the intended recipient (or have received this e-mail in error)
please notify the sender immediately and destroy this e-mail. Any
unauthorized copying, disclosure or distribution of the material in this
e-mail is strictly forbidden.




___
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] Selecting overlapping instances

2007-02-22 Thread Emil Axelsson

Hello!

I have a problem with overlapping instances for which I already know a 
workaround. However, I'm still curious to know if there isn't a simpler solution 
available. I have a feeling that -fallow-incoherent-instances might be the 
answer, but I can't get it to work.


In the code at the end of the message, (Block w n s e) is a representation of a 
geometrical block whose west-/north-/south-/eastern edge has type w/n/s/e 
respectively. (*||*) composes two blocks horizontally and (*=*) composes 
vertically. In this simplified example, there is only one primitive block -- 
unitBlock.


Now, I want to be able to make grids of unitBlock:s where the edges can have any 
type that can be obtained using (,) and (). This is what the Grid class attempts.


The program compiles fine until I add the test program


test :: Block ((),()) ((),()) ((),()) ((),())
test = grid


which raises an Overlapping instances error. What I would like is for the 
compiler to pick *either* of the two matching instances first, and then the 
other one, because in this particular case, it doesn't matter which one it picks 
first.


The workaround is to explicitly pick an order by giving the additional instance 
(requires -fallow-overlapping-instances):



instance ( Grid x1 y1
 , Grid x1 y2
 , Grid x2 y1
 , Grid x2 y2
 ) = Grid (x1,x2) (y1,y2)
  where
grid = grid *||* grid


Is there any way to make this work without adding this last instance?

Thanks!

/ Emil






data Block w n s e = Block

(*||*) :: Block w1 n1 s1 x - Block x n2 s2 e2 - Block w1 (n1,n2) (s1,s2) e2
(*||*) = undefined

(*=*) :: Block w1 x s1 e1 - Block w2 n2 x e2 - Block (w1,w2) n2 s1 (e1,e2)
(*=*) = undefined

unitBlock :: Block () () () ()
unitBlock = undefined

class Grid x y
  where
grid :: Block x y y x

instance Grid () ()
  where
grid = unitBlock

instance (Grid x1 y, Grid x2 y) = Grid (x1,x2) y
  where
grid = grid *=* grid

instance (Grid x y1, Grid x y2) = Grid x (y1,y2)
  where
grid = grid *||* grid



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


Re: [Haskell-cafe] Haskell as embedded DSL

2006-07-05 Thread Emil Axelsson

Joel Reymont skrev:


On Jul 5, 2006, at 3:07 PM, Niklas Broberg wrote:


Lava: http://www.cs.chalmers.se/~koen/Lava/


Excellent example, thank you Niklas!

Are you using QuickCheck for verification?



I assume you're asking if Lava (rather than Niklas) uses QuickCheck.

In Lava, you write properties in a style similar to QuickCheck props., but the 
actual verification is done by external tools. You still get the nice benefit of 
having description and verification within the same language.


About teaching Lava (and probably other Haskell DSLs) to non Haskellers, I think 
that higher-order functions (and the type errors you get when using them 
incorrectly) is what causes most confusion among our students. A minority of 
them also finds it hard to use recursion instead of loops. Luckily, they don't 
have to use monads...


I've been talking to a person at Intel who has been trying to teach their 
hardware designers to use a functional language (somewhat like Lava). This 
turned out to be much harder than expected, since the designers were so used to 
the imperative style. I'm not sure what the current status is, but they really 
have to make a trade-off between the time it takes to convert the designers 
and the quality (correctness/maintainability/performance/coding time/etc.) of 
the resulting code. It is important to show that functional programming has an 
advantage on the latter aspect (if that is the case).


/ Emil

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


  1   2   >