Re: [Haskell-cafe] Writing functions over GADTs

2011-03-16 Thread Benedikt Huber

On 16.03.11 10:26, Dominic Mulligan wrote:

Dear all,

I'm working on a small proof assistant in Haskell.  In the logic that
I'm implementing it's very important that I distinguish between `large'
and `small' types for consistency reasons.  I have worked to get this
distinction reflected in my types with the use of GADTs, like so:


 data Type   :: * -  * where
SVariable :: Decoration -  Type Small
LVariable :: Decoration -  Type Large
[...]

 data ArgList :: * -  * where
Empty  :: ArgList a
SmallCons  :: Type Small -  ArgList a -  ArgList a
LargeCons  :: Type Large -  ArgList a -  ArgList Large

 Great, but one problem.  How do you write functions over these data
 types?  Consider as an example the function `toList', which drops an
 `ArgList a' down into a vanilla Haskell list `[a]'.

 Attempting a straightforward implementation like so:

 toList :: ArgList a -  [Type a]
 [...]
Hi Dominic,
As you noticed, this type signature is not correct.
Consider for example

toList (SmallCons t Empty :: ArgList Large)

t is of type 'Type Small', but the result needs to be a list with 
elements of type 'Type Large', i.e., of type [Type Large].


Also note that this instance would also need to typecheck:

toList (Empty :: ArgList Cookie) :: [Type Cookie]


My coworker showed me a way of doing this in O'Caml using polymorphic
variants.  This allows us to form a subtype of both `Small' and `Large'.
I'm taken to believe that HList can simulate many of the properties that
polymorphic variants enjoy, so perhaps the answer lies there?


There are many solutions to this problem in Haskell as well, but HList 
is probably not what you want.


Here is one variant, which is polymorphic in the type constructor 
parametrized over Small or Large:


-- For each t, Ex t is either (t Small) or (t Large)
data Ex :: (* - *) - * where
  ExS :: t Small - Ex t
  ExL :: t Large - Ex t
toList :: ArgList a - [Ex Type]
toList Empty   = []
toList (SmallCons h t) = ExS h : toList t
toList (LargeCons h t) = ExL h : toList t

As in your case, the datatype constructor tells you whether you are 
dealing with a small or large type, a more generic encoding of 
existentials would be fine too I guess:


data Ex :: (* - *) - * where
  Ex :: t a - Ex t

Kind Regards,
Benedikt

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


[Haskell-cafe] Re: String vs ByteString

2010-08-16 Thread Benedikt Huber

On 16.08.10 14:44, Daniel Fischer wrote:

Hi Bulat,
On Monday 16 August 2010 07:35:44, Bulat Ziganshin wrote:

Hello Daniel,

Sunday, August 15, 2010, 10:39:24 PM, you wrote:

That's great. If that performance difference is a show stopper, one
shouldn't go higher-level than C anyway :)


*all* speed measurements that find Haskell is as fast as C, was
broken.


That's a pretty bold claim, considering that you probably don't know all
such measurements ;)

[...]
If you are claiming that his test was flawed (and since the numbers clearly
showed Haskell slower than C, just not much, I suspect you do, otherwise I
don't see the point of your post), could you please elaborate why you think
it's flawed?

Hi Daniel,
you are right, the throughput of 'cat' (as proposed by Bulat) is not a 
fair comparison, and 'all speed measurements favoring haskell are 
broken' is hardly a reasonable argument. However, 'wc -m' is indeed a 
rather slow way to count the number of UTF-8 characters. Python, for 
example, is quite a bit faster (1.60s vs 0.93s for 70M) on my 
machine[1,2]. Despite of all this, I think the performance of the text 
package is very promising, and hope it will improve further!


cheers, benedikt

[1] A special purpose C implementation (as the one presented here: 
http://canonical.org/~kragen/strlen-utf8.html) is even faster (0.50), 
but that's not a fair comparison either.

[2] I do not know Python, so maybe there is an even faster way than
 print len(sys.stdin.readline().decode('utf-8'))
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] Re: ANN: weighted-regexp-0.1.0.0

2010-07-29 Thread Benedikt Huber

Sebastian Fischer schrieb:


On Jul 29, 2010, at 12:47 AM, Benedikt Huber wrote:

Taking a quick look at the PyPy blog post on JIT code generation for 
regular expressions, I thought it would be fun to implement a 
generator using the excellent LLVM bindings for haskell.


Interesting. Would you mind elaborating on your code? Maybe even write a 
blog about how it works?

Hi,
so the current implementation (a little bit cleaned up at
  http://github.com/visq/llvm-regexp
), works as follows:

It generates an LLVM function which matches a bytestring against a given 
 regular expression. The state of the 'automaton' consists of one bit for
each leaf of the regexp AST, corresponding to the marks in the article's 
figure. It then generates straight-line code updating the state given an 
input character (generateRegexpCode and matchCharSet in Text.RegExp.LLVM).


For example, for matching '.a' , the generated code looks like this in a 
simplified pseudo code notation:


 ... next ~ first character matched
 ... ch   ~ input character
   next1 = bitmask[0]  -- was '.' marked ?
   bitmask[0] = next   -- mark '.' if initial
   next2 = bitmask[1]  -- was 'a' marked ?
   bitmask[1] = ch == 'a'  next1 -- mark 'a' if '.' was marked 


-- and input is 'a'

At the end of the string, code is generated to check whether the 
automaton is in a final state (genFinalStateCheck). In the example 
above, this corresponds to


   final = bitmask[1]

The rest is either LLVM boilerplate (regexMatcher) or adaptions from 
weighed-regexp. Additionally, I've adapted the Parser.y from 
weighted-regexp, but some things (e.g. character classes like \w) are 
not implemented.


Generating one big basic block for the whole regular expressions does 
not work well when there are more than a few thousand nodes in the AST. 
Using functions for large regular expressions and loop for repititions 
would be one solution. The other problem is that the matcher only 
operates on Word8s at the moment.


Trying it out (if you have llvm+haskell bindings) is also easy (do not 
cabal-easy):


 $ git clone g...@github.com:visq/llvm-regexp.git  cd llvm-regexp
 $ make
 $ ./Grep '.*spotlight.*'  /etc/passwd
 Line 45 matches

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


[Haskell-cafe] Re: The 8 Most Important GSoC Projects

2010-04-02 Thread Benedikt Huber

Ivan Lazar Miljenovic schrieb:

Stephen Tetley stephen.tet...@gmail.com writes:

I had a little experiment along the lines of A Package Versioning
Policy Checker a few months ago. I got as far as using
Haskell-src-exts to extract module export list, but didn't work out
out a hashing scheme for the actual type signatures.


I've been thinking of doing something similar for a year or so now, but
there's one big problem that I can think of: how to deal with functions
that don't have an explicit type signature in the source.  My
understanding is that to derive these signatures at checking time
would require using something like the GHC API, which immediately
reduces the niceness and portability of such a tool/library.


I've done a brief experiment diffing APIs using the hoogle backend of 
haddock. While the hoogle files where not a perfect match, what are the 
drawbacks of using a haddock backend if you want to use a GHC API based 
approach?


However, the major problem with a GHC API based approach is that the 
result relies on the installed dependencies of the package. For example, 
it is hard to compute the API changes for older versions which do not 
build anymore. I also believe that inferring the type of an exported 
function is not a good idea for the PVPC, as this way the result is 
somewhat indeterministic, depending on installed dependencies.


Therefore it seems that a solution based on eg haskell-src-exts, which 
does not rely on correctly installed dependencies, is preferrable.


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


[Haskell-cafe] Re: fast, strongly typed heterogeneous collections

2010-02-19 Thread Benedikt Huber

Alberto G. Corona schrieb:

Hi

What is the speed of hProjectByLabel/s in Data.HList.Record? . The 
documentation in hackage 
http://hackage.haskell.org/packages/archive/HList/latest/doc/html/Data-HList-Record.html#t%3AH2ProjectByLabelsdoes 
not mention it. Perhaps this is because Hlist is designed for supposedly 
short records and this does not matter too much.
looking at the code I guess that everything in HList is O(n) because it 
uses type-level list structure, but I think that nothing prevents from 
using a type level balanced tree, Data.Map style, instead.


This would permit to implement large heterogeneous Maps with fast access 
and strongly typed. AFAIK, the alternative is to use a fast data 
container with data elements encapsulated within Data.Dynamic, that is 
weakly typed, produces type errors at runtime, which is unsatisfactory 
and dangerous.



Any comments?

Hi Alberto,
I think this idea isn't unreasonable, and I am curious whether it would 
pay off in practice. I think you are right with your O(n) guess for the 
standard HList implementation. Rebalancing the trees at the type level 
and mirroring the rebalancing efficiently at the term level could be a 
little bit tricky though. Btw, I found type-level functions to be more 
comfortable than type classes when playing with heterogenous lists.

cheers, benedikt







___
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: no sparks?

2009-12-20 Thread Benedikt Huber

Felipe Lessa schrieb:

On Mon, Dec 21, 2009 at 12:39:06AM +0100, Daniel Fischer wrote:

Am Sonntag 20 Dezember 2009 23:25:02 schrieb Jamie Morgenstern:

Also, I was wondering if something akin to a parallel or exists. By this,
I mean I am looking for a function which, given x : a , y : a, returns
either, whichever computation returns first.

This wouldn't be easy to reconcile with referential transparency.
You can do that in IO, roughly

m - newEmptyMVar
t1 - forkIO $ method1 = putMVar m
t2 - forkIO $ method2 = putMVar m
rs - takeMVar m
killThread t1
killThread t2
return rs

But in pure code, I think not.


There's 'unamb' in Hackage, however I think you should carefully
understand its implementation details before using it.  

Hello Jamie,
you might want to have a look at the implementation of `race` in the 
Conal's 'unamb' package:


http://hackage.haskell.org/packages/archive/unamb/0.2.2/doc/html/src/Data-Unamb.html#race

As your left and right branch do not neccessarily have the same result, 
you have to stay in the IO monad.

The function provided by that package is:

 amb :: a - a - IO a


Not that I use it myself.

Neither do I, btw.

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


[Haskell-cafe] Re: no sparks?

2009-12-20 Thread Benedikt Huber

Daniel Fischer schrieb:

Am Sonntag 20 Dezember 2009 23:25:02 schrieb Jamie Morgenstern:

Hello;

Also, I was wondering if something akin to a parallel or exists. By this,
I mean I am looking for a function which, given x : a , y : a, returns
either, whichever computation returns first.


This wouldn't be easy to reconcile with referential transparency.
You can do that in IO, roughly

m - newEmptyMVar
t1 - forkIO $ method1 = putMVar m
t2 - forkIO $ method2 = putMVar m
rs - takeMVar m
killThread t1
killThread t2
return rs


And in this case (returning (Maybe Proof)), you are not happy with any 
of the results, but with one of the proofs. So you would need something like


solve :: Ctx - Prop - Int - IO (Maybe Proof)
solve ctx goal n = amb leftRight rightLeft
  where
leftRight = m1 `mplus` m2
rightLeft = m2 `mplus` m1
m1 = (tryRight ctx goal n)
m2 = (tryLeft ctx goal n)

I think the idea of directly supporting this kind of thing is quite 
interesting.


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


[Haskell-cafe] Re: Why are these record accesses ambiguous

2009-06-06 Thread Benedikt Huber

Hi John,

The record field disambiguation only works if you
use the form

  C{ field-name = variable }

where C is a datatype constructor.
In your example you have to write

 let TypeA{ x = v } = getA
 print v

You're right, after type inference it is clear (for us) that x should
mean A.x, but this kind of reasoning (disambiguate names based on the
results of type inference) is not supported by ghc - and that's a good
thing, in my opinion, as otherwise it would be incredibly hard to find
the definition in scope.
There was a long thread on cafe on this subject.


cheers,
benedikt


John Ky schrieb:

Hi Luke,

You're right.  My code had a typo.  Unfortunately, I still get the same 
error whichever way I do it.


For example:

  {-# LANGUAGE DisambiguateRecordFields #-}
  import A
  import B
 
  main = do
 let xx = getA
 print (x xx)

and:

#!/usr/bin/env runhaskell

  {-# LANGUAGE DisambiguateRecordFields #-}
  import A
  import B
 
  main = do
 let xx = getA
 putStrLn $ show (x xx)

both give me:

test.lhs:8:22:
Ambiguous occurrence `x'
It could refer to either `A.x', imported from A at test.lhs:3:2-9
  (defined at A.hs:5:5)
  or `B.x', imported from B at test.lhs:4:2-9
  (defined at B.hs:5:5)

Any ideas?

$ ghc --version
The Glorious Glasgow Haskell Compilation System, version 6.10.3

Thanks,

-John

On Sat, Jun 6, 2009 at 6:41 PM, Luke Palmer lrpal...@gmail.com 
mailto:lrpal...@gmail.com wrote:


On Sat, Jun 6, 2009 at 1:48 AM, John Ky newho...@gmail.com
mailto:newho...@gmail.com wrote:

Hi Haskell Cafe,

In the following code, I get an error saying Ambiguous
occurrence `x'.  Why can't Haskell work out which x to call
based on the type of getA?

Thanks

-John

#!/usr/bin/env runhaskell

  {-# LANGUAGE DisambiguateRecordFields #-}
  import A
  import B
 
  main = do
 let xx = getA
 putStrLn $ show x xx


This is parsed as two arguments passed to the show function (which
only takes one argument).

putStrLn $ show (x xx)

Or because putStrLn . show = print;

print $ x xx
 




--

module A where

data TypeA = TypeA
   { a :: Int
   , x :: Int
   }

getA = TypeA { a = 1, x = 2 }

-

module B where

data TypeB = TypeB
   { b :: Int
   , x :: Int
   }

getB = TypeB { b = 1, x = 3 }

--

./test.lhs:8:21:
Ambiguous occurrence `x'
It could refer to either `A.x', imported from A at
./test.lhs:3:2-9
  (defined at A.hs:5:5)
  or `B.x', imported from B at
./test.lhs:4:2-9
  (defined at B.hs:5:5)


___
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] Re: I have forgotten .. my bad

2009-05-15 Thread Benedikt Huber

Vasili I. Galchin schrieb:

Hello,

   darcs get --init ?? I want to pull down Data.FiniteMap. I 
have forgotten the path to Hackage .. I tried 

Hi Vasili,
Hackage does not host the darcs repositories.
You can get the FinitMap's source code via

 cabal unpack FiniteMap

though.

benedikt




 sudo darcs get http://hackage.haskell.org/ Data.FiniteMap
[sudo] password for vigalchin:
Invalid repository:  http://hackage.haskell.org

darcs failed:  Failed to download URL 
http://hackage.haskell.org/_darcs/inventory : HTTP error (404?)


??

Obviously the code I am cabalizing needs to be upgraded(i.e. not using 
deprecated packages) but first I want it to build!
 


Thanks,

Vasili





___
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: ANNOUNCE: Utrecht Haskell Compiler (UHC) -- first release

2009-04-19 Thread Benedikt Huber

Thomas Davie schrieb:

 On 19 Apr 2009, at 00:31, Antoine Latter wrote:

 ...
 Apparently a user install of uuagc and fgl isn't good enough.  Fun
 to know.

 I've found user installs don't work at all on OS X, various people in
 #haskell were rather surprised to discover this, so apparently it's
 not the default behavior on other platforms.

Why do user installs 'not work at all' on OS X ??

I'm on OS X 10.5, I always use cabal install (user), and never 
encountered any problems. The only caveat duncan mentioned is to pass 
--user to 'runhaskell Setup.hs' (which I never use, because there's cabal).


For me, following 'cabal install fgl uulib uuagc', uhc compiled without 
any problems. There is a small issue (5) with 'make install' though: The 
'bin' directory is not created if neccessary.



benedikt


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


[Haskell-cafe] Re: ANNOUNCE: Utrecht Haskell Compiler (UHC) -- first release

2009-04-19 Thread Benedikt Huber

a...@cs.uu.nl schrieb:

Utrecht Haskell Compiler -- first release, version 1.0.0



The UHC team is happy to announce the first public release of the
Utrecht Haskell Compiler (UHC).

Great to see another haskell compiler !


Features:

  * Experimental language extensions, some of which have not been
implemented before.

Maybe you could add a section 'Differences to GHC 6.10' to the manual ?

From a quick look, partial type signatures and local instances seem to 
be 'novel features', and there are some differences with respect to type 
/ kind inference.


Section 4.2 (Proposed in haskell prime but not in UHC) and Section 4.3 
(Available in UHC but not in Haskell98 or Haskell prime) are a little 
bit confusing (and imho superfluous):

- Many language extensions have been 'proposed' for haskell prime
  (http://hackage.haskell.org/trac/haskell-prime/wiki/Status).
- MPTCs are accepted for haskell prime
- 'Existential Quantification' is accepted for haskell prime, but 
different from 'Existential Types' described in the manual

- Functional Dependencies are not available in UHC ;)

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


[Haskell-cafe] Re: Performance question

2009-02-26 Thread Benedikt Huber

hask...@kudling.de schrieb:

Hi,

i have compared a C++ implementation with a Haskell implementation of the Monte 
Carlo Pi approximation:

http://lennart.kudling.de/haskellPi/

The Haskell version is 100 times slower and i wonder whether i do something 
obvious wrong.


Hi,
Nice benchmark, but I think the culprit is the random number generator.
For simplicity, here is a 1-1 translation of the C++ code:

 main =
do args - getArgs
   let samples = read $ head args
   randomNumbers - genRandoms
   print (monteCarlo samples randomNumbers)
 genRandoms :: IO [Double]
 genRandoms = liftM randoms getStdGen
 monteCarlo :: Int - [Double] - Double
 monteCarlo samples = go 0 samples where
 go cnt 0 _ = (4.0 :: Double) * (fromIntegral cnt) /
  (fromIntegral  samples)
 go cnt k (x:y:rs) | sqrt (x*x + y*y) = 1.0 = go (cnt+1) (k-1) rs
   | otherwise   = go cnt (k-1) rs

The profiling shows that most time is spend in genRandoms:

genRandoms Main 199 1  96.5   98.396.5   98.3

When replacing genRandoms by (repeat 0.5), the haskell code is only a 
little bit slower than the C++ code *with* random number generation.


Of course, the random number generation in C++ takes time too:

 montecarlo(0) $ pprof --text ./monte_carlo /tmp/profile
 Total: 6691 samples
3928  58.7%  58.7% 5965  89.1% _main
2134  31.9%  90.6% 2134  31.9% _do_rand
 435   6.5%  97.1%  435   6.5% _rand
 194   2.9% 100.0%  194   2.9% 0x3072
   0   0.0% 100.0% 6691 100.0% __mh_execute_header
   0   0.0% 100.0% 6691 100.0% start

But the factor 100 is clearly due to genRandoms.

cheers, benedikt


Profiling says that the majority of the time is spend in main. But i have no 
idea where.

Can someone give me a hint?

Thanks,
Lenny

   individual
inherited
COST CENTRE  MODULE   
no.entries  %time %alloc   %time %alloc

MAIN MAIN   
1   0   0.00.0   100.0  100.0
 mainMain 
254   1  88.1   90.8   100.0  100.0
  monteCarloPi   Main 
255   1   0.61.111.99.2
   pairs Main 
2571000   0.71.4 0.71.4
   countHits Main 
2561001   4.22.910.66.7
accumulateHitMain 
25827852236   3.02.3 6.43.8
 isInCircle  Main 
2593000   3.31.5 3.31.5
 CAF:lit_r1A7Main 
248   1   0.00.0 0.00.0
  isInCircle Main 
260   0   0.00.0 0.00.0


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


[Haskell-cafe] Re: Class Instances

2009-02-13 Thread Benedikt Huber
Cetin Sert schrieb:
 Hi,
 
 class Processor a where
   ready :: (forall b c. a → [b → c])
 
 instance Processor (b → c) where
   ready = repeat
 ...
 ---
 Why can I not declare the above instances and always get:
Hi Cetin,
in your class declaration you state that a (Processor T) provides a function
 ready :: T - [b - c]
so
 ready (t::T)
has type (forall b c. [b - c]), a list of functions from arbitrary
types b to c.

The error messages tell you that e.g.
 repeat (f :: t1 - t2)
has type
 (t1-t2) - [t1-t2]
and not the required type
 (t1-t2) - [a - b]

With your declarations,
 head (ready negate) hi
has to typecheck, that's probably not what you want.

 Is there a way around this?

Maybe you meant

 class Processor a where
   ready :: a b c - [b - c]
 instance Processor (-) where
   ready = repeat
 newtype FunList b c = FunList [b-c]
 instance Processor FunList where
   ready (FunList fl) = fl

I think the newtype FunList is neccessary here.
benedikt

 
 message.hs:229:10:
 Couldn't match expected type `b' against inferred type `b1'
   `b' is a rigid type variable bound by
   the instance declaration at message.hs:228:20
   `b1' is a rigid type variable bound by
the type signature for `ready' at message.hs:226:19
   Expected type: b - c
   Inferred type: b1 - c1
 In the expression: repeat
 In the definition of `ready': ready = repeat
 
 message.hs:229:10:
 Couldn't match expected type `c' against inferred type `c1'
   `c' is a rigid type variable bound by
   the instance declaration at message.hs:228:24
   `c1' is a rigid type variable bound by
the type signature for `ready' at message.hs:226:21
   Expected type: b - c
   Inferred type: b1 - c1
 In the expression: repeat
 In the definition of `ready': ready = repeat
 
 message.hs:232:10:
 Couldn't match expected type `b1' against inferred type `b'
   `b1' is a rigid type variable bound by
the type signature for `ready' at message.hs:226:19
   `b' is a rigid type variable bound by
   the instance declaration at message.hs:231:20
   Expected type: [b1 - c]
   Inferred type: [b - c1]
 In the expression: id
 In the definition of `ready': ready = id
 
 message.hs:232:10:
 Couldn't match expected type `c1' against inferred type `c'
   `c1' is a rigid type variable bound by
the type signature for `ready' at message.hs:226:21
   `c' is a rigid type variable bound by
   the instance declaration at message.hs:231:24
   Expected type: [b - c1]
   Inferred type: [b1 - c]
 In the expression: id
 In the definition of `ready': ready = id
 
 Is there a way around this?
 
 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


[Haskell-cafe] Re: Class Instances

2009-02-13 Thread Benedikt Huber
Cetin Sert schrieb:
 Thank you for your answer!
 
 This comes close to solving the problem but in the last line of the 
 above I want to be able to say:
 
 either
   print $ broadcast id [1..10]
 
 or
   print $ broadcast [ (x +) | x ← [1..10] ] [1..10]
 
 both need to be possible*.
 
 So is there a way to make the FunList disappear completely?
Hi Cetin,
yes, if you're willing to use multi-parameter typeclasses:
 class Processor p b c | p - b c where
  ready :: p - [b - c]
 instance Processor (b - c) b c where
  ready = repeat
 instance Processor [b - c] b c where
  ready = id
 broadcast :: Processor p b c = p - [b] - [c]

Maybe there are other possibilities as well.
--
benedikt

 
 Regards,
 Cetin
 
 P.S.: * broadcast is a dummy function, I need this for tidying up the 
 interface of a little experiment: http://corsis.blogspot.com/
 
 2009/2/13 Benedikt Huber benj...@gmx.net mailto:benj...@gmx.net
 
 Cetin Sert schrieb:
   Hi,
  
   class Processor a where
 ready :: (forall b c. a → [b → c])
  
   instance Processor (b → c) where
 ready = repeat
   ...
   ---
   Why can I not declare the above instances and always get:
 Hi Cetin,
 in your class declaration you state that a (Processor T) provides a
 function
   ready :: T - [b - c]
 so
   ready (t::T)
 has type (forall b c. [b - c]), a list of functions from arbitrary
 types b to c.
 
 The error messages tell you that e.g.
   repeat (f :: t1 - t2)
 has type
   (t1-t2) - [t1-t2]
 and not the required type
   (t1-t2) - [a - b]
 
 With your declarations,
   head (ready negate) hi
 has to typecheck, that's probably not what you want.
 
   Is there a way around this?
 
 Maybe you meant
 
   class Processor a where
 ready :: a b c - [b - c]
   instance Processor (-) where
 ready = repeat
   newtype FunList b c = FunList [b-c]
   instance Processor FunList where
 ready (FunList fl) = fl
 
 I think the newtype FunList is neccessary here.
 benedikt
 
  
   message.hs:229:10:
   Couldn't match expected type `b' against inferred type `b1'
 `b' is a rigid type variable bound by
 the instance declaration at message.hs:228:20
 `b1' is a rigid type variable bound by
  the type signature for `ready' at message.hs:226:19
 Expected type: b - c
 Inferred type: b1 - c1
   In the expression: repeat
   In the definition of `ready': ready = repeat
  
   message.hs:229:10:
   Couldn't match expected type `c' against inferred type `c1'
 `c' is a rigid type variable bound by
 the instance declaration at message.hs:228:24
 `c1' is a rigid type variable bound by
  the type signature for `ready' at message.hs:226:21
 Expected type: b - c
 Inferred type: b1 - c1
   In the expression: repeat
   In the definition of `ready': ready = repeat
  
   message.hs:232:10:
   Couldn't match expected type `b1' against inferred type `b'
 `b1' is a rigid type variable bound by
  the type signature for `ready' at message.hs:226:19
 `b' is a rigid type variable bound by
 the instance declaration at message.hs:231:20
 Expected type: [b1 - c]
 Inferred type: [b - c1]
   In the expression: id
   In the definition of `ready': ready = id
  
   message.hs:232:10:
   Couldn't match expected type `c1' against inferred type `c'
 `c1' is a rigid type variable bound by
  the type signature for `ready' at message.hs:226:21
 `c' is a rigid type variable bound by
 the instance declaration at message.hs:231:24
 Expected type: [b - c1]
 Inferred type: [b1 - c]
   In the expression: id
   In the definition of `ready': ready = id
  
   Is there a way around this?
  
   Regards,
   CS
  
  
  
 
  
   ___
   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] Re: Graph library, was: Haskell.org GSoC

2009-02-12 Thread Benedikt Huber

Daniel Kraft schrieb:

Don Stewart wrote:

- Graphs.


True graphs (the data structure) are still a weak point! There's no
canonical graph library for Haskell. 


That sounds interesting...  What do you mean by no canonical library? 
 Are there already ones but just no standard one?  But in this case, I 
don't think adding yet another one will help :D  Or isn't there a real 
general graph library?

I would also like to see a project working on a new graph library.
Currently, there is at least Data.Graph (just one Module, package 
containers), based on Array - adjacency lists, and the functional graph 
library (package fgl).


I think a good general purpose graph library is tricky though:
- There are lot of variants of graphs (trees, bipartite, acyclic, 
undirected, simple, edge labeled etc.), hard to find adequate and easy 
to use abstraction.

- There is no single 'best' implementation (mutable vs. unmutable etc.).
- Its hard to find good traversal and zipper abstractions, though fgl 
has some nice ones.
- The complexity of algorithms varies greatly depending on the 
particular kind of graph.

Anyway, that's why it is challenging and interesting.

If so, this would be a nice thing to do :)  I could look at existing 
ones (like Boost's graphs) to get a feeling for how an interface might 
look like and what functionality to implement.


BTW, is there some sort of project hosting specifically for such 
Haskell projects?  Or should I go with sourceforge (for instance) for 
developing this, if I gave it a try?

code.haskell.org / community.haskell.org
provides webspace, trac, mailing-list, darcs.

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


[Haskell-cafe] Re: Graph library, was: Haskell.org GSoC

2009-02-12 Thread Benedikt Huber

Daniel Kraft schrieb:

Benedikt Huber wrote:

I would also like to see a project working on a new graph library.
Currently, there is at least Data.Graph (just one Module, package 
containers), based on Array - adjacency lists, and the functional 
graph library (package fgl).


I don't know those, but functional graph library suggests it is meant 
to be something like what we're discussing here (and this is also what 
Google returns for Haskell + graph library).  What's the problem with it 
or in which way is it different?

(I hope the following explanation is correct, apologies otherwise)
The fgl is build upon the concept of Inductive Graphs, described in
Martin Erwig's Inductive Graphs and Functional Graph Algorithms
(http://web.engr.oregonstate.edu/~erwig/papers/InductiveGraphs_JFP01.pdf).
The basic idea is that for traversals, you don't mark visited notes,
but decompose the graph like that:

 (nodeContext,restGraph) = matchAny graph
 {- or -}
 (nodeContext,restGraph) = match nodeId graph

This is in some sense 'more functional' than relying on tables for 
marking visited nodes.

DFS e.g. is implemented as (comments for clarification)

 xdfsWith :: Graph gr = (Context a b - [Node]) - -- neighbours
 (Context a b - c) -  -- compute result
 [Node] -  -- start
 gr a b -  -- the graph
 [c]-- result list
 xdfsWith _ _ [] _ = [] -- no more nodes to visit
 xdfsWith _ _ _  g | isEmpty g = [] -- empty graph
 xdfsWith d f (v:vs) g =
   case match v g of-- decompose graph
   -- compute result, add neighbours to todo list, recursive dfs
   (Just c,g')  - f c:xdfsWith d f (d c++vs) g'
   -- Couldn't find node, continue
   (Nothing,g') - xdfsWith d f vs g'

There's certainly more to say about the fgl, just read the paper.

Now for many applications this is fine, and the fgl is indeed a fine 
library. But obviously there is some overhead in matching, and the API 
is sometimes a little difficult to understand. And it's not the only way 
to do graph algorithms in haskell.



I think a good general purpose graph library is tricky though:
- There are lot of variants of graphs (trees, bipartite, acyclic, 
undirected, simple, edge labeled etc.), hard to find adequate and easy 
to use abstraction.


Well, while an undirected tree / acyclic graph can obviously be 
represented as a tree structure

Acyclic graphs are not tree-like.
The point about trees is that sometimes it is useful to view them as 
general purpose graphs, so they should also be represented in a graph 
library. However, in my opionion the library should also have a 
specialized representation of trees, as most algorithms are much simpler 
(Like containers' Data.Tree).


all the others would resolve around 
having nodes and for each node a list of edges to neighbouring nodes; at 
least concept-wise, wouldn't they?
From an implementation point of view, yes, adjacency lists, as arrays 
or trees, and matrices.
But there is a wide range of possibilities for algorithms, from monadic 
implementations (using ST/UArray) to inductive graphs.
For efficient algorithms, somethink like Array's freeze/thaw seems to be 
a good idea, too.


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


[Haskell-cafe] Re: type metaphysics

2009-02-02 Thread Benedikt Huber

Ryan Ingram schrieb:

2009/2/2 Luke Palmer lrpal...@gmail.com:

However!  If we have a function f : Nat - Nat - Bool, we can construct the
diagonalization g : Nat - Bool as:  g n = not (f n n), with g not in the
range of f.  That makes Nat - Bool computably uncountable.


This is making my head explode.  How is g not in the range of f?

In particular, f is a program, which I can easily implement; given:


f is 'easy to implement' if it enumerates all functions, not just total 
ones. Otherwise, f is hard to implement ;)


In the first case, if we have (f n n) = _|_, then g n = not (f n n) = 
_|_ as well, so the diagonalization argument does not hold anymore.


But I do agree that proofs by contradiction do not map well to haskell ...

benedikt




compiler :: String - Maybe (Nat - Bool)
mkAllStrings :: () - [String]  -- enumerates all possible strings

I can write f as

f n = validPrograms () !! n
  where
validPrograms = map fromJust . filter isJust . map compiler . mkAllStrings

Now, in particular, mkAllStrings will generate the following string at
some index, call it stringIndexOfG:

source code for compiler
source code for mkAllStrings
source code for f
g n = not (f n n)

This is a valid program, so the compiler will compile it successfully,
and therefore there is some index validProgramIndexOfG less than or
equal to stringIndexOfG which generates this program.

But your argument seems to hold as well, so where is the contradiction?

  -- ryan


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


[Haskell-cafe] Re: C-like Haskell

2009-01-28 Thread Benedikt Huber

Ross Mellgren schrieb:
Duncan, I think you must have some magics -- on my machine the original 
code also takes forever.
Running with +RTS -S indicates it's allocating several gig of memory or 
more.


Applying some bang patterns gives me ~8s for 10^8 and somewhat more than 
a minute for 10^9:

Hi,
same here, with bang patterns ~100s / 1Mb but


The C program is quite fast:

r...@hugo:~$ time ./circ-orig
1302219321

looks wrong to me


real0m1.073s


cafe(0) $ time ./gauss
3141592649589764829
real0m17.894s

So my 32-bit machine is really slow ...

benedikt





On Wed, 2009-01-28 at 16:42 -0800, drblanco wrote:

I do already have the number I wanted, but was wondering how this 
could be
made faster, or even why it's so slow.  This is all on GHC 6.8.3 
under OS X

Intel, using ghc -O2.


I'm not exactly sure what's different, but for me it works pretty well.
I put back in the Int64 type signature.


For comparison, the C code below runs in 1 second.


You've got a faster machine than me :-)

I compiled both the Haskell and C versions to standalone executables
with ghc/gcc -O2 and ran them with time.

C version:
$ time ./circ
3141592649589764829

real0m2.430s
user0m2.428s
sys0m0.000s

Haskell version:
time ./circ2
3141592653589764829

real0m2.753s
user0m2.756s
sys0m0.000s


Not too bad I'd say! :-)

I was using ghc-6.10 for this test. It would appear that ghc-6.8 is a
bit slower, I get:

3141592653589764829

real0m5.767s
user0m5.768s
sys0m0.000s

Now the other difference is that I'm using a 64bit machine so perhaps
ghc just produces terrible code for Int64 on 32bit machines.

Duncan

___
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: The problem with Monads...

2009-01-13 Thread Benedikt Huber

Rafael Gustavo da Cunha Pereira Pinto schrieb:
Yes, I've read it twice, and it is a nice explanation that yes, the 
reader monad is an application and is a monad. How do I use it? Why not 
the function itself? How would the plumbing work in a real world example?

Hi Rafael,

First of all, I agree that the documentation for mtl should be improved.
Especially Control.Monad.RWS and Control.Monad.List really need some 
more information.


The documentation for the Reader and Identity monad are quite detailled 
though. They seem to be inspired by 
http://www.haskell.org/all_about_monads/, which also has documentation 
on Writer and Cont.


Control.Monad.List is a good example for the lack of documentation:
There is a single sentence at the beginning
 The List monad.
and then one declaration
 newtype ListT m a = ListT { runListT :: m [a] }
while the important information is hidden as one of many instance 
declarations:

 Monad m = Functor (ListT m)
 Monad m = MonadPlus (ListT m)

Btw, the quality of the examples in Control.Monad.Reader is debutable. 
From Example 1:


 -- The Reader monad, which implements this complicated check.
 calc_isCountCorrect :: Reader Bindings Bool
 calc_isCountCorrect = do
count - asks (lookupVar count)
bindings - ask
return (count == (Map.size bindings))

I think it is wrong (or weird at least) to call the function a 'Reader 
monad'; the name 'calc_isCountCorrect' is horrible too (because of the 
calc_ prefix),  Finally, implementing


 isCountCorrect :: Bindings - Bool
 isCountCorrect bs = (bs Map.! count) == Map.size bs

using the Reader monad will convince everybody _not_ to use it.

A suggestion: If license permits it, short versions of the articles on 
all_about_monads would make a great documentation for mtl (except for 
RWS and List, which are missing).


benedikt




BTW, the article is really great as an brief introduction to monad 
transformers. For the whole concept of monads, my all time favorite is 
The Haskell Programmer's Guide to the IO Monad by Stefan Klinger.


Chapters 14 to 19 of Real World Haskell also have a good introduction 
on the usage of the monads, but it lacks other monads, like the RWS or 
the Continuation...


See, that is my point. The mathematical concept of monads is very 
palatable. The idea that monads are either patterns or structures to 
hide computations in sequence is also very easy to see. But how do we 
use them?

Why should I use a Writer monad when I can use a (a,w) tuple?



On Tue, Jan 13, 2009 at 13:51, Jonathan Cast jonathancc...@fastmail.fm 
mailto:jonathancc...@fastmail.fm wrote:


On Tue, 2009-01-13 at 12:56 -0200, Rafael Gustavo da Cunha Pereira Pinto
wrote:
 
  Last night I was thinking on what makes monads so hard to take, and
  came to a conclusion: the lack of a guided tour on the implemented
  monads.

...

  Inspired by the paper Functional Programming with Overloading and
  Higher-Order Polymorphism,
  Mark P Jones
  (http://web.cecs.pdx.edu/~mpj/pubs/springschool.html
http://web.cecs.pdx.edu/%7Empj/pubs/springschool.html)
Advanced School of Functional Programming, 1995.
 
  SO WHAT?

So have you read Jones' paper?  Or do you have a *concrete* explanation
of how it differs from your desired `guided tour'?

jcc





--
Rafael Gustavo da Cunha Pereira Pinto
Electronic Engineer, MSc.




___
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: Parsec : Problems with operator precedence (solution)

2009-01-02 Thread Benedikt Huber

Erik de Castro Lopo schrieb:

Erik de Castro Lopo wrote:


binaryOp :: String - (SourcePos - a - a - a) - E.Assoc - E.Operator 
Char st a
binaryOp name con assoc =
E.Infix (reservedOp name 
getPosition =
return . con) assoc


Replacing reservedOp above with:

reservedOpNf :: String - CharParser st ()
reservedOpNf name = try (reservedOp name  notFollowedBy (oneOf |=))

fixed the problem.


Hi Erik,
There is an easy, better solution, modifying the lexer:

 lexer = makeTokenParser $ emptyDef
   { L.reservedOpNames = words  ||  | ^ }
 reservedOp = P.reservedOp lexer
 identifier = P.identifier lexer
 ...

I'd try to avoid 'try', if possible.

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


[Haskell-cafe] Re: Parsec question

2008-12-23 Thread Benedikt Huber

Erik de Castro Lopo schrieb:

Erik de Castro Lopo wrote:


qualifiedIdentifier :: CharParser st [ String ]


Ahh, figured it out myself:

qualifiedIdentifier :: CharParser st [ String ]
qualifiedIdentifier = do
i - identifier
r - dotIdentifier
return (i : r)
where
dotIdentifier = do
char '.'
i - identifier
r - dotIdentifier
return (i  : r)
| return []

Does that look sane to people who know Haskell and Parsec
better than  me?

Hi Erik,
have a look at the module Text.ParserCombinators.Parsec.Combinator.
Those functions should help you to build up parsers from smaller 
building blocks.


Using sepBy1, the above parser can be written as

dot = T.dot lexer
qualifiedIdentifier = sepBy1 identifier dot

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


[Haskell-cafe] Re: Pretty Print, text or ++?

2008-08-15 Thread Benedikt Huber

Paul Keir schrieb:
 Hi there,

 I'm writing a pretty printer using the Text.PrettyPrint library, and
 there's a pattern I'm coming across quite often. Does anyone know 
whether,


 text (a ++ b ++ c ++ d)
 or
 text a + text b + text c + text d

 runs quicker?

Hi Paul,

 text (a ++ b ++ c ++ d)

is the same as

 hcat (map text [a,b,c,d])

(horizontal concatenation without seperating spaces)
while

 text a + text b + text c + text d

corresponds to

 hsep (map text [a,b,c,d])

or

 text (unwords [a,b,c,d])

With +, hsep or hcat, pretty printing won't choose the best layout -
you tell the pretty printer to layout documents 'beside'.
For autolayout, see sep,cat and the paragraph-fill variants fsep and fcat.

Regarding performance: `unwords` will propably be a little faster 
(untested), but less flexible. There is no asymptotic overhead when 
using the pretty printer.


cheers,
benedikt


 Cheers,
 Paul


 

 ___
 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] Fwd: ANN: Initial release of Language.C

2008-08-14 Thread Benedikt Huber

Hello,

I'm forwarding this to cafe, in case some of you are interested in  
this as well but not subscribed to libraries. Again, feedback is most  
welcome.


I've almost finished integrating Language.C with c2hs too (fixing a  
few bugs along the way), so there will be a quite complex example  
available soon.


Thanks for your interest.

Begin forwarded message to [EMAIL PROTECTED]:

From: Benedikt Huber [EMAIL PROTECTED]
Date: 13. August 2008 15:45:50 GMT+02:00


I'm pleased to announce the first release of Language.C, a library for  
analysing and generating C code.


This release features

  * A reasonably well tested parser handling and recording all of C99  
and most GNU extensions, most notably gcc's attribute syntax.


  * A pretty printer generating source code from the AST, covering  
the same language subset as the parser.


  * A preview of the analysis framework, including functionality for  
dissecting C's cruel type and variable declarations.


Places:

 * The project's homepage is located at http://www.sivity.net/projects/language.c 
 (Getting Started, Bug Tracker)


 * The package is available via hackage (language-c-0.3)

 * darcs repo: http://code.haskell.org/language-c

 * API docs: http://code.haskell.org/~bhuber/docs/language-c-latest/

The library originated from the C-related code in c2hs (http://www.cse.unsw.edu.au/~chak/haskell/c2hs/ 
), and is the topic of my SoC project, mentored by Iavor Diatchki.  
(Iavor, Don Steward and Duncan Coutts provided great support, thank you)


Feedback and suggestions in any form are most welcome, especially  
because there is a large range of features which could be implemented.  
The current status and a few ideas for the next releases are  
summarized at http://www.sivity.net/projects/language.c/wiki/ 
ProjectPlan.


best regards,
benedikt

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


[Haskell-cafe] Re: (Lazy) SmallCheck and peano numbers

2008-06-20 Thread Benedikt Huber

Levi Stephen schrieb:

On Fri, Jun 20, 2008 at 3:30 AM, Benedikt Huber [EMAIL PROTECTED] wrote:

Levi Stephen schrieb:

Hi,

I have the following definitions

type Zero
type Succ a

so that I can muck around with a Vector type that includes its length
encoded in its type.

I was wondering whether it was possible to use SmallCheck (or
QuickCheck) to generate random Peano numbers? Is there an issue here
in that what I actually want to generate is a type rather than a
value?

I do have

reifyInt :: Int - (forall a. ReflectNum a = a - b) - b

but, I'm not sure if this can help me when I need to generate other
values based upon that type (e.g., two vectors with the same size
type)

Hi Levi,

For QuickCheck, I know it is possible as long as you do not need to use type
level functions in your tests. For example, using Alfonso's type-level and
parametrized-data packages, one can write:


instance (Nat n, Arbitrary a) = Arbitrary (FSVec n a) where
   arbitrary =
 liftM (unsafeVector (undefined :: n)) $
   mapM (const arbitrary) [1..toInt (undefined :: n)]
propLength :: forall n a. (Nat n) = FSVec n Integer - Bool
propLength (FSVec xs) = P.length xs == toInt (undefined :: n)
propLengthEqual :: forall n a. (Nat n) =
   FSVec n Integer - FSVec n Integer - Bool
propLengthEqual v1 v2 = length v1 == length v2
tests1 = forM_ [0..100] $ \n - reifyIntegral n $ \(t :: ty) -
   quickCheck (propLength :: FSVec ty Integer - Bool)
tests2 = forM_ [0..100] $ \n - reifyIntegral n $ \(t :: ty) -
   quickCheck (uncurry propLengthEqual ::
(FSVec ty Integer,FSVec ty Integer) - Bool)


Thanks for the example code. Ideally it would be great to have n generated also.


Generating n isn't hard, in IO above you could just use Random.
But I assume you want to use QuickCheck, so see below.


Any thoughts on whether something like

propLengthEqual :: forall n a. (Nat n) = n - FSVec n Integer -
FSVec n Integer - Bool
propLengthEqual _ v1 v 2 = length v1 == length v2

with an arbitrary instance for generate all Nat n's is possible?


propLengthEqual is exactly the same as propLength, I just left out the 
first argument (it is redundant).


You cannot use an `Arbitrary' instance to generate some type level 
number, at least not in the same way as for ordinary numbers.


What you can do is introduce an existential type

 data SomeNat = forall n. (Nat n) = SomeNat Int n
 instance Show SomeNat where show (SomeNat value typ) = show value

 instance Arbitrary SomeNat where
arbitrary = sized $ \n - reifyIntegral n (return . SomeNat n)


If you look into the QuickCheck source, you'll find that a property
is a result generator: newtype Property = Prop (Gen Result)

So a property can be written as a result generator:

 propLength' :: SomeNat - Gen Result
 propLength' (SomeNat vn (n :: t)) = do
(vector :: FSVec t Integer) - arbitrary
buildResult [show vn , show vec] $ propLength vector

--
What follows next is the neccessary boilerplate to have a working example

 buildResult :: [String] - Bool - Gen Result
 buildResult args b = evaluate b = \r -
return $ r { arguments = show args : arguments r}
 natProp :: (SomeNat - Gen Result) - Property
 natProp f = flip forAll id $ do
(k::Int) - choose (0,10)
n - resize k arbitrary
f n
 deriving instance Show Result


Finally, run the tests

 tests = verboseCheck (natProp propLength')

Hope that helps.


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


[Haskell-cafe] Re: Meaning of ribbonsPerLine at Text.PrettyPrint.HughesPJ ?

2008-06-19 Thread Benedikt Huber

Evan Laforge schrieb:

byorgey: fons: I can't explain it, all I know is that you must set it
to 1 or else it does bizarre things
fons: hahah, ok
fons: byorgey: that's funny considering its default value is 1.5
byorgey: if you set it to 1 then lineLength means what you think it should
byorgey: fons: EXACTLY


Excellent, thanks for solving a nagging problem I couldn't be bothered
to track down.  I was wondering why my pretty printing was a little
messed up and slightly too wide.

And isn't 100 columns a bit non-standard for a default?  I thought 80
columns had more traction?  I know that's what my terminals are at...


Hi,

The ribbon length is used when choosing the most beautiful layout:
I'll just summarize the relevant section from John Hughes paper 
(http://www.cs.chalmers.se/~rjmh/Papers/pretty.ps), which explains it 
very nicely:


... Using [the criterion whether the text fits on the page] alone tends 
to produce layouts such as


 for i = 1 to 100; for j=1 to 100; for k=1 to 100; a[i][j][k]:=0;

which fits on a page {== line-width} but cannot be described as pretty. 
We therefore impose an additional constraint limiting the number of 
characters on each line [== ribbon-width} [...]


 for i = 1 to 100
 for j = 1 to 100
 ...


So the pretty printer tries to avoid sequences (ribbons) of characters 
which are longer than ribbon_length, when using auto layout stuff like 
`sep'.


In the source code, we have (paraphrased)

 ribbon_length = line_length / ribbonsPerLine

and

 choose_nicest_layout indent p q =
   if p + indent fits into line_length and p fits into ribbon_length
then p
else q

Working example below.

I'm not sure 80 characters is still standard when _pretty_-printing - 
the longest line in Text.PrettyPrint.HughesPJ is 109 characters wide ;)


Setting the ribbon ratio to 1 essentially disables the ribbon feature.

Btw: while studying the source code, I also found the cat (and sep) can 
be implemented in a more space efficient way (currently, cat needs to 
evaluate every document in a list to yield some output). Does this make 
sense (see below) ?


cheers,

benedikt


-- * ribbon example

 -- lineLength = 26, ribbonsPerLine = 1.5 == ribbonLength = 17
 -- therefore, we have a line break if width-indent  17 or width  26
 testStyle = Style { mode = PageMode,
lineLength = 26,
ribbonsPerLine = 1.5 }
 ribbonTest = renderStyle testStyle $

   -- use hsep as width == 17 = ribbonLength
   sep [ txt 5, txt 11 ]

   -- linebreak, as width-indent = width = 18  ribbonLength
   $+$ sep [ txt 5, txt 12 ]

   -- use hsep, as width - indent == 17, and width == 22  lineLength
   $+$ sep (map (nest 5) $ [txt 5, txt 11] )

   -- linebreak, as width would be 27  lineLength
   $+$ sep (map (nest 10) $ [txt 5, txt 11] )

 txt :: Int - Doc
 txt 0 = text 
 txt k = text $
  let ks = show k in
   (replicate (k - (length ks)) '_') ++ ks


-- * lazy variants of vcat and hcat
--   you need the constructors from the HughesPJ module

 vcat' = foldAbove . foldr vcomp2 empty
 hcat' = foldBeside . foldr hcomp2 empty

 foldAbove :: Doc - Doc
 foldAbove (Above Empty _ d2) = d2
 foldAbove (Above d1 f d2) = Above d1 f $ foldAbove d2
 foldAbove doc = doc

 vcomp2 :: Doc - Doc - Doc
 vcomp2 d1 Empty = d1
 -- do not match `vcomp2 Empty d1' !
 vcomp2 d1 d2 = Above d1 False d2

 foldBeside :: Doc - Doc
 foldBeside (Beside Empty _ d2) = d2
 foldBeside (Beside d1 f d2) = Beside d1 f $ foldBeside d2
 foldBeside doc = doc

 hcomp2 :: Doc  - Doc - Doc
 hcomp2 p Empty = p
 hcomp2 p q = Beside p False q

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


[Haskell-cafe] Re: (Lazy) SmallCheck and peano numbers

2008-06-19 Thread Benedikt Huber

Levi Stephen schrieb:

Hi,

I have the following definitions

type Zero
type Succ a

so that I can muck around with a Vector type that includes its length
encoded in its type.

I was wondering whether it was possible to use SmallCheck (or
QuickCheck) to generate random Peano numbers? Is there an issue here
in that what I actually want to generate is a type rather than a
value?

I do have

reifyInt :: Int - (forall a. ReflectNum a = a - b) - b

but, I'm not sure if this can help me when I need to generate other
values based upon that type (e.g., two vectors with the same size
type)


Hi Levi,

For QuickCheck, I know it is possible as long as you do not need to use 
type level functions in your tests. For example, using Alfonso's 
type-level and parametrized-data packages, one can write:


 instance (Nat n, Arbitrary a) = Arbitrary (FSVec n a) where
arbitrary =
  liftM (unsafeVector (undefined :: n)) $
mapM (const arbitrary) [1..toInt (undefined :: n)]

 propLength :: forall n a. (Nat n) = FSVec n Integer - Bool
 propLength (FSVec xs) = P.length xs == toInt (undefined :: n)

 propLengthEqual :: forall n a. (Nat n) =
FSVec n Integer - FSVec n Integer - Bool
 propLengthEqual v1 v2 = length v1 == length v2

 tests1 = forM_ [0..100] $ \n - reifyIntegral n $ \(t :: ty) -
quickCheck (propLength :: FSVec ty Integer - Bool)
 tests2 = forM_ [0..100] $ \n - reifyIntegral n $ \(t :: ty) -
quickCheck (uncurry propLengthEqual ::
 (FSVec ty Integer,FSVec ty Integer) - Bool)

It is also possible to reify type-level numbers with more context; I 
managed to get as far as (iirc)


 reifyPos :: Integer -
   (forall n. (Pos n, Succ n n', DivMod10 n nd nm) =
n - r) - r

This way you can test head, tail e.g., but I found it to be a lot of 
work to write additional reifications.


I do not know if it is possible (I think it is not) to have a 
reification which allows you to use total type level functions such as 
Add, e.g.


 tylvl = reifyIntegral? k $ \(n :: ty) - toInt (m :: Add ty D9)
 -- (D9 is the type level number 9)


I'm really curious what exactly would make this possible.

best regards,

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


[Haskell-cafe] Re: type-level integers using type families

2008-05-30 Thread Benedikt Huber

Peter Gavin schrieb:

Has anyone else tried implementing type-level integers using type families?

I tried using a couple of other type level arithmetic libraries 
(including type-level on Hackage) and they felt a bit clumsy to use.  I 
started looking at type families and realized I could pretty much build 
an entire Scheme-like language based on them.


In short, I've got addition, subtraction,  multiplication working after 
just a days worth of hacking. I'm going to post the darcs archive 
sometime, sooner if anyone's interested.


I really like the type-families based approach to this, it's a lot 
easier to understand, and you can think about things functionally 
instead of relationally.  (Switching back and forth between Prolog-ish 
thinking and Haskell gets old quick.) Plus you can do type arithmetic 
directly in place, instead of using type classes everywhere.


I tried to rewrite Alfonso Acosta's type-level library (the one on 
hackage) using type-families too, because, right, they are much nicer to 
use than MPTCs.


It is a straigtforward translation, I've uploaded it to

http://code.haskell.org/~bhuber/type-level-tf-0.2.1.tar.gz

now (relevant files: src/Data/TypeLevel/{Bool.hs,Num/Ops.hs}).

I've also added a type-level ackermann to torture ghc a little bit ;),
but left out logarithms. Plus, I did very little testing.


One thing that I'd like to be able to do is lazy unification on type instances, 
so that things like

data True
data False

type family Cond x y z
type instance Cond True y z = y
type instance Cond False y z = z 


I'm not sure if this is what you had in mind, but I also found that e.g.

 type instance Mod x y = Cond (y :: x) x  (Mod (Sub x y) y)

won't terminate, as

 Mod D0 D1 == Cond True D0 (Mod (Sub D0 D1) D0) == loop

rather than

 Mod D0 D1 == Cond True D0 ? == D0

For Mod, I used the following (usual) encoding:

 type family Mod' x y x_gt_y
 type instance Mod' x y False = x
 type instance Mod' x y True  = Mod' (Sub x y) y ((Sub x y) :=: y)
 type family Mod x y
 type instance Mod x y = Mod' x y (x :=: y)

There are few other things you cannot do with type families, and some 
for which you need type classes anyway (Alfonso pointed me to 
http://www.haskell.org/pipermail/haskell-cafe/2008-February/039489.html 
). Here's what I found:



1) One cannot define type equality (unless total type families become
available), i.e. use the overlapping instances trick:

instance Eq e e  True
instance Eq e e' False


Consequently, all type-level functions which depend on type equality
(see HList) need to be encoded using type classes.

2) One cannot use superclass contexts to derive instances e.g. to define

instance Succ (s,s') =  Pred (s',s)


In constrast, when using MPTC + FD, one can establish more than one TL 
function in one definition


 class Succ x x' | x - x', x' - x

3) Not sure if this is a problem in general, but I think you cannot 
restrict the set of type family instances easily.


E.g., if you have an instance

 type instance Mod10 (x :* D0) = D0

then you also have

 Mod10 (FooBar :* D0) ~ D0

What would be nice is something like

 type instance (IsPos x) = Mod10 (x :* D0) = D0

though

 type family AssertThen b x
 type instance AssertThen True x = x
 type instance Mod10 (x :* D0) = AssertThen (IsPos x) D0

seems to work as well.

4) Not really a limitation, but if you want to use instance methods of
Nat or Bool (e.g. toBool) on the callee site, you have to provide
context that the type level functions are closed w.r.t. to the type class:


test_1a :: forall a b b1 b2 b3.
  (b1 ~ And a b,
   b2 ~ Not (Or a b),
   b3 ~ Or b1 b2,
   Bool b3) = a - b - Prelude.Bool
test_1a a b = toBool (undefined :: b3)


Actually, I think the 'a ~ b' syntax is very nice.

I'm really looking forward to type families.

best regards,

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


[Haskell-cafe] Re: is there a more concise way to generate helper functions for a datatype built on records?

2007-11-28 Thread Benedikt Huber

apfelmus schrieb:

Benedikt Huber wrote:

So, the Ref deriviation is really nice for sequential updates;
parallel updates on the other hand need some work.
..
While the select part of the Ref is expressed using , I don't know
how the
parallel update can be expressed in terms of combinators. Any hints ?


You can't do that, and for good reason! While

  players :: Lens Game (Player,Player)

is entirely fine since  Game ~ (Player,Player,Object2D), there cannot be
a general parallel combinator

  () :: Lens a b - Lens a c - Lens a (b,c)


Thanks for the nice overview.
I see there can't be a general purpose combinator () for lenses.
One could still define a helper function though:

combineDisjoint :: Lens a b - Lens a c - Lens a (b,c)
combineDisjoint l1 l2 = Lens $ select  update
  where
select = (fst . focus l1)  (fst . focus l2)
update cx (a,b) = flip (snd . focus l2) b $ (snd . focus l1) cx a

which performs the first update using the initial context, and the
second one using the updated context. Just to have a simple way of
defining lensPlayers in term of lensPlayer1 `combineDisjoint`
lensPlayer2. While it is not a (general purpose) combinator, it is still
helpfull for combining lenses focusing on fields of a record.

--

I just want to rephrase my question about paralell updates; it has more
to do with records updates than with References / Lenses, though:

Suppose we have a record

data R = R { a:: A, b :: B, c :: C } deriving (Show {-! Ref !-})

and update functions

fa :: a - a, fb :: b - b, fc :: c - c

Now the standard way to perform the update on R would be

updateR = \r@(R {a=a,b=b,c=c}) - r { a = fa a,b = fb b,c = fc c }

which is 'a little bit' cumbersome.


With update deriviations (like Update using DrIFT), references (Ref 
using Data.Derive) or lenses it is easy to perform the update 
sequentially (using DrIFT style for simplicity):


updateR' = a_u fa . b_u fb . c_u fc

But this corresponds to

updateR' = (\f r - r { a = f (a r) }) fa .
   (\f r - r { b = f (b r) }) fb .
   (\f r - r { c = f (c r) }) fc

which (in some way) is not 'the same' as updateR.

First, I (uneducatedly) guess that the record updates cannot be 
'executed' in paralell, i.e. the record has to be deconstructed and 
build up again three times.
And second, neither the types of the updates (e.g. a_u fa :: R - R) nor 
the structure of updateR' (composing R-R functions) do reflect the fact

that actually disjoint fields of the record are updated.


Now I know there are great record proposals (which extend the haskell
language or use some type hackery), but I wondered if there is also a
solution which can be used right now and which works fine with the
standard record types.

I'll give a naive ad-hoc example to illustrate the idea.
One could automatically derive the following data type and the
associated functions for R:

data R_upd = R_upd { updA :: A - A, updB :: B - B, updC :: C - C }
rUpd = R_upd id id id
updR :: R_upd - R - R
updR rupd r@(R { a=a,b=b,c=c }) = r
  { a = (updA rupd a),
b = (updB rupd b),
c = (updC rupd c) }

which would allow to write things like

updGame $
  gameUpdate { updPlayer1 = increaseScore, updPlayer2 = decreaseScore })

Though simple, I hope it is possible to understand the idea (I know 
there is a lot of namespace pollution).

And of course, someone has thought of something much more sophistacted
already :)
What are the drawbacks of such an approach ?

thanks,
benedikt


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


[Haskell-cafe] Re: is there a more concise way to generate helper functions for a datatype built on records?

2007-11-26 Thread Benedikt Huber

Neil Mitchell wrote:
 Hi

 Some of these can be automatically derived by the Data.Derive tool...
 The derivations Set, Is, From, Has, LazySet all look useful.
 ...

 On Nov 24, 2007 4:01 PM, Thomas Hartman [EMAIL PROTECTED] wrote:
 I think I'm running into more or less the same issue discussed at

 http://bloggablea.wordpress.com/2007/04/24/haskell-records-considered-grungy/

 Just wondering if I missed anything, or if any of the ideas
 considering better records setter/getters have been implemented in  
the

 meantime.

Hi,
the Ref deriviation (included in Data.Derive) seems to be a good way  
to solve some aspects

of this problem; I have some questions on my own though.
Here is a working example of updating the two player's state in the  
pong game:


 {-# OPTIONS -cpp #-}
 {-# OPTIONS_DERIVE --output=file.h #-}
 module Main where
 import Control.Arrow
 #include file.h

Refs as in (http://www.haskell.org/pipermail/haskell-cafe/2007-June/026477.html 
):


 type Upd a = a - a
 data Ref cx t
 = Ref { select :: cx - t , update :: Upd t - Upd cx }
 (@.) :: Ref a b - Ref b c - Ref a c
 a @. b
 =  Ref { select = select b . select a,
  update = update a . update b }

The game model:

 data Object2D
  = Object2D { x :: Double, y :: Double } deriving (Show {-! Ref !-})
 data Player
 = Player { points :: Int, pos :: Object2D } deriving (Show {-!  
Ref !-})

 data Game
 = Game { p1 :: Player, p2 :: Player, ball :: Object2D } deriving  
(Show {-! Ref !-})

 sampleGame :: Game
 sampleGame = Game { p1 = Player 0 (Object2D 5 0), p2 = Player 0  
(Object2D 5 10), ball = Object2D 5 5 }


Game update proceeds in several steps, we now consider the first one:
Updating the 2 player's position - this happens, at least  
conceptually, *in paralell*
(for example: both players might be aloud to have a look at the other  
players position in the last turn, but

not at the updated position).

Here's the update for one player:

 updatePlayerPos :: Bool - Upd Player
 updatePlayerPos moveRight
  = update (refPos @. refX) $
case moveRight of
  True  - ((min 10) . (+1))
  False - ((max  0) . (+(-1)))

If sequential update is ok for us, the game state update is simply:

 updatePositions :: Bool - Bool - Upd Game
 updatePositions move1 move2 = update refP1 (updatePlayerPos  
move1) . update refP2 (updatePlayerPos move2)


To get it *actually* work in parallel we have to create a new  
reference for both players:


 refPlayers :: Ref Game (Player,Player)
 refPlayers = Ref { select = select refP1  select refP2,
update = \pu g - let (p1',p2') = pu (p1 g, p2  
g) in g { p1 = p1', p2 = p2' } }


While the select part of the Ref is expressed using , I don't know  
how the

paralell update can be expressed in terms of combinators. Any hints ?

Now, the game state update in the parallel version is easy. Note that  
it would also be possible now
to take one player's position into account when updating the other  
player's position:


 updatePositionsPar move1 move2 = (update refPlayers) $  
updatePlayerPos move1 *** updatePlayerPos move2


So, the Ref deriviation is really nice for sequential updates;
paralell updates on the other hand need some work.
Furthermore, I don't really know how well Refs work if updates
need information on other parts of the state without modifying it.
(e.g. the AI player needs to know where the ball is, but does not  
modify the ball).

I'd really appreciate if anyone has some additional clues.

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