Re: [Haskell-cafe] ANN: generic-deepseq 1.0.0.0

2012-02-25 Thread Andres Löh
 Would you have an example of a type for which it would be useful to have
 a DeepSeq instance, and that would require a V1 instance? I cannot think
 of one now; I originaly thought it would be necessary to permit deriving
 DeepSeq instances for types tagged with void types, but as José
 explained, in that case, the V1 instance isn't needed because those void
 types don't show up in the representation.

While void datatypes are rare, it just doesn't make sense to exclude
them. It's an arbitrary restriction. Here's a constructed example:

data X a = C1 Int | C2 a
data Z -- empty

type Example = X Z

We're using Z as a parameter to X in order to exclude the use of the
C2 case. Without a V1 case, you cannot use deepSeq on values of type
Example.

Cheers,
  Andres

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


Re: [Haskell-cafe] ANN: generic-deepseq 1.0.0.0

2012-02-25 Thread José Pedro Magalhães
2012/2/25 Andres Löh andres.l...@googlemail.com

  Would you have an example of a type for which it would be useful to have
  a DeepSeq instance, and that would require a V1 instance? I cannot think
  of one now; I originaly thought it would be necessary to permit deriving
  DeepSeq instances for types tagged with void types, but as José
  explained, in that case, the V1 instance isn't needed because those void
  types don't show up in the representation.

 While void datatypes are rare, it just doesn't make sense to exclude
 them. It's an arbitrary restriction. Here's a constructed example:

 data X a = C1 Int | C2 a
 data Z -- empty

 type Example = X Z

 We're using Z as a parameter to X in order to exclude the use of the
 C2 case. Without a V1 case, you cannot use deepSeq on values of type
 Example.


Yes, I agree. There should be a V1 instance, and it should return
`undefined`. This gives the expected behavior of `seq` on an empty
datatype, I think. If there is no V1 instance, you'll get a type-checking
error (no instance for V1), preventing generic deepseq on any datatype that
happens to use an empty datatype in its definition.


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


Re: [Haskell-cafe] ANN: generic-deepseq 1.0.0.0

2012-02-25 Thread Maxime Henrion
On Sat, 2012-02-25 at 11:38 +0100, José Pedro Magalhães wrote:
 2012/2/25 Andres Löh andres.l...@googlemail.com
  Would you have an example of a type for which it would be
 useful to have
  a DeepSeq instance, and that would require a V1 instance? I
 cannot think
  of one now; I originaly thought it would be necessary to
 permit deriving
  DeepSeq instances for types tagged with void types, but as
 José
  explained, in that case, the V1 instance isn't needed
 because those void
  types don't show up in the representation.
 
 
 While void datatypes are rare, it just doesn't make sense to
 exclude
 them. It's an arbitrary restriction. Here's a constructed
 example:
 
 data X a = C1 Int | C2 a
 data Z -- empty
 
 type Example = X Z
 
 We're using Z as a parameter to X in order to exclude the use
 of the
 C2 case. Without a V1 case, you cannot use deepSeq on values
 of type
 Example.
 
 Yes, I agree. There should be a V1 instance, and it should return
 `undefined`. This gives the expected behavior of `seq` on an empty
 datatype, I think. If there is no V1 instance, you'll get a
 type-checking error (no instance for V1), preventing generic deepseq
 on any datatype that happens to use an empty datatype in its
 definition.

Thanks for all the input guys. I have just released generic-deepseq
2.0.1.0 to hackage, with fixed U1 and V1 instances per this discussion.

Cheers,
Maxime



signature.asc
Description: This is a digitally signed message part
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] Call for Journal Papers: STVR Special Issue on Tests and Proofs

2012-02-25 Thread Achim D. Brucker
Apologies for duplicates.

  CALL FOR PAPERS 
  STVR Special Issue on Tests and Proofs
http://lifc.univ-fcomte.fr/tap2012/stvr/

The Software Testing, Verification  Reliability (STVR) journal
(http://www3.interscience.wiley.com/journal/13635/home) invites 
authors to submit papers to a Special Issue on Tests and Proofs.

Background
==
The increasing use of software and the growing system complexity make
focused software testing a challenging task. Recent years have seen an
increasing industrial and academic interest in the use of static and
dynamic analysis techniques together. Success has been reported
combining different test techniques such as model-based testing,
structural testing, or concolic testing with static techniques such as
program slicing, dependencies analysis, model-checking, abstract
interpretation, predicate abstraction, or verification. This special
issue serves as a platform for researchers and practitioners to
present theory, results, experience and advances in Tests and Proofs
(TAP).

Topics
==
This special issue focuses on all topics relevant to TAP. In
particular, the topics of interest include, but are not limited to:
* Program proving with the aid of testing techniques
* New challenges in automated reasoning emerging from
  specificities of test generation
* Verification and testing techniques combining proofs and tests
* Generation of test data, oracles, or preambles by deductive
  techniques such as: theorem proving, model checking, symbolic
  execution, constraint logic programming, SAT and SMT solving
* Model-based testing and verification
* Automatic bug finding
* Debugging of programs combining static and dynamic analysis
* Transfer of concepts from testing to proving (e.g., coverage
  criteria) and from proving to testing
* Formal frameworks for test and proof
* Tool descriptions, experience reports and evaluation of test and
  proof
* Case studies combining tests and proofs
* Applying combination of test and proof techniques to new
  application domains such as validating security procotols or
  vulnerability detection of programs
* The processes, techniques, and tools that support test and proof

Submission Information
==
The deadline for submissions is 17th December, 2012. Notification of
decisions will be given by April 15th, 2013.

All submissions must contain original unpublished work not being
considered for publication elsewhere. Original extensions to
conference papers - identifing clearly additional contributions - are
also encouraged unless prohibited by copyright. Submissions will be
refereed according to standard procedures for Software Testing,
Verification and Reliability.  Please submit your paper electronically
using the Software Testing, Verification  Reliability manuscript
submission site. Select Special Issue Paper and enter Tests and
Proofs as title.

Important Dates:

* Paper submission: December 17, 2012
* Notification: April 15, 2013

Guest Editors
=
* Achim D. Brucker, SAP Research, Germany
  http://www.brucker.ch/
* Wolfgang Grieskamp, Google, U.S.A.
  http://www.linkedin.com/in/wgrieskamp
* Jacques Julliand, University of Franche-Comté, France
  http://lifc.univ-fcomte.fr/page_personnelle/accueil/8   

-- 
Dr. Achim D. Brucker, SAP Research, Vincenz-Priessnitz-Str. 1, D-76131 Karlsruhe
 Phone: +49 6227 7-52595, http://www.brucker.ch

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


[Haskell-cafe] Monadic Design Patterns for the Web Chapter Review

2012-02-25 Thread Greg Meredith
*Dear Supporters, Friends and Colleagues,

i’m writing to you to say that i will be going over the material in
Chapters 3 through 9 of the book, MDP4tW in a Google+ hangout, 1 Chapter /
week. If any would like to participate in reviewing the material presented,
please let me know. i will limit participation in these reviews to 5 people
/ session with preference give to people who contributed to the Kickstarter
campaign. Please RSVP to me at lgreg.mered...@gmail.com and i will let you
know the dates and times.*

Best wishes,

--greg


-- 
L.G. Meredith
Managing Partner
Biosimilarity LLC
1219 NW 83rd St
Seattle, WA 98117

+1 206.650.3740

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


Re: [Haskell-cafe] Using multiplate to get free variables from a syntax tree

2012-02-25 Thread Sjoerd Visscher

On Feb 24, 2012, at 10:09 PM, Stephen Tetley wrote:

 I'm not familiar with Multiplate either, but presumably you can
 descend into the decl - collect the bound vars, then descend into the
 body expr. 

 Naturally you would need a monadic traversal
 rather than an applicative one...


It turns out the traversal is still applicative. What we want to collect are 
the free and the declared variables, given the bound variables. ('Let' will 
turn the declared variables into bound variables.) So the type is [Var] - 
([Var], [Var]). Note that this is a Monoid, thanks to the instances for ((-) 
r), (,) and []. So we can use the code from preorderFold, but add an exception 
for the 'Let' case.

freeVariablesPlate :: Plate (Constant ([Var] - ([Var], [Var])))
freeVariablesPlate = handleLet (varPlate `appendPlate` multiplate 
freeVariablesPlate)
  where 
varPlate = Plate {
  expr = \x - Constant $ \bounded - ([ v | EVar v - [x], v `notElem` 
bounded], []),
  decl = \x - Constant $ const ([], [ v | v := _ - [x]])
}
handleLet plate = plate { expr = exprLet }
  where
exprLet (Let d e) = Constant $ \bounded - 
  let
(freeD, declD) = foldFor decl plate d bounded
(freeE, _) = foldFor expr plate e (declD ++ bounded)
  in
(freeD ++ freeE, [])
exprLet x = expr plate x

freeVars :: Expr - [Var]
freeVars = fst . ($ []) . foldFor expr freeVariablesPlate

 freeVars $ Let (x := Con 42) (Add (EVar x) (EVar y))
[y]

--
Sjoerd Visscher
https://github.com/sjoerdvisscher/blog





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


[Haskell-cafe] How far away is a release of cabal-install that works with ghc 7.4?

2012-02-25 Thread Magnus Therning
It looks like HEAD on the dev branch of cabal (cabal/cabal-install)
compiles fine with 7.4.1, so any thoughts on when we see an update
posted on Hackage?

/M

-- 
Magnus Therning  OpenPGP: 0xAB4DFBA4 
email: mag...@therning.org   jabber: mag...@therning.org
twitter: magthe   http://therning.org/magnus

I invented the term Object-Oriented, and I can tell you I did not have
C++ in mind.
 -- Alan Kay


pgp3Ed9GWXj1M.pgp
Description: PGP signature
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Using multiplate to get free variables from a syntax tree

2012-02-25 Thread Thomas Schilling
That will give you the wrong answer for an expression like:

  (let x = 1 in x + y) + x

Unless you do a renaming pass first, you will end up both with a bound
x and a free x.

On 25 February 2012 16:29, Sjoerd Visscher sjo...@w3future.com wrote:

 On Feb 24, 2012, at 10:09 PM, Stephen Tetley wrote:

 I'm not familiar with Multiplate either, but presumably you can
 descend into the decl - collect the bound vars, then descend into the
 body expr.

 Naturally you would need a monadic traversal
 rather than an applicative one...


 It turns out the traversal is still applicative. What we want to collect are 
 the free and the declared variables, given the bound variables. ('Let' will 
 turn the declared variables into bound variables.) So the type is [Var] - 
 ([Var], [Var]). Note that this is a Monoid, thanks to the instances for ((-) 
 r), (,) and []. So we can use the code from preorderFold, but add an 
 exception for the 'Let' case.

 freeVariablesPlate :: Plate (Constant ([Var] - ([Var], [Var])))
 freeVariablesPlate = handleLet (varPlate `appendPlate` multiplate 
 freeVariablesPlate)
  where
    varPlate = Plate {
      expr = \x - Constant $ \bounded - ([ v | EVar v - [x], v `notElem` 
 bounded], []),
      decl = \x - Constant $ const ([], [ v | v := _ - [x]])
    }
    handleLet plate = plate { expr = exprLet }
      where
        exprLet (Let d e) = Constant $ \bounded -
          let
            (freeD, declD) = foldFor decl plate d bounded
            (freeE, _)     = foldFor expr plate e (declD ++ bounded)
          in
            (freeD ++ freeE, [])
        exprLet x = expr plate x

 freeVars :: Expr - [Var]
 freeVars = fst . ($ []) . foldFor expr freeVariablesPlate

 freeVars $ Let (x := Con 42) (Add (EVar x) (EVar y))
 [y]

 --
 Sjoerd Visscher
 https://github.com/sjoerdvisscher/blog





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



-- 
Push the envelope. Watch it bend.

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


Re: [Haskell-cafe] Using multiplate to get free variables from a syntax tree

2012-02-25 Thread Sjoerd Visscher
I don't understand what you mean.

 ($[]) . foldFor expr freeVariablesPlate $ Add (Let (x := Con 1) (Add 
 (EVar x) (EVar y))) (EVar x)
([y,x],[])

I.e. free variables y and x, no bound variables. Is that not correct?

Sjoerd

On Feb 25, 2012, at 7:15 PM, Thomas Schilling wrote:

 That will give you the wrong answer for an expression like:
 
  (let x = 1 in x + y) + x
 
 Unless you do a renaming pass first, you will end up both with a bound
 x and a free x.
 
 On 25 February 2012 16:29, Sjoerd Visscher sjo...@w3future.com wrote:
 
 On Feb 24, 2012, at 10:09 PM, Stephen Tetley wrote:
 
 I'm not familiar with Multiplate either, but presumably you can
 descend into the decl - collect the bound vars, then descend into the
 body expr.
 
 Naturally you would need a monadic traversal
 rather than an applicative one...
 
 
 It turns out the traversal is still applicative. What we want to collect are 
 the free and the declared variables, given the bound variables. ('Let' will 
 turn the declared variables into bound variables.) So the type is [Var] - 
 ([Var], [Var]). Note that this is a Monoid, thanks to the instances for 
 ((-) r), (,) and []. So we can use the code from preorderFold, but add an 
 exception for the 'Let' case.
 
 freeVariablesPlate :: Plate (Constant ([Var] - ([Var], [Var])))
 freeVariablesPlate = handleLet (varPlate `appendPlate` multiplate 
 freeVariablesPlate)
  where
varPlate = Plate {
  expr = \x - Constant $ \bounded - ([ v | EVar v - [x], v `notElem` 
 bounded], []),
  decl = \x - Constant $ const ([], [ v | v := _ - [x]])
}
handleLet plate = plate { expr = exprLet }
  where
exprLet (Let d e) = Constant $ \bounded -
  let
(freeD, declD) = foldFor decl plate d bounded
(freeE, _) = foldFor expr plate e (declD ++ bounded)
  in
(freeD ++ freeE, [])
exprLet x = expr plate x
 
 freeVars :: Expr - [Var]
 freeVars = fst . ($ []) . foldFor expr freeVariablesPlate
 
 freeVars $ Let (x := Con 42) (Add (EVar x) (EVar y))
 [y]
 
 --
 Sjoerd Visscher
 https://github.com/sjoerdvisscher/blog
 
 
 
 
 
 ___
 Haskell-Cafe mailing list
 Haskell-Cafe@haskell.org
 http://www.haskell.org/mailman/listinfo/haskell-cafe
 
 
 
 -- 
 Push the envelope. Watch it bend.
 

--
Sjoerd Visscher
https://github.com/sjoerdvisscher/blog






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


Re: [Haskell-cafe] Using multiplate to get free variables from a syntax tree

2012-02-25 Thread Thomas Schilling
No that's correct.  I have to say the multiplate code is incredibly
hard to decipher.

On 25 February 2012 19:47, Sjoerd Visscher sjo...@w3future.com wrote:
 I don't understand what you mean.

 ($[]) . foldFor expr freeVariablesPlate $ Add (Let (x := Con 1) (Add 
 (EVar x) (EVar y))) (EVar x)
 ([y,x],[])

 I.e. free variables y and x, no bound variables. Is that not correct?

 Sjoerd

 On Feb 25, 2012, at 7:15 PM, Thomas Schilling wrote:

 That will give you the wrong answer for an expression like:

  (let x = 1 in x + y) + x

 Unless you do a renaming pass first, you will end up both with a bound
 x and a free x.

 On 25 February 2012 16:29, Sjoerd Visscher sjo...@w3future.com wrote:

 On Feb 24, 2012, at 10:09 PM, Stephen Tetley wrote:

 I'm not familiar with Multiplate either, but presumably you can
 descend into the decl - collect the bound vars, then descend into the
 body expr.

 Naturally you would need a monadic traversal
 rather than an applicative one...


 It turns out the traversal is still applicative. What we want to collect 
 are the free and the declared variables, given the bound variables. ('Let' 
 will turn the declared variables into bound variables.) So the type is 
 [Var] - ([Var], [Var]). Note that this is a Monoid, thanks to the 
 instances for ((-) r), (,) and []. So we can use the code from 
 preorderFold, but add an exception for the 'Let' case.

 freeVariablesPlate :: Plate (Constant ([Var] - ([Var], [Var])))
 freeVariablesPlate = handleLet (varPlate `appendPlate` multiplate 
 freeVariablesPlate)
  where
    varPlate = Plate {
      expr = \x - Constant $ \bounded - ([ v | EVar v - [x], v `notElem` 
 bounded], []),
      decl = \x - Constant $ const ([], [ v | v := _ - [x]])
    }
    handleLet plate = plate { expr = exprLet }
      where
        exprLet (Let d e) = Constant $ \bounded -
          let
            (freeD, declD) = foldFor decl plate d bounded
            (freeE, _)     = foldFor expr plate e (declD ++ bounded)
          in
            (freeD ++ freeE, [])
        exprLet x = expr plate x

 freeVars :: Expr - [Var]
 freeVars = fst . ($ []) . foldFor expr freeVariablesPlate

 freeVars $ Let (x := Con 42) (Add (EVar x) (EVar y))
 [y]

 --
 Sjoerd Visscher
 https://github.com/sjoerdvisscher/blog





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



 --
 Push the envelope. Watch it bend.


 --
 Sjoerd Visscher
 https://github.com/sjoerdvisscher/blog






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



-- 
Push the envelope. Watch it bend.

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


Re: [Haskell-cafe] Data.IntMap union complexity

2012-02-25 Thread wren ng thornton

On 2/24/12 3:40 AM, Christoph Breitkopf wrote:

On Fri, Feb 24, 2012 at 4:48 AM, wren ng thorntonw...@freegeek.org  wrote:

When the two maps are of vastly different sizes, O(min(m,n)) is a more
intuitive way to think about it. Since you only have to look at the places
where the spines clash, that will be on the order of the smaller map.


 Folding insert might still be a win if one of the maps is very much 

smaller

than the other, but since size is O(n) for Data.IntMap, there's no way to
find out if that's the case.


It's possible (due to the constant factors I keep mentioning), though I 
wouldn't expect it to. The reasoning why is as follows:


In the smaller map every key will have some shared prefix with other 
keys. (Excepting degenerate cases like the empty map and singleton 
maps.) As such, calling insert with two keys that share a prefix means 
that you'll be traversing the larger map's spine for that prefix twice. 
Whereas, with the merge-based implementation we only traverse once.


Moreover, when performing repeated insertions, we have to reconstruct 
the structure of the smaller map, which can lead to producing excessive 
garbage over the merge-based implementation. For example, consider the 
case where we have keys K and L in the smaller map which diverge at some 
prefix P. If P does not lay in the spine of the larger map, then we will 
have to merge P with some other prefix Q in order to produce a Bin. 
Let's say that P and Q diverge at R (thus there is a Bin at R, with 
children P and Q). After inserting K we now have a map where there is a 
spine from R to K. Now, when we insert L, since we know that P lays on 
the spine between R and K, that means we'll have to merge P with K to 
produce another Bin. The spine from R to K is now garbage--- but it 
wouldn't have been allocated in the merge-based implementation, since K 
and L would have been inserted simultaneously.



If it's really a concern, then I still say the best approach is to just 
benchmark the two options; the API gives you the tools you need. As for 
the O(n) size, you can always define your own data structure which 
memoizes the size; e.g.,


-- N.B., the size field is lazy and therefore only computed on
-- demand, yet it is shared and so only costs O(n) the first
-- time it's accessed since the map was updated.
data SizedIntMap a = SIM Int !(IntMap a)

size (SIM s _) = s

insert k v (SIM _ m) = SIM (IM.size m') m'
where m' = IM.insert k v m

...

It's a lot of boilerplate, and it's be nice if that boilerplate were 
provided once and for all by containers (as Data.IntMap.Sized, or the 
like), but it's simple enough to do.


--
Live well,
~wren

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


Re: [Haskell-cafe] Data.IntMap union complexity

2012-02-25 Thread wren ng thornton

Evan Laforge qdun...@gmail.com wrote:
 I've wondered if it's faster to insert many keys by successive
 insertion, or by building another map and then unioning, and likewise
 with deletion.  I eventually decided on successive, thinking a log n
 build + merge is going to be slower than a m*log n for successive
 insertion.  So I wound up with:

If you don't already have the keys in a map, I don't think you gain much 
by building a map and then merging rather than just inserting them 
directly. It will produce extra garbage (unless you have some interest 
in the map you're building), and you have to make the same spine 
traversals in building the map as you would have inserting into the 
larger map (and then you have to traverse the larger map during 
merging). But again, thanks to Criterion, benchmarking is cheap and 
easy. No need to believe in the folklore or opinions of others :)


Though, if the set of keys to be added is very large, then the 
build+merge approach would allow you to parallelize the building of the 
map (split the key set in half and build maps for each set, recursing 
as necessary; then either merge the new maps together before merging 
with the target map, or just merge them with the target map in serial).


--
Live well,
~wren

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