[Haskell-cafe] ANN: dnscache - caching DNS resolver

2010-11-24 Thread Ertugrul Soeylemez
Hello everybody,

I've just uploaded a caching DNS resolver library, which also includes a
command line utility for quick mass DNS resolution:

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

Although I've tested it throroughly it's still in beta phase.  Feel free
to play around with it.  Feedback is highly appreciated.

Thank you.


Greets,
Ertugrul


-- 
nightmare = unsafePerformIO (getWrongWife = sex)
http://ertes.de/


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


[Haskell-cafe] ANN: dnscache - caching DNS resolver

2010-11-24 Thread Ertugrul Soeylemez
Hello everybody,

(second try, since the first mail somehow didn't arrive)

I've just uploaded a caching DNS resolver library, which also includes a
command line utility for quick mass DNS resolution:

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

Although I've tested it throroughly it's still in beta phase.  Feel free
to play around with it.  Feedback is highly appreciated.

Thank you.


Greets,
Ertugrul


-- 
nightmare = unsafePerformIO (getWrongWife = sex)
http://ertes.de/


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


[Haskell-cafe] ANNOUNCE: Graphalyze-0.11.0.0 and SourceGraph-0.7.0.0

2010-11-24 Thread Ivan Lazar Miljenovic
I am pleased to announce the 0.7.0.0 release of my graph-theoretic
source code analysis tool SourceGraph [1], and the library it uses
Graphalyze 0.11.0.0 [2].

[1]: http://hackage.haskell.org/package/SourceGraph
[2]: http://hackage.haskell.org/package/Graphalyze

Changes in SourceGraph (apart from those resulting from improvements
to Graphalyze):

* Edge widths are now log-based rather than being the number of
function calls; this avoids having absurdly thick edges.

* Source files that were not able to be parsed are now listed both to
stderror and in the resulting report (thus helping you work out why
you're missing some code)

* Also builds with Cabal-1.10; whilst I do not currently have GHC 7
installed anywhere and thus can't test this, I know of no reason why
SourceGraph cannot be built with GHC 7 (unless it uses a library that
isn't buildable on GHC 7 that I have no control over).

Changes in Graphalyze:

* Legends can now contain text-only fields rather than just graphs;
also, the title of each legend is now displayed first rather than what
it describes.

* To fix a bug spotted by Han Joosten, the reports currently use
Posix-style path separators even on Windows (otherwise, HTML documents
produced on Windows were not in a state to be uploaded elsewhere).

-- 
Ivan Lazar Miljenovic
ivan.miljeno...@gmail.com
IvanMiljenovic.wordpress.com
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Derived type definition

2010-11-24 Thread Miguel Mitrofanov

 Well, you can resort to functional dependencies, I guess...

{-# LANGUAGE FlexibleInstances, FunctionalDependencies, MultiParamTypeClasses, 
UndecidableInstances #-}
module FunDeps where
data Rec a r = Rec a r
data RecNil = RecNil
data Wrapper a = Wrapper a
class Wrapped r w | r - w where i :: r - w
instance Wrapped RecNil RecNil where i RecNil = RecNil
instance Wrapped r w = Wrapped (Rec a r) (Rec (Wrapper a) w) where i (Rec a r) 
= Rec (Wrapper a) (i r)
type TTest = Rec Int (Rec String RecNil)
type TTestWrapped = Rec (Wrapper Int) (Rec (Wrapper String) RecNil)
a :: TTest
a = Rec 1 (Rec a RecNil)
f :: TTestWrapped - (Int, String)
f (Rec (Wrapper n) (Rec (Wrapper s) RecNil)) = (n, s)
r = f (i a)

...but that would be just an awkward way to do the same thing, so, my advice: 
don't. Type families are much nicer.

On the other hand, you could do your Rec type polimorphic in wrapper; 
assuming your real-life Wrapper is not just an identity, this would be worth considering:

{-# LANGUAGE KindSignatures #-}
module PolyM where
data Rec a r w = Rec (w a) (r w)
data RecNil (w :: * - *) = RecNil
data Wrapper a = Wrapper a -- in reality it should be something else
newtype Identity a = Identity a
class Wrapped r where i :: r Identity - r Wrapper
instance Wrapped RecNil where i RecNil = RecNil
instance Wrapped r = Wrapped (Rec a r) where i (Rec (Identity a) r) = Rec 
(Wrapper a) (i r)
type TTest = Rec Int (Rec String RecNil) Identity
type TTestWrapped = Rec Int (Rec String RecNil) Wrapper
a :: TTest
a = Rec (Identity 1) (Rec (Identity a) RecNil)
f :: TTestWrapped - (Int, String)
f (Rec (Wrapper n) (Rec (Wrapper s) RecNil)) = (n, s)
r = f (i a)

24.11.2010 12:24, kg пишет:

Ok, it's exactly what i hoped.

And I would like to know (for fun) if it's possible to do it without type 
family extension.
I've tried ... without success.

Thx.

On 11/22/2010 10:46 PM, Miguel Mitrofanov wrote:

Sure, it's possible with TypeFamilies. The following compiles OK:

{-# LANGUAGE TypeFamilies #-}
module TypeCalc where
data Rec a r = Rec a r
data RecNil = RecNil
data Wrapper a = Wrapper a
class TypeList t where
type Wrapped t
i :: t - Wrapped t
instance TypeList RecNil where
type Wrapped RecNil = RecNil
i RecNil = RecNil
instance TypeList r = TypeList (Rec a r) where
type Wrapped (Rec a r) = Rec (Wrapper a) (Wrapped r)
i (Rec a r) = Rec (Wrapper a) (i r)
type TTest = Rec Int (Rec String RecNil)
type TTestWrapped = Rec (Wrapper Int) (Rec (Wrapper String) RecNil)
a :: TTest
a = Rec 1 (Rec a RecNil)
f :: TTestWrapped - (Int, String)
f (Rec (Wrapper n) (Rec (Wrapper s) RecNil)) = (n, s)
r = f (i a) -- so, i a is of the type TTestWrapped.


On 22 Nov 2010, at 23:43, kg wrote:


Hi,

I've tried to simplify as much as possible my problem. Finally, I think I can 
resume it like that:

Suppose these following data types :
data Rec a r = Rec a r
data RecNil = RecNil
data Wrapper a = Wrapper a

Then, we can build the following type:
type TTest = Rec Int (Rec String RecNil)
or this type:
type TTestWrapped = Rec (Wrapper Int) (Rec (Wrapper String) RecNil)

Is it possible to build TTestWrapped from TTest ?


Thx in advance,
Antoine.

___
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] Another Quasi-Quotation question

2010-11-24 Thread jean-christophe mincke
Hello,

I am still playing with template-haskell...

I wonder, is there any reason why a quasiquoter cannot create haskell
statements and declarations in addition to expressions and patterns? Or more
generally create any legal Haskell syntax tree.

I.e Suppose I would like to create a quasiquoter for the C language (please,
imagine that it could be useful).

I could write sth such as :

[$c|

int a = 6;
int b = 7;
int c = a +b;

struct S { int x; int y}
|]

It could be nice to generate the appropriate haskell code:

a = 6
b= 7
c= a + b
data S = S {  x::Int; y:Int}
etc

That would allow to really embed any kind of language in a more or less easy
way into haskell, provided that code can be translated into legal haskell.

Is there anything that prevent these features.

Thank you

Regards

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


[Haskell-cafe] Re: [Haskell-beginners] Problem grouping a list

2010-11-24 Thread Aai
I don't know what this tuple is representing, but if you want to group you'll 
have to specify on 'what':

- the tuple,
- the fst or
- the snd

Here's a possibility with grouping on the fst

import Data.List
import Data.Ord
import Data.Function

groupAtoms ::
  (Float - Bool)
  - [(Float,Integer)]
  -  ([[(Float,Integer)]],[[(Float,Integer)]])
groupAtoms p = partition (p.sum. map fst). groupBy ((==)`on`fst). sortBy 
(comparing fst)


Use:

groupAtoms (=1.0) myList

If this is what you want: proper lists are in the fst of the result.





Hallo João Paulo Pizani Flor, je schreef op 23-11-10 18:23:

Hello dear Haskellers!

I've been a user and big fan of Haskell for a while, but only now I'm writing 
my first big project in Haskell (some thousands of lines of code perhaps). 
It's an interpreter for a programming language, the source code is music! Yes, 
sheet music! :D


OK, so my specific problem goes like this: I have a list of tuples
:t  myList
[ (Float, Integer) ]

And I want to group this list into a nested list
groupAtoms :: [ (Float,Integer) ]  -  [ [(Float,Integer)] ]

Of course, I want that the concatenation of the groups yield me the original 
list, i.e,  (foldl (++) [] . groupAtoms == id), and the criterion that defines 
a group is that:
The sum of the first elements in the tuples comprising the list must be 
greater than or equal to 1.0. That is, given a list of tuples, the boolean 
predicate deciding whether this list is a PROPER group (True) or TOO SMALL 
(False) is:

\g - sum (map fst g) =  1.0


Although the criterion is very clear, I've tried hard until now and couldn't 
come up with a function for producing the nested list based on this grouping 
criterion. I am sure that the Haskell Hierarchical Libraries have something

to help me, but only now I see I'm still a big noob :P

Could someone please help me writing this function?


My best regards from Brazil,

João Paulo Pizani Flor
joaopiz...@gmail.com mailto:joaopiz...@gmail.com
Federal University of Santa Catarina


___
Beginners mailing list
beginn...@haskell.org
http://www.haskell.org/mailman/listinfo/beginners


--
Met vriendelijke groet,
=@@i

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


[Haskell-cafe] Confused about missing data constructor

2010-11-24 Thread Adam Miezianko
I'm working through Learn You a Haskell for Great Good [1] and getting
a compiler error while playing around with some of the code.  I have
this:

-- BEGIN state.hs
import Control.Monad.State

type Stack = [Int]

pop :: State Stack Int
pop = State $ \(x:xs) - (x,xs)

push :: Int - State Stack ()
push x = State $ \xs - ((), x:xs)

stackManip :: State Stack Int
stackManip = do
push 3
pop
pop
-- END state.hs

But when I try to load it into ghci I get the following errors:

  Prelude :load /home/admi/.pe/state.hs
  [1 of 1] Compiling Main ( /home/admi/.pe/state.hs, interpreted )

  /home/admi/.pe/state.hs:6:6: Not in scope: data constructor `State'

  /home/admi/.pe/state.hs:9:9: Not in scope: data constructor `State'
  Failed, modules loaded: none.
  Prelude

Now, I'm not exactly sure how to read the documentation for
Control.Monad.State [2] but it seems that newtype State s a = State
{...} defines a constructor, or am I wrong on that point too?  So,
what am I missing here?  In case it matters, I am using mtl-2.0.1.0
and ghci 6.12.3.

[1] http://learnyouahaskell.com/for-a-few-monads-more
[2] http://cvs.haskell.org/Hugs/pages/libraries/mtl/Control-Monad-State.html

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


[Haskell-cafe] ANNOUNCE: graphviz-2999.11.0.0

2010-11-24 Thread Ivan Lazar Miljenovic
I am pleased to announce version 2999.11.0.0 of graphviz [1], my
Haskell bindings to the Graphviz suite of graph visualisation tools
[2].

[1]: http://hackage.haskell.org/package/graphviz
[2]: http://graphviz.org/

This release is mostly backwards-compatible (unless you dealt directly
with Point and LayerList values); the changes are:

* Improved documentation, including examples of how to use `GraphvizParams`
  values (since several people indicated that they found them confusing)

* Addition of the `Labellable` class (and its method `toLabel`) to
  make it easier to construct labels.

* Backslashes (i.e. the `\` character) are now escaped/unescaped
  properly (bug spotted by Han Joosten).  As part of this:

- Dot-specific escapes such as `\N` are now also handled
  correctly, so the slash does not need to be escaped.

- Newline (`'\n'`) characters in labels, etc. are escaped to
  centred-newlines in Dot code, but not unescaped.

* `Point` values can now have the optional third dimension and end in
  a `!` to indicate that that position should be used (as input to
  Graphviz).

* `LayerList` uses `LayerID` values, and now has a proper `shrink`
  implementation in the test suite.

-- 
Ivan Lazar Miljenovic
ivan.miljeno...@gmail.com
IvanMiljenovic.wordpress.com
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] save the dates: SF Bay Area Haskell Hackathon: Feb 11~13, 2011

2010-11-24 Thread Mark Lentczner
Bryan O'Sullivan and I are hosting a SF Bay Area Haskell Hackathon at the 
Hacker Dojo in Mountain View, California.

Details are all sketchy at this point, but we plan on two components:
1) Haskell Project Hackathon
2) Learn Haskell Workshop

See:
http://wiki.hackerdojo.com/w/page/Haskell-Hackathon-2011

At this stage we're trying to gauge interest, size, and volunteers to help with 
organizing and running it. Either add yourself to that wiki page, or e-mail me.

- Mark Lentczner

Mark Lentczner
http://www.ozonehouse.com/mark/
IRC: mtnviewmark



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


[Haskell-cafe] Another Quasi Quotation question

2010-11-24 Thread jean-christophe mincke
Hello,

I am still playing with template-haskell...

I wonder, is there any reason why a quasiquoter cannot create haskell
statements and declarations in addition to expressions and patterns? Or more
generally create any legal Haskell syntax tree.

I.e Suppose I would like to create a quasiquoter for the C language (please,
imagine that it could be useful).

I could write sth such as :

[$c|

int a = 6;
int b = 7;
int c = a +b;

struct S { int x; int y}
|]

It could be nice to generate the appropriate haskell code:

a = 6
b= 7
c= a + b
data S = S {  x::Int; y:Int}
etc

That would allow to really embed any kind of language in a more or less easy
way into haskell, provided that code can be translated into legal haskell.

Is there anything that prevent these features.

Thank you

Regards

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


Re: [Haskell-cafe] Confused about missing data constructor

2010-11-24 Thread Anthony Cowley
On Tue, Nov 23, 2010 at 7:58 PM, Adam Miezianko a...@theorylounge.org wrote:
 I'm working through Learn You a Haskell for Great Good [1] and getting
 a compiler error while playing around with some of the code.  I have
 this:
 Now, I'm not exactly sure how to read the documentation for
 Control.Monad.State [2] but it seems that newtype State s a = State
 {...} defines a constructor, or am I wrong on that point too?  So,
 what am I missing here?  In case it matters, I am using mtl-2.0.1.0
 and ghci 6.12.3.

 [1] http://learnyouahaskell.com/for-a-few-monads-more
 [2] http://cvs.haskell.org/Hugs/pages/libraries/mtl/Control-Monad-State.html

Wrong documentation page, the one you want is
http://hackage.haskell.org/packages/archive/mtl/2.0.1.0/doc/html/Control-Monad-State-Lazy.html

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


[Haskell-cafe] Confused about missing data constructor

2010-11-24 Thread Antoine Latter
On Tue, Nov 23, 2010 at 6:58 PM, Adam Miezianko a...@theorylounge.org wrote:
 I'm working through Learn You a Haskell for Great Good [1] and getting
 a compiler error while playing around with some of the code.  I have
 this:

 -- BEGIN state.hs
 import Control.Monad.State

 type Stack = [Int]

 pop :: State Stack Int
 pop = State $ \(x:xs) - (x,xs)

 push :: Int - State Stack ()
 push x = State $ \xs - ((), x:xs)

 stackManip :: State Stack Int
 stackManip = do
    push 3
    pop
    pop
 -- END state.hs

 But when I try to load it into ghci I get the following errors:

  Prelude :load /home/admi/.pe/state.hs
  [1 of 1] Compiling Main             ( /home/admi/.pe/state.hs, interpreted )

  /home/admi/.pe/state.hs:6:6: Not in scope: data constructor `State'

  /home/admi/.pe/state.hs:9:9: Not in scope: data constructor `State'
  Failed, modules loaded: none.
  Prelude

 Now, I'm not exactly sure how to read the documentation for
 Control.Monad.State [2] but it seems that newtype State s a = State
 {...} defines a constructor, or am I wrong on that point too?  So,
 what am I missing here?  In case it matters, I am using mtl-2.0.1.0
 and ghci 6.12.3.

 [1] http://learnyouahaskell.com/for-a-few-monads-more
 [2] http://cvs.haskell.org/Hugs/pages/libraries/mtl/Control-Monad-State.html


It looks like your documentation doesn't match the library you're using.

The documentation for mtl-2.x is here: http://hackage.haskell.org/package/mtl

Starting in version 2.0, the mtl package no longer exports a
constructor called 'State' - but there is a function 'state' which
servers the same purpose.

However you might be better served using the 'modify' function.

I hope that helps,
Antoine

 --
 Adam Miezianko
 ___
 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] Re: Another Quasi-Quotation question

2010-11-24 Thread Geoffrey Mainland
On 11/24/2010 03:14, jean-christophe mincke wrote:
 Hello,
 
 I am still playing with template-haskell...
 
 I wonder, is there any reason why a quasiquoter cannot create haskell
 statements and declarations in addition to expressions and patterns? Or
 more generally create any legal Haskell syntax tree.

In GHC 7, quasiquotes can appear in place of expressions, patterns,
types and top-level declarations. The latter two are new (see [1]).

 I.e Suppose I would like to create a quasiquoter for the C language
 (please, imagine that it could be useful).

It is useful, and it already exists [2] :)

 I could write sth such as :
 
 [$c|
 
 int a = 6;
 int b = 7;
 int c = a +b;
 
 struct S { int x; int y}
 |]
 
 It could be nice to generate the appropriate haskell code:
 
 a = 6
 b= 7
 c= a + b
 data S = S {  x::Int; y:Int}
 etc

language-c-quote doesn't translate C to Haskell, but lets you build C
abstract syntax trees using C's concrete syntax.

 That would allow to really embed any kind of language in a more or less
 easy way into haskell, provided that code can be translated into legal
 haskell.
  
 Is there anything that prevent these features.

Check out GHC 7. The ability to quasiquote top-level definitions is
being used in the Haskell version of PADS [3].

 Thank you
 
 Regards
 
 J-C

Geoff

[1]
http://new-www.haskell.org/ghc/docs/7.0.1/html/users_guide/template-haskell.html#th-quasiquotation

[2] http://hackage.haskell.org/package/language-c-quote

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


Re: [Haskell-cafe] Confused about missing data constructor

2010-11-24 Thread Bas van Dijk
On Wed, Nov 24, 2010 at 7:08 PM, Antoine Latter aslat...@gmail.com wrote:
 I meant that 'pop' and 'push' should have been written with 'modify', 'get',
 and 'set' instead of the raw constructor, not as a drop-in replacement.

Indeed, you can also use the 'state' function instead of the 'State'
constructor in your definition of 'pop'.

'state' and the other constructor functions like 'reader' and
'writer' were introduced in mtl-2 to make the transition from mtl-1
easier.

Regards,

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


[Haskell-cafe] Monadic function purity

2010-11-24 Thread Gregory Propf
I have a pretty basic question.  I've been wondering about whether monadic 
functions that do NOT us IO can be pure or not.  There seems to be some 
confusion on this topic on the web.  I'm especially interested in whether they 
can be memoized.  It seems to me that something like a function in the State 
monad should be pure provided the same initial state and same function 
arguments are present.  Likewise with the list monad and most other monads in 
fact.



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


Re: [Haskell-cafe] Monadic function purity

2010-11-24 Thread Miguel Mitrofanov
Generally speaking, all Haskell functions are pure unless they use unsafe- 
functions or FFI inside.

Отправлено с iPhone

Nov 24, 2010, в 23:46, Gregory Propf gregorypr...@yahoo.com написал(а):

 I have a pretty basic question.  I've been wondering about whether monadic 
 functions that do NOT us IO can be pure or not.  There seems to be some 
 confusion on this topic on the web.  I'm especially interested in whether 
 they can be memoized.  It seems to me that something like a function in the 
 State monad should be pure provided the same initial state and same function 
 arguments are present.  Likewise with the list monad and most other monads in 
 fact.
 
 ___
 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] Monadic function purity

2010-11-24 Thread Daniel Fischer
On Wednesday 24 November 2010 21:46:22, Gregory Propf wrote:
 I have a pretty basic question.  I've been wondering about whether
 monadic functions that do NOT us IO can be pure or not.  There seems to
 be some confusion on this topic on the web.  I'm especially interested
 in whether they can be memoized.  It seems to me that something like a
 function in the State monad should be pure provided the same initial
 state and same function arguments are present.  Likewise with the list
 monad and most other monads in fact.

Yes, most monads are unambiguously pure.
From a suitable point of view, IO is pure too (the functions assembling the 
IO-actions are pure, impurity is constrained to the RTS executing the IO-
actions).
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] Eq instance for Chan

2010-11-24 Thread Mitar
Hi!

Why is there no Eq instance for Chan? There is Eq for MVar so it is
quite possible to define also Eq for Chan?

What I would like to do is keep track how many consumers I have for
each Chan so duplicating them with dupChan as necessary. So I was
thinking of storing a list of Chans which already have a consumer and
then duplicating it if another (and every additional) consumer would
be added. But without Eq it is not possible to check if there is Chan
already in a list (and I hope Eq would compare just Chan and not its
content).

Is there some other way to achieve this?


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


[Haskell-cafe] Equality constraint synonyms

2010-11-24 Thread Hugo Pacheco
Dear Haskellers,

When programming with type functions, I often find myself with a set of
invariants that are frequent in my programs and can be expressed as equality
constraints on the context of the functions.

I wonder if there is any way in current GHC to express some kind of synonyms
for equality constraints, to avoid a fixed set of constraints for a smaller
expression. The natural way for type classes would be to create a superclass
containing all the desired instances

class (A a, B a) = C a where {}

but as from http://hackage.haskell.org/trac/ghc/ticket/2715, equality
constraints are currently not supported in class contexts, what might be
reasonable.
However, in fact I am just looking for some kind syntactic sugar. Would this
be a desired feature for other people?

Regards,
hugo

-- 
www.di.uminho.pt/~hpacheco
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] GHC 7.0.1 developer challenges

2010-11-24 Thread John D. Ramsdell
A quick review of GHC 7.0.1 revealed two challenges for developers.

I downloaded the GHC 7.0.1 sources, configured for a home directory
install, and built and installed the compiler.  Very close to the end,
my machine froze, perhaps due to memory exhaustion.  In any event, a
reboot allowed me to complete the installation.

I tested the new compiler on an application I distribute, CPSA.  The
algorithm implemented by the program is not guaranteed to terminate,
and it's hard to predict when non-termination is inevitable.
Sometimes the way it terminates is to allocate all the memory in swap
space and freeze the machine.  It's an ugly crash.  So in my
documentation, I recommend people supply a runtime flag limiting
memory usage.

Due to a security concern, GHC 7.0.1 disables all runtime flags unless
a new flag is provided during linking.  Since limiting memory usage is
so important, many developers will modify their cabal files to add the
linker flag or prepare for complaints from users that the developer's
program caused their machine to freeze and lose their work.

The irony of this situation is deep.  CPSA is a program that analyzes
cryptographic protocols in an effort to expose security flaws.  To
ensure that the program does not crash a user's machine, I have to use
a linker option that may expose the user to some security problems.

There is one more disappointment in GHC 7.0.1 for developers.  Cabal
sdist is still hosed.  Since ten months ago, cabal sdist fails to
preserve the file mode bits of the source files put into the tarball
being generated (Ticket #627 reported by draconx). An executable shell
script and a source file world readable both have a mode of 600 in the
tarball!  So developers, continue to keep GHC 6.10.4 around so you can
create source distributions.  That's what I do.

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


Re: [Haskell-cafe] Equality constraint synonyms

2010-11-24 Thread Sebastian Fischer
On Thu, 2010-11-25 at 10:41 +0900, Hugo Pacheco wrote:
 Would this be a desired feature for other people?

I'd like to have Haskell Type Constraints Unleashed

http://users.ugent.be/~tschrijv/Research/papers/constraint_families.pdf

which includes equality constraint synonyms.

Sebastian


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


[Haskell-cafe] How to instance class with functional dependency?

2010-11-24 Thread Magicloud Magiclouds
Hi,
  In System.Posix.IOCtl, there is such a class:
class Storable d = IOControl req d | req - d where
ioctlReqSource :: req - CInt
  How to instance it? I do it as:
data TIOCGWINSZ = TIOCGWINSZ

#starttype struct winsize
#field ws_row , CUShort
#field ws_col , CUShort
#field ws_xpixel , CUShort
#field ws_ypixel , CUShort
#stoptype

instance IOControl TIOCGWINSZ C'winsize where
  ioctlReq _ = #const TIOCGWINSZ

  Then I got:
topIO.hs:19:0:
Couldn't match expected type `C'winsize'
   against inferred type `Int'
When using functional dependencies to combine
  IOControl
(Foreign.C.Types.CUShort
 - Foreign.C.Types.CUShort
 - Foreign.C.Types.CUShort
 - Foreign.C.Types.CUShort
 - C'winsize)
Int,
arising from a use of `ioctl'' at topIO.hs:21:35-60
  IOControl
(Foreign.C.Types.CUShort
 - Foreign.C.Types.CUShort
 - Foreign.C.Types.CUShort
 - Foreign.C.Types.CUShort
 - C'winsize)
C'winsize,
arising from a use of `ioctl'' at topIO.hs:20:12-37
When generalising the type(s) for `main'
-- 
竹密岂妨流水过
山高哪阻野云飞
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Equality constraint synonyms

2010-11-24 Thread Hugo Pacheco
Thank you for the info., I didn't know that it had already been proposed.
The constraint families seem definitely useful.

hugo

On Thu, Nov 25, 2010 at 12:53 PM, Sebastian Fischer fisc...@nii.ac.jpwrote:

 On Thu, 2010-11-25 at 10:41 +0900, Hugo Pacheco wrote:
  Would this be a desired feature for other people?

 I'd like to have Haskell Type Constraints Unleashed

 http://users.ugent.be/~tschrijv/Research/papers/constraint_families.pdf

 which includes equality constraint synonyms.

 Sebastian





-- 
www.di.uminho.pt/~hpacheco
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] ANN: tskiplist-0.0.0

2010-11-24 Thread Peter Robinson
This package [1] provides an implementation of a skip list using STM.
A skip list
is a probabilistic data structure with Data.Map-like operations. In contrast
to a balanced tree, a skip list does not need any (expensive) rebalancing,
which makes it particularly suitable for concurrent programming.

You can find some documentation on how to use it here:
http://darcs.monoid.at/tskiplist/dist/doc/html/tskiplist/Control-Concurrent-STM-TSkipList.html

Feedback appreciated!

 Peter

[1] http://hackage.haskell.org/package/tskiplist-0.0.0
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe