Re: [haskell art] [Haskell-cafe] the library of beautiful instruments implemented in haskell / csound

2015-09-13 Thread Tom Murphy
These sound great, congratulations! "Batteries included" is a great place
to be. Can you point to references you used to create the instrument
definitions?

Tom


On Sun, Sep 13, 2015 at 9:13 AM, Anton Kholomiov <anton.kholom...@gmail.com>
wrote:

> Status update for my haskell synth csound-expression. The main point is
> presence of many cool instruments. They are implemented in the package
> csound-catalog. All packages are compiled with GHC-7.10 So the hackage
> fails to build them and unfortunately docs a broken too. But you can look
> at the source code of the module Csound.Patch to now  the names of the
> instruments. The usage is pretty straightforward. It's described here:
>
>
> https://github.com/spell-music/csound-expression/blob/master/tutorial/chapters/Patches.md
>
> There is an mp3 file to listen to the instruments.
> http://ge.tt/1jNETqN2/v/0
>
> *The 4.8.3 is out! New features:*
>
> This is a very important release to me. It tries to solve the problem
> present in the most open source music-production libraries. It's often the
> pack of beautiful sounds/timbres is missing. User is presented with many
> audio primitives but no timbres are present to show the real power of the
> framework. This release solves this problem. See the friend package
> csound-catalog on Hackage. It defines 200+ beautiful instruments ready to
> be used.
>
> The csound-expression defines a new type called Patch for description of
> an instrument with a chain of effects. It's good place to start the journey
> to the world of music production.
>
> There are new functions for synchronized reaction on events. The
> triggering of events can be synchronized with given BPM.
>
> The library is updated for GHC-7.10!
>
>
> github repo: https://github.com/spell-music/csound-expression
>
> hackage: http://hackage.haskell.org/package/csound-expression
>
>
> Cheers!
>
> ___
> Haskell-Cafe mailing list
> Haskell-Cafe@haskell.org
> http://mail.haskell.org/cgi-bin/mailman/listinfo/haskell-cafe
>
>

-- 

Read the whole topic here: Haskell Art:
http://lurk.org/r/topic/LXpcfpWIOB9FgiWYyp93a

To leave Haskell Art, email haskell-...@group.lurk.org with the following email 
subject: unsubscribe


[Haskell-cafe] Lenses that work with Arrows

2013-10-07 Thread Tom Ellis
Dear all,

I introduce a very simple extension to the Lens datatype from Control.Lens
that allows it to work with Arrows:

https://gist.github.com/tomjaguarpaw/6865080

I would particularly like to discuss this with authors of Control.Lens to
see if such an idea is suitable for inclusion in their library.

I have also started a Reddit discussion here:


http://www.reddit.com/r/haskell/comments/1nwetz/lenses_that_work_with_arrows/

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


Re: [Haskell-cafe] Lifting IO actions into Applicatives

2013-10-07 Thread Tom Ellis
On Mon, Oct 07, 2013 at 07:57:23PM +0400, Daniil Frumin wrote:
 Isn't it the case that there could be more than one natural transformation
 between functors?

Definitely.  In addition rwbarton responded to my challenge by finding two
different applicative morphisms between the same applicative, one which
extends to a monad morphism and one which does not:


http://www.reddit.com/r/haskell/comments/1ni8r6/should_it_be_monadio_applicativeio_functorio_or/ccjodj5

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


Re: [Haskell-cafe] Lenses that work with Arrows

2013-10-07 Thread Tom Ellis
On Mon, Oct 07, 2013 at 07:14:44PM +0200, Niklas Haas wrote:
 On Mon, 7 Oct 2013 10:40:13 +0100, Tom Ellis 
 tom-lists-haskell-cafe-2...@jaguarpaw.co.uk wrote:
  I introduce a very simple extension to the Lens datatype from Control.Lens
  that allows it to work with Arrows:
  
  https://gist.github.com/tomjaguarpaw/6865080
 
 The reason we don't tend to have combinators like ‘view’ or ‘over’
 generalized in their return profunctor like that is because you very
 quickly run into type ambiguity issues.

Perhaps I didn't explain clearly what I am asking for.  The crux of the
issue is whether it is possible *at all* to write the function

overArr :: Arrow arr = Lens s t a b - arr a b - arr s t

not whether it should be merged with over.

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


Re: [Haskell-cafe] Lenses that work with Arrows

2013-10-07 Thread Tom Ellis
On Mon, Oct 07, 2013 at 06:22:33PM +0100, Tom Ellis wrote:
 On Mon, Oct 07, 2013 at 07:14:44PM +0200, Niklas Haas wrote:
  On Mon, 7 Oct 2013 10:40:13 +0100, Tom Ellis 
  tom-lists-haskell-cafe-2...@jaguarpaw.co.uk wrote:
   I introduce a very simple extension to the Lens datatype from Control.Lens
   that allows it to work with Arrows:
   
   https://gist.github.com/tomjaguarpaw/6865080
  
  The reason we don't tend to have combinators like ‘view’ or ‘over’
  generalized in their return profunctor like that is because you very
  quickly run into type ambiguity issues.
 
 Perhaps I didn't explain clearly what I am asking for.  The crux of the
 issue is whether it is possible *at all* to write the function
 
 overArr :: Arrow arr = Lens s t a b - arr a b - arr s t
 
 not whether it should be merged with over.

Edward Kmett has answered in the affirmative, which pleases me greatly!


http://www.reddit.com/r/haskell/comments/1nwetz/lenses_that_work_with_arrows/ccmtfkj
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Any precedent or plan for guaranteed-safe Eq and Ord instances?

2013-10-02 Thread Tom Ellis
On Wed, Oct 02, 2013 at 11:24:39AM +0200, Heinrich Apfelmus wrote:
 I'm not sure whether the  Eq  instance you mention is actually
 incorrect. I had always understood that  Eq  denotes an equivalence
 relation, not necessarily equality on the constructor level.

There's a difference between implementors being able to distingush equals,
and application programmers.  Internal implementations are allowed to break
all sorts of invariants, but, by definition, APIs shouldn't.

Are there examples where application programmers would like there so be some
f, a and b such that a == b but f a /= f b (efficiency concerns aside)?  I
can't think of any obvious ones.

 One prominent example would be equality of Data.Map itself: two maps
 are equal if they contain the same key-value pairs,
 
 map1 == map2  =  toAscList map1 == toAscList map2
 
 but that doesn't mean that their internal representation -- the
 balanced tree -- is the same. Virtually all exported operations in
 Data.Map preserve this equivalence, but the library is, in
 principle, still able to distinguish equal maps.

I had a quick skim of 


http://www.haskell.org/ghc/docs/latest/html/libraries/containers/Data-Map-Lazy.html

to find such examples, and the only one that jumped out was showTree.  Are
there others?

Still, although the library is, in principle, able to distinguish equal
maps, isn't this just a leaking implementation detail?  Is it somehow of
benefit to API users?

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


Re: [Haskell-cafe] Any precedent or plan for guaranteed-safe Eq and Ord instances?

2013-10-02 Thread Tom Ellis
On Wed, Oct 02, 2013 at 03:46:42PM +0200, Stijn van Drongelen wrote:
 * Operators in Eq and Ord diverge iff any of their parameters are bottom.

What's the benefit of this requirement, as opposed to, for example

   False = _ = True
   ...

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


Re: [Haskell-cafe] Lifting IO actions into Applicatives

2013-10-01 Thread Tom Ellis
On Tue, Oct 01, 2013 at 09:29:00AM +0200, Niklas Haas wrote:
 On Tue, 1 Oct 2013 02:21:13 -0500, John Lato jwl...@gmail.com wrote:
  It's not a solution per se, but it seems to me that there's no need for the
  Monad superclass constraint on MonadIO.  If that were removed, we could
  just have
  
  class LiftIO t where
  liftIO :: IO a - t a
  
  and it would Just Work.
 
 One concern with this is that it's not exactly clear what the semantics
 are on LiftIO (is liftIO a  liftIO b equal to liftIO (a  b) or not?)
 and the interaction between LiftIO and Applicative/Monad would have to
 be some sort of ugly ad-hoc law like we have with Bounded/Enum etc.

Shouldn't it be an *Applicative* constraint?

class Applicative t = ApplicativeIO t where
liftIO :: IO a - t a

and require that

liftIO (pure x) = pure x
liftIO (f * x) = liftIO f * liftIO x

Seems like ApplicativeIO makes more sense than MonadIO, which is
unnecessarily restrictive.  With planned Functor/Applicative/Monad shuffle,
the former could completely replace the latter.

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


Re: [Haskell-cafe] Lifting IO actions into Applicatives

2013-10-01 Thread Tom Ellis
On Tue, Oct 01, 2013 at 12:11:23PM +0300, Roman Cheplyaka wrote:
  Shouldn't it be an *Applicative* constraint?
  
  class Applicative t = ApplicativeIO t where
  liftIO :: IO a - t a
  
  and require that
  
  liftIO (pure x) = pure x
  liftIO (f * x) = liftIO f * liftIO x
  
  Seems like ApplicativeIO makes more sense than MonadIO, which is
  unnecessarily restrictive.  With planned Functor/Applicative/Monad shuffle,
  the former could completely replace the latter.
 
 Agreed, this makes perfect sense. It simply says that liftIO is an
 applicative homomorphism.

Indeed.  A related question is whether, when m and m' are monads, an
applicative homomorphism between m and m' is automatically a monad
homomorphism.  That seems important in determining if one typeclass is
actually enough.

In fact we could go crazy and define

class Functor f = FunctorIO f where
liftIO :: IO a - f a

and require that

liftIO . fmap f = fmap f . liftIO

i.e. essentially that liftIO is a natural transformation between IO and f. 
I don't know whether there are simpler sufficient conditions that allow one
to determine that such an instance is also an applicative and monad
morphism.

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


Re: [Haskell-cafe] Lifting IO actions into Applicatives

2013-10-01 Thread Tom Ellis
On Tue, Oct 01, 2013 at 03:17:40PM +0300, Yitzchak Gale wrote:
 Tom Ellis wrote:
  Shouldn't it be an *Applicative* constraint?
 
  class Applicative t = ApplicativeIO t where
  liftIO :: IO a - t a
 
  and require that
 
  liftIO (pure x) = pure x
  liftIO (f * x) = liftIO f * liftIO x
 
  Seems like ApplicativeIO makes more sense than MonadIO, which is
  unnecessarily restrictive.  With planned Functor/Applicative/Monad shuffle,
  the former could completely replace the latter.
 
 In fact, it even makes sense to define it as FunctorIO, with the only laws
 being that liftIO commutes with fmap and preserves id, i.e., that it is
 a natural transformation. (Those laws are also needed for ApplicativeIO
 and MonadIO.)

I think that law follows automatically from parametricity, doesn't it?

 Since Haskell is not dependently typed and we specify laws only as
 human-readable comments, should we define only FunctorIO and
 then just specify in the comments the additional laws that should
 be satisfied for Applicative and Monad? Or should we have equivalent
 definitions that differ only in the laws that are expected to be satisfied?
 Or should the different definitions have different superclass constraints?

In tackling such questions I think it would be useful to know how many such
instances there can be.  Can there be more than one morphism between two
monads?  Between two applicatives?  I would guess there are plenty of
examples of functors with more than one functor morphism (natural
transformation) between them.

Perhaps these questions are easy, but I don't know how to approach them.

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


[Haskell-cafe] Product Profunctor and Contravariant

2013-09-29 Thread Tom Ellis
Does anyone recognise these typeclasses:

import Data.Profunctor (Profunctor)
import Data.Functor.Contravariant (Contravariant)

class Profunctor p = ProductProfunctor p where
  empty :: p () ()
  (***!) :: p a b - p a' b' - p (a, a') (b, b')

class Contravariant f = ProductContravariant f where
  point :: f ()
  (***) :: f a - f b - f (a, b)

They are both a bit like Applicative, and ProductProfunctor is basically
Arrow without the Category part.  I'm finding ProductProfunctor useful for
marshalling data from a database into Haskell, and both of them come up a
lot inside my database library.

Has anyone ever seen these before?  Has Edward Kmett written a library for
these already?  Thanks,

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


Re: [Haskell-cafe] Mystery of an Eq instance

2013-09-20 Thread Tom Ellis
On Fri, Sep 20, 2013 at 06:34:04PM +0200, Stijn van Drongelen wrote:
 Please find yourself a copy of What Every Computer Scientist Should Know
 About Floating-Point Arithmetic by David Goldberg, and read it. It should
 be very enlightening. It explains a bit about how IEEE754, pretty much the
 golden standard for floating point math, defines these precision rules.

Ah, this is definitely the best advice in the thread.
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Mystery of an Eq instance

2013-09-20 Thread Tom Ellis
On Fri, Sep 20, 2013 at 09:47:24PM +0530, damodar kulkarni wrote:
 Ok, let's say it is the effect of truncation. But then how do you explain
 this?
 
 Prelude sqrt 10.0 == 3.1622776601683795
 True
 Prelude sqrt 10.0 == 3.1622776601683796
 True
 
 Here, the last digit **within the same precision range** in the fractional
 part is different in the two cases (5 in the first case and 6 in the second
 case) and still I am getting **True** in both cases.

What do you mean the same precision range?  Notice:

Prelude 3.1622776601683795 == 3.1622776601683796
True
Prelude 3.1622776601683795 == 3.1622776601683797
True
Prelude 3.1622776601683795 == 3.1622776601683798
False

The truncation happens base 2, not base 10.  Is that what's confusing you?

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


Re: [Haskell-cafe] Bytestring map/zipWith rationale

2013-09-12 Thread Tom Ellis
On Thu, Sep 12, 2013 at 09:21:20AM -0400, Scott Lawrence wrote:
 Something's always bothered me about map and zipWith for ByteString. Why is it
 
 map :: (Word8 - Word8) - ByteString - ByteString
 
 but
 
 zipWith :: (Word8 - Word8 - a) - ByteString - ByteString - [a]

Well, what if you wanted to zipWith a function of type Word8 - Word8 -
Foo instead of Word8 - Word8 - Word8?

Tom

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


Re: [Haskell-cafe] Unary functions and infix notation

2013-09-06 Thread Tom Ellis
On Fri, Sep 06, 2013 at 05:04:12PM +0200, Johannes Emerich wrote:
 Weirdly, however, infix notation can also be used for unary functions with
 polymorphic types, as the following ghci session shows:
 
Prelude :t (`id` 1)
(`id` 1) :: Num a = (a - t) - t
Prelude (`id` 1) (\y - show y ++ .what)
1.what

There's nothing special about infix notation here:

Prelude :t \x - id x 1
\x - id x 1 :: Num a = (a - t) - t
Prelude (\x - id x 1) (\y - show y ++ .what)
1.what

Tom

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


Re: [Haskell-cafe] Strange IO sequence behaviour (Was: sequence causing stack overflow on pretty small lists)

2013-09-06 Thread Tom Ellis
On Wed, Sep 04, 2013 at 04:35:17PM +0100, Tom Ellis wrote:
 As an addendum to the recent discussion, can anyone explain why main crashes
 quickly with a stack overflow, whereas main' is happy to print Hi for ages
 (eventually crashing due to an out of memory condition)?
 
 bignum = 100 * 1000 * 1000
 main   = replicateM bignum (return ())
 main'  = replicateM bignum (putStrLn Hi)

FYI, rwbarton on Reddit produced a nice answer:


http://www.reddit.com/r/haskell/comments/1luan1/strange_io_sequence_behaviour/cc32ec4

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


[Haskell-cafe] Strange IO sequence behaviour (Was: sequence causing stack overflow on pretty small lists)

2013-09-04 Thread Tom Ellis
As an addendum to the recent discussion, can anyone explain why main crashes
quickly with a stack overflow, whereas main' is happy to print Hi for ages
(eventually crashing due to an out of memory condition)?

bignum = 100 * 1000 * 1000
main   = replicateM bignum (return ())
main'  = replicateM bignum (putStrLn Hi)

Tom

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


Re: [Haskell-cafe] How to read a file and return a String?

2013-09-04 Thread Tom Ellis
On Wed, Sep 04, 2013 at 10:21:37PM +0800, yi lu wrote:
 I want to read a text file, and store it in a *String*. But readFile will
 get *IO String*. I search with google and they tell me it is not
 necessarily to do so. Can you explain to me why is this? Furthermore, How
 to read a file and store it in a String?

You need to lift 'lines' into the IO functor, rather than trying to remove
the String from IO (which doesn't make sense).  Try

fmap lines (readFile filename)

Tom





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


Re: [Haskell-cafe] sequence causing stack overflow on pretty small lists

2013-08-27 Thread Tom Ellis
On Mon, Aug 26, 2013 at 12:05:14PM -0700, Bryan O'Sullivan wrote:
 On Mon, Aug 26, 2013 at 1:46 AM, Niklas Hambüchen m...@nh2.me wrote:
  This is because sequence is implemented as
 
   sequence (m:ms) = do x - m
xs - sequence ms
return (x:xs)
 
  and uses stack space when used on some [IO a].
 
 
 This problem is not due to sequence, which doesn't need to add any
 strictness here. It occurs because the functions in System.Random are
 excessively lazy. In particular, randomIO returns an unevaluated thunk.

I don't understand this.  The same stack overflow occurs with

tenmil :: Int
tenmil = 10 * 1000 * 1000

main :: IO ()
main = do  
list - replicateM tenmil (return ()) :: IO [()] 
list `seq` return ()

return () is not excessiely lazy, is it?  Could you explain further?

Tom

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


Re: [Haskell-cafe] Lifting strictness to types

2013-08-22 Thread Tom Ellis
On Thu, Aug 22, 2013 at 12:51:24PM -0300, Thiago Negri wrote:
 How hard would it be to lift strictness annotations to type-level? E.g.
 instead of
 f :: Int - Int
 f !x = x + 1
 write
 f :: !Int - Int
 f x = x + 1
 which would have the same effect. At least it would be transparent to the
 developer using a particular function.

See also the recent Reddit thread


http://www.reddit.com/r/haskell/comments/1ksu0v/reasoning_about_space_leaks_with_space_invariants/cbsac5m

where I and others considered the possibility of a strict language with
explicit thunk datatype.  NB OCaml essentially already has this

http://caml.inria.fr/pub/docs/manual-ocaml/libref/Lazy.html

but I think Haskellers would do it better because we have a lot of
experience with purity, laziness and monad and comonad transformers.

Tom

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


Re: [Haskell-cafe] Errors in non-monadic code

2013-08-19 Thread Tom Ellis
On Mon, Aug 19, 2013 at 02:20:23PM -0400, jabolo...@google.com wrote:
 Yeah, non-monadic is not the best term... The problem is that it's
 always so hard to communicate when you want to say a total function
 that is not in the context of the IO monad. There should be a simple,
 short name for these functions, so we can easily talk about them.

Why, what would be different in your question for a non-total function or
one in the context of the IO monad?

Tom

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


Re: [Haskell-cafe] Errors in non-monadic code

2013-08-19 Thread Tom Ellis
On Mon, Aug 19, 2013 at 05:15:39PM -0400, jabolo...@google.com wrote:
 But I would like to see more code move away from exceptions and into
 types like Maybe or Either or other types defined for the
 particular situation (as some people were suggesting in the beginning
 of the thread). And the reason for this it is because when you program
 against types you have to make a decision whether to handle the error
 or let it bleed through: you can't ignore the choice because you can't
 ignore the type. On the other hand, with exceptions, you can easily
 forget to handle the exception if you're not looking at the
 documentation at the time when you write the code.

This is /exactly/ the reason to avoid exceptions where possible.

Tom

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


Re: [Haskell-cafe] Errors in non-monadic code

2013-08-19 Thread Tom Ellis
On Tue, Aug 20, 2013 at 12:25:44AM +0200, Jerzy Karczmarczuk wrote:
 Le 20/08/2013 00:19, jabolo...@google.com a écrit :
 If I understand correctly, by escaping continuations you mean that
 you can easily transfer control between the point where the exception
 is raised and the exception handler.
 
 If this is what you mean, you can achieve the same effect with monadic
 code by chaining monads together
 
 José, this is mainly the question of efficiency. You don't need to
 establish contact between the distant stack frames, and you may
 propagate failures if this happens seldom. But if the escaping
 continuation is a frequent case, it might be more economic to
 jump. This is as simple as that.

That's all very well, in which case I wish implementors of such code would
wrap their possibly-exception-throwing values in a

newtype ThisMightThrowAnException a = ThisMightThrowAnException a

monad.  Then at least we'd all know.

Tom

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


Re: [Haskell-cafe] Database.postgreSQL.Simple - ambigious type

2013-08-18 Thread Tom Ellis
On Sun, Aug 18, 2013 at 10:16:06PM +0200, Hartmut Pfarr wrote:
 I played a bit with your suggestion, and it is running now :-)
 But instead of  IO [Int]  I think we need  IO [Only Int]   because
 of the 1-element-tupel problem?

Yes you're right.  I had forgotten that postgresql-simple dealt with
single-column tables with Only.  Well done for getting it working!

Tom

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


Re: [Haskell-cafe] inv f g = f . g . f

2013-08-17 Thread Tom Ellis
On Sat, Aug 17, 2013 at 11:11:07AM +0200, Christopher Done wrote:
 Anyone ever needed this? Me and John Wiegley were discussing a decent
 name for it, John suggested inv as in involution. E.g.
 
 inv reverse (take 10)
 inv reverse (dropWhile isDigit)
 trim = inv reverse (dropWhile isSpace) . dropWhile isSpace

This sounds like a job for a lens, or similar.

Tom


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


Re: [Haskell-cafe] Database.postgreSQL.Simple - ambigious type

2013-08-17 Thread Tom Ellis
On Sat, Aug 17, 2013 at 11:59:24PM +0200, Hartmut Pfarr wrote:
 {-# LANGUAGE OverloadedStrings #-}
 
 import Database.PostgreSQL.Simple
 import Database.PostgreSQL.Simple.FromRow
 
 hello :: (FromRow a) = IO [a]
 hello = do
   conn - connect defaultConnectInfo
   query_ conn select 2 + 2

Either

main = print = (hello :: IO [Int])

or give hello a monomorphic type signature, such as 

hello :: IO [Int]

Tom

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


Re: [Haskell-cafe] Applicative is like an Arrow

2013-08-16 Thread Tom Ellis
On Fri, Aug 16, 2013 at 10:26:42AM -0400, Brandon Allbery wrote:
 My understanding is that there's a rework of Arrow in progress that may
 change this in the future, since *theoretical* Arrows are more distinct,
 flexible and useful than the current implementation.

I'd like to know more about that if you can provide any references.  I am using
arrows very heavily.

Tom

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


Re: [Haskell-cafe] ANN: hi2 -- a better indentation mode for Emacs' haskell-mode

2013-08-09 Thread Tom Ellis
On Fri, Aug 09, 2013 at 12:53:56PM +0200, Gergely Risko wrote:
 In the last 2-3 weeks I've been working on Haskell indentation inside
 Emacs.  I had some annoyances for a long time and fixed some of them.
 
 The new mode is called hi2, it's heavily based on the current
 haskell-indentation (part of haskell-mode).  The changes are mainly to
 the UI, although, I plan to have a look on the parser too.
 
 The code can be found on github: https://github.com/errge/hi2.  Feel
 free to send me feedback, bug reports, pull requests, etc.

Just tried it and I already like it!  Thanks.

Tom

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


Re: [Haskell-cafe] Alternative name for return

2013-08-08 Thread Tom Ellis
On Thu, Aug 08, 2013 at 01:19:27AM +0200, Jerzy Karczmarczuk wrote:
 Bardur Arantsson comments the comment of Joe Quinn:
 On 8/7/2013 11:00 AM, David Thomas wrote:
 twice :: IO () - IO ()
 twice x = x  x
 
 I would call that evaluating x twice (incidentally creating two
 separate evaluations of one pure action description), but I'd like to
 better see your perspective here.
 
 x is only evaluated once, but/executed/  twice. For IO, that means
 magic. For other types, it means different things. For Identity, twice =
 id!
 
 Your point being? x is the same thing regardless of how many times you
 run it.
 
 What do you mean by the same thing? You cannot compare 'them' in
 any reasonable sense.
 
 This, the impossibility to check putStr c == putStr c, is btw, a
 refutation of the claim by Tom Ellis that you can do even less with
 (). The void object is an instance of the Eq and Ord classes. And of
 Show as well.

If I were writing a Haskell compiler I could certainly define 'IO' to be a
datatype that would allow me to compare 'putStr c' to itself.  The
comparison could not be of operational equivalence, but it would still be
possible to compare values in IO in a reasonable sense.

Tom

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


Re: [Haskell-cafe] Identity of indiscernibles (Was: Alternative name for return)

2013-08-08 Thread Tom Ellis
On Thu, Aug 08, 2013 at 11:38:08AM +0200, Jerzy Karczmarczuk wrote:
 Tom Ellis:
 If I were writing a Haskell compiler I could certainly define 'IO' to be a
 datatype that would allow me to compare 'putStr c' to itself.  The
 comparison could not be of operational equivalence, but it would still be
 possible to compare values in IO in a reasonable sense.
 
 Would you add to all this:
 getLine == getLine
 etc.?
 
 Good luck!
 
 I suspect that you would have to establish also the equality
 relation between functions and between infinite streams.
 And you would end as Giordano Bruno and Jeanne d'Arc. But for
 different reasons.

Not at all.  One could simply implement IO as a free monad, to take one
example.

Tom

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


Re: [Haskell-cafe] Identity of indiscernibles (Was: Alternative name for return)

2013-08-08 Thread Tom Ellis
On Thu, Aug 08, 2013 at 08:41:25AM -0400, Jake McArthur wrote:
 I don't know what the denotation for this would be, but I can't think of
 any reasonable ones for which I can write (==) to respect the denotation.
 For example, is set A, then set B equal to set B, then set A?
[...]

I'm a bit lost as to what's actually being discussed in this thread, but
Jerzy seemed to suggest that the impurity of IO was somehow related to it
not supporting very many operations.  I was trying to point out that this
doesn't seem to be a good characterisation.  I do not, however, have a good
candidate for the definition of impure.

Tom

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


Re: [Haskell-cafe] Identity of indiscernibles

2013-08-08 Thread Tom Ellis
On Thu, Aug 08, 2013 at 03:38:41PM +0200, Jerzy Karczmarczuk wrote:
 One could simply implement IO as a free monad
 Interesting. I wonder how.

See [1] for an explanation of free monads in general.  For IO in particular,
define a functor

data IOF a = GetChar (Char - a) | PutChar Char a | ...

with constructors for all elementary IO operations.  Then take

type IO a = Free IOF a

and define

getChar :: IO Char
getChar = liftF (GetChar id)
   
putChar :: Char - IO ()
putChar c = liftF (PutChar c ())

etc..  I make no claims about the performance of a runtime system based on
suhc a representation!

Tom

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


Re: [Haskell-cafe] Identity of indiscernibles

2013-08-08 Thread Tom Ellis
On Thu, Aug 08, 2013 at 05:23:50PM +0100, Oliver Charles wrote:
 On 08/08/2013 05:05 PM, Tom Ellis wrote:
  On Thu, Aug 08, 2013 at 03:38:41PM +0200, Jerzy Karczmarczuk wrote:
  One could simply implement IO as a free monad
  Interesting. I wonder how.
  
  See [1] for an explanation of free monads in general
 
 You're lacking a matching definition of [1] :)

Ah thank you!

[1]  
http://www.haskellforall.com/2012/06/you-could-have-invented-free-monads.html

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


Re: [Haskell-cafe] Identity of indiscernibles

2013-08-08 Thread Tom Ellis
On Thu, Aug 08, 2013 at 06:25:12PM +0200, Daniel Trstenjak wrote:
  See [1] for an explanation of free monads in general.  For IO in particular,
  define a functor
  
  data IOF a = GetChar (Char - a) | PutChar Char a | ...
  
  with constructors for all elementary IO operations.
 
 But how should this work if the user adds an IO operation, e.g by wrapping a 
 C function?

Wrapping a C function could perhaps be provided by something like

data IOF a = ... | forall i o. Foreign String i (o - a) | ...

csin :: Double - IO Double
csin x = liftF (Foreign math.h sin x id)

Tom

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


Re: [Haskell-cafe] Identity of indiscernibles

2013-08-08 Thread Tom Ellis
On Thu, Aug 08, 2013 at 05:44:11PM +0100, Tom Ellis wrote:
 On Thu, Aug 08, 2013 at 06:25:12PM +0200, Daniel Trstenjak wrote:
   See [1] for an explanation of free monads in general.  For IO in 
   particular,
   define a functor
   
   data IOF a = GetChar (Char - a) | PutChar Char a | ...
   
   with constructors for all elementary IO operations.
  
  But how should this work if the user adds an IO operation, e.g by wrapping 
  a C function?
 
 Wrapping a C function could perhaps be provided by something like
 
 data IOF a = ... | forall i o. Foreign String i (o - a) | ...
 
 csin :: Double - IO Double
 csin x = liftF (Foreign math.h sin x id)

I suppose that should actually be 'csin :: CDouble - IO CDouble', but
hopefully the general method is clear.

Tom


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


Re: [Haskell-cafe] Identity of indiscernibles

2013-08-08 Thread Tom Ellis
On Fri, Aug 09, 2013 at 12:38:45AM +0700, Kim-Ee Yeoh wrote:
 On Thu, Aug 8, 2013 at 11:05 PM, Tom Ellis 
 tom-lists-haskell-cafe-2...@jaguarpaw.co.uk wrote:
  On Thu, Aug 08, 2013 at 03:38:41PM +0200, Jerzy Karczmarczuk wrote:
   One could simply implement IO as a free monad
   Interesting. I wonder how.
 
  See [1] for an explanation of free monads in general.  For IO in
  particular,
  define a functor
 
  data IOF a = GetChar (Char - a) | PutChar Char a | ...
 
  with constructors for all elementary IO operations.
 
 If I understand correctly, you're proposing equality of (IO a) based on the
 AST of imperatives, similar to what comes out of GCC's front-end for C [1].

I'm not proposing it.  I'm just pointing out it could be done, as a
challenge to Jerzy's assertion that In fact, you can do almost nothing with
[values of type IO ()].

However, I may have misunderstood Jerzy's point anyway.

Tom

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


Re: [Haskell-cafe] Alternative name for return

2013-08-06 Thread Tom Ellis
On Tue, Aug 06, 2013 at 10:03:04AM +0200, J. Stutterheim wrote:
 `putStrLn Hi` is not a pure value...

Why not?

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


Re: [Haskell-cafe] Alternative name for return

2013-08-06 Thread Tom Ellis
On Tue, Aug 06, 2013 at 04:26:05PM +0200, Jerzy Karczmarczuk wrote:
 1. First, it is not true  that you can do with, say, (printStr Ho!
 ) whatever you want. In fact, you can do almost nothing with it. You
 can transport it as such, and you can use it as the argument of
 (=).

I don't think this argument holds much water.  You can do even less with ().

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


Re: [Haskell-cafe] Hoogle problems?

2013-08-01 Thread Tom Ellis
On Thu, Aug 01, 2013 at 01:25:22PM +0100, Richard Evans wrote:
 It still doesn't work when I try it.

What URL are you using?  http://www.haskell.org/hoogle works fine for me.

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


Re: [Haskell-cafe] ANNOUNCE: hdbi-1.0.0 and hdbi-postgresql-1.0.0

2013-07-31 Thread Tom Ellis
On Wed, Jul 31, 2013 at 09:45:50AM +0600, Alexey Uimanov wrote:
 Hello, haskellers. This is the first release of HDBI (Haskell Database
 Independent interface).

Hi, thanks for this Alexey.  It's great that there is continued development
of this really important infrustructure for Haskell.

I have a question about variable interpolation, that is, using ? parameter
placeholders in the query strings, as documented here:


http://hackage.haskell.org/packages/archive/hdbi/1.0.0/doc/html/Database-HDBI.html

I know postgresql-simple does this, and presumably database access libraries
in other languages do this too.

What is the rationale for this when in Haskell we have safer methods of
interpolation at our disposal (for example HoleyMonoid)?  Is it simply a
matter of using the most familiar interface, or is there a deeper reason
this is necessary?

Thanks,

Tom


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


Re: [Haskell-cafe] ANNOUNCE: hdbi-1.0.0 and hdbi-postgresql-1.0.0

2013-07-31 Thread Tom Ellis
On Wed, Jul 31, 2013 at 01:22:42PM +0600, Alexey Uimanov wrote:
 I also have the idea do not throw the exceptions in IO but return  (Either
 SqlError a) from all the Connection and Statement methods for safe data
 processing.  What do you think about ?

I feel very strongly that you should use Either.  One of the things I find
worst about postgres-simple is the exceptions it throws.  The benefit of
Haskell is that we can do things in a Haskelly way!

Tom

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


Re: [Haskell-cafe] ANNOUNCE: hdbi-1.0.0 and hdbi-postgresql-1.0.0

2013-07-31 Thread Tom Ellis
On Wed, Jul 31, 2013 at 05:28:02PM +0600, Alexey Uimanov wrote:
 The rationale is that the low-level database interface accepts parameters
 directly instead of inserting them inside the query manually.
[...]
 Low-level database interface knows better how to work with parameters, so
 the driver must pass them to it instead of parameters substitution.

Letting the low-level database interface (I'm guessing you're talking about
a C library provided by the database vendor) do the escaping certainly makes
a lot of sense.

However, it would still be possible to make sure that the *number* of
parameters supplied matches the number of placeholders in the query string. 
That would make sense, don't you think?

Tom


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


Re: [Haskell-cafe] Proposal: Non-recursive let

2013-07-25 Thread Tom Ellis
On Thu, Jul 25, 2013 at 07:34:55PM +1200, Richard A. O'Keefe wrote:
 It's a queer thing, I always feel that the advice about
 keeping function bodies small is patronising nonsense for
 beginners and that *my* code is perfectly readable no matter
 how big it is, but end up wishing that *other* people kept
 *their* functions small.

For example, breaking this code into smaller functions could make it
transparent that 'token' is only used in 'ast1', 'title' is only used in
'headers1' and that the 'mv' that is the argument to 'write_period' is only
used in the Nothing branch of the massive case statement.

It seems there are a number of straightforward ways to make this code much
clearer that do not require non-recursive let.

Tom

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


Re: [Haskell-cafe] memoization

2013-07-24 Thread Tom Ellis
On Wed, Jul 24, 2013 at 10:06:59AM +0200, Andreas Abel wrote:
 For -O1 and greater, ghc seems to see that x is not mentioned in the
 where clauses and apparently lifts them out.  Thus, for -O1..
 memoized_fib is also memoizing.  (I ran it, this time ;-) !)

Right, I believe this is the full laziness transformation I mentioned
before

http://foldoc.org/full+laziness 
 

 
http://www.haskell.org/pipermail/haskell-cafe/2013-February/105201.html

Tom

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


Re: [Haskell-cafe] memoization

2013-07-23 Thread Tom Ellis
On Mon, Jul 22, 2013 at 04:04:33PM -0700, wren ng thornton wrote:
 Consider rather,
 
 f1 = let y = blah blah in \x - x + y
 
 f2  x = let y = blah blah in x + y
 
 The former will memoize y and share it across all invocations of f1;
 whereas f2 will recompute y for each invocation.

Indeed.

 In principle, we could translate between these two forms (the f2 == f1
 direction requires detecting that y does not depend on x). However, in
 practice, the compiler has no way to decide which one is better since it
 involves a space/time tradeoff which: (a) requires the language to keep
 track of space and time costs, (b) would require whole-program analysis to
 determine the total space/time costs, and (c) requires the user's
 objective function to know how to weight the tradeoff ratio.

This is called the full laziness transformation

http://foldoc.org/full+laziness

and indeed with optimization on GHC (sometimes) does it, even when not 
appropriate

http://www.haskell.org/pipermail/haskell-cafe/2013-February/105201.html

Tom

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


Re: [Haskell-cafe] memoization

2013-07-22 Thread Tom Ellis
On Mon, Jul 22, 2013 at 12:02:54AM -0800, Christopher Howard wrote:
  A binding is memoized if, ignoring everything after the equals sign,
  it looks like a constant.
[...]
 Thanks. That's very helpful to know. Yet, it seems rather strange and
 arbitrary that f x = ... and f = \x - ... would be treated in such
 a dramatically different manner.

This is actually rather subtle, and it's to do with desugaring of pattern
matching and where.

f x = expression s x where s = subexpression

desugars to

f = \x - (let s = subexpression in expression s x)

This is not the same as

f = expression s where s = subexpression

which desugars to

f = let s = subexpression in (expression s)

which I think is the same as

f = let s = subexpression in (\x - expression s x)

In the first case a new thunk for s is created each time an argument is
applied to f.  In the second case the same thunk for s exists for all
invocations of f.

This is nothing to do with explicit memoization by the compiler, but is
simply the operational semantics of lazy evaluation in terms of thunks.

(I think I got this all right, and if not I hope someone will chime in with
a correction.  I spent some time trying to grasp this a few months ago, but
as I said it's subtle, at least to someone like me who hasn't studied lambda
calculus in depth!)

Tom

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


Re: [Haskell-cafe] memoization

2013-07-22 Thread Tom Ellis
On Mon, Jul 22, 2013 at 07:52:06PM +1200, Chris Wong wrote:
 A binding is memoized if, ignoring everything after the equals sign,
 it looks like a constant.
 
 In other words, these are memoized:
[...]
 f = \x - x + 1
[...]
 and these are not:
 
 f x = x + 1

In what sense is the former memoised?  I'm not aware of any difference
between these two definitions.

Tom

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


Re: [Haskell-cafe] memoization

2013-07-22 Thread Tom Ellis
On Mon, Jul 22, 2013 at 04:16:19PM +0200, Andreas Abel wrote:
 In general, I would not trust such compiler magic, but just let-bind
 anything I want memoized myself:
 
 memoized_fib :: Int - Integer
 memoized_fib x = fibs !! x
 where fibs  = map fib [0..]   -- lazily computed infinite list
   fib 0 = 0
   fib 1 = 1
   fib n = memoized_fib (n-2) + memoized_fib (n-1)
 
 The eta-expansions do not matter.

But this is *not* memoized (run it and see!).  The eta-expansions do
indeed matter (although I don't think they are truly eta-expasions because
of the desugaring of the where to a let).

What matters is not the let binding, but where the let binding occurs in
relation to the lambda.  There's no compiler magic here, just operational
semantics.

Tom

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


Re: [Haskell-cafe] Wrapping all fields of a data type in e.g. Maybe

2013-07-16 Thread Tom Ellis
On Tue, Jul 16, 2013 at 04:57:59PM -0400, Michael Orlitzky wrote:
 This all works great, except that when there's 20 or so options, I
 duplicate a ton of code in the definition of OptionalCfg. Is there some
 pre-existing solution that will let me take a Cfg and create a new type
 with Cfg's fields wrapped in Maybe?

You can always try

data Cfg f = Cfg { verbose :: f Bool }

and set f to Maybe or Identity depending on what you use it for.  It will be
slightly notationally cumbersome to extract values from the Identity functor
though.

Tom

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


Re: [Haskell-cafe] What have happened to haskell.org?

2013-07-15 Thread Tom Ellis
On Mon, Jul 15, 2013 at 07:19:12AM -0700, Kirill Zaborsky wrote:
 http://www.haskell.org/hoogle/ responds with some ELF file.

After running strings on it, it does seem to be (at least part of) the
hoogle binary.

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


Re: [Haskell-cafe] Linux users needed for OpenGL extensions survey

2013-07-09 Thread Tom Ellis
On Mon, Jul 08, 2013 at 09:55:08PM -0700, Kirill Zaborsky wrote:
 Brian, I think it would be better to provide your email in the thread. E.g. 
 from http://www.haskell.org/pipermail/haskell-cafe/2013-July/109061.html I 
 can only reply to the maillist. I'm answering now through Google Groups 
 hope it will get to you.

Brian's email address is at the top of that page.  Just replace at with
@.

Tom

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


[Haskell-cafe] Probabilistic functional programming with Baysig/BayesHive

2013-07-09 Thread Tom Nielsen
Dear cafe,

I would like to announce that the Baysig programming language and the
BayesHive analytics environment (http://bayeshive.com) are now
available for beta testers.

Baysig is a new probabilistic, functional and typed programming
language that attempts to realise the vision of fully Bayesian
computing. That is, in Baysig almost all the work in data processing
consists of building a probabilistic model of the incoming data.
Almost everything else -- optimal decisions, categorisation, measuring
hidden parameters or states, forecasting, testing hypothesis --
becomes trivial. This paradigm can in principle be applied to a large
number of domains, although for the moment we are focusing on models
that are based on continuous parameters. It will therefore be of
interest to users of statistics and dynamical systems models,
including in finance, physics and life sciences.

To analyse data in Baysig, you write a program in the random-number
supply monad that generates simulated data. A special construct,
estimate, then applies Bayes' theorem to this program and returns
the probability distribution of the model parameters given observed
data. The estimate procedure is difficult to implement in Haskell or
similar languages, which encouraged us to develop a new language.
However, in many respects Baysig should feel like Haskell, and we hope
that Baysig will encourage the Haskell community to experiment with
statistical modelling.

We have built a web-based environment to help users, including those
with little-to-no programming experience, use Baysig, at
bayeshive.com. This web application allows you to upload data from
spreadsheets or timeseries, and to build statistical models with a
point-and-click web interface which ends up generating Baysig code.
Code and the results of running it are collected in shareable and
editable literate programming documents.

We would appreciate any feedback from the Haskell community before
releasing our platform to unsuspecting statisticians and researchers.
Almost everything is written in Haskell, including the Baysig
compiler. The BayesHive website is written using Yesod, with which we
are mostly happy. We also use the Stan package (mc-stan.org), and the
web front-end is written using AngularJS. For the moment the Baysig
language is only available through the BayesHive web interface, but
that will change. If you want to run Baysig on your own computer,
please send me an email at t...@openbrain.org.

Finally, both the BayesHive web application and the Baysig language
implementation are still prototypes and very much work-in-progress. We
promise to work hard at fixing the bugs you find!

Links:

BayesHive, including a few videos:
http://bayeshive.com

Baysig quick tour (QuickBAYSIG):
http://bayeshive.com/helppage/Baysig%20quick%20tour:%20fundamentals

More documentation:
http://bayeshive.com/help

Regards,
Tom Nielsen
OpenBrain Ltd.

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


Re: [Haskell-cafe] Casting newtype to base type?

2013-07-02 Thread Tom Ellis
On Tue, Jul 02, 2013 at 03:03:08PM +0200, Vlatko Basic wrote:
 Is there a nicer way to extract the 'IO String' from 'IOS',
 without 'case' or without pattern matching the whole 'P'?
 
 newtype IOS = IOS (IO String)
 data P = P {
   getA :: String,
   getB :: String,
   getC :: IOS
   } deriving (Show, Eq)
 
 
 getC_IO :: P - IO String
 getC_IO p =
   case getC p of
 IOS a - a
 getC_IO (P _ _ (IOS a)) = a

How about

unIOS :: IOS - IO String
unIOS (IOS a) = a

getC_IO :: P - IO String
getC_IO = unIOS . getC

Tom

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


Re: [Haskell-cafe] question about indentation conventions

2013-07-01 Thread Tom Ellis
On Mon, Jul 01, 2013 at 05:18:39PM +1200, Richard A. O'Keefe wrote:
 On 1/07/2013, at 1:04 PM, Richard Cobbe wrote:
  I should have been clearer in my original question: I'm curious about what
  to do when a multi-argument function application gets split across lines.
  That wiki page dicsusses how the layout rule interacts with various special
  forms (let, where, if, do, case), but it doesn't seem to address function
  applications, beyond implying that it's ok to indent the continuing lines
  of a function application.
 
 It looked pretty explicit to me:
 
   The golden rule of indentation
   ...
   you will do fairly well if you just remember a single rule:
   Code which is part of some expression should be indented 
   further in than the beginning of that expression (even if
   the expression is not the leftmost element of the line).
 
 This means for example that
   f (g x
   y
   z)
 is OK but
   f (g x
   y z)
 is not.

It seems to me that this means

f x1 x2
x3 x4

is not.  The OP was initially asking about this situation.

Tom


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


Re: [Haskell-cafe] Casting newtype to base type?

2013-07-01 Thread Tom Ellis
On Mon, Jul 01, 2013 at 05:07:00PM +0200, Vlatko Basic wrote:
 Hello Cafe!
 
 I had a (simplified) record
 
   data P = P {
 a :: String,
 b :: String,
 c :: IO String
 } deriving (Show, Eq)
 
 but to get automatic deriving of 'Show' and 'Eq' for 'data P' I have
 created 'newtype IOS' and its 'Show' and 'Eq' instances
 
   newtype IOS = IO String
   instance Show (IOS) where show _ = (IO String) function
   instance Eq   (IOS) where _ == _ = True

An Eq instance for something containing IO is bound to lead to puzzlement
somewhere down the line.  I think you're better off defining something like

data P_lesser = P_lesser {
a_lesser :: String,
b_lesser :: String
} deriving (Show, Eq)

to_lesser p = P_lesser (a p) (b p)

and just factoring everything through to_lesser when you want to compare
or show.

Tom

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


Re: [Haskell-cafe] Spam on list??

2013-07-01 Thread Tom Ellis
Yeah I'm getting stuff from j...@eukor.com every time I post.

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


Re: [Haskell-cafe] tangential request...

2013-06-24 Thread Tom Ellis
On Mon, Jun 24, 2013 at 08:02:17AM -0700, Mark Lentczner wrote:
 And yet, just four fonts make up over 75% of the sample - and two of those
 are essentially identical!

Inconsolata and Consolas?

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


Re: [Haskell-cafe] data constructor names

2013-06-22 Thread Tom Ellis
On Sat, Jun 22, 2013 at 04:26:14AM -0500, Brian Lewis wrote:
 Say you write
 data Callback = Error ... | ...
[...]
 
 Then, later, you write
 data Error = ...
[...]
 
 They're both good names, but there's a conflict.

What do you mean by a conflict?  That's fine as far as the compiler is
concerned because constructors live in a different namespace from types.

If you meant it will be too confusing for the programmer that's fair enough.

Tom

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


[Haskell-cafe] Best practices for Arrows?

2013-06-22 Thread Tom Ellis
I feel I may be doing a lot of programming with Arrows in the near future. 
Currently I'm delighted that Arrow notation[1] exists.  It makes using
Arrows much less painful.

Are there any best-practices I should be aware of with Arrows?  Or is it
just a case of getting on with it?

Tom

1.  http://www.haskell.org/ghc/docs/latest/html/users_guide/arrow-notation.html

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


Re: [Haskell-cafe] Best practices for Arrows?

2013-06-22 Thread Tom Ellis
Hi Ertugul.  Thanks for taking the time to write me an in-depth reply!  I
have a few comments and a question.

On Sat, Jun 22, 2013 at 03:36:15PM +0200, Ertugrul Söylemez wrote:
 Tom Ellis tom-lists-haskell-cafe-2...@jaguarpaw.co.uk wrote:
 
  Are there any best-practices I should be aware of with Arrows?  Or is
  it just a case of getting on with it?
 
 The best practice is probably to avoid them.  If your type is a monad,
 there is little reason to use the awkward arrow interface.

Unfortunately my type doesn't have a Monad instance.

 In most cases when you expose an `Arrow` interface you can also expose a
 `Category`+`Applicative` interface, which is pretty much equivalent
 (except for a few extra laws):
 
 proc x - do
 y1 - a1 - x
 y2 - a2 - x
 id - x + y1 + y2^2
 
 Is equivalent to:
 
 liftA3 (\x y1 y2 - x + y1 + y2^2) id a1 a2

Yes, I can see how that would be useful.  My question is: are you talking
about this Applicative instance:

data MyArr a b = ...

instance Arrow MyArr where
...

instance Functor (MyArr a) where
  fmap f = (arr f )

instance Applicative (MyArr a) where
  pure = arr . const
  f * g = arr (uncurry ($))  (f  g)

 If the interface is not under your control, make yourself comfortable
 with the complete arrow syntax, most notably how it handles operators,
 combinators and the `(| banana bracket notation |)`.  This is very
 valuable information.

Interesting.  I hadn't noticed the `(| banana bracket notation |)` on the
GHC Arrows page[1] before, but just saw it when I went back to check.

 Try to separate individual computations as much as possible and compose
 using `(.)` (or `()`/`()` if you prefer).  This makes your code
 much more readable:

Yes, agreed.  I'm a strong proponent of using (.) for functions and (=)
when dealing with Monads.

 There is one case where the arrow notation is really indispensable:
 value recursion via `ArrowLoop`:
[...]

I think I will be able to make my Arrow an ArrowLoop, but I haven't
checked.

Thanks again,

Tom

[1] http://www.haskell.org/ghc/docs/latest/html/users_guide/arrow-notation.html

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


Re: [Haskell-cafe] opengl type confusion

2013-06-17 Thread Tom Ellis
On Sun, Jun 16, 2013 at 05:22:59PM -0700, bri...@aracnet.com wrote:
  Vertex3 takes three arguments, all of which must be of the same instance of
  VertexComponent.  Specifying GLdoubles in the signature of wireframe
  specifies the types in the last three calls to Vertex3, but (0.0 ::
  GLdouble) is still requried on the first to fix the type there.  How else
  could the compiler know that you mean 0.0 to be a GLdouble and not a
  GLfloat?
 
 it's curious that 
 
 (0.0::GLdouble) 0.0 0.0 
 
 is good enough and that 
 
 (0.0::GLdouble) (0.0::GLdouble) (0.0::GLdouble)
 
 is not required.  I suspect that's because, as you point out, they all
 have to be the same argument and ghc is being smart and saying if the
 first arg _must_ be GLdouble (because I'm explicitly forcing the type),
 then the rest must be too.

That is exactly the reason.

Tom

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


Re: [Haskell-cafe] opengl type confusion

2013-06-16 Thread Tom Ellis
On Sun, Jun 16, 2013 at 01:03:48PM -0700, bri...@aracnet.com wrote:
 wireframe :: Double - Double - Double - IO ()
 wireframe wx wy wz = do 
   -- yz plane
   renderPrimitive LineLoop $ do
vertex $ Vertex3 0.0 0.0 0.0
vertex $ Vertex3 0.0 wy 0.0
vertex $ Vertex3 0.0 wy wz
vertex $ Vertex3 0.0 0.0 wz
[...]
 
 No instance for (VertexComponent Double)
   arising from a use of `vertex'
[...]
 
 Changing the declaration to GLdouble - GLdouble - GLdouble - IO() and using
 (0.0::GLdouble) fixes it

Vertex3 takes three arguments, all of which must be of the same instance of
VertexComponent.  Specifying GLdoubles in the signature of wireframe
specifies the types in the last three calls to Vertex3, but (0.0 ::
GLdouble) is still requried on the first to fix the type there.  How else
could the compiler know that you mean 0.0 to be a GLdouble and not a
GLfloat?

Tom

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


Re: [Haskell-cafe] (no subject)

2013-06-10 Thread Tom Ellis
On Mon, Jun 10, 2013 at 05:41:05PM +0530, Zed Becker wrote:
  Haskell, is arguably the best example of a design-by-committee language.
 The syntax is clean and most importantly, consistent. The essence of a
 purely functional programming is maintained, without disturbing its real
 world capacity.
 
  To all the people who revise the Haskell standard, and implement the
 language,
 
1.  Promise to me, and the rest of the community, that you will keep
up the good effort :)
2.  Promise to me, and the rest of the community, that Haskell will
always spiritually remain the same clean, consistent programming
language as it is now!

Hear hear!  Hopefully we, the Haskell community, will be able to support
this endevour with our time and efforts.

Tom

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


Re: [Haskell-cafe] Only vaporware needs promises

2013-06-10 Thread Tom Ellis
On Mon, Jun 10, 2013 at 03:21:28PM +0200, Ertugrul Söylemez wrote:
 Tom Ellis tom-lists-haskell-cafe-2...@jaguarpaw.co.uk wrote:
  Hear hear!  Hopefully we, the Haskell community, will be able to
  support this endevour with our time and efforts.
 
 Every Haskell user does this in their own way by use, feedback, uploads
 to Hackage, authoring wiki articles or blog articles or simply by
 helping people.  The Haskell community has a huge momentum right now and
 the language is developed by smart people.
 
 What does /not/ help is a thread like this.  If you want to support the
 development of Haskell, don't unsafeCoerce people into making useless
 promises.  Instead grab your web browser, text editor or whiteboard and
 do your part!

Indeed Ertugul, that's exactly what I mean.

Tom

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


Re: [Haskell-cafe] (no subject)

2013-06-10 Thread Tom Ellis
On Mon, Jun 10, 2013 at 05:44:26PM +0400, MigMit wrote:
 It really sounds rude, to demand promises from somebody who just gave you a 
 big present.

Without wishing to preempt Zed Becker, I interpreted his email as an
expression of delight at how well Haskell has been designed and of hope that
it may endure, rather than literally as a demand for the Haskell committee
to grant him promises.  I hope I haven't misunderstood.

Tom

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


Re: [Haskell-cafe] Question about Newtype op() function arguments.

2013-06-07 Thread Tom Ellis
On Fri, Jun 07, 2013 at 07:08:19AM -0700, David Banas wrote:
 op :: 
 Newtypehttp://hackage.haskell.org/packages/archive/newtype/0.2/doc/html/Control-Newtype.html#t:Newtype
 n
 o = (o - n) - n -
 oSourcehttp://hackage.haskell.org/packages/archive/newtype/0.2/doc/html/src/Control-Newtype.html#op
 
 This function serves two purposes:
 
1. Giving you the unpack of a newtype without you needing to remember
the name.
2. Showing that the first parameter is *completely ignored* on the value
level, meaning the only reason you pass in the constructor is to provide
type information. Typeclasses sure are neat.
 
 As point #2, above, emphasizes, the only purpose for the first argument to
 the function (i.e. - the constructor (o - n)) is to specify the type of
 'n'. However, being a *newtype*, 'n' can have only one constructor. So, why
 is it necessary to pass in the constructor to this function, when we're
 already passing in 'n'?

I am puzzled by this too.

What does op stand for?  I hypothesis opposite in the sense of inverse,
since as Roman points out op Constructor :: n - o is the inverse of
Constructor :: o - n.

But I admit I do not see how this provides value over unpack itself.

Tom

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


Re: [Haskell-cafe] Question about Newtype op() function arguments.

2013-06-07 Thread Tom Ellis
On Fri, Jun 07, 2013 at 04:05:09PM -0400, Joe Q wrote:
 The phantom parameter solves the same problem as scoped type variables.
 Granted, if you find yourself in that kind of polymorphic soup you have
 deeper problems...

I don't understand this.  Scoped type variables are used when you want to
use a type variable from the top level within the body of a function.  If
you use op and specify a particular constructor then you don't have a
variable but a concrete instance of a type.  But maybe I'm missing some more
powerful way this can be used ...

Tom




 On Jun 7, 2013 2:53 PM, Tom Ellis 
 tom-lists-haskell-cafe-2...@jaguarpaw.co.uk wrote:
  On Fri, Jun 07, 2013 at 07:08:19AM -0700, David Banas wrote:
   op :: Newtype
  http://hackage.haskell.org/packages/archive/newtype/0.2/doc/html/Control-Newtype.html#t:Newtype
  
   n
   o = (o - n) - n -
   oSource
  http://hackage.haskell.org/packages/archive/newtype/0.2/doc/html/src/Control-Newtype.html#op
  
  
   This function serves two purposes:
  
  1. Giving you the unpack of a newtype without you needing to remember
  the name.
  2. Showing that the first parameter is *completely ignored* on the
  value
  level, meaning the only reason you pass in the constructor is to
  provide
  type information. Typeclasses sure are neat.
  
   As point #2, above, emphasizes, the only purpose for the first argument
  to
   the function (i.e. - the constructor (o - n)) is to specify the type
  of
   'n'. However, being a *newtype*, 'n' can have only one constructor. So,
  why
   is it necessary to pass in the constructor to this function, when we're
   already passing in 'n'?
 
  I am puzzled by this too.
 
  What does op stand for?  I hypothesis opposite in the sense of inverse,
  since as Roman points out op Constructor :: n - o is the inverse of
  Constructor :: o - n.
 
  But I admit I do not see how this provides value over unpack itself.
 
  Tom
 
  ___
  Haskell-Cafe mailing list
  Haskell-Cafe@haskell.org
  http://www.haskell.org/mailman/listinfo/haskell-cafe
 

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


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


[Haskell-cafe] PPDP'13: Last call for papers

2013-06-06 Thread Tom Schrijvers
   University of Cambrige, UK
Bruno C. d. S. Oliveira   National University of Singapore, Singapore
Alberto Pettorossi Universita di Roma Tor Vergata, Italy
Enrico PontelliNew Mexico State University, USA
Kristoffer RoseIBM Research, USA
Sukyoung Ryu   KAIST, South Korea
Vitor Santos Costa University of Porto, Portugal
Torsten Schaub University Potsdam, Germany
Tom Schrijvers Ghent University, Belgium
Martin SulzmannHochschule Karlsruhe, Germany
Wouter Swierstra   Universiteit Utrecht, The Netherlands
Tarmo Uustalu  Institute of Cybernetics, Estonia
Janis Voigtlaender University of Bonn, Germany
Meng Wang  Chalmers University of Technology, Sweden
Jan Wielemaker Universiteit van Amsterdam, The Netherlands

Program Chair

Tom Schrijvers
Department of Applied Mathematics and Computer Science
Ghent University
9000 Gent, Belgium

General Chair

Ricardo Pena
Facultad de Informatica
Universidad Complutense de Madrid
28040 Madrid, Spain


-- 
prof. dr. ir. Tom Schrijvers

Programming Languages Group
Department of Applied Mathematics and Computer Science
University of Ghent

Krijgslaan 281 S9
9000 Gent
Belgium
Phone: +32 9 264 4805
http://users.ugent.be/~tschrijv/
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Array, Vector, Bytestring

2013-06-04 Thread Tom Ellis
On Tue, Jun 04, 2013 at 04:01:37PM +0200, Peter Simons wrote:
   How is this a problem?
  
   If you're representing text, use 'text'.
   If you're representing a string of bytes, use 'bytestring'.
   If you want an array of values, think c++ and use 'vector'.
 
 the problem is that all those packages implement the exact same data
 type from scratch, instead of re-using an implementation of a
 general-purpose array internally. That is hardly desirable, nor is it
 necessary.

Just to clarify for those on the sidelines, the issue is duplication of
implementation details, rather than duplication of functionality?

Tom

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


Re: [Haskell-cafe] Array, Vector, Bytestring

2013-06-04 Thread Tom Ellis
On Tue, Jun 04, 2013 at 11:23:16PM +0200, Peter Simons wrote:
   On Tue, Jun 04, 2013 at 04:01:37PM +0200, Peter Simons wrote:
 If you're representing text, use 'text'.
 If you're representing a string of bytes, use 'bytestring'.
 If you want an array of values, think c++ and use 'vector'.
  
   the problem is that all those packages implement the exact same data
   type from scratch, instead of re-using an implementation of a
   general-purpose array internally. That is hardly desirable, nor is it
   necessary.
  
   Just to clarify for those on the sidelines, the issue is duplication of
   implementation details, rather than duplication of functionality?
 
 I am not sure what the terms duplication of implementation details and
 duplication of functionality mean in this context. Could you please
 explain how these two concepts differ in your opinion?

Hi Peter,

When I say duplication of implementation details I believe I mean
something like your implementing the exact same data type from scratch.

By duplication of functionality, on the other hand, I mean providing two
libraries with similar APIs which essentially serve the same purpose.

I believe you are suggesting that there is redundancy in the implementation
details of these libraries, not in the APIs they expose.  Then again, I was
just trying to understand the discussion at hand.  I don't have an opinion
on it.

Tom

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


Re: [Haskell-cafe] Type classes

2013-05-28 Thread Tom Ellis
On Tue, May 28, 2013 at 04:42:35PM +0200, Johannes Gerer wrote:
 By the same argument, could'nt I say, that any type class (call it
 AnyClass) can do everything a Monad can:
 
 instance AnyClass m = Monad (Cokleilsi m ())

That doesn't say that AnyClass can do anything a Monad can.  AnyClass m =
Monad m would say that, but that's not what you've got.

What you've got is that Cokleisli m () i.e. (-) m () is a Monad for any
m.  This is not surprising.  The implementation is the same as the Reader
monad.

Check out the instance implementations for Monad (Reader r) and Monad
(CoKleisli w a).  You will find they are the same.


http://hackage.haskell.org/packages/archive/mtl/1.1.0.2/doc/html/src/Control-Monad-Reader.html#Reader

http://hackage.haskell.org/packages/archive/comonad/3.0.0.2/doc/html/src/Control-Comonad.html#Cokleisli

Tom

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


Re: [Haskell-cafe] Type classes

2013-05-28 Thread Tom Ellis
On Tue, May 28, 2013 at 05:21:58PM +0200, Johannes Gerer wrote:
 That makes sense. But why does
 
 instance Monad m = ArrowApply (Kleisli m)
 
 show that a Monad can do anything an ArrowApply can (and the two are
 thus equivalent)?

I've tried to chase around the equivalence between these two before, and
I didn't find the algebra simple.  I'll give an outline.

In non-Haskell notation

1) instance Monad m = ArrowApply (Kleisli m)

means that if m is a Monad then _ - m _ is an ArrowApply.

2) instance ArrowApply a = Monad (a anyType)

means that if _ ~ _ is an ArrowApply then a ~ _ is a Monad.

One direction seems easy: for a Monad m, 1) gives that _ - m _ is an
ArrowApply.  By 2), () - m _ is a Monad.  It is equivalent
to the Monad m we started with.

Given an ArrowApply _ ~ _, 2) shows that () ~ _ is a Monad.  Thus by
1) _ - (() ~ _) is an ArrowApply.  I believe this should be the same
type as _ ~ _ but I don't see how to demonstrate the isomorphsim here.

Tom

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


Re: [Haskell-cafe] Type classes

2013-05-28 Thread Tom Ellis
On Tue, May 28, 2013 at 09:09:48PM +0200, Johannes Gerer wrote:
 What about these two very simple type classes. Are they equivalent?
[...]
 class Pointed f where
   pure  :: a - f a
 
 class Unit f where
   unit :: f a a
 
 newtype UnitPointed f a = UnitPointed f a a
 instance Unit f = Pointed (UnitPointed f) where
   pure f = UnitPointed unit
 
 newtype Kleisli f a b = Kleisli (a - f b)
 instance Pointed f = Unit (Kleisli f) where
   unit = Kleisli pure

This is implausible, since pure f does not depend on f.

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


Re: [Haskell-cafe] Type classes

2013-05-28 Thread Tom Ellis
On Tue, May 28, 2013 at 11:22:22PM +0200, Johannes Gerer wrote:
 I have to ask, why was plausability and looking at the actual definition
 (not just the types) not important for the other examples.

It would also be important to check the definitions in the other examples
too, but it's hard enough to get the types to match!

 But I think my problem lies somewhere else. Maybe all would become
 evident, if I knew the rigorous definition of A is more general than
 B in this context. Especially when A is a class of type, that takes
 two arguments (i.e. Unit and Arrow) and B for ones, that takes only
 one (like Monad, Pure,..)

I'm not sure what the right definition is.  You are right that it is far
from obvious (at least to you and me!).

For a definition of equivalence, I feel it should go something like this:

To every instance a of A I can assign an instance b of B, and to every
instance b of B I can assign an instance a' of A.  Moreover there should be
a function polymorphic in all parameters between a and a', which has a
polymorphic inverse.  (And likewise for A and B swapped).  These functions
might need to be required to commute with all member functions of A.

Perhaps this is perfectly obvious and well known, but I haven't managed to
work it out on my own.

Tom

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


Re: [Haskell-cafe] hackage update brigade (was Re: ANNOUNCE: new bridge! (prelude-prime))

2013-05-27 Thread Tom Ellis
On Mon, May 27, 2013 at 02:10:28PM -0400, Clark Gaebel wrote:
 I'd be down for helping update packages when the time comes.

As am I, for what it's worth.

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


Re: [Haskell-cafe] HTML framework for web-ui

2013-05-21 Thread Tom Ellis
On Tue, May 21, 2013 at 06:18:16PM +0800, Adrian May wrote:
 * can I use postgres from Haskell?

I've been successfully using

http://hackage.haskell.org/package/postgresql-simple

It's fine so far except it throws exceptions willy-nilly.  (I find
exceptions very un-Haskell but some people seem to like them).

Tom

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


[Haskell-cafe] More general pattern matching

2013-05-19 Thread Tom Ellis
Suppose I have a Category C

 import Prelude hiding ((.), id)
 import Control.Category

 data C a b

 instance Category C where
(.) = undefined
id = undefined

which has products in the sense that there exists a factors function
with suitable properties

 factors :: C a (b, c) - (C a b, C a c)
 factors = undefined

Then I can define this interesting combinator

 (~~) :: (C a b - r) - (C a c - r') - C a (b, c) - (r, r')
 (f ~~ g) h = let (l, r) = factors h in (f l, g r)

which allows some form of pattern matching, for example

 a :: C z a
 b :: C z b 
 c :: C z c
 d :: C z d
 e :: C z e
 ((a, b), (c, (d, e))) = ((id ~~ id) ~~ (id ~~ (id ~~ id))) undefined

and even

 w :: C a w
 x :: C a x
 y :: C a y
 z :: (C a z, C a z')
 ((w, x), (y, z)) = ((id ~~ id) ~~ (id ~~ (id ~~ id))) undefined

Does anyone have anything to say about this?  I'm sure others must have come
across it before.  There's something very lensy going on here too.  There's
nothing special about 'Category's here, but it's an example where the
structure is demonstrated nicely.

It's a shame that the structure of the pattern must be duplicated on the
left and right of the binding.

Tom

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


Re: [Haskell-cafe] fromIntegral not enough?

2013-05-13 Thread Tom Ellis
On Mon, May 13, 2013 at 02:08:26PM -0800, Christopher Howard wrote:
 instance Integral a = Coord2 (CircAppr a) where
 
   coords2 (CircAppr divns ang rad) =
   let dAng = 2 * pi / (fromIntegral divns) in
   let angles = map (* dAng) [0..divns] in
   undefined -- To be coded...

Your definition of angles forces dAng to be of type a.  Then in order
to define dAng as the result of a / there must be a Fractional instance 
for
a.

Hope that helps.

Tom

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


Re: [Haskell-cafe] fromIntegral not enough?

2013-05-13 Thread Tom Ellis
On Mon, May 13, 2013 at 11:43:41PM +0100, Tom Ellis wrote:
 On Mon, May 13, 2013 at 02:08:26PM -0800, Christopher Howard wrote:
  instance Integral a = Coord2 (CircAppr a) where
  
coords2 (CircAppr divns ang rad) =
let dAng = 2 * pi / (fromIntegral divns) in
let angles = map (* dAng) [0..divns] in
undefined -- To be coded...
 
 Your definition of angles forces dAng to be of type a.  Then in order
 to define dAng as the result of a / there must be a Fractional instance 
 for
 a.

You probably want

let angles = map ((* dAng) . fromInteger) [0..divns] in
...

instead.

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


[Haskell-cafe] PPDP 2013: 2nd Call for Papers

2013-05-07 Thread Tom Schrijvers
 Universite de Montreal, Canada
Alan Mycroft   University of Cambrige, UK
Bruno C. d. S. Oliveira   National University of Singapore, Singapore
Alberto Pettorossi Universita di Roma Tor Vergata, Italy
Enrico PontelliNew Mexico State University, USA
Kristoffer RoseIBM Research, USA
Sukyoung Ryu   KAIST, South Korea
Vitor Santos Costa University of Porto, Portugal
Torsten Schaub University Potsdam, Germany
Tom Schrijvers Ghent University, Belgium
Martin SulzmannHochschule Karlsruhe, Germany
Wouter Swierstra   Universiteit Utrecht, The Netherlands
Tarmo Uustalu  Institute of Cybernetics, Estonia
Janis Voigtlaender University of Bonn, Germany
Meng Wang  Chalmers University of Technology, Sweden
Jan Wielemaker Universiteit van Amsterdam, The Netherlands

Program Chair

Tom Schrijvers
Department of Applied Mathematics and Computer Science
Ghent University
9000 Gent, Belgium

General Chair

Ricardo Pena
Facultad de Informatica
Universidad Complutense de Madrid
28040 Madrid, Spain
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Fwd: Backward compatibility

2013-05-05 Thread Tom Ellis
On Sun, May 05, 2013 at 10:46:23PM +0200, Alberto G. Corona  wrote:
 The case of WASH is a pity. Architecturally It was more advanced that many
 recent haskell web frameworks.  The package would have been a success with
 little changes in the DSL syntax.

Could you briefly summarise the difference between WASH's approach and that
of the more recent frameworks?

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


Re: [Haskell-cafe] Backward compatibility

2013-05-03 Thread Tom Ellis
On Fri, May 03, 2013 at 09:34:21PM +0800, Adrian May wrote:
 I never doubted that people add new stuff for valid reasons. What I'm
 interested in is whether or not it could have been done without breaking
 anything. But having thought about it for a while, I'm tending to think
 that version controlling all the standard modules is the only general
 solution.

I think you may be overestimating the severity of the breakage that
applies to the WashNGo package.

In Haskell2010 a number of module locations were renamed in order to reduce
clutter.  For example, IO became System.IO, List became Data.List and Monad
became Control.Monad.

I'm pretty sure that updating all of these module names will fix the
problem.  No one has bothered because the package is very old and there are
more suitable alternatives these days.

Tom

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


Re: [Haskell-cafe] Backward compatibility

2013-05-03 Thread Tom Murphy
On Thu, May 2, 2013 at 9:48 PM, Adrian May
adrian.alexander@gmail.comwrote:



 Is anybody in the Haskell community still interested in attracting new
 users? If so I suggest you go play with Ruby on Rails. Then you'll know
 what it's like to approach a complex and unfamiliar system where every
 crumb requires a precise version of every other. If you had my job, you'd
 find out what you needed to know within half an hour.



Rails is in many ways as (more?) backwards-incompatible as Haskell. E.g.,
Rails 4 requires(!) Ruby 1.9.3+. 1.9.3 was released in the fall of 2011.
When new major versions of Rails or Ruby come out, developers are generally
expected to make the incremental changes to keep up. It's the donkey in a
well thing -- you never get buried if you make small changes over time.

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


Re: [Haskell-cafe] Backward compatibility

2013-05-02 Thread Tom Ellis
On Thu, May 02, 2013 at 09:26:15PM +0800, Adrian May wrote:
 How about the Haskell Platform? Is that ancient history? Certainly not: it
 doesn't compile on anything but the very newest GHC. Not 7.4.1 but 7.4.2.

I'm uninformed in such matters, but from

http://www.haskell.org/platform/changelog.html

it looks like GHC 7.4.2 is *part* of Haskell Platform 2012.4.0.0, so it
doesn't make sense to talk about the latest Platform without 7.4.2.

I know that sounds like a technicality, but I don't think it actually is! 
The important question is whether *your* old code breaks with the latest
Platform, not whether the latest Platform breaks with GHC 7.4.1.

Tom

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


Re: [Haskell-cafe] Backward compatibility

2013-05-02 Thread Tom Ellis
On Thu, May 02, 2013 at 10:36:18PM +0800, Adrian May wrote:
 Please would somebody explain to me what getPackageId did to incriminate
 itself?

What's getPackageId?  It does not appear in the WASH source.

Tom

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


Re: [Haskell-cafe] Backward compatibility

2013-05-02 Thread Tom Ellis
On Thu, May 02, 2013 at 11:10:33PM +0800, Adrian May wrote:
  What's getPackageId?  It does not appear in the WASH source.

 It's in Setup.lhs, in WashNGo.

Which source of WashNGo are you using?  It doesn't appear in either of these
versions:

http://hackage.haskell.org/package/WashNGo-2.12
http://hackage.haskell.org/package/WashNGo-2.12.0.1

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


Re: [Haskell-cafe] Backward compatibility

2013-05-02 Thread Tom Ellis
On Thu, May 02, 2013 at 11:23:12PM +0800, Adrian May wrote:
  Which source of WashNGo are you using?  It doesn't appear in either of
  these
  versions:
 
  http://hackage.haskell.org/package/WashNGo-2.12
  http://hackage.haskell.org/package/WashNGo-2.12.0.1

 http://www.informatik.uni-freiburg.de/~thiemann/WASH/WashNGo-2.12.tgz

I get a 403 FORBIDDEN on that.  How did you get it?


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


Re: [Haskell-cafe] Backward compatibility

2013-05-02 Thread Tom Ellis
On Thu, May 02, 2013 at 11:35:27PM +0800, Adrian May wrote:
  I get a 403 FORBIDDEN on that.  How did you get it?

 I guess you just gotta know the right people ;-)
 
 I attached the tarball. Don't say you got it from me, OK.

That tarball still doesn't contain the string getPackageId.

You're complaining that you can't build a package, which hasn't been
maintained for several years, which you got from a secret source, and whose
whose Hackage page specifically says it doesn't build beyond GHC 7.0.  I
don't think this is indicative of a serious failure of Haskell.

Tom

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


Re: [Haskell-cafe] Monad Transformer Space Leak

2013-04-23 Thread Tom Ellis
On Tue, Apr 23, 2013 at 09:36:04AM +0200, Petr Pudlák wrote:
 I tested it on GHC 6.12.1, which wasn't affected by the recent ackermann
 bug, but still it leaks memory.

I tested it on GHC 7.4.1 and I don't see any space leak.

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


Re: [Haskell-cafe] ANN: Groundhog 0.3 - mysql, schemas and enhanced queries

2013-04-19 Thread Tom Ellis
On Fri, Apr 19, 2013 at 11:42:14AM +0300, Boris Lykah wrote:
 The full description of the configuration options is available at
 http://hackage.haskell.org/packages/archive/groundhog-th/0.3.0/doc/html/Database-Groundhog-TH.html

Hi Boris, the docs for 0.3.0 don't currently seem to exist.

Tom

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


[Haskell-cafe] ANN: rematch, an library for composable assertions with human readable failure messages

2013-04-16 Thread Tom Crayford
I kept on running into this thing where I was calling error in quickcheck
to get good error messages about the things I was comparing. In Java land,
this stuff is handled by Hamcrest: a library for composable assertions with
good error messages. This library is basically a port of hamcrest's core
api, but I've been very pleased with how it turned out.

I've been using this in tests for production code for a month or so now,
and I'm very pleased with it.

Running a matcher (in this example in an hunit test) looks like this:

expect [1] (is [1])

 The core API is very simple:

data Matcher a = Matcher {
match :: a - Bool
  -- ^ A function that returns True if the matcher should pass, False if it
should fail
  , description :: String
  -- ^ A description of the matcher (usually of its success conditions)
  , describeMismatch :: a - String
  -- ^ A description to be shown if the match fails.
  }

This means you can add/write your own matchers happily, which occasionally
means you can write *very* nice test code (here's an example of using a
custom matcher for checking the state of an issue in a hypothetical issue
tracking app):

expect latestIssue (hasState Resolved)

-- I removed the supporting code to make this assertion actually run,
-- this email is already pretty long.

There are numerous matchers (and functions for creating matchers) in the
rematch library, including some composition functions that provide good
failure messages.

There are some shims to hook rematch into the common haskell test
frameworks (specifically hunit and quickcheck).

The two libraries are up on hackage:
http://hackage.haskell.org/package/rematch
http://hackage.haskell.org/package/rematch-text

The code is all up on github:

http://github.com/tcrayford/rematch

I get rather frustrated when my tests give bad failure explanations, and
using rematch goes a long way to fix that.

Lastly, rematch is pretty isolated from test frameworks/etc, with a very
small and easy to understand surface api. Hopefully it'll help with the
thing I've seen in other languages (cough ruby cough) with every test
framework reinventing this idea, and not all frameworks having all the
matchers I want to use.

Let me know if you have any feedback/thoughts

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


Re: [Haskell-cafe] ANN: rematch, an library for composable assertions with human readable failure messages

2013-04-16 Thread Tom Ellis
On Tue, Apr 16, 2013 at 10:17:48AM +0100, Tom Crayford wrote:
 I kept on running into this thing where I was calling error in quickcheck
 to get good error messages about the things I was comparing. In Java land,
 this stuff is handled by Hamcrest: a library for composable assertions with
 good error messages. This library is basically a port of hamcrest's core
 api, but I've been very pleased with how it turned out.
[...]
 Let me know if you have any feedback/thoughts

I've been feeling the need for something like this for some time.  I'll
check it out.  Thanks!

Tom
 

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


Re: [Haskell-cafe] Monad fold

2013-04-16 Thread Tom Ellis
On Tue, Apr 16, 2013 at 01:53:19PM +0100, Oliver Charles wrote:
 On 04/16/2013 01:47 PM, Lyndon Maydwell wrote:
 You could do:
 
 runKleisli . mconcat . map Kleisli :: Monoid (Kleisli m a b) = [a
 - m b] - a - m b
 
 Would that work for you?
 I can't find an instance for Monoid (Kleisli m a b) in `base`, so
 presumably the author would also have to write this instance? If so
 - would that really be any different to using that fold?

It doesn't make sense anyway.  It would have to be Kleisli m a a which
would presumably require a newtype.

Tom

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


Re: [Haskell-cafe] ANN: rematch, an library for composable assertions with human readable failure messages

2013-04-16 Thread Tom Crayford
Roman,

Thanks for the feedback! I'd originally left the QuickCheck and HUnit
implementations in this library for convenience, thinking that there aren't
going to be many people who care about the transitive dep. But you care, so
I'm happy moving them out of core. I'll release a 0.2 with both the HUnit
and the QuickCheck runners in separate libraries soonish.

Thanks for the haddock tip and the implementation tips.

Re the Control namespace, these matchers aren't exclusively a testing tool.
I've been using the core api for other purposes as well (primarily for
validating forms in user interfaces in conjunction with
digestive-functors). I couldn't figure anything better to put it in apart
from Control (I definitely don't want it in Test, even though that's going
to be what most people use it for). I guess it could be in `Data`, but that
doesn't sound much better to me.

I'm not amazingly strong at building more principled interfaces right now,
so I guess that's something I'll improve on. Are there any concrete
suggestions you have there? I'd *like* these to have an `Alternative`
instance, but making `Applicative`/`Functor` instances is beyond me right
now (I guess I'd have to change the core API for that to work out).

Tom


On 16 April 2013 15:09, Roman Cheplyaka r...@ro-che.info wrote:

 Hi Tom,

 This is a neat idea! I'd like to use something like this in smallcheck
 and test-framework-golden.

 The main obstacle to that is that your package depends on QuickCheck and
 HUnit, and every package using rematch would transitively depend on
 them, too. This has little sense, especially for smallcheck which is in
 some sense a replacement for QuickCheck.

 The alternative is either to put HUnit and QuickCheck interfaces in
 the separate packages, or try to get them accepted into the HUnit and
 QuickCheck directly.

 Below are some more suggestions regarding the package:

 1. You need to escape single and double quotes in the haddock
documentation; otherwise they'll be turned into (bad) links.

 2. Your 'join' function is a special case of 'intercalate' from
Data.List.

 3. The Control namespace doesn't quite match the purpose of your
modules, since they are not about control flow. Perhaps Test?

 I also wonder whether there is a more principled approach to such an API —
 say, based on applicative functors.

 Roman

 * Tom Crayford tcrayf...@gmail.com [2013-04-16 10:17:48+0100]
  I kept on running into this thing where I was calling error in quickcheck
  to get good error messages about the things I was comparing. In Java
 land,
  this stuff is handled by Hamcrest: a library for composable assertions
 with
  good error messages. This library is basically a port of hamcrest's core
  api, but I've been very pleased with how it turned out.
 
  I've been using this in tests for production code for a month or so now,
  and I'm very pleased with it.
 
  Running a matcher (in this example in an hunit test) looks like this:
 
  expect [1] (is [1])
 
   The core API is very simple:
 
  data Matcher a = Matcher {
  match :: a - Bool
-- ^ A function that returns True if the matcher should pass, False if
 it
  should fail
, description :: String
-- ^ A description of the matcher (usually of its success conditions)
, describeMismatch :: a - String
-- ^ A description to be shown if the match fails.
}
 
  This means you can add/write your own matchers happily, which
 occasionally
  means you can write *very* nice test code (here's an example of using a
  custom matcher for checking the state of an issue in a hypothetical
 issue
  tracking app):
 
  expect latestIssue (hasState Resolved)
 
  -- I removed the supporting code to make this assertion actually run,
  -- this email is already pretty long.
 
  There are numerous matchers (and functions for creating matchers) in the
  rematch library, including some composition functions that provide good
  failure messages.
 
  There are some shims to hook rematch into the common haskell test
  frameworks (specifically hunit and quickcheck).
 
  The two libraries are up on hackage:
  http://hackage.haskell.org/package/rematch
  http://hackage.haskell.org/package/rematch-text
 
  The code is all up on github:
 
  http://github.com/tcrayford/rematch
 
  I get rather frustrated when my tests give bad failure explanations, and
  using rematch goes a long way to fix that.
 
  Lastly, rematch is pretty isolated from test frameworks/etc, with a very
  small and easy to understand surface api. Hopefully it'll help with the
  thing I've seen in other languages (cough ruby cough) with every test
  framework reinventing this idea, and not all frameworks having all the
  matchers I want to use.
 
  Let me know if you have any feedback/thoughts
 
  Tom

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

Re: [Haskell-cafe] unsafeInterleaveST (and IO) is really unsafe [was: meaning of referential transparency]

2013-04-11 Thread Tom Ellis
On Thu, Apr 11, 2013 at 12:49:40PM +1200, Richard A. O'Keefe wrote:
 On 10/04/2013, at 2:45 PM, o...@okmij.org wrote:
 ... unsafeInterleaveST is really unsafe ...
 
  import Control.Monad.ST.Lazy (runST)
  import Control.Monad.ST.Lazy.Unsafe (unsafeInterleaveST)
  import Data.STRef.Lazy
  
  bad_ctx :: ((Bool,Bool) - Bool) - Bool
  bad_ctx body = body $ runST (do
r - newSTRef False
x - unsafeInterleaveST (writeSTRef r True  return True)
y - readSTRef r
return (x,y))
  
  t1 = bad_ctx $ \(x,y) - x == y   -- True
  t2 = bad_ctx $ \(x,y) - y == x   -- False

[...]
 I don't understand what it does or *how* it breaks this code.  Does it
 involve side effects being reordered in some weird way?

As I understand it, unsafeInterleaveST defers the computation of x, so

  * if x is forced before y, then writeSTRef r True
is run before readSTRef r, thus the latter yields True

  * if y is forced before x, then writeSTRef r True is run after
readSTRef r, thus the latter yields False

Tom

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


Re: [Haskell-cafe] Numerics and Warnings

2013-04-10 Thread Tom Ellis
On Wed, Apr 10, 2013 at 03:38:35PM +0100, Barak A. Pearlmutter wrote:
 In fiddling around with some numeric code in Haskell, I noticed some
 issues.  Basically, you get warnings if you write
 
   energy mass = mass * c^2
 
 but not if you write
 
   energy mass = mass * c * c

Numeric typeclasses are syntactically convenient, but are rather too
implicit for my taste.  I prefer using monomorphic versions once the code
becomes serious.  For example,

import Prelude hiding ((^))
import qualified Prelude

(^) :: Num a = a - Integer - a
(^) = (Prelude.^)

energy mass = mass * c^2

This does not solve your other issues though.

Tom

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


Re: [Haskell-cafe] Numerics and Warnings

2013-04-10 Thread Tom Ellis
On Wed, Apr 10, 2013 at 11:20:15PM +0400, Aleksey Khudyakov wrote:
 This IS rather annoying problem for numeric code. Raising value to positive
 power is quite common operation yet ^ operator generally couldn't be used
 because it leads to warning about type defaulting (rightfully) and one
 wants to keep code warning free. Actually it's problem with warnings and
 I don't think adding some ad-hoc rules for generating warning is necessarily
 bad idea

Like I demonstrated in my reply to Barak, there is a way around this which
does not require adding ad-hoc complexity to the compiler.

Tom

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


Re: [Haskell-cafe] Numerics and Warnings

2013-04-10 Thread Tom Ellis
On Thu, Apr 11, 2013 at 12:56:05AM +0100, Barak A. Pearlmutter wrote:
  ... in most of the cases I do want this warnings. It's possible to get
  something default to Integer when it should be Int. There are only few
  cases when it's not appropriate. Only ^ and ^^ with literals I think
 
 There are a few other cases, albeit less annoying.  Like this:
 
 c = fromIntegral 2 :: Int
 
 Granted this is silly code, but the same case arises inside pretty much
 any code that is generic over Integral, in which case the warning you
 get is not the *right* warning.  Example:
 
 genericTake n xs = take (fromIntegral n) xs
 genericTake 44 foobar

Hi Barak,

I don't write a lot of numeric code so I am under-educated in this area.
Could you write a more substantial example so I get a clearer idea of what's
going on?

Thanks,

Tom

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


Re: [Haskell-cafe] Prolog-style patterns

2013-04-08 Thread Tom Murphy
On Mon, Apr 8, 2013 at 7:59 AM, Joachim Breitner
m...@joachim-breitner.dewrote:

 Hi,

 I believe one problem with non-linear patterns would be that the
 compiler has to figure out what notion of equality you want here. An
 obvious choice is (==), but the Eq instances might not do what you want.
 Using pattern guards or view patterns explicates this choice.


What other types of equality would be possibilities?


Also, for some history, this was discussed a while back:
http://www.mail-archive.com/haskell@haskell.org/msg03721.html

Erlang programmers have this feature without shooting themselves in the
foot too often. That said, I'm happy without it.

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


Re: [Haskell-cafe] Haskell is a declarative language? Let's see how easy it is to declare types of things.

2013-04-06 Thread Tom Ellis
On Sat, Apr 06, 2013 at 05:14:48PM -0400, Albert Y. C. Lai wrote:
 On 13-04-05 04:56 AM, Tom Ellis wrote:
 any is very ambiguous.  Doesn't the problem go away if you replace it with
 all?
 
 Yes, that is even better.
 
 The world would be simple and elegant if it did things your way, and
 would still be not too shabby if it did things my way, no?

I'm not sure what your way is, but since you seem to be arguing for
explicitness then I agree.

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


  1   2   3   4   5   6   7   >