[Haskell-cafe] Mutually recursive modules

2013-05-08 Thread Roman Cheplyaka
I wonder whether it's always possible to break cycles using GHC's
.hs-boot files.

Consider the following schematic example:

  module A where

  import B

  data A

  f :: B - A
  f = undefined B.g

  module B where

  import A

  data B

  g :: A - B
  g = undefined A.f

A.hs-boot must give a type signature for f, and since the signature
contains 'B', it must import 'B'. Ditto for B.hs-boot — it must import
'A'.

Even if we treat all imports as {-# SOURCE #-}, there is still a cycle
between the hs-boot files.

So, am I right in understanding that these recursive modules cannot be
compiled by GHC at all?

Roman

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


Re: [Haskell-cafe] Incrementation fails

2013-05-08 Thread Roel van Dijk
Hi John,

Can you tell us what your function is supposed to do? It appears to be some
kind of search-and-replace for strings. What is the relationship between
'findStr', 'replaceStrList' and 'myText'?


2013/5/8 John knowledge1...@gmail.com

 Hello All,

 I'm in a big trouble with incrementation of a counter in this code. It
 doesn't increment.

 Could you please tell me where the problem ist and how can I solve it?

 replaceBasedIdx::  String  -  [String]  -  String  -  String
 replaceBasedIdxfindStr replaceStrList myText = replaceBasedIdxSub
 findStr replaceStrList myText 0

 replaceBasedIdxSub  ::  String  -  [String]  -  String  - Int - String
 replaceBasedIdxSub findStr replaceStrList myText counter = loop myText
   where
 loop [] = []
 loop myText =
   let (prefix, rest) = splitAt n myText
   in
 if findStr == prefix-- found an
 occurrence?
 then (replaceStrList !! (counter+1)) ++ loop rest   -- yes: replace
 it

 else head myText : loop (tail myText)   -- no: keep
 looking
 n = length findStr

 Thank you very mutch!

 Greetings!

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


Re: [Haskell-cafe] Incrementation fails

2013-05-08 Thread Roel van Dijk
I stared at the code some more and deduced what I think is the
intented meaning. Occurences of 'findStr' in 'myText' are replaced
with the strings in 'replaceStrList'.

So replaceBasedIdx X [b,d,f] aXcXeXg = abcdefg

The reason your counter didn't increment is because it was defined as
an argument to 'replaceBasedIdxSub'. That means its value is fixed
once you evaluate that function. Its value will not change no matter
how many times the inner 'loop' function is evaluated. The solution is
to pass the counter as an argument to said 'loop' function. Now when
'loop' enters the recursion you can pass a different value, such as
counter + 1.

 replaceBasedIdx :: String - [String] - String - String
 replaceBasedIdx findStr replaceStrList myText = replaceBasedIdxSub
findStr replaceStrList myText

 replaceBasedIdxSub :: String - [String] - String - String
 replaceBasedIdxSub findStr replaceStrList myText = loop 0 myText
   where
 loop :: Int - String - String
 loop counter [] = []
 loop counter myText =
   let (prefix, rest) = splitAt n myText
   in if findStr == prefix
  then (replaceStrList !! counter) ++ loop (counter + 1) rest
  else head myText : loop counter (tail myText)

 n :: Int
 n = length findStr
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Mutually recursive modules

2013-05-08 Thread Francesco Mazzoli
At Wed, 8 May 2013 09:46:08 +0300,
Roman Cheplyaka wrote:
 
 I wonder whether it's always possible to break cycles using GHC's
 .hs-boot files.
 
 Consider the following schematic example:
 
   module A where
 
   import B
 
   data A
 
   f :: B - A
   f = undefined B.g
 
   module B where
 
   import A
 
   data B
 
   g :: A - B
   g = undefined A.f
 
 A.hs-boot must give a type signature for f, and since the signature
 contains 'B', it must import 'B'. Ditto for B.hs-boot — it must import
 'A'.
 
 Even if we treat all imports as {-# SOURCE #-}, there is still a cycle
 between the hs-boot files.
 
 So, am I right in understanding that these recursive modules cannot be
 compiled by GHC at all?

This configuration works for me:

A.hs:

module A where
import B

data A

f :: B - A
f = undefined B.g

A.hs-boot:

module A where

import {-# SOURCE #-} B

data A

f :: B - A

B.hs:

module B where
import {-# SOURCE #-} A

data B

g :: A - B
g = undefined A.f

B.hs-boot:

module B where
data B

Then I can compile them:

bitonic@clay /tmp % ghc -c B.hs-boot
bitonic@clay /tmp % ghc -c A.hs-boot
bitonic@clay /tmp % ghc -c B.hs 
bitonic@clay /tmp % ghc -c A.hs 

Francesco

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


Re: [Haskell-cafe] Incrementation fails

2013-05-08 Thread Roel van Dijk
 problem = replaceBasedIdx X [b,d,f] aXcXeXgX
 -- abcdefg*** Exception: Prelude.(!!): index too large

This problem occurs because you never check if 'counter' is a valid
index in the 'replaceStrList'. You can solve it by not using the !!
operator at all. The solution is to also pass 'replaceStrList' in the
recursion. That way you can check whether you have exhausted all
strings in that list and as a bonus you do not need your counter
anymore:

 replaceBasedIdx :: String - [String] - String - String
 replaceBasedIdx findStr replaceStrList myText = loop replaceStrList myText
   where
 loop :: [String] - String - String
 loop rs [] = []
 -- Check for empty list of replacements
 loop [] text = text
 -- Pattern match on the list of replacements to get both the
 -- entire list rs, the first element r and the tail rs'.
 loop rs@(r:rs') text =
   let (prefix, rest) = splitAt n text
   in if findStr == prefix
  then r ++ loop rs' rest
  else head text : loop rs (tail text)

 n :: Int
 n = length findStr



2013/5/8 Roel van Dijk vandijk.r...@gmail.com

 I stared at the code some more and deduced what I think is the
 intented meaning. Occurences of 'findStr' in 'myText' are replaced
 with the strings in 'replaceStrList'.

 So replaceBasedIdx X [b,d,f] aXcXeXg = abcdefg

 The reason your counter didn't increment is because it was defined as
 an argument to 'replaceBasedIdxSub'. That means its value is fixed
 once you evaluate that function. Its value will not change no matter
 how many times the inner 'loop' function is evaluated. The solution is
 to pass the counter as an argument to said 'loop' function. Now when
 'loop' enters the recursion you can pass a different value, such as
 counter + 1.

  replaceBasedIdx :: String - [String] - String - String
  replaceBasedIdx findStr replaceStrList myText = replaceBasedIdxSub
 findStr replaceStrList myText

  replaceBasedIdxSub :: String - [String] - String - String
  replaceBasedIdxSub findStr replaceStrList myText = loop 0 myText
where
  loop :: Int - String - String
  loop counter [] = []
  loop counter myText =
 let (prefix, rest) = splitAt n myText
in if findStr == prefix
   then (replaceStrList !! counter) ++ loop (counter + 1) rest
   else head myText : loop counter (tail myText)
 
  n :: Int
  n = length findStr


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


Re: [Haskell-cafe] Mutually recursive modules

2013-05-08 Thread Roman Cheplyaka
Ah yes, thank you!

* Francesco Mazzoli f...@mazzo.li [2013-05-08 08:51:12+0100]
 At Wed, 8 May 2013 09:46:08 +0300,
 Roman Cheplyaka wrote:
  
  I wonder whether it's always possible to break cycles using GHC's
  .hs-boot files.
  
  Consider the following schematic example:
  
module A where
  
import B
  
data A
  
f :: B - A
f = undefined B.g
  
module B where
  
import A
  
data B
  
g :: A - B
g = undefined A.f
  
  A.hs-boot must give a type signature for f, and since the signature
  contains 'B', it must import 'B'. Ditto for B.hs-boot — it must import
  'A'.
  
  Even if we treat all imports as {-# SOURCE #-}, there is still a cycle
  between the hs-boot files.
  
  So, am I right in understanding that these recursive modules cannot be
  compiled by GHC at all?
 
 This configuration works for me:
 
 A.hs:
 
 module A where
 import B
 
 data A
 
 f :: B - A
 f = undefined B.g
 
 A.hs-boot:
 
 module A where
 
 import {-# SOURCE #-} B
 
 data A
 
 f :: B - A
 
 B.hs:
 
 module B where
 import {-# SOURCE #-} A
 
 data B
 
 g :: A - B
 g = undefined A.f
 
 B.hs-boot:
 
 module B where
 data B
 
 Then I can compile them:
 
 bitonic@clay /tmp % ghc -c B.hs-boot
 bitonic@clay /tmp % ghc -c A.hs-boot
 bitonic@clay /tmp % ghc -c B.hs 
 bitonic@clay /tmp % ghc -c A.hs 
 
 Francesco

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


Re: [Haskell-cafe] Categories (cont.)

2013-05-08 Thread Conal Elliott
Hi Wren,

Have you taken this constrained categories experiment further,
particularly for adding products? As I mentioned in a haskell-cafe note
yesterday, I tried and got a frightening proliferation of constraints when
defining method defaults and utility functions (e.g., left- or
right-associating).

-- Conal



On Fri, Dec 21, 2012 at 8:59 PM, wren ng thornton w...@freegeek.org wrote:

 On 12/21/12 2:35 PM, Chris Smith wrote:

 It would definitely be nice to be able to work with a partial Category
 class, where for example the objects could be constrained to belong to a
 class.  One could then restrict a Category to a type level representation
 of the natural numbers or any other desired set.  Kind polymorphism should
 make this easy to define, but I still don't have a good feel for whether
 it
 is worth the complexity.


 Actually, what you really want is ConstraintKinds. The following works
 just fine in GHC 7.6.1:

 {-# LANGUAGE KindSignatures
, ConstraintKinds
, PolyKinds
, TypeFamilies
, MultiParamTypeClasses
, FunctionalDependencies
, FlexibleInstances
, FlexibleContexts
#-}

 class Category (c :: k - k - *) where

 -- | The kind of domain objects.
 type DomC c x :: Constraint

 -- | The kind of codomain objects.
 type CodC c x :: Constraint

 -- | The identity morphisms.
 id  :: (ObjC c x) = c x x

 -- | Composition of morphisms.
 (.) :: (DomC c x, ObjC c y, CodC c z) = c y z - c x y - c x z

 -- | An alias for objects in the centre of a category.
 type ObjC c x = (Category c, DomC c x, CodC c x)

 -- | An alias for a pair of objects which could be connected by a
 -- @c@-morphism.
 type HomC c x y = (Category c, DomC c x, CodC c y)

 Notably, we distinguish domain objects from codomain objects in order to
 allow morphisms into or out of the category, which is indeed helpful in
 practice.

 Whether there's actually any good reason for distinguishing DomC and CodC,
 per se, remains to be seen. In Conal Elliott's variation[1] he moves HomC
 into the class and gets rid of DomC and CodC. Which allows constraints that
 operate jointly on both the domain and codomain, whereas the above version
 does not. I haven't run into the need for that yet, but I could easily
 imagine it. It does add a bit of complication though since we can no longer
 have ObjC be a derived thing; it'd have to move into the class as well, and
 we'd have to somehow ensure that it's coherent with HomC.

 The above version uses PolyKinds as well as ConstraintKinds. I haven't
 needed this myself, since the constraints act as a sort of kind for the
 types I'm interested in, but it'll definitely be useful if you get into
 data kinds, or want an instance of functor categories, etc.


 [1] https://github.com/conal/**linear-map-gadt/blob/master/**
 src/Control/ConstraintKinds/**Category.hshttps://github.com/conal/linear-map-gadt/blob/master/src/Control/ConstraintKinds/Category.hs
 

 --
 Live well,
 ~wren


 __**_
 Haskell-Cafe mailing list
 Haskell-Cafe@haskell.org
 http://www.haskell.org/**mailman/listinfo/haskell-cafehttp://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: Robot - Simulate keyboard and mouse events under X11

2013-05-08 Thread Niklas Hambüchen
Hi,

I just started using your library to move my cursor.

Is it possible that it ignores negative values in moveBy?

In other words, I can only move the cursor into one direction.

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


[Haskell-cafe] Formal Methods/Functional programming job position at Intel

2013-05-08 Thread Levent Erkok
Our formal methods team at Intel has a full-time position available that I
think would be a good fit for functional programming and formal methods
enthusiasts. I'm including the description below. Do not hesitate to
contact me if you've any questions, or just want to talk about it in
general. To apply for the position, please visit:
http://www.intel.com/jobs/jobsearch/index.htm, and in the advanced search
area enter the job number: 709631.

Thanks,

-Levent.

Job Description

*Formal Methods  Validation Architect* *-* *709631*
Description



If you're interested in products going into future super computer markets
then the Intel® Many Integrated Core (Intel® MIC) Hardware Engineering
Group is the place for you!  We design and validate silicon chips with many
Intel cores integrated inside being used in high performance computing
architectures.



In this position you will work as part of the pre-silicon formal methods,
tools, and verification team to support a continued high quality of the
future Intel many core processor products. You will work together with
Intel's formal verification and validation community, the Formal
Verification Center of Expertise (FV CoE) in a team of experts in formal
methods and AV Validation.



Your specific responsibilities will include defining formal verification
(FV) test plans as well as Cluster Test Environment (CTE) based test plans
for dynamic simulation validation (DV). The goal is to help optimize a
combined use of FV and CTE based validation techniques (DV) and contribute
to an increasing use of formal methods at Intel. Based on the test plans
you will write properties in formal language, and prove the properties
using our model checkers and theorem proving tools. You will also write CTE
based test cases and coverage plans. Your area of strength may currently
lie within either FV or DV with strong skills rooted in software
development. But through your skills and work, you will become an expert in
both formal methods and validation technologies. You will interact very
closely with design teams, and other validation teams, as well as with
Intel's internal RD groups that continue to improve and develop formal
method and verification tools.



You must be able to communicate effectively with various technical groups
and coordinate activities amongst those groups.
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] Algebra in Haskell

2013-05-08 Thread Robert Goss

Dear all,

There are several libraries in haskell for abstract algebra but they 
don't seem to cover my use case I was wondering if other people have had 
similar issues and if there are any packages I am missing.


What I am prinicpaly interested in is operation on algebraic stuctures 
(homomorphisms, kernels, quotients, colimits, etc) whereas most algebra 
packages seem to just give operations on the elements of an algebraic 
structure.


So I would like to be able to write something like...

g = freeGroup([x,y])
h = freeGroup([z])
phi = grpMorphismOnGens([(x,z^6) , (y,z)])
k = grpKernel phi
(gens,rels) = grpPresentation (grpQuotient g k)




Thank you,

Robert Goss

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


Re: [Haskell-cafe] ANN: Robot - Simulate keyboard and mouse events under X11

2013-05-08 Thread Chris Wong
On Thu, May 9, 2013 at 4:47 AM, Niklas Hambüchen m...@nh2.me wrote:
 Hi,

 I just started using your library to move my cursor.

 Is it possible that it ignores negative values in moveBy?

 In other words, I can only move the cursor into one direction.

I did some research, and traced this to a bug in an old (1.6) version
of xcb-proto [1]. The coordinates were declared incorrectly as Word16,
instead of Int16 as they should have been. It's been fixed in
xcb-proto since 1.7.

I've cc'd Antoine Latter, the maintainer of XHB, about this bug. Once
he uploads a new version of XHB, I'll be happy to fix it on my end.

[1] 
http://cgit.freedesktop.org/~keithp/xcb-proto/commit/src/xtest.xml?id=f3ae971edce37ad96ef0b8a6059c1f853e88fcf3

On Tue, May 7, 2013 at 5:18 AM, Jeanne-Kamikaze
jeannekamik...@gmail.com wrote:
 Looks like an interesting library. Will it be able to read pixels from a
 window at some point?

Not sure -- I have no idea how screen capturing works in X11. Calling
gnome-screenshot should probably cover most use cases.

Chris

--
Chris Wong, fixpoint conjurer
  e: lambda.fa...@gmail.com
  w: http://lfairy.github.io/

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


[Haskell-cafe] ghci: Difference in garbage collection etc. between REPL and function

2013-05-08 Thread Niklas Hambüchen
I have an annoying bug in a C binding that can be triggered like this:


handle - open ...

prep - makePreparedStatement handle INSERT ...

performGC

runStatement prep

close handle

If I run these steps one by one in ghci, garbage ends up in my handle as
expected.

However, if I let main = do ... this whole block in order to pack it
in a test case, it does not happen, neither in ghci nor ghc.

What might be the special magic in ghci's REPL that allows me to trigger
my bug so easily there?

Thanks
Niklas


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


Re: [Haskell-cafe] ghci: Difference in garbage collection etc. between REPL and function

2013-05-08 Thread Jason Dagit
On Wed, May 8, 2013 at 6:54 PM, Niklas Hambüchen m...@nh2.me wrote:
 I have an annoying bug in a C binding that can be triggered like this:


 handle - open ...

 prep - makePreparedStatement handle INSERT ...

 performGC

 runStatement prep

 close handle

 If I run these steps one by one in ghci, garbage ends up in my handle as
 expected.

 However, if I let main = do ... this whole block in order to pack it
 in a test case, it does not happen, neither in ghci nor ghc.

 What might be the special magic in ghci's REPL that allows me to trigger
 my bug so easily there?

One thing to investigate: Thread Local Storage

By default ghci puts each action you run into a thread and executes
it. If the underlying C code stores something (or accesses it) from
thread local storage, then you will run into issues like this.

Try starting ghci with -fno-ghci-sandbox. If the bad behavior goes
away there, try running each step of your test case inside a forkIO
from ghc with the threaded RTS. If the problem disappears in ghci but
shows up with forkIO, then it's a pretty good indicator that it's
related to the way the C code uses thread local storage.

I hope that helps,
Jason

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


Re: [Haskell-cafe] ghci: Difference in garbage collection etc. between REPL and function

2013-05-08 Thread Jason Dagit
On Wed, May 8, 2013 at 8:12 PM, Jason Dagit dag...@gmail.com wrote:
 On Wed, May 8, 2013 at 6:54 PM, Niklas Hambüchen m...@nh2.me wrote:
 I have an annoying bug in a C binding that can be triggered like this:


 handle - open ...

 prep - makePreparedStatement handle INSERT ...

 performGC

 runStatement prep

 close handle

 If I run these steps one by one in ghci, garbage ends up in my handle as
 expected.

 However, if I let main = do ... this whole block in order to pack it
 in a test case, it does not happen, neither in ghci nor ghc.

 What might be the special magic in ghci's REPL that allows me to trigger
 my bug so easily there?

 One thing to investigate: Thread Local Storage

 By default ghci puts each action you run into a thread and executes
 it. If the underlying C code stores something (or accesses it) from
 thread local storage, then you will run into issues like this.

My point was meant to be, it's something to try but I have no idea if
it's going to be the issue here.

The caveat I forgot to add is: I've never seen the thread local
storage issue affect GC. In particular, ghc might be running a
finalizer in the case of individual actions because it doesn't know
you are about to use the handle?

Now that I think about it more, I suspect that is more likely to be the case.

Jason

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


[Haskell-cafe] Test access resources files in cabal-dev

2013-05-08 Thread Graham Berks
Hi, whats the recommended way to access a resource file for a test within 
cabal. 

I have a text file containing data that I use in a test and want to be able to 
access it in a root path independent manner.

Thanks 

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


[Haskell-cafe] Accessing resource files in tests

2013-05-08 Thread Graham Berks
Hi, whats the recommended way to access a resource file for a test within cabal.

I have a text file containing data that I use in a test and want to be able to 
access it in a root path independent manner.

Thanks 

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