Re: [Haskell-cafe] Can Haskell outperform C++?

2012-05-08 Thread Yves Parès
One thing that baffles me is the comparison Haskell V. Java:
http://shootout.alioth.debian.org/u32/benchmark.php?test=alllang=ghclang2=java

Would've expected always shorter code and better performances on average.

2012/5/8 Silvio Frischknecht silvio.fris...@gmail.com

 -BEGIN PGP SIGNED MESSAGE-
 Hash: SHA1

  Can anyone provide a code in Haskell that performs better in terms
  of execution speed than a well-written C/C++ program?

 http://shootout.alioth.debian.org/ compares a lot of programming
 languages on a lot of problems. Haskell is never as fast as C++, but
 for some problems it comes close.

 Also I challenge anyone to improve one of the haskell programs there.
 It'd be cool if we could make haskell get a higher rank. I recently
 managed to improve the Fasta algorithm, but not by much. Also I think
 the benchmarks don't use llvm flag. It says somewhere that they don't
 measure llvm because they don't have time. But I think they are
 refering to clang. So maybe someone should tell them to turn on the
 llvm flag since it makes a lot of haskell programs faster.

 Silvio
 -BEGIN PGP SIGNATURE-
 Version: GnuPG v1.4.11 (GNU/Linux)
 Comment: Using GnuPG with Mozilla - http://enigmail.mozdev.org/

 iQIcBAEBAgAGBQJPqKicAAoJEDLsP+zrbatWmSIP+gNSI61KMvY2VRsWRhd7+j5U
 YAO3CnBTt6lSbMNplFf5AZnbPnY3NVJSG2ZUN12n7ZcaOawmwub3H+N9e0XTXv38
 vOEGzFb/t/OTIx4GHXiWz6kZfzyiTVQpEhzoqx/ZX4KZqrUBt5ZuSpmWtPrPXCfF
 joCZiBZIwxfOkI/l1zsb8vW3Xaqxs9dfRQOJEf7GLB5zGXwUA2ZLWG5HYvAUHu0G
 9xB9cBgaX7HKdBwo3af2WZEFznZnZ1LUpc8TuacL54wVmLpLNJU2EaeqH2LsH0R3
 VxX9yU1TIQUBubDa1Tui73xJ2L4Ns7AVD7Kx14yK5cu61wpz/KeUOU/wgedp+wNe
 o54alfqzrfOC+GAJGJFg+3aIkXuij4j1jTXZ+/3ya7nofcBZwtqoZUWCvjYSoEaI
 xecxuHLCK2pd3zwPk7ZUnG0Mo0vu4ZpVKpCs4u8nPRzVl0101mGkHSVTVXjVP8R/
 d3AIPwy74B4nvCk9gohxHwtsvsmzxoRZr7E5XkGDTQdbj0Ly5bJfBW3c1X/jvq9c
 FHvxCspERGf6S+aX9L6lg9v3/aje/av2q0zUL7jizA4no3q7D/ZvWkmIWF5ySyRh
 +QrC39I6GHDMvxXn0HIp9m2226sNGL4vpvBTgucJWJcHUX+FdytFIe7VQ0ZvdXvx
 IjxCrgMAPVy5/TH44PP+
 =TaFj
 -END PGP SIGNATURE-

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

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


Re: [Haskell-cafe] Can Haskell outperform C++?

2012-05-08 Thread Simon Marlow

On 06/05/2012 07:40, Janek S. wrote:

a couple of times I've encountered a statement that Haskell programs
can have performance comparable to programs in C/C++. I've even read
that thanks to functional nature of Haskell, compiler can reason and
make guarantess about the code and use that knowledge to
automatically parallelize the program without any explicit
parallelizing commands in the code. I haven't seen any sort of
evidence that would support such claims. Can anyone provide a code in
Haskell that performs better in terms of execution speed than a
well-written C/C++ program? Both Haskell and C programs should
implement the same algorithm (merge sort in Haskell outperforming
bubble sort in C doesn't count), though I guess that using
Haskell-specific idioms and optimizations is of course allowed.


On the subject of parallelism in particular, there is no fully implicit
parallelism in Haskell at the moment.  When people ask about this I
typically point to this paper:

http://citeseerx.ist.psu.edu/viewdoc/summary?doi=10.1.1.145.8183

which shows that it is possible to get some gains doing this, but it is
hard and the gains were not great.


However, what Haskell does give you is a guarantee that you can safely
call any function in parallel (with itself or with something else), as
long as the function does not have an IO type.  This is about as close
to automatic parallelisation as you can practically get.  Take any pure
function from a library that someone else wrote, and you can use it with
parMap or call it from multiple threads, and reasonably expect to get a
speedup.  Furthermore with parMap you're guaranteed that the result will
be deterministic, and there are no race conditions or deadlocks to worry
about.

Cheers,
Simon

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


Re: [Haskell-cafe] Can Haskell outperform C++?

2012-05-08 Thread Daniël de Kok
On May 8, 2012, at 12:18 PM, Yves Parès wrote:
 Would've expected always shorter code

It's not so surprising if you consider that some of the programs are 
practically imperative programs in Haskell. To give an example:

http://shootout.alioth.debian.org/u32/program.php?test=fannkuchreduxlang=ghcid=3

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


[Haskell-cafe] Annotaing abstract syntax trees

2012-05-08 Thread José Romildo Malaquias
Hello.

I am reading Martijn's MSc Thesis Generic Selections of
Subexpressions, where one can found some discussions about annotating
abstract syntax trees (AST).

In order to follow the discussion I wrote the attached Haskell program,
which is an interpreter for an simple typed expression language. The
Annotations package is used.

The expression pattern is represented by a single recursive data
type. Annotations are used for positions in the input source, and also
for the type of expressions and subexpressions.

I would like somebody to review the code and comment on it, as I am not
sure I am using the concepts right.

Also I would like the type checker to produce an expression annotated
with both positions and calculated types. Currently it discards the
position annotations. Any sugestions on how to modify it is welcome.

Next step is adding a new form of expression to introduce local variable
bindings.

After that I want to start working with ASTs represented by mutually
recursive data types. Then I will need multirec...

Romildo
{-# LANGUAGE FlexibleContexts #-}

module Main where

import Control.Applicative (Applicative(pure,(*)),($),($),(*))
import Data.Traversable (Traversable(traverse))
import Data.Foldable (Foldable(foldr))
import Text.Parsec hiding (chainl1)
import Data.Char (isDigit,isAlpha,isAlphaNum)
import Data.Tree (Tree(Node),drawTree)

import Annotations.F.Fixpoints
import Annotations.F.Annotated
import Annotations.Except

-- the goal is to implement an interpreter for a simple language of
-- typed expressions using annotations on recursive data types

-- type of expressions
data ExprType
  = NUMERIC
  | LOGIC
  deriving (Show)

-- value of an expression
data ExprValue
  = Numeric Double
  | Logic Bool
  deriving (Show)

-- identifiers are strings
type Id = String

-- binary operators used in expressions
data Op
  = Add | Sub | Mul | Div -- arithmetic
  | Eq | Ne | Gt | Ge | Lt | Le   -- relational
  | And | Or  -- logical
  deriving (Show)

-- pattern of an expression
data ExprF r
  = Num Double -- numeric literal
  | Log Bool   -- logical literal
  | Var Id -- variable
  | Bin Op r r -- binary operation
  deriving (Show)

-- mapping a function over an expression pattern
instance Functor ExprF where
  fmap _ (Num n)  = Num n
  fmap _ (Log b)  = Log b
  fmap _ (Var v)  = Var v
  fmap f (Bin op x y) = Bin op (f x) (f y)

-- traversing an expression pattern
instance Traversable ExprF where
  traverse _ (Num n)  = pure (Num n)
  traverse _ (Log b)  = pure (Log b)
  traverse _ (Var v)  = pure (Var v)
  traverse f (Bin op x y) = Bin op $ f x * f y

-- folding an expression pattern
instance Foldable ExprF where
  foldr _ z (Num _)  = z
  foldr _ z (Log _)  = z
  foldr _ z (Var _)  = z
  foldr f z (Bin op l r) = f l (f r z)

-- bare expressions
newtype Expr
  = Expr { runExpr :: Fix ExprF }
  deriving (Show)


-- range of source positions: used to delimit where something appeared
-- in a source input
data Range
  = Range SourcePos SourcePos

instance Show Range where
  show (Range p1 p2)
| n1 == n2  = if null n1
  then showLC lc1 ++ - ++ showLC lc2
  else showN n1 ++   ++ showLC lc1 ++ - ++ showLC lc2
| otherwise = showN n1 ++   ++ showLC lc1 ++ - ++ showN n2 ++   ++ showLC lc2
where
  n1 = sourceName p1
  lc1 = (sourceLine p1,sourceColumn p1)
  n2 = sourceName p2
  lc2 = (sourceLine p2,sourceColumn p2)
  showN n = \ ++ n ++ \
  showLC (l,c) = show l ++ : ++ show c

-- expressions annoted with positions
newtype PosExpr
  = PosExpr { runPosExpr :: Fix (Ann Range ExprF) }
  deriving (Show)

-- convert an expression to a rose tree of strings
-- this helps to visualize the expression structure
exprTree :: Algebra ExprF (Tree String)
exprTree (Num n) = Node (Num:  ++ show n) []
exprTree (Log b) = Node (Log:  ++ show b) []
exprTree (Var v) = Node (Var:  ++ v) []
exprTree (Bin op l r) = Node (Bin:  ++ show op) [l,r]

-- convert an annotated expression to a tree of strings
-- this helps to visualize the annotated expression structure
annExprTree :: Show a = Algebra (Ann a ExprF) (Tree String)
annExprTree (Ann z expr) =
  case expr of
Num n  - Node (annot (Num:  ++ show n)) []
Log b  - Node (annot (Log:  ++ show b)) []
Var v  - Node (annot (Var:  ++ v)) []
Bin op l r - Node (annot (Bin:  ++ show op)) [l,r]
  where
annot x = x ++   ++ show z

-- a memory is just an association list between
-- variable names and values
type Memory = [(Id,ExprValue)]

-- an algebra to find the value of an expression annotated with
-- positions, given a memory
exprEval :: Memory - ErrorAlgebra ExprF String ExprValue
exprEval _ (Num n) = Right (Numeric n)
exprEval _ (Log b) = Right (Logic b)
exprEval m (Var v) = case lookup v m of
   Just x  - Right x;
   Nothing - Left (undefined 

[Haskell-cafe] anyone else driven mad by trying to setup a gmp free version of haskell platform?

2012-05-08 Thread Anatoly Yakovenko
i would really like to be able to ship haskell based linux binaries,
but the gmp dependency makes it virtually impossible.  so what version
of host os, host ghc, and haskell-platform sources are known to build
a working compiler?

any reason why the dependency on gmp is static?  are the interfaces
between versions actually different?  or can we build a version fo the
compiler that loads the library via dlopen on demand?

Thanks,
Anatoly

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


[Haskell-cafe] Unit and pair

2012-05-08 Thread MigMit
Hi café, a quick question.

Is there a somewhat standard class like this:

class Something c where
unit :: c () ()
pair :: c x y - c u v - c (x, u) (y, v)

?

I'm using it heavily in my current project, but I don't want to repeat somebody 
else's work, and it seems general enough to be defined somewhere; but my quick 
search on Hackage didn't reveal anything.

I know about arrows; this, however, is something more general, and it's 
instances aren't always arrows.
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Unit and pair

2012-05-08 Thread Felipe Almeida Lessa
On Tue, May 8, 2012 at 2:36 PM, MigMit miguelim...@yandex.ru wrote:
 Hi café, a quick question.

 Is there a somewhat standard class like this:

 class Something c where
    unit :: c () ()
    pair :: c x y - c u v - c (x, u) (y, v)

 ?

 I'm using it heavily in my current project, but I don't want to repeat 
 somebody else's work, and it seems general enough to be defined somewhere; 
 but my quick search on Hackage didn't reveal anything.

 I know about arrows; this, however, is something more general, and it's 
 instances aren't always arrows.

Are you aware of generalized arrows [1]? It's still a lot more than
your Something, though.

[1] http://www.cs.berkeley.edu/~megacz/garrows/

-- 
Felipe.

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


Re: [Haskell-cafe] Unit and pair

2012-05-08 Thread MigMit

On 8 May 2012, at 21:42, Felipe Almeida Lessa wrote:

 On Tue, May 8, 2012 at 2:36 PM, MigMit miguelim...@yandex.ru wrote:
 Hi café, a quick question.
 
 Is there a somewhat standard class like this:
 
 class Something c where
unit :: c () ()
pair :: c x y - c u v - c (x, u) (y, v)
 
 ?
 
 I'm using it heavily in my current project, but I don't want to repeat 
 somebody else's work, and it seems general enough to be defined somewhere; 
 but my quick search on Hackage didn't reveal anything.
 
 I know about arrows; this, however, is something more general, and it's 
 instances aren't always arrows.
 
 Are you aware of generalized arrows [1]? It's still a lot more than
 your Something, though.

I've heard of them, but some instances of my Something class aren't categories 
either, which rules out GArrows too.
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] Can Haskell outperform C++?

2012-05-08 Thread Isaac Gouy
2012/5/8 Silvio Frischknecht

Also I challenge anyone to improve one of the haskell programs there. It'd be 
cool if we could make haskell get a higher rank. I recently managed to 
improve the Fasta algorithm, but not by much. Also I think the benchmarks 
don't use llvm flag. It says somewhere that they don't measure llvm because 
they don't have time. But I think they are refering to clang. So maybe 
someone should tell them to turn on the llvm flag since it makes a lot of 
haskell programs faster.


Several GHC versions have come and gone since the Haskell benchmarks game 
programs were written, so perhaps it is time that a dozen new programs were 
written to replace those old programs - new programs that take advantage of GHC 
7.4.1 and -llvm.

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


[Haskell-cafe] Handcranked install of ghc / cabal-install and warning from ghc-pkg check

2012-05-08 Thread Graham Berks
Have installed 7.4.1 ghc and 0.14.0 cabal-install and then did alex, happy  
haddock.

When I do a ghc-pkg check I get 

$ ghc-pkg check
Warning: haddock-interfaces: 
/usr/local/Cellar/cabal-install/0.14.0/share/doc/random-1.0.1.1/html/random.haddock
 doesn't exist or isn't a file
Warning: haddock-html: 
/usr/local/Cellar/cabal-install/0.14.0/share/doc/random-1.0.1.1/html doesn't 
exist or isn't a directory
Warning: haddock-interfaces: 
/usr/local/Cellar/cabal-install/0.14.0/share/doc/zlib-0.5.3.3/html/zlib.haddock 
doesn't exist or isn't a file
Warning: haddock-html: 
/usr/local/Cellar/cabal-install/0.14.0/share/doc/zlib-0.5.3.3/html doesn't 
exist or isn't a directory
Warning: haddock-interfaces: 
/usr/local/Cellar/cabal-install/0.14.0/share/doc/HTTP-4000.2.3/html/HTTP.haddock
 doesn't exist or isn't a file
Warning: haddock-html: 
/usr/local/Cellar/cabal-install/0.14.0/share/doc/HTTP-4000.2.3/html doesn't 
exist or isn't a directory
Warning: haddock-interfaces: 
/usr/local/Cellar/cabal-install/0.14.0/share/doc/network-2.3.0.11/html/network.haddock
 doesn't exist or isn't a file
Warning: haddock-html: 
/usr/local/Cellar/cabal-install/0.14.0/share/doc/network-2.3.0.11/html doesn't 
exist or isn't a directory
Warning: haddock-interfaces: 
/usr/local/Cellar/cabal-install/0.14.0/share/doc/parsec-3.1.2/html/parsec.haddock
 doesn't exist or isn't a file
Warning: haddock-html: 
/usr/local/Cellar/cabal-install/0.14.0/share/doc/parsec-3.1.2/html doesn't 
exist or isn't a directory
Warning: haddock-interfaces: 
/usr/local/Cellar/cabal-install/0.14.0/share/doc/text-0.11.2.0/html/text.haddock
 doesn't exist or isn't a file
Warning: haddock-html: 
/usr/local/Cellar/cabal-install/0.14.0/share/doc/text-0.11.2.0/html doesn't 
exist or isn't a directory
Warning: haddock-interfaces: 
/usr/local/Cellar/cabal-install/0.14.0/share/doc/mtl-2.1/html/mtl.haddock 
doesn't exist or isn't a file
Warning: haddock-html: 
/usr/local/Cellar/cabal-install/0.14.0/share/doc/mtl-2.1/html doesn't exist or 
isn't a directory
Warning: haddock-interfaces: 
/usr/local/Cellar/cabal-install/0.14.0/share/doc/transformers-0.3.0.0/html/transformers.haddock
 doesn't exist or isn't a file
Warning: haddock-html: 
/usr/local/Cellar/cabal-install/0.14.0/share/doc/transformers-0.3.0.0/html 
doesn't exist or isn't a directory
Warning: haddock-interfaces: 
/usr/local/share/doc/haddock-2.10.0/html/haddock.haddock doesn't exist or isn't 
a file
Warning: haddock-html: /usr/local/share/doc/haddock-2.10.0/html doesn't exist 
or isn't a directory
Warning: haddock-interfaces: 
/usr/local/share/doc/xhtml-3000.2.0.5/html/xhtml.haddock doesn't exist or isn't 
a file
Warning: haddock-html: /usr/local/share/doc/xhtml-3000.2.0.5/html doesn't exist 
or isn't a directory
Warning: haddock-interfaces: 
/usr/local/share/doc/ghc-paths-0.1.0.8/html/ghc-paths.haddock doesn't exist or 
isn't a file
Warning: haddock-html: /usr/local/share/doc/ghc-paths-0.1.0.8/html doesn't 
exist or isn't a directory
Warning: haddock-interfaces: /usr/local/share/doc/mtl-2.1.1/html/mtl.haddock 
doesn't exist or isn't a file
Warning: haddock-html: /usr/local/share/doc/mtl-2.1.1/html doesn't exist or 
isn't a directory
Warning: haddock-interfaces: 
/usr/local/share/doc/transformers-0.3.0.0/html/transformers.haddock doesn't 
exist or isn't a file
Warning: haddock-html: /usr/local/share/doc/transformers-0.3.0.0/html doesn't 
exist or isn't a directory
Warning: haddock-interfaces: 
/usr/local/share/doc/QuickCheck-2.4.2/html/QuickCheck.haddock doesn't exist or 
isn't a file
Warning: haddock-html: /usr/local/share/doc/QuickCheck-2.4.2/html doesn't exist 
or isn't a directory
Warning: haddock-interfaces: 
/usr/local/share/doc/random-1.0.1.1/html/random.haddock doesn't exist or isn't 
a file
Warning: haddock-html: /usr/local/share/doc/random-1.0.1.1/html doesn't exist 
or isn't a directory


Any suggestions to fix this ? 

Thanks 

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


Re: [Haskell-cafe] Unit and pair

2012-05-08 Thread Daniel Peebles
FullBinaryTreeRelation? :P

On Tue, May 8, 2012 at 1:36 PM, MigMit miguelim...@yandex.ru wrote:

 Hi café, a quick question.

 Is there a somewhat standard class like this:

 class Something c where
unit :: c () ()
pair :: c x y - c u v - c (x, u) (y, v)

 ?

 I'm using it heavily in my current project, but I don't want to repeat
 somebody else's work, and it seems general enough to be defined somewhere;
 but my quick search on Hackage didn't reveal anything.

 I know about arrows; this, however, is something more general, and it's
 instances aren't always arrows.
 ___
 Haskell-Cafe mailing list
 Haskell-Cafe@haskell.org
 http://www.haskell.org/mailman/listinfo/haskell-cafe

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


Re: [Haskell-cafe] Unit and pair

2012-05-08 Thread Daniel Peebles
To expand on that, this class basically allows you to prove your
relation cholds pointwise across arbitrary binary trees, represented
by nested tuples
and terminated by ()s. If individual instances of the class had additional
ways of constructing values (i.e., proving the relation for the two type
parameters), then your trees could contain other types.

For example, if you had another type

data Iso a b = Iso (a - b) (b - a) -- the functions must be inverses

you could write an instance of Something for Iso and build a proof that ((),
(a, ((), b)) is isomorphic to ((), (c, ((), d)) given Iso a c and Iso
b dusing your class.

I'm not sure I'd bundle the two parts together, but I'd call your
pairmethod (or the class it lives in) something like congruent or
ProductsRespectThisRelation :)

Dan

On Tue, May 8, 2012 at 3:15 PM, Daniel Peebles pumpkin...@gmail.com wrote:

 FullBinaryTreeRelation? :P

 On Tue, May 8, 2012 at 1:36 PM, MigMit miguelim...@yandex.ru wrote:

 Hi café, a quick question.

 Is there a somewhat standard class like this:

 class Something c where
unit :: c () ()
pair :: c x y - c u v - c (x, u) (y, v)

 ?

 I'm using it heavily in my current project, but I don't want to repeat
 somebody else's work, and it seems general enough to be defined somewhere;
 but my quick search on Hackage didn't reveal anything.

 I know about arrows; this, however, is something more general, and it's
 instances aren't always arrows.
 ___
 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] bytestring, array and Safe Haskell

2012-05-08 Thread Francesco Mazzoli
Why are 
http://hackage.haskell.org/packages/archive/bytestring/0.9.2.1/doc/html/Data-ByteString-Unsafe.html 
and 
http://hackage.haskell.org/packages/archive/array/0.4.0.0/doc/html/Data-Array-Unsafe.html 
Safe-inferred?


The first one uses inlinePerformIO, so it clearly shouldn't be marked as 
Safe. Maybe Safe Haskell doesn't check that function?
The second is a bit messier since it uses unboxed types and primitive 
operations... But they clearly should be marked as Unsafe, and it 
surprises me that Safe Haskell is that relaxed when checking for safe 
functions.


Francesco.

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


Re: [Haskell-cafe] Unit and pair

2012-05-08 Thread MigMit
That's an interesting idea, thanks.

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

08.05.2012, в 23:31, Daniel Peebles pumpkin...@gmail.com написал(а):

 To expand on that, this class basically allows you to prove your relation c 
 holds pointwise across arbitrary binary trees, represented by nested tuples 
 and terminated by ()s. If individual instances of the class had additional 
 ways of constructing values (i.e., proving the relation for the two type 
 parameters), then your trees could contain other types.
 
 For example, if you had another type
 
 data Iso a b = Iso (a - b) (b - a) -- the functions must be inverses
 
 you could write an instance of Something for Iso and build a proof that ((), 
 (a, ((), b)) is isomorphic to ((), (c, ((), d)) given Iso a c and Iso b d 
 using your class.
 
 I'm not sure I'd bundle the two parts together, but I'd call your pair method 
 (or the class it lives in) something like congruent or 
 ProductsRespectThisRelation :)
 
 Dan
 
 On Tue, May 8, 2012 at 3:15 PM, Daniel Peebles pumpkin...@gmail.com wrote:
 FullBinaryTreeRelation? :P
 
 On Tue, May 8, 2012 at 1:36 PM, MigMit miguelim...@yandex.ru wrote:
 Hi café, a quick question.
 
 Is there a somewhat standard class like this:
 
 class Something c where
unit :: c () ()
pair :: c x y - c u v - c (x, u) (y, v)
 
 ?
 
 I'm using it heavily in my current project, but I don't want to repeat 
 somebody else's work, and it seems general enough to be defined somewhere; 
 but my quick search on Hackage didn't reveal anything.
 
 I know about arrows; this, however, is something more general, and it's 
 instances aren't always arrows.
 ___
 Haskell-Cafe mailing list
 Haskell-Cafe@haskell.org
 http://www.haskell.org/mailman/listinfo/haskell-cafe
 
 
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] bytestring, array and Safe Haskell

2012-05-08 Thread Austin Seipp
The reasoning is outlined in the user manual here:

http://www.haskell.org/ghc/docs/7.4.1/html/users_guide/safe-haskell.html#safe-inference

Basically, these modules will compile without error if they were to be
compiled with -XSafe enabled. Thus, they are safe-inferred. The check
does not scrutinize individual functions in any way; all of SH works
on the level of module boundaries, as well as packages (whether or not
to enforce package trust when compiling clients.) As to why they are
safe-inferred, considering they are importing primitive
libraries/modules, and the module inlinePerformIO lives in should be
marked unsafe, well, I don't know. This is just a simple check, and
anything more powerful would likely be considerably more complex and
difficult to get right.

They should be marked as -XUnsafe since their use in a safe program
could cause crashes. It's likely not a conscious choice that this is
the case, as much as it is probably an oversight. Many of the core
libraries have needed refactoring/changes at the module level due to
Safe Haskell (and hence there is now a proliferation of *.Unsafe and
*.Safe modules, a la ForeignPtr.)

I do not know if the next major version of the ByteString library
(0.10) or array has marked these as unsafe or not. They should be if
not.

Perhaps someone else who's more aware of the new Safe Haskell design
can comment further.

On Tue, May 8, 2012 at 3:03 PM, Francesco Mazzoli f...@mazzo.li wrote:
 Why are
 http://hackage.haskell.org/packages/archive/bytestring/0.9.2.1/doc/html/Data-ByteString-Unsafe.html
 and
 http://hackage.haskell.org/packages/archive/array/0.4.0.0/doc/html/Data-Array-Unsafe.html
 Safe-inferred?

 The first one uses inlinePerformIO, so it clearly shouldn't be marked as
 Safe. Maybe Safe Haskell doesn't check that function?
 The second is a bit messier since it uses unboxed types and primitive
 operations... But they clearly should be marked as Unsafe, and it surprises
 me that Safe Haskell is that relaxed when checking for safe functions.

 Francesco.

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



-- 
Regards,
Austin

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


Re: [Haskell-cafe] bytestring, array and Safe Haskell

2012-05-08 Thread Francesco Mazzoli

On 08/05/12 21:45, Austin Seipp wrote:

The reasoning is outlined in the user manual here:

http://www.haskell.org/ghc/docs/7.4.1/html/users_guide/safe-haskell.html#safe-inference


Yes, I was looking at that while writing that message.

Mine wasn't that much a complaint regarding the wrong inference (even if 
it looks like  it should be possible to fix the inference those instance 
- especially the bytestring one), but rather regarding the fact that 
those modules should be marked unsafe manually.


Francesco.

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


Re: [Haskell-cafe] Unit and pair

2012-05-08 Thread Tony Morris
On 09/05/12 03:49, MigMit wrote:
 On 8 May 2012, at 21:42, Felipe Almeida Lessa wrote:

 On Tue, May 8, 2012 at 2:36 PM, MigMit miguelim...@yandex.ru wrote:
 Hi café, a quick question.

 Is there a somewhat standard class like this:

 class Something c where
unit :: c () ()
pair :: c x y - c u v - c (x, u) (y, v)

 ?

 I'm using it heavily in my current project, but I don't want to repeat 
 somebody else's work, and it seems general enough to be defined somewhere; 
 but my quick search on Hackage didn't reveal anything.

 I know about arrows; this, however, is something more general, and it's 
 instances aren't always arrows.
 Are you aware of generalized arrows [1]? It's still a lot more than
 your Something, though.
 I've heard of them, but some instances of my Something class aren't 
 categories either, which rules out GArrows too.
 ___
 Haskell-Cafe mailing list
 Haskell-Cafe@haskell.org
 http://www.haskell.org/mailman/listinfo/haskell-cafe
data-lens has something similar (Tensor):

http://hackage.haskell.org/packages/archive/data-lens/2.10.0/doc/html/Control-Category-Product.html

-- 
Tony Morris
http://tmorris.net/



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


Re: [Haskell-cafe] Fixed point newtype confusion

2012-05-08 Thread Sebastien Zany
Hmm, I don't understand how that would work.


I wish I could define something like this:

class (Functor f) = Fixpoint f x | x - f where
fix :: x - Fix f

instance (Functor f) = Fixpoint f (forall a. f a) where
fix = id

instance (Functor f, Fixpoint f x) = Fixpoint f (f x) where
fix = Fix . fmap fix


but instances with polymorphic types aren't allowed. (Why is that?)


Alternatively if I could write a function that could turn

e :: forall a. F (F (F ... (F a) ... ))


into

specialize e :: F (F (F ... (F X) ... ))


that would work too, but I don't see how that's possible.

On Mon, May 7, 2012 at 6:59 PM, wren ng thornton w...@freegeek.org wrote:

 On 5/7/12 8:55 PM, Sebastien Zany wrote:

 To slightly alter the question, is there a way to define a class

  class (Functor f) =  Fixpoint f x where
 ...


 You can just do that (with MPTCs enabled). Though the usability will be
 much better if you use fundeps or associated types in order to constrain
 the relation between fs and xs. E.g.:

-- All the following require the laws:
--  fix . unfix == id
--  unfix . fix == id

-- With MPTCs and fundeps:
class (Functor f) = Fixpoint f x | f - x where
fix   :: f x - x
unfix :: x - f x

class (Functor f) = Fixpoint f x | x - f where
fix   :: f x - x
unfix :: x - f x

class (Functor f) = Fixpoint f x | f - x, x - f where
fix   :: f x - x
unfix :: x - f x

-- With associated types:
-- (Add a type/data family if you want both Fix and Pre.)
class (Functor f) = Fixpoint f where
type Fix f :: *
fix   :: f (Fix f) - Fix f
unfix :: Fix f - f (Fix f)

class (Functor f) = Fixpoint f where
data Fix f :: *
fix   :: f (Fix f) - Fix f
unfix :: Fix f - f (Fix f)

class (Functor (Pre x)) = Fixpoint x where
type Pre x :: * - *
fix   :: Pre x x - x
unfix :: x - Pre x x

class (Functor (Pre x)) = Fixpoint x where
data Pre x :: * - *
fix   :: Pre x x - x
unfix :: x - Pre x x

 Indeed, that last one is already provided in the fixpoint[1] package,
 though the names are slightly different. The differences between using x
 - f, f - x, or both, and between using data or type, are how it
 affects inference. That is, implicitly there are two relations on types:

Fix \subseteq * \cross *
Pre \subseteq * \cross *

 And we need to know: (1) are these relations functional or not? And, (2)
 are they injective or not? The answers to those questions will affect how
 you can infer one of the types (f or x) given the other (x or f).


 [1] 
 http://hackage.haskell.org/**package/fixpointhttp://hackage.haskell.org/package/fixpoint


 --
 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] Fixed point newtype confusion

2012-05-08 Thread Sebastien Zany
Er, sorry – fix = id should be fix = Fix.

On Tue, May 8, 2012 at 5:24 PM, Sebastien Zany 
sebast...@chaoticresearch.com wrote:

 Hmm, I don't understand how that would work.


 I wish I could define something like this:

 class (Functor f) = Fixpoint f x | x - f where
 fix :: x - Fix f

 instance (Functor f) = Fixpoint f (forall a. f a) where
 fix = id

  instance (Functor f, Fixpoint f x) = Fixpoint f (f x) where
 fix = Fix . fmap fix


 but instances with polymorphic types aren't allowed. (Why is that?)


 Alternatively if I could write a function that could turn

 e :: forall a. F (F (F ... (F a) ... ))


 into

 specialize e :: F (F (F ... (F X) ... ))


 that would work too, but I don't see how that's possible.

 On Mon, May 7, 2012 at 6:59 PM, wren ng thornton w...@freegeek.orgwrote:

 On 5/7/12 8:55 PM, Sebastien Zany wrote:

 To slightly alter the question, is there a way to define a class

  class (Functor f) =  Fixpoint f x where
 ...


 You can just do that (with MPTCs enabled). Though the usability will be
 much better if you use fundeps or associated types in order to constrain
 the relation between fs and xs. E.g.:

-- All the following require the laws:
--  fix . unfix == id
--  unfix . fix == id

-- With MPTCs and fundeps:
class (Functor f) = Fixpoint f x | f - x where
fix   :: f x - x
unfix :: x - f x

class (Functor f) = Fixpoint f x | x - f where
fix   :: f x - x
unfix :: x - f x

class (Functor f) = Fixpoint f x | f - x, x - f where
fix   :: f x - x
unfix :: x - f x

-- With associated types:
-- (Add a type/data family if you want both Fix and Pre.)
class (Functor f) = Fixpoint f where
type Fix f :: *
fix   :: f (Fix f) - Fix f
unfix :: Fix f - f (Fix f)

class (Functor f) = Fixpoint f where
data Fix f :: *
fix   :: f (Fix f) - Fix f
unfix :: Fix f - f (Fix f)

class (Functor (Pre x)) = Fixpoint x where
type Pre x :: * - *
fix   :: Pre x x - x
unfix :: x - Pre x x

class (Functor (Pre x)) = Fixpoint x where
data Pre x :: * - *
fix   :: Pre x x - x
unfix :: x - Pre x x

 Indeed, that last one is already provided in the fixpoint[1] package,
 though the names are slightly different. The differences between using x
 - f, f - x, or both, and between using data or type, are how it
 affects inference. That is, implicitly there are two relations on types:

Fix \subseteq * \cross *
Pre \subseteq * \cross *

 And we need to know: (1) are these relations functional or not? And, (2)
 are they injective or not? The answers to those questions will affect how
 you can infer one of the types (f or x) given the other (x or f).


 [1] 
 http://hackage.haskell.org/**package/fixpointhttp://hackage.haskell.org/package/fixpoint


 --
 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] anyone else driven mad by trying to setup a gmp free version of haskell platform?

2012-05-08 Thread Greg Fitzgerald
 can we build a version of the compiler that loads [GMP] via dlopen on demand?

An explanation from well-typed:  http://www.well-typed.com/blog/32

But that was ~3 years ago.  Anybody still looking at possible solutions?

Maintaining the INTEGER_SIMPLE branch of GHC, minor as it is, is still
a pain.  If you follow the GHC recommendation of getting GHC from the
Haskell Platform distribution, it means finding the matching GHC
version, hoping you got all the build dependencies right, and then
either overlaying the result in the HP installation or pointing HP to
the new build.  Not a ton of work, but not something I want to do each
HP release.  What are other commercial users of GHC doing?

Thanks,
Greg


On Tue, May 8, 2012 at 8:07 AM, Anatoly Yakovenko aeyakove...@gmail.com wrote:
 i would really like to be able to ship haskell based linux binaries,
 but the gmp dependency makes it virtually impossible.  so what version
 of host os, host ghc, and haskell-platform sources are known to build
 a working compiler?

 any reason why the dependency on gmp is static?  are the interfaces
 between versions actually different?  or can we build a version fo the
 compiler that loads the library via dlopen on demand?

 Thanks,
 Anatoly

 ___
 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] LLVM M.D. source code?

2012-05-08 Thread Greg Fitzgerald
A paper, LLVM M.D.: A Denotational Translation Validator, mentions the
source code for LLVM M.D is available here:

http://llvm-md.seas.harvard.edu/

I can't seem to spot it there or on Hackage.  Anyone seen it?

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


[Haskell-cafe] [Q] multiparam class undecidable types - how to get this example to typecheck?

2012-05-08 Thread Matthias Fischmann


Hi everybody,

I am torturing the ghc type inference extensions, and I think i
managed to break something, either in ghc or (more likely) in my
brain:


| {-# language FlexibleInstances, MultiParamTypeClasses, UndecidableInstances 
#-}
| 
| module Main
| where
| 
| class Table table cell where
|   toLists :: table - [[cell]]
|   fromLists :: [[cell]] - table
| 
| instance Table [[cell]] cell where
|   toLists = id
|   fromLists = id
| 
| -- why i am using a class (not relevant for my question) -
| -- data FastTable a = FastTable ...
| -- instance Table (FastTable a) a where ...
| 
| instance (Table a c, Show c) = Show a where
|   showsPrec p t = showParen (p  10) $ showString fromLists  . shows 
(toLists t)


ghc 7.0.3 sais:


| Overlapping instances for Show [[cell0]]
|   arising from a use of `shows'
| Matching instances:
|   instance Show a = Show [a] -- Defined in GHC.Show
|   instance (Table a c, Show c) = Show a
| -- Defined at /home/mf/tmp/z.hs:18:10-38
| In the second argument of `(.)', namely `shows (toLists t)'


I would have thought that there is on overlap: the instance in my code
above defines how to show a table if the cell is showable; the
(allegedly) overlapping instance defines how to show lists of alpha if
alpha is showable.

So I was expecting the reduction to go something like:

 . table ~ [[cell]] (via whichever instance of class Table applies)
 . [[cell]] ~ [cell] (via instance Show a = Show [a])
 . [cell] ~ cell (via instance Show a = Show [a])


But it gets worse.  I decided to ignore the problem for now and be
happy with at least showing the first cell in the upper left corner of
the table:


| instance (Table a c, Show c) = Show a where
|   showsPrec p t = showParen (p  10) $ showString fromLists  . shows (head 
. head $ toLists t)


to that, ghc 7.0.3 sais:


| /home/mf/tmp/z.hs:19:66:
| Context reduction stack overflow; size = 21
| Use -fcontext-stack=N to increase stack size to N
|   $dShow :: Show c19
|   $dShow :: Show c18
| [...]


shouldn't type inference be able to determine that

|  ((head . head $ toLists t) :: c

and use the instance guaranteed by the instance declaration's class
constraint (Show c)?

I suspect that there should be a type annotation that would make this
approach possible, but even then I am curious what this behavior
means.

Should I upgrade to a more grown-up release of ghc?

Any hints or pointers appreciated.  (:

Thanks,
Cheers,
Matthias

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