Re: [Haskell-cafe] Using lenses

2013-10-03 Thread Tony Morris
Lenses for nested sum types e.g. Either.
 On 03/10/2013 6:08 PM, Simon Peyton-Jones simo...@microsoft.com wrote:

  (I sent this to ‘libraries’ but Kim-Ee suggested adding Café, where so
 many smart people hang out.)

 ** **

 Friends

 ** **

 Some of you will know that I’ve promised to give a talk about Edward’s
 lens library http://hackage.haskell.org/package/lens at the Haskell
 Exchange http://skillsmatter.com/event/scala/haskell-exchange in London
 next Wednesday (9th).  I did this to give everyone (including me) a break
 from GHC hackery, and also to force me to learn about this lens voodoo that
 everyone is twittering about.  Edward generously gave me quite a bit of
 one-to-one attention last week (my hair is still standing on end), but this
 message is to ask your help too.


 *Specifically, I’d like to give some compelling use-cases*.   If you are
 using the lens library yourself, could you spare a few minutes to tell me
 how you are using it?  I expect to cover Lens and Traversal but not Prism.
 

 ** **

 The use-case everyone starts with is nested records, but I’d like to go
 beyond that.  The next levels seem to be:

 **· **Lenses as views of data that isn’t “really there” e.g.
 regarding a record with rectangular coordinates as having polar coordinates
 too.

 **· **Lenses and Traversals that focus on elements of finite maps
 (Control.Lens.At)

 ** **

 What else? I’m sure you are using them in all sorts of cool ways that I
 would never think of, and I’d love to know.

 ** **

 Please don’t tell me anything secret!  To give everyone the benefit I may
 just concatenate all the replies and send to you all, so please say if you
 don’t want me to do that with yours. 

 ** **

 And don’t burn too many cycles on this...I don’t want to waste your time,
 and I can always get back to you if I can’t understand what you say.
 Sooner is better than later...Weds is coming.

 ** **

 Simon “Edward’s prophet” PJ

 ** **

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


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


Re: [Haskell-cafe] Traversals of monomorphic containers

2013-09-03 Thread Tony Morris
These questions are exactly what Control.Lens answers.
 On 04/09/2013 12:50 PM, Mario Blažević blama...@acanac.net wrote:

 On 09/02/13 06:53, Nicolas Trangez wrote:

 # Redirected to haskell-cafe

 On Sun, 2013-09-01 at 14:58 +0400, Artyom Kazak wrote:

 Would this be an appropriate place to propose adding mapM_ (and then
 possibly mapM) to bytestring library?

 Was it suggested before? If yes, why was it rejected?


 This got me wondering: there are several type-classes useful for
 polymorphic container types, e.g. Functor, Foldable  Traversable which
 all apply to some type of kind (* - *).

 Are there related things for monomorphic containers, like ByteString,
 Text or some newtype'd Vector with fixed element type, e.g.

 class MFunctor f a where
  mfmap :: (a - a) - f - f

 instance MFunctor ByteString Word8 where
  mfmap = ByteString.map



 I'm not aware of this particular class, but I have considered it.
 In the end I've chosen to generalize the class to FactorialMonoid instead:

 class Monoid m = FactorialMonoid m where
...
foldMap :: Monoid n = (m → n) → m → n

 ByteString and Text are instances of the class, and so are lists,
 maps, and other containers, and Sum and Product as well.


 http://hackage.haskell.org/**packages/archive/monoid-**
 subclasses/0.3.2/doc/html/**Data-Monoid-Factorial.htmlhttp://hackage.haskell.org/packages/archive/monoid-subclasses/0.3.2/doc/html/Data-Monoid-Factorial.html




 or (maybe even better)

 class MFunctor f where
  type Elem
  mfmap :: (Elem - Elem) - f - f

 instance MFunctor ByteString where
  type Elem = Word8
  mfmap = ByteString.map

 and similar for other classes.

 Nicolas


 __**_
 Haskell-Cafe mailing list
 Haskell-Cafe@haskell.org
 http://www.haskell.org/**mailman/listinfo/haskell-cafehttp://www.haskell.org/mailman/listinfo/haskell-cafe



 __**_
 Haskell-Cafe mailing list
 Haskell-Cafe@haskell.org
 http://www.haskell.org/**mailman/listinfo/haskell-cafehttp://www.haskell.org/mailman/listinfo/haskell-cafe

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


Re: [Haskell-cafe] mapFst and mapSnd

2013-05-31 Thread Tony Morris
class BinaryFunctor f where
  bimap :: (a - c) - (b - d) - f a b - f c d

mapFst = (`bimap id`)
mapSnd = bimap id
 On 31/05/2013 12:16 PM, Shachaf Ben-Kiki shac...@gmail.com wrote:

 On Thu, May 30, 2013 at 7:12 PM, Shachaf Ben-Kiki shac...@gmail.com
 wrote:
  One generalization of them is to lenses. For example `lens` has
  both, _1, _2, such that mapPair = over both, mapFst = over
  _1, etc., but you can also get fst = view _1, set _2 = \y' (x,_)
  - (x,y'), and so on. (Since both refers to two elements, you end
  up with view both = \(x,y) - mappend x y.) The types you end up
  with are simple generalizations of mapFoo, with just an extra Functor
  or Applicative (think mapMFoo):
 
  both :: Applicative f = (a - f b) - (a,a) - f (b,b)
  both f (x,y) = (,) $ f x * g y
 
  _2 :: Functor f = (a - f b) - (e,a) - f (e,b)
  _2 f (x,y) = (,) x $ f y
 
  With an appropriate choice of f you can get many useful functions.
 

 I spoke too quickly -- your mapPair is something different. Indeed
 bimap (or (***), if you prefer base) is the place to find it -- lenses
 don't really fit here. My both is for mapping one function over both
 elements.

 Shachaf

 ___
 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] LambdaJam 2013

2013-03-04 Thread Tony Morris
Hey haskell guys,
LambdaJam 2013 is a functional programming conference to be held in
Brisbane in early May.

Call for submissions ends this Friday 08 March. If you are planning to
make a submission, please make sure you do soon!

If you are stuck somehow, I'd love to be able to help you get to the
goal. So feel free to send me an email or I am on IRC (dibblego),
lurking around the #haskell channel or privmsg if you like. Personally,
I would love see more haskell submissions :)

LambdaJam2013 call for papers:
http://www.yowconference.com.au/lambdajam/Call.html

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


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


Re: [Haskell-cafe] CoArbitrary

2013-02-10 Thread Tony Morris
On 09/02/13 15:08, Roman Cheplyaka wrote:
 I don't think the question was about generating functions...
 FWIW, both QuickCheck and SmallCheck generate functions. There was also
 an interesting paper at the last ICFP by Koen related to this.

 But I think Tony is looking for some kind of a pattern here...

 Roman

 * Stephen Tetley stephen.tet...@gmail.com [2013-02-09 10:50:45+]
 I think GAST - the Clean equivalent of Quickcheck - generates
 functions. There are certainly quite a few papers by members of the
 Clean team documenting how they generate them.

 On 9 February 2013 07:07, Tony Morris tonymor...@gmail.com wrote:
 [...]
 I hope I have phrased this in a way to make the point. I found it a bit
 difficult to articulate and I do wonder (hope!) that others encounter
 similar scenarios. Thanks for any tips!
 ___
 Haskell-Cafe mailing list
 Haskell-Cafe@haskell.org
 http://www.haskell.org/mailman/listinfo/haskell-cafe
Yeah I am looking for a possible pattern. I am struggling to explain the
problem. Perhaps some code will help.

This code compiles, however the function problem is the one I am
looking for. There are two data structures here:
1) Op, which is a functor
2) FreeOp, which is a monad that arises from the Op functor (i.e. an
instance of the free monad)

There are some functions for demonstration:
1) productOp -- An example of zipping two FreeOp instances, just to show
that you can (though, this is trivial by the monad)
2) booleanOp -- Produces a FreeOp Bool by using the IntOp constructor for Op
3) coproductOp -- An example of splitting out two FreeOp instances, to
show this is possible too.

* The question is, what about a function FreeOp b - FreeOp (a - b)?
* Can I constrain the 'a' type variable somehow to come up with
something similar to CoArbitrary (QuickCheck)?
* Can I generalise this idea i.e. not just FreeOp? Or for CoArbitrary,
not just for Gen?
* Is there a pattern here that is currently not part of my mental tool
kit? I am struggling to see it; maybe just it's not there.

As always, thanks for any pointers!

Begin code...


data Op a =
  DoubleOp (Double - a)
  | IntOp (Int - a)

data FreeOp a =
  Suspend (Op (FreeOp a))
  | Point a

 examples

productOp ::
  FreeOp a
  - FreeOp b
  - FreeOp (a, b)
productOp a b =
  do a' - a
 b' - b
 return (a', b')

boolOp ::
  FreeOp Bool
boolOp =
  Suspend (fmap Point (IntOp even))

coproductOp ::
  FreeOp a
  - FreeOp b
  - FreeOp (Either a b)
coproductOp a b =
  boolOp = \p - if p then fmap Left a else fmap Right b

 The Problem

problem ::
  -- ? c =
  -- ? other arguments
  FreeOp b
  - FreeOp (a - b)
problem =
  error what constraints on 'a' to allow an implementation of this
function that uses the argument?
  -- fmap const -- type-checks, but ignores the argument, unlike e.g.
QuickCheck which uses CoArbitrary to perturb that result with the
argument.

 support libraries

instance Functor Op where
  fmap f (DoubleOp g) =
DoubleOp (f . g)
  fmap f (IntOp g) =
IntOp (f . g)

instance Functor FreeOp where
  fmap f =
(=) (return . f)

instance Monad FreeOp where
  return =
Point
  Suspend o = f =
Suspend (fmap (= f) o)
  Point a = f =
f a


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


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


[Haskell-cafe] CoArbitrary

2013-02-08 Thread Tony Morris
Hello,
In the QuickCheck library, there is a type-class called CoArbitrary. It
is defined like so:

class CoArbitrary a where
  coarbitrary :: a - Gen b - Gen b -- Gen is a monad

Its purpose is to allow generation of functions. In other words, for
taking Gen x - Gen (a - x), which could be done rather degenerately
(fmap const) but QuickCheck constrains with (CoArbitrary a) to perturb
the resulting value instead of ignoring (const) it.

It has always puzzled me in the general sense of thinking about the
scenario: f x - f (a - x) and whether the CoArbitrary is a
good/general solution, perhaps for the specific case of f=Gen or maybe
even more generally.

-- approximate
(a - f x - f x) -- e.g. CoArbitrary to perturb the result
- f x -- e.g. Gen x
- f (a - x) -- e.g. Gen (a - x)

So I often wonder about what might be a better (and perhaps more
general) constraint to produce functions f x - f (a - x) for a given
Monad f. I was wondering if there is an existing abstraction (or paper)
that might point me in that direction. It is a problem that I encounter
on occasion in general programming and I am using Arbitrary/CoArbitrary
as an example to help make my point, but I am dissatisfied (for reasons
that I am unsure about) with the solution provided by CoArbitrary.

What about other monads? For example, what is a general constraint to be
placed to permit a function Maybe x - Maybe (a - x) that does not
simply const away the argument.

I hope I have phrased this in a way to make the point. I found it a bit
difficult to articulate and I do wonder (hope!) that others encounter
similar scenarios. Thanks for any tips!

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


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


Re: [Haskell-cafe] Control.bimap?

2012-12-12 Thread Tony Morris
Check out Control.Lens on hackage.

On 13/12/12 07:54, Gregory Guthrie wrote:

 I found a nice idiom for a graph algorithm where the pairs of nodes
 representing links could be merged into node lists by something like:

 ns = nub $ map fst  g--head nodes

 ne = nub $ map snd g   -- tail nodes

  

 And found a nicer approach:

(ns,ne) = (nub***nub) unzip g

 Or perhaps:

(ns.ne) = bimap nub nub $ unzip g-- from Control.Bifunctor

  

 The SO reference I saw described bimap as a way to map a function over
 a pair, and it seemed like a great match, but I cannot find the bimap
 function, and cabal reports no package Control.Bifunctor.

 ??

 ---



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


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

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


Re: [Haskell-cafe] Segment Tree based Set

2012-10-29 Thread Tony Morris
It is not a Set, but a Map. Of course, I could use it to implement the
function I need with something like: type SSet a = STree [()] a, but
then I'd have to unnecessarily go beyond Haskell98.

Hoping there might be an interval tree or segment tree specifically for
this task.

On 29/10/12 18:36, Roman Cheplyaka wrote:
 If you searched hackage, you'd find
 http://hackage.haskell.org/package/SegmentTree

 Roman

 * Tony Morris tonymor...@gmail.com [2012-10-29 15:38:07+1000]
 Er, oops.

 ...can be implemented as:
 \a rs - let s = Set.fromList (rs = \(a, b) - [a..b]) in a `member` s

 Something like that!

 On Mon, Oct 29, 2012 at 2:48 PM, Tony Morris tonymor...@gmail.com wrote:

 Hi,
 I was wondering if anyone knows of a package implementing a fast lookup
 for an element in ranges.

 For example, this operation:
 Ord a = a - [(a, a)] - Bool

 ...can be implemented:
 \a rs - let s = Set.fromList rs in a `member` s

 This is not particularly efficient. A segment tree seems like a more
 appropriate data structure to store the ranges. Does such a library exist?


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



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


Re: [Haskell-cafe] Segment Tree based Set

2012-10-29 Thread Tony Morris
Yeah that looks useful indeed. I am surprised there isn't a DIET on hackage.

On Tue, Oct 30, 2012 at 3:55 AM, Stephen Tetley stephen.tet...@gmail.comwrote:

 Are Martin Erwig's diets anything close?

 http://web.engr.oregonstate.edu/~erwig/diet/

 On 29 October 2012 04:48, Tony Morris tonymor...@gmail.com wrote:
  Hi,
  I was wondering if anyone knows of a package implementing a fast lookup
  for an element in ranges.
 
  For example, this operation:
  Ord a = a - [(a, a)] - Bool
 

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


[Haskell-cafe] Segment Tree based Set

2012-10-28 Thread Tony Morris
Hi,
I was wondering if anyone knows of a package implementing a fast lookup
for an element in ranges.

For example, this operation:
Ord a = a - [(a, a)] - Bool

...can be implemented:
\a rs - let s = Set.fromList rs in a `member` s

This is not particularly efficient. A segment tree seems like a more
appropriate data structure to store the ranges. Does such a library exist?

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



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


Re: [Haskell-cafe] Segment Tree based Set

2012-10-28 Thread Tony Morris
Er, oops.

...can be implemented as:
\a rs - let s = Set.fromList (rs = \(a, b) - [a..b]) in a `member` s

Something like that!

On Mon, Oct 29, 2012 at 2:48 PM, Tony Morris tonymor...@gmail.com wrote:

 Hi,
 I was wondering if anyone knows of a package implementing a fast lookup
 for an element in ranges.

 For example, this operation:
 Ord a = a - [(a, a)] - Bool

 ...can be implemented:
 \a rs - let s = Set.fromList rs in a `member` s

 This is not particularly efficient. A segment tree seems like a more
 appropriate data structure to store the ranges. Does such a library exist?

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





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


Re: [Haskell-cafe] foldr (.) id

2012-10-26 Thread Tony Morris
It's the Endo monoid.

? :t ala Endo foldMap -- see newtype package
ala Endo foldMap :: Foldable t = t (a - a) - a - a
? ala Endo foldMap [(+1), (*2)] 8
17
? :i ala
ala ::
  (Newtype n o, Newtype n' o') =
  (o - n) - ((o - n) - b - n') - b - o'
  -- Defined in Control.Newtype


On 27/10/12 04:41, Greg Fitzgerald wrote:
 Hi Haskellers,

 I've recently found myself using the expression: foldr (.) id to compose
 a list (or Foldable) of functions.  It's especially useful when I need to
 map a function over the list before composing.  Does this function, or the
 more general foldr fmap id, defined in a library anywhere?  I googled and
 hoogled, but no luck so far.

 Thanks,
 Greg



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


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


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


Re: [Haskell-cafe] Why Kleisli composition is not in the Monad signature?

2012-10-24 Thread Tony Morris
As a side note, I think a direct superclass of Functor for Monad is not
a good idea, just sayin'

class Functor f where
  fmap :: (a - b) - f a - f b

class Functor f = Apply f where
  (*) :: f (a - b) - f a - f b

class Apply f = Bind f where
  (=) :: (a - f b) - f a - f b

class Apply f = Applicative f where
  unit :: a - f a

class (Applicative f, Bind f) = Monad f where

Same goes for Comonad (e.g. [] has (=) but not counit)
... and again for Monoid, Category, I could go on...


On 17/10/12 04:14, David Thomas wrote:
 I think the version below (with a Functor or Applicative superclass)
 is clearly the right answer if we were putting the prelude together
 from a clean slate.  You can implement whichever is easiest for the
 particular monad, use whichever is most appropriate to the context
 (and add optimized versions if you prove to need them).  I see no
 advantage in any other specific proposal, except the enormous
 advantage held by the status quo that it is already written, already
 documented, already distributed, and already coded to.

 Regarding mathematical purity of the solutions, this is in every
 way isomorphic to a monad, but we aren't calling it a monad because we
 are describing it a little differently than the most common way to
 describe a monad in category theory strikes me as *less*
 mathematically grounded than we are calling this a monad because it
 is in every way isomorphic to a monad.

 On Tue, Oct 16, 2012 at 7:03 AM, AUGER Cédric sedri...@gmail.com wrote:
 So I think that an implicit question was why wouldn't we have:

 class Monad m where
   return :: a - m a
   kleisli :: (a - m b) - (b - m c) - (a - m c)
   bind = \ x f - ((const x) = f) ()
   join = id=id :: (m (m a) - m a)
 ___
 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


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



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


[Haskell-cafe] Flipping type constructors

2012-08-13 Thread Tony Morris
I have a data-type that is similar to EitherT, however, I have ordered
the type variables like so:

data EitherT (f :: * - *) (a :: *) (b :: *) = ...

This allows me to declare some desirable instances:

instance Functor f = Bifunctor (EitherT f)
instance Foldable f = Bifoldable (EitherT f)
instance Traversable f = Bitraversable (EitherT f)

However, I am unable to declare a MonadTrans instance:

instance MonadTrans (EitherT a) -- kind error

I looked at Control.Compose.Flip to resolve this, but it does not appear
to be kind-polymorphic.
http://hackage.haskell.org/packages/archive/TypeCompose/0.9.1/doc/html/src/Control-Compose.html#Flip

I was wondering if there are any well-developed techniques to deal with
this? Of course, I could just write my own Flip with the appropriate
kinds and be done with it. Maybe there is a more suitable way?


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



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


Re: [Haskell-cafe] Martin Odersky on What's wrong with Monads

2012-06-24 Thread Tony Morris
Odersky is repeatedly wrong on this subject and specifically for the
claim that you quote, the only response is simply not true.

On 24/06/12 15:31, Jonathan Geddes wrote:
 Cafe,

 I was watching a panel on languages[0] recently and Martin Odersky (the
 creator of Scala) said something about Monads:

 What's wrong with Monads is that if you go into a Monad you have to change
 your whole syntax from scratch. Every single line of your program changes
 if you get it in or out of a Monad. They're not polymorphic so it's really
 the old days of Pascal. A monomorphic type system that says 'well that's
 all I do' ... there's no way to abstract over things.  [0, 53:45]

 Thoughts?

 --J Arthur

 [0] - http://css.dzone.com/articles/you-can-write-large-programs



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


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


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


Re: [Haskell-cafe] Perth Functional Programmers meetup group launched

2012-06-13 Thread Tony Morris
Hi Todd,
I am over the other side. I help organise the Brisbane Functional
Programming Group.
http://bfpg.org/

Although we discuss FP in general, we have a pretty strong emphasis on
Haskell. Let me know how it goes or if we can help out in any way!


On 14/06/12 00:46, Todd Owen wrote:
 We are pleased to announce that a functional programming user group has
 recently been formed in Perth, Australia.

 Being a small community, we aim to keep the group as inclusive as possible,
 and welcome new members from all levels of experience and language
 backgrounds. (That said, Haskellers currently account for about half our
 membership, followed by F#, and then a heap of other languages).

 As this is a global mailing list, I would also like to invite our
 colleagues from around Australia, and indeed anywhere in the world, to get
 in touch if you are ever passing through Perth. We're always happy to share
 a beer and talk about programming!

 For more information, visit: http://www.meetup.com/PerthFP/



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


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


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


Re: [Haskell-cafe] Unit and pair

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

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

 Is there a somewhat standard class like this:

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

 ?

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

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

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

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



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


[Haskell-cafe] Haskell source AST zipper with state

2012-05-02 Thread Tony Morris
Is there a library to traverse a source AST keeping state?

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



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


Re: [Haskell-cafe] Does somebody know about these functions?

2012-02-29 Thread Tony Morris
On 01/03/12 14:40, wren ng thornton wrote:
 Of course, you can simplify the implementation by:

 inter f xs = zipWith f xs (tail xs) 
inter f = zipWith f * tail

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



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


Re: [Haskell-cafe] Not an isomorphism, but what to call it?

2012-01-19 Thread Tony Morris
-BEGIN PGP SIGNED MESSAGE-
Hash: SHA1

On 01/20/2012 07:24 AM, Sean Leather wrote:
 I have two types A and B, and I want to express that the composition of two
 functions f :: B - A and g :: A - B gives me the identity idA = f . g ::
 A - A. I don't need g . f :: B - B to be the identity on B, so I want a
 weaker statement than isomorphism.
 
 I understand that:
 (1) If I look at it from the perspective of f, then g is the right inverse
 or section (or split monomorphism).
 (2) If I look at from g, then f is the left inverse or retraction (or split
 epimorphism).
 
 But I just want two functions that give me an identity on one of the two
 types and I don't care which function's perspective I'm looking at it from.
 Is there a word for that?
 
 Regards,
 Sean
 
 
 
 
 ___
 Haskell-Cafe mailing list
 Haskell-Cafe@haskell.org
 http://www.haskell.org/mailman/listinfo/haskell-cafe

It is not clear to me exactly what you are asking, so shot in the dark:
injection or surjection?


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

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

iQEcBAEBAgAGBQJPGJNXAAoJEPxHMY3rBz0PHt0IAKP1lVcfDXZm00h4W1WQPDBT
h6LB9nLlp0cgAh5CH06FsdQFqdtDVJNMkV7/9q3H/wTFOoscZHCTigr1G+vE/kA8
lh1/Gb3caQByt6rWkgD79998FL5ZCBdHN2HYh1o/RPBwA/BYxA041P92pE0EFTKB
1oylh5ldUfv8rEzvHhQVw0USrJ11uiZfn/T3+UrO2s2xLQZS1oTWNZhsKMccjB95
tYaqEw+20Q+8yBanVnDJFOqD3yPXIRBHkTSJTOFO+Y++oen4gXUzSJJ2lkpXLECE
ojMNHD/9Yh43gCm1Jq3Wuz5B6mr+v+RTRuLkxiVMsK7wxW+lfmOgeMyxHyr8pxU=
=aPtB
-END PGP SIGNATURE-

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


Re: [Haskell-cafe] Functor0?

2012-01-15 Thread Tony Morris
On 01/16/2012 03:26 PM, Evan Laforge wrote:
 Often when I define some type that wraps something else, I find myself writing
 a function like the following:

 newtype Thing = Thing X
 liftThing f (Thing x) = Thing (f x)

 It's like a Functor, but I can't make it an instance because Functor
 requires that the type be parametric.  So I've been using type families to
 make a kind of 0 argument functor:

 class Functor0 a where
 type Elem a :: *
 fmap0 :: (Elem a - Elem a) - a - a

 instance Functor0 Thing where
 type Elem Thing = X
 fmap0 = liftThing

 Is there a name for this?  A better way to do it?

 ___
 Haskell-Cafe mailing list
 Haskell-Cafe@haskell.org
 http://www.haskell.org/mailman/listinfo/haskell-cafe
?
http://hackage.haskell.org/packages/archive/newtype/0.2/doc/html/Control-Newtype.html
?

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



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


Re: [Haskell-cafe] strict, lazy, non-strict, eager

2011-12-24 Thread Tony Morris
On 24/12/11 17:54, Yves Parès wrote:
 See that's typically the speech that scares people away from Haskell...



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

Wait what?

I find it intriguing, helpful, provocative and potentially helpful
toward the common goal of helping others. I am interested in further
commentary. I'm not scared and you shouldn't be either.

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


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


Re: [Haskell-cafe] strict, lazy, non-strict, eager

2011-12-24 Thread Tony Morris
On 24/12/11 18:41, Gregory Crosswhite wrote:
 On Dec 24, 2011, at 6:22 PM, Tony Morris wrote:

 Wait what?

 I find it intriguing, helpful, provocative and potentially helpful toward 
 the common goal of helping others. I am interested in further commentary. 
 I'm not scared and you shouldn't be either.
 Asking honest questions is imminently reasonable; accusing others of being 
 incompetent hypocrites --- especially when you go to great length to make it 
 clear that this is *exactly* what you are doing --- is not.  The former is 
 helpful, but the latter is poisonous.  Yves's point is that doing the latter 
 risks scaring people away.

 Cheers,
 Greg

If I am an incompetent hypocrite, I want to know more. Toughen up.

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



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


[Haskell-cafe] Lens with merge (Semigroup)

2011-09-05 Thread Tony Morris
A regular Lens can be represented as follows:

data CoState a = CoState (a - b) a

newtype Lens a b = Lens (a - CoState b a)

I once read about a lens representation that permits a general merge
operation. I forget where I read it -- I think it was #haskell IRC.
However, as I recall, perhaps incorrectly, the merge operation involves
a Semigroup[1] and helps to overcome the fact that Lens is not an Arrow
and so does not have a () operation.

I am interested to know what this Lens operation is and the associated
merge operation.

[1]
-- Approximate
data SemigroupT f a = SemigroupT (a - a - f a)


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



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


Re: [Haskell-cafe] Smarter do notation

2011-09-03 Thread Tony Morris
-BEGIN PGP SIGNED MESSAGE-
Hash: SHA1

Tasty.

On 04/09/11 12:34, Daniel Peebles wrote:
 Hi all,
 
 I was wondering what people thought of a smarter do notation. Currently,
 there's an almost trivial desugaring of do notation into (=), (), and
 fail (grr!) which seem to naturally imply Monads (although oddly enough,
 return is never used in the desugaring). The simplicity of the desugaring is
 nice, but in many cases people write monadic code that could easily have
 been Applicative.
 
 For example, if I write in a do block:
 
 x - action1
 y - action2
 z - action3
 return (f x y z)
 
 that doesn't require any of the context-sensitivty that Monads give you, and
 could be processed a lot more efficiently by a clever Applicative instance
 (a parser, for instance). Furthermore, if return values are ignored, we
 could use the ($), (*), or (*) operators which could make the whole thing
 even more efficient in some instances.
 
 Of course, the fact that the return method is explicitly mentioned in my
 example suggests that unless we do some real voodoo, Applicative would have
 to be a superclass of Monad for this to make sense. But with the new default
 superclass instances people are talking about in GHC, that doesn't seem too
 unlikely in the near future.
 
 On the implementation side, it seems fairly straightforward to determine
 whether Applicative is enough for a given do block. Does anyone have any
 opinions on whether this would be a worthwhile change? The downsides seem to
 be a more complex desugaring pass (although still something most people
 could perform in their heads), and some instability with making small
 changes to the code in a do block. If you make a small change to use a
 variable before the return, you instantly jump from Applicative to Monad and
 might break types in your program. I'm not convinced that's necessary a bad
 thing, though.
 
 Any thoughts?
 
 Thanks,
 Dan
 
 
 
 
 ___
 Haskell-Cafe mailing list
 Haskell-Cafe@haskell.org
 http://www.haskell.org/mailman/listinfo/haskell-cafe


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

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

iQEcBAEBAgAGBQJOYuR6AAoJEPxHMY3rBz0PRE8IAMK8sQTzxtgRYeWcyP6JmWso
Yl3eDUjny2uMSzIkifJix/t7tYuYG092H6SvA5VhgVBPQUd8LnZH/91X3PDGANBu
ufjmCJLuN5+bgeNxvyzBHwz5iYM3GOkPhGvpJ3hJzYFIBlDVnVmMNoCDkki46/nq
xJ/gsAIwfgpe4+Ll1LWu9DjVaQHb9nWmdBpTvpbXb7W+WEX7MHIsVsP/KysVFZkc
XwPESJntb7oTHCcS3q1GEVTYdMFNKHlWOFcrdkGGQlegvwfjdt221oVDNToZi4z1
wJ268MdvXLSVIcU+JHLYxElQj6zrf2D51oQbHWLS/wlHRnpZHU5gtmrMTKvPvf8=
=d1uz
-END PGP SIGNATURE-

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


Re: [Haskell-cafe] Pointed, but not Applicative

2011-08-28 Thread Tony Morris
-BEGIN PGP SIGNED MESSAGE-
Hash: SHA1

On 28/08/11 01:41, Sönke Hahn wrote:
 Hi!
 
 I was reading through the Typeclassopedia ([1]) and I was wondering which 
 type could be an instance of Pointed, but not of Applicative. But I can't 
 think of one. Any ideas?
 
 Sönke
 
 [1] http://www.haskell.org/haskellwiki/Typeclassopedia
 
 
 ___
 Haskell-Cafe mailing list
 Haskell-Cafe@haskell.org
 http://www.haskell.org/mailman/listinfo/haskell-cafe

Pointed f = Pointed (StateT s f)

but not

Applicative f = Applicative (StateT s f)

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

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

iQEcBAEBAgAGBQJOWhtaAAoJEPxHMY3rBz0Pa3oIAMrqoyv4DW39VjIXwzV3/4Ir
W5s0+fdoPj7h1j6eyCB81VcDHNtGQmWhZ3+g2AhHo1jLAzmH8G5ACdD1c1FeF2dn
a0iO7uvH5sM0xovpsqUwZC8BkomdeAnRuYF5Ohzar5M/Ip2BD0k7QpIWJt3RdLZm
uCpwDnsQ2foHJCJYlGmmGkpzDAnkwePOfER93KrKXmzHqQxhS0oACQy6LKfXODTM
+d2VVzzb4tWuzijXE4NflpdtW/4jSs3gVFmkZ7BmXSg8XxZO3naO/y4gtrU4YVjw
7TKo4IOIygQVMsFbdV2WZHprMHU/VaM6MTByiNECyB0q/yhJhsXtGsd9eeR2jng=
=X4nM
-END PGP SIGNATURE-

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


Re: [Haskell-cafe] Simon PJ in Australia

2011-08-19 Thread Tony Morris
On 08/19/2011 05:56 PM, Simon Peyton-Jones wrote:

 This is a message for *Australian FPers* -- sorry to spam the rest of you.

  

 I'm crossing the planet to Australia for YOW (Melbourne Dec 1-2,
 Brisbane Dec 5-6).  http://www.yowconference.com.au/YOW2011/

  

 I'm committed for the conference dates of course, but I could spend a
 few days before or afterwards, hanging out with some of you guys. 
 Hack on GHC, give a talk, eat pizza, university departments, Haskell
 users groups, surfing (on water, that is)

  

 Do drop me (not the list) a line if any of that sounds fun.

  

 Simon

  

 PS: John Hughes is coming to Yow too, so you could try luring him into
 your lair too.


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

...and I will be running a Haskell/FP workshop. I'm as keen as Simon to
meet others from further afield with similar interests.
http://www.yowconference.com.au/YOW2011/general/workshopDetails.html?eventId=3552

PS: we have a significant FP community here in Brisbane with nearly 250
members http://bfpg.org/

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


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


[Haskell-cafe] Data.Time

2011-06-25 Thread Tony Morris

-BEGIN PGP SIGNED MESSAGE-
Hash: SHA1

I recently set out to write a library that required a decent time
library. Having only had a flirt with Data.Time previously, I assumed
it would be robust like many other haskell libraries. I don't know
about consensus, but I have been massively let down. I won't go in to
the details, since this is not the point -- I don't wish to complain
- -- I wish to get on with it.

So, assuming the consensus is in agreement, is there a reasonable
alternative to Data.Time (I looked on hackage and nothing seemed to
have come close)? Am I wrong in assuming Data.Time is pretty useless?

If I am right, and there is no alternative, I see no option but to
take an excursion into writing my own. Ultimately, I am just trying to
avoid this. Tips welcome.

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

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

iEYEARECAAYFAk4Ggx4ACgkQmnpgrYe6r61BRQCfbn+1jqNSjR+lxM+4h3gpvAMM
VskAoKxqDCETyVAaOdoYDmFJGz1fOGd/
=IC7O
-END PGP SIGNATURE-


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


[Haskell-cafe] Iteratee stack-consumption

2011-05-30 Thread Tony Morris

-BEGIN PGP SIGNED MESSAGE-
Hash: SHA1

I have written iteratees on the JVM, which does not include tail-call
in its instruction set. They incur a stack frame per iteratee input,
which can be expensive and unable to scale beyond a few thousand. Is
there some trick to permitting this? Some sort of chunking the
enumeratee or something? I was unable to find any good general hints
in any of the hackage libraries.

Thanks for any pointers.

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

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

iEYEARECAAYFAk3jNHEACgkQmnpgrYe6r63QcACfSeZvvy+iYVisZ3e/dhWQd3D6
790AnRZCjJT6eCY21XlsVqcpTuamfuXY
=ADo5
-END PGP SIGNATURE-


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


Re: [Haskell-cafe] *GROUP HUG*

2011-05-25 Thread Tony Morris
On 24/05/11 22:41, Johannes Waldmann wrote:
 Then tell me, why does calculating the length of a (Haskell) 
 list has O(n) complexity. 
Infiniticity aside, tail would become O(n) if you store a length with
each cons cell.

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



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


Re: [Haskell-cafe] *GROUP HUG*

2011-05-25 Thread Tony Morris
On 25/05/11 16:46, Eugene Kirpichov wrote:
 data FList a = FNil | FCons Int a (FList a)
 empty = FNil
 len FNil = 0
 len (FCons n _) = n
 cons x xs = FCons (1 + len xs) x xs
 tail (FCons _ _ xs) = xs
My mistake, sorry. Currently looking for original reason to have
accidentally come to believe that.

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



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


Re: [Haskell-cafe] *GROUP HUG*

2011-05-24 Thread Tony Morris
Just laugh mate. It's the best possible outcomes sometimes.

On 24/05/11 15:10, Gregory Crosswhite wrote:
 Hey everyone,

 Okay, this will sound silly, but I ventured into the Scala mailing
 list recently and asked an ignorant question on it, and I was shocked
 when people reacted not by enlightening me but by jumping on me and
 reacting with hostility.  I bring this up not to badmouth the Scala
 community (they are apparently going through growing pains and will
 hopefully mature with time!) but just because it made me appreciate
 just how awesome you guys are, so I just feel the need to publicly
 express my admiration and thank to everyone on this list for having
 fostered such an incredibly professional, fanatically nonhostile, and
 generally pleasant place to talk about Haskell!!!

 *GROUP HUG*

 Okay, I'm done now.  :-)

 Cheers,
 Greg

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


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



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


Re: [Haskell-cafe] Robert Harper on monads and laziness

2011-05-02 Thread Tony Morris
On 02/05/11 17:54, Ketil Malde wrote:
 I'm following Harper's blog, Existential Type¹, which I find to be an
 enjoyable and entertainingly written tirade about the advantages of
 teaching functional programming - specifically ML - to students.  Of
 course, he tends to be critical of Haskell, but it's nice to get some
 thought provoking opinion from somebody who knows a bit about the
 business.

 Recently, he had a piece on monads, and how to do them in ML, and one
 statement puzzled me:

   There is a particular reason why monads had to arise in Haskell,
though, which is to defeat the scourge of laziness.

 My own view is/was that monads were so successful in Haskell since it
 allowed writing flexible programs with imperative features, without
 sacrificing referential transparency.  Although people are quick (and
 rightly so) to point out that this flexibility goes way beyond IO, I
 think IO was in many ways the killer application for monads.  Before IO,
 we had very limited functionality (like 'interact' taking a 'String -
 String' function and converting it into an exectuable program) to build
 real programs from.

 Laziness does require referential transparency (or at least, it is
 easier to get away with the lack of RT in a strict language), so I can
 see that he is indirectly correct, but RT is a goal in itself.  Thus, I
 wonder if there are any other rationale for a statement like that?

 -k

 ¹ http://existentialtype.wordpress.com/
Interesting how I have been authoring and subsequently using monads in
scala for several years and it is strictness that gets in the way more
than anything.

http://github.com/scalaz/scalaz/

I have been teaching functional programming for quite a while, both in
universities and outside of academia, and I am of the opinion that
Haskell's suitability in first place has no close second place. I wonder
why I am wrong, but this post (and previous) is hardly persuasive.

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



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


Re: [Haskell-cafe] Python is lazier than Haskell

2011-04-27 Thread Tony Morris
On 27/04/11 20:02, Thomas Davie wrote:
 This completely misses what laziness gives Haskell – it gives a way of 
 completing a smaller number of computations than it otherwise would have to 
 at run time.  The hope being that this speeds up the calculation of the 
 result after the overhead of laziness is taken into account.
This is not what laziness gives us. Rather, it gives us terminating
programs that would otherwise not terminate.

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



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


Re: [Haskell-cafe] How large is the Haskell community ?

2011-02-12 Thread Tony Morris

-BEGIN PGP SIGNED MESSAGE-
Hash: SHA1

On 13/02/11 08:37, Erik de Castro Lopo wrote:
 Aaron Gray wrote:

 I am wondering if mailing list statistics would be the best guide
 ?

 I am the organiser of FP-Syd, the Sydney (Australia) functiona
 prgramming group.

 Of the people who are regaular attendees to FP-Syed meetings, who
 say they are haskell users, I have seen less than 50% of these
 people post to this or other haskell mailing lists.

 Mailing list statistics may not be a good guide.

 Erik
I am the co-organiser of Brisbane Functional Programming Group with
nearly 200 members. I have not seen anywhere near 50% post here.

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

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

iEYEARECAAYFAk1XDbEACgkQmnpgrYe6r63g7ACghYtq7+lyba3S/UscZ34+DEvx
hxEAoJ0uDPTwNhM2LnvUekpmTG7C5SNV
=O/WP
-END PGP SIGNATURE-


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


Re: [Haskell-cafe] Generalizing catMaybes

2011-01-08 Thread Tony Morris

-BEGIN PGP SIGNED MESSAGE-
Hash: SHA1

Thanks guys for all the solutions. A slight correction below.

On 09/01/11 03:54, David Menendez wrote:

 Naturally, if you also have pure and fmap, you also have a monad.
You have a pointed functor but not necessarily a monad. There are many
pointed functors that are not monads. The paper, Applicative
Programming with Effects (McBride, Paterson) lists a couple.

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

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

iEYEARECAAYFAk0o4AgACgkQmnpgrYe6r62z4wCgk4A1njS5lLH3RHtxfnIkVGTL
t3sAoKNm7HjVQyk/Gb1AL5LxahRHPmKN
=5D4j
-END PGP SIGNATURE-


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


[Haskell-cafe] Generalizing catMaybes

2011-01-07 Thread Tony Morris

-BEGIN PGP SIGNED MESSAGE-
Hash: SHA1

 I am wondering if it possible to generalise catMaybes:

(Something f, SomethingElse t) = t (f a) - t a

I have being doing some gymnastics with Traversable and Foldable and a
couple of other things from category-extras to no avail. Perhaps
someone else's brain is molded into an appropriate shape to reveal an
answer!

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

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

iEYEARECAAYFAk0n0lwACgkQmnpgrYe6r6155gCeLjYizQ/5w1r2qkecbEqiQqq5
ihIAn1bmmK/qNFxM2sSusqjJu/g2/lH7
=+SdM
-END PGP SIGNATURE-


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


[Haskell-cafe] UTF-8 BOM

2011-01-04 Thread Tony Morris
I am reading files with System.IO.readFile. Some of these files start
with a UTF-8 Byte Order Marker (0xef 0xbb 0xbf). For some functions that
process this String, this causes choking so I drop the BOM as shown
below. This feels particularly hacky, but I am not in control of many of
these functions (that perhaps could use ByteString with a better solution).

I'm wondering if there is a better way of achieving this goal. Thanks
for any tips.


dropBOM ::
  String
  - String
dropBOM [] =
  []
dropBOM s@(x:xs) = 
  let unicodeMarker = '\65279' -- UTF-8 BOM
  in if x == unicodeMarker then xs else s

readBOMFile ::
  FilePath
  - IO String
readBOMFile p =
  dropBOM `fmap` readFile p




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



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


Re: [Haskell-cafe] (Co/Contra)Functor and Comonad

2010-12-23 Thread Tony Morris

-BEGIN PGP SIGNED MESSAGE-
Hash: SHA1

...regardless of the utility of a contravariant functor type-class, I
strongly advocate for calling it Contrafunctor and not Cofunctor. I
have seen numerous examples of confusion over this, particularly in
other languages.

On 24/12/10 12:16, Mario Blažević wrote:

 On Thu, Dec 23, 2010 at 5:25 PM, Stephen Tetley
 stephen.tet...@gmail.com mailto:stephen.tet...@gmail.com
 wrote:

 On 23 December 2010 21:43, Mario Blažević mblaze...@stilo.com
 mailto:mblaze...@stilo.com wrote:
 Why are Cofunctor and Comonad classes not a part of the base
 library? [SNIP]
 Later on I found that this question has been raised before by
 Conal Elliott,
 nearly four years ago.


 http://www.haskell.org/pipermail/libraries/2007-January/006740.html




- From a somewhat philistine persepective, that Conal's question
 went unanswered says something:

 Does anyone have useful functionality to go into a Cofunctor
 module (beyond the class declaration)?

 Successful post-H98 additions to Base (Applicative, Arrows, ...)
 brought a compelling programming style with them. For Comonads,
 Category-extras does define some extra combinators but otherwise
 they have perhaps seemed uncompelling.



 There are plenty of potential Cofunctor instances on Hackage, as
 I've pointed out. The other side of the proof of the utility of
 the class would be to find existing libraries that could be
 parameterized by an arbitrary functor: in other words, some
 examples in Hackage of

 class Cofunctor c = ... instance Cofunctor c = ... f ::
 Cofunctor c = ...

 This would be rather difficult to prove - such signatures cannot
 be declared today, and deciding if existing declarations could be
 generalized in this way would require a pretty deep analysis. The
 only thing I can say is build it and they will come.

 To turn the proof obligation around, what could possibly be the
 downside of adding a puny Cofunctor class to the base library?



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


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

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

iEYEARECAAYFAk0UIJ0ACgkQmnpgrYe6r62kWgCeNwZnYLetOFevK6bpCBE/joKO
2QQAniaX4IGzAmdjEC8kdDV27upUTsBw
=NP27
-END PGP SIGNATURE-

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


[Haskell-cafe] dot-ghci files

2010-12-08 Thread Tony Morris
I teach haskell quite a lot. I recommend using .ghci files in projects.
Today I received complaints about the fact that ghci will reject .ghci
if it is group-writeable. I didn't offer an opinion on the matter. I am
wondering if these complaints have legitimate grounds i.e. maybe you
want to have group write on that file for some reason.

I'd appreciate some comments on this issue. Thanks.

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



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


[Haskell-cafe] Load testing

2010-11-28 Thread Tony Morris
Does there exist a package for convenient load-testing against a
website? e.g. making lots of HTTP requests against a server, including
timing, and collecting the results?

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


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


[Haskell-cafe] category-extras clash with transformers

2010-11-20 Thread Tony Morris
-BEGIN PGP SIGNED MESSAGE-
Hash: SHA1

I have installed mtl-1.1.1.0 so that xmonad-contrib-0.9.1 would compile
with GHC 6.12.1.
http://permalink.gmane.org/gmane.comp.lang.haskell.xmonad/10603

Then I tried to installed category-extras-0.53.5, which clashed with
transformers-0.2.2.0 for the Applicative/Monad instances for Either.

Is there any way out of this problem? Thanks for any pointers.

$ ghc-pkg list | grep mtl
mtl-1.1.1.0
mtl-2.0.1.0
$ ghc-pkg list | grep transformers
transformers-0.2.2.0
$ cabal install category-extras
...
[39 of 99] Compiling Control.Monad.Either ( src/Control/Monad/Either.hs,
dist/build/Control/Monad/Either.o )

src/Control/Monad/Either.hs:44:9:
Duplicate instance declarations:
  instance Monad (Either e)
-- Defined at src/Control/Monad/Either.hs:44:9-24
  instance Monad (Either e)
-- Defined in transformers-0.2.2.0:Control.Monad.Trans.Error

src/Control/Monad/Either.hs:49:9:
Duplicate instance declarations:
  instance Applicative (Either e)
-- Defined at src/Control/Monad/Either.hs:49:9-30
  instance Applicative (Either e)
-- Defined in transformers-0.2.2.0:Control.Monad.Trans.Error

src/Control/Monad/Either.hs:53:9:
Duplicate instance declarations:
  instance MonadFix (Either e)
-- Defined at src/Control/Monad/Either.hs:53:9-27
  instance MonadFix (Either e)
-- Defined in transformers-0.2.2.0:Control.Monad.Trans.Error
cabal: Error: some packages failed to install:
category-extras-0.53.5 failed during the building phase. The exception
was:
ExitFailure 1

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

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

iEYEARECAAYFAkznxgQACgkQmnpgrYe6r60dkACfZQkYKbMOQuGfaVpFb2MfhJWD
asAAn1/hoX+m/YpUOch3r4NsR99y2htz
=IsZc
-END PGP SIGNATURE-

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


Re: [Haskell-cafe] category-extras clash with transformers

2010-11-20 Thread Tony Morris
-BEGIN PGP SIGNED MESSAGE-
Hash: SHA1

On 21/11/10 04:43, Ross Paterson wrote:
 On Sat, Nov 20, 2010 at 10:58:44PM +1000, Tony Morris wrote:
 I have installed mtl-1.1.1.0 so that xmonad-contrib-0.9.1 would
 compile with GHC 6.12.1.
 http://permalink.gmane.org/gmane.comp.lang.haskell.xmonad/10603

 Then I tried to installed category-extras-0.53.5, which clashed
 with transformers-0.2.2.0 for the Applicative/Monad instances for
 Either.

 Is there any way out of this problem? Thanks for any pointers.

 The instance in question is in the base package from GHC 7, which
 should avoid this problem of clashing orphans in the future.
 Unfortunately that doesn't help you -- I think both xmonad-contrib
 and category-extras need to be updated.
 ___ Haskell-Cafe
 mailing list Haskell-Cafe@haskell.org
 http://www.haskell.org/mailman/listinfo/haskell-cafe
Thanks Ross,
I just wish to confirm -- I'm totally screwed, right?

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

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

iEYEARECAAYFAkzoSnsACgkQmnpgrYe6r62K3QCgnxkRqnQbv0FlKBy1sfrxcoKC
1zcAoM295VGFZBo/OQR1Qq4jW1zI3C+D
=FRrh
-END PGP SIGNATURE-

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


Re: [Haskell-cafe] category-extras clash with transformers

2010-11-20 Thread Tony Morris
-BEGIN PGP SIGNED MESSAGE-
Hash: SHA1

On 21/11/10 08:41, Edward Z. Yang wrote:
 No, you're not totally screwed; you just need to bug
 xmonad-contrib and category-extras to fix their code.

 Edward
I am wondering if upgrading from 6.12.1 to 6.12.3 will allow me to
compile xmonad-contrib* and therefore, be ride of the old version of
mtl and therefore, can install category extras.

*

$ cabal install xmonad-contrib
Resolving dependencies...
Configuring xmonad-contrib-0.9.1...
Preprocessing library xmonad-contrib-0.9.1...
Building xmonad-contrib-0.9.1...
[  1 of 180] Compiling XMonad.Util.Replace ( XMonad/Util/Replace.hs,
dist/build/XMonad/Util/Replace.o )

XMonad/Util/Replace.hs:1:0:
Warning: Module `Prelude' is deprecated:
   You are using the old package `base' version 3.x.
   Future GHC versions will not support base version 3.x. You
   should update your code to use the new base version 4.x.
[  2 of 180] Compiling XMonad.Util.CustomKeys (
XMonad/Util/CustomKeys.hs, dist/build/XMonad/Util/CustomKeys.o )

XMonad/Util/CustomKeys.hs:80:23:
Not in scope: data constructor `Reader'
cabal: Error: some packages failed to install:
xmonad-contrib-0.9.1 failed during the building phase. The exception was:
ExitFailure 1



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

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

iEYEARECAAYFAkzoUrYACgkQmnpgrYe6r60E4QCfXjGuWsu9xLcEVn142+lJkzRQ
+0QAoJpbYpioJaIeuygxZXKLHKb7fRBk
=dBSD
-END PGP SIGNATURE-

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


[Haskell-cafe] Non-hackage cabal source

2010-11-02 Thread Tony Morris
I am trying to set up an apache server as an additional source to
hackage for haskell packages.

I have added to my ~/.cabal/config file:
remote-repo: myhackage:http://myhackage/packages

I am able to successfully make the HTTP requests:
http://myhackage/packages/00-index.tar.gz
http://myhackage/packages/MyPackage/0.0.1/MyPackage-0.0.1-tar.gz

I can execute:

$ tar -tvf 00-index.tar.gz
-rw-r--r-- root/root  1491 2010-11-03 15:16
./MyPackage/0.0.1/MyPackage.cabal

However, when I try to unpack my package with cabal:
$ cabal unpack MyPackage
Downloading MyPackage-0.0.1...
cabal: Failed to download
http://myhackage/packages/package/MyPackage-0.0.1.tar.gz : ErrorMisc
Unsucessful HTTP code: 404

Why is cabal even making this request?
Why is it not making the request to
http://myhackage/packages/MyPackage/0.0.1/MyPackage-0.0.1.tar.gz

Thanks for any tips.

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

 

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


Re: [Haskell-cafe] Re: Re: A rant against the blurb on the Haskell front page

2010-10-16 Thread Tony Morris


On 17/10/10 12:03, Ben Franksen wrote:
 wren ng thornton wrote:
   
 On 10/16/10 10:48 AM, Ben Franksen wrote:
 
 Don Stewart wrote:
   
 It is open source, and was born open source. It is the product of
 research.
 
 How can a language be open source, or rather, how can it *not* be open
 source? The point of a (programming) language is that it has a published
 ('open') definition. Nothing prevents anyone from creating a proprietary
 compiler or interpreter for Haskell, AFAIK.
   
 Miranda[TM] is/was a proprietary language, quite definitively so. If
 nothing else, this should be apparent by the fact that every reference
 to it in research papers of the era (a) included the TM sigil, and (b)
 had footnotes indicating who the IP holders are. That was before my
 time, but I was under the impression that Haskell was open from the
 beginning ---by express intention--- in order to enable work on lazy
 functional languages without being encumbered by Miranda[TM]'s closed
 nature.

 For that matter, until rather recently Java was very much a closed
 language defined by the runtime system provided by Sun Microsystems and
 not defined by the sequence of characters accepted by that system, nor
 by the behavior of the system when it accepts them. Sun even went
 through some trouble to try to shut out competitive development of
 runtime systems such as SoyLatte, IcedTea, and the like.

 Even the venerable C language has a long history of companies making
 proprietary extensions to the language in order to require you to buy
 their compiler, and they would most certainly pursue legal action if
 someone else copied the features. This is why GCC is as big a coup for
 the free/open-source movement as Linux is--- long before GCC changed its
 name and focus to being a compiler collection.

 The languages which are open-source are in close correspondence with the
 languages which have a free/open-source implementation. There are a lot
 of them, including the vast majority of recent languages. But don't be
 seduced into thinking that a language is a predicate on acceptable
 strings, a transducer from those strings into computer behaviors, or
 that such predicates and transducers are public domain.
 
 Sigh. Yes, you are right, of course. All this is true, sadly. There are
 stupid people who think that they can own a programming language. I hope
 they will go the way all the other mis-adapted creatures have gone and just
 die out.

 Still, Haskell is an open source product doesn't sound right to me.
 Even Haskell is open source (without the product) has a bad ring
 because source is short for source code and source code is not
 something a programming language has.

 I agree that non-proprietary is a valid and important characterization of
 the language. This should be mentioned where we speak about libraries and
 community, since the active and friendly community is the motor behind the
 growing set of libraries, and you get this sort of participation only with
 a free/non-proprietary language. This applies not only to individuals but
 to companies as well, maybe even more.

 I anticipate the objection that potential commercial users might be scared
 off by the terms non-proprietary or free, whereas the term open
 source has been coined to (and probably actually does) sound more commerce
 friendly. To countermand such an effect, we can point out that most
 libraries have non-copyleft licenses and that there are a number of
 companies who have done and still do a lot to support and advance Haskell.

 Cheers
 Ben

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

   
I am somewhat sympathetic to your argument, but I care far less overall.

Nevertheless, perhaps this would appease:

Haskell is an open standard with a robust open source implementation.

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


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


[Haskell-cafe] Network.HTTP, BasicAuth+Headers

2010-10-04 Thread Tony Morris
I'm trying to send a simple request using Network.HTTP and getting a bit
lost in all the possibilities. I've experimented with both Network.HTTP and
Network.Browser but have been unable to come up with something specific to
my needs, which are quite simple.

I'd like to send a request equivalent to the following curl:

curl --basic -u user:pass -H Accept: application/xml -H Content-type:
application/xml https://host/path;

It seems with Network.Browser I cannot send headers, but with Network.HTTP I
cannot see how to send the BasicAuth information.

Any tips are appreciated.

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


Re: [Haskell-cafe] Unwrapping newtypes

2010-09-08 Thread Tony Morris
I think you might want -XGeneralizedNewtypeDeriving

http://haskell.org/ghc/docs/6.12.2/html/users_guide/deriving.html#id659906

On 08/09/10 22:01, Kevin Jardine wrote:
 I have a generic object that I want to wrap in various newtypes to
 better facilitate type checking.

 For example,

 newtype Blog = Blog Obj
 newtype Comment = Comment Obj
 newtype User = User Obj

 Unlike Obj itself, whose internal structure is hidden in a library
 module, the newtype wrappings are purely to facilitate type checking.
 It is no secret that each is just a wrapper around Obj.

 It is obvious how to construct the various wrapper objects. It is not
 so obvious how to extract the Obj they contain in a reasonably generic
 way however. What I want is a getObj function that works on all of
 them.

 Of course this could work if someone using the library wrote an
 instance for each wrapper object:

 instance GetObject Blog where
 getObj (Blog obj) = obj

 but this is a pain in the neck to write for each newtype.

 I discovered that Foldable defines a handy toList function that
 extracts content from generic Foldable structures.

 So that I could write:

 toObj :: Foldable thing = thing Obj - Obj
 toObj w = head $ toList w

 Slightly kludgy but it works.

 Even better, recent versions of GHC will allow you to automatically
 derive Foldable.

 Unfortunately,

 newtype Blog = Blog Obj deriving Foldable

 returns a kind error.

 What does work is:

 newtype BlogF a = Blog a deriving Foldable
 type Blog = BlogF Obj

 After having spent close to a day on this, I am a bit baffled that
 such a seemingly trivial problem seems so hard to do.

 I am wondering if I am missing something really, really obvious.

 Any suggestions? Or is there perhaps a more Haskelly way to place type
 constraints on a more generic type?

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

   

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


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


Re: [Haskell-cafe] Re: Unwrapping newtypes

2010-09-08 Thread Tony Morris


On 08/09/10 22:19, Kevin Jardine wrote:
 Hi Tony,

 I stared at that specific section for at least half an hour earlier
 today but could not figure out how it applied in my specific case. The
 only examples I have see are for deriving Num. Do you have any more
 detail on how I could use that extension?

   
Here is an example:

{-# LANGUAGE GeneralizedNewtypeDeriving #-}

class C a where
  c :: a - Int

data G = G

instance C G where
  c _ = 7

newtype H = H G deriving C

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


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


[Haskell-cafe] lambdacats

2010-08-05 Thread Tony Morris
Hello, does anyone happen to have the lambdacats page cached? The domain (
arcanux.org) and server have disappeared and the wayback machine doesn't
have the images.

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


Re: [Haskell-cafe] lambdacats

2010-08-05 Thread Tony Morris
I wonder if the original site is recoverable from this, but I suspect there
are some missing.

On Fri, Aug 6, 2010 at 2:33 PM, Don Stewart d...@galois.com wrote:

 ivan.miljenovic:
  On 6 August 2010 14:12, Tony Morris tonymor...@gmail.com wrote:
   Hello, does anyone happen to have the lambdacats page cached? The
 domain
   (arcanux.org) and server have disappeared and the wayback machine
 doesn't
   have the images.
 

 Plenty of stuff shows up on google:

http://images.google.com/images?q=lambdacats




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


[Haskell-cafe] Monad transformers, design

2010-07-31 Thread Tony Morris
Hello I have a question regarding monad transformers and how to design
an API with a transformer. I have a narrowed code example of the
question. Please see the questions in the comments below.



import Data.Monoid
import Control.Monad

-- Suppose some data type
newtype Inter a = Inter (Int - a)

-- and a monad transformer for that data type.
newtype InterT m a = InterT (m (Inter a))

-- It's easy to implement this type-class
instance (Monoid a) = Monoid (Inter a) where
  mempty = Inter (const mempty)
  Inter a `mappend` Inter b = Inter (a `mappend` b)

-- and for the transformer too by lifting into the monad
instance (Monad m, Monoid a) = Monoid (InterT m a) where
  mempty = InterT (return mempty)
  InterT a `mappend` InterT b = InterT (liftM2 mappend a b)

-- But what about this type-class?
class Ints a where
  ints :: a - Int - Int

-- Seems easy enough
instance (Integral a) = Ints (Inter a) where
  ints (Inter a) n = fromIntegral (a n)

-- OH NO!
{-
instance (Monad m, Integral a) = Ints (InterT m a) where
  ints (InterT a) n = error OH NO!
-}

-- We could try this
class Copointed f where
  copoint :: f a - a

-- but it seems rather impractical
instance (Copointed m, Integral a) = Ints (InterT m a) where
  ints (InterT a) = ints (copoint a)

{-
So it seems that for some type-classes it is possible to implement
for both the data type and the transformer, but not all type-classes.

Is there a general approach to this problem?
-}



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


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


Re: [Haskell-cafe] Monad transformers, design

2010-07-31 Thread Tony Morris
gah you're right, @mtl had confuzzled me.

Well that changes things then, thanks.

Ross Paterson wrote:
 On Sat, Jul 31, 2010 at 10:56:31PM +1000, Tony Morris wrote:
   
 -- Suppose some data type
 newtype Inter a = Inter (Int - a)

 -- and a monad transformer for that data type.
 newtype InterT m a = InterT (m (Inter a))
 

 The monad transformer should be Inter (m a).
 ___
 Haskell-Cafe mailing list
 Haskell-Cafe@haskell.org
 http://www.haskell.org/mailman/listinfo/haskell-cafe

   

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


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


Re: [Haskell-cafe] Type-Level Programming

2010-06-26 Thread Tony Morris
http://www.cs.nott.ac.uk/~txa/publ/ydtm.pdf

Andrew Coppin wrote:
 Liam O'Connor wrote:
 It means that not only can values have types, types can have values.
   

 Uh, don't types have values *now*?

 An example of the uses of a dependent type would be to encode the
 length of a list in it's type.
   

 Oh, right. So you mean that as well as being able to say Foo Bar,
 you can say Foo 7, where 7 is (of course) a value rather than a
 type. (?)

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


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


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


Re: [Haskell-cafe] Retrospective type-class extension

2010-05-20 Thread Tony Morris
Ivan Miljenovic wrote:
 On 20 May 2010 14:42, Tony Morris tonymor...@gmail.com wrote:
   
 We all know that class (Functor f) = Monad f is preferable but its
 absence is a historical mistake. We've all probably tried once:

 instance (Functor f) = Monad f where
 

 Do you mean the reverse of this (instance (Monad m) = Functor m where) ?
   
Yes.

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


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


Re: [Haskell-cafe] Retrospective type-class extension

2010-05-20 Thread Tony Morris
I've compared and clearly the former is significantly superior :)

I'm rather interested if there are any sound suggestions to resolve the
general issue of retrospective type-class extension.


Miguel Mitrofanov wrote:
 That won't be a great idea; if I just want my monad to be declared as
 one, I would have to write

 instance Functor MyMonad where fmap = ...
 instance Pointed MyMonad where pure = ...
 instance Applicative MyMonad where (*) = ...
 instance Monad MyMonad where join = ...

 Compare this with

 instance Monad MyMonad where
   return = ...
   (=) = ...

 and take into account that (=) is usually easier to write than join.

 Limestraël wrote:
 Then it would be:

 class Functor f where
 fmap :: (a - b) - f a - f b

 class (Functor f) = Pointed f where
 pure :: a - f a

 class (Pointed f) = Applicative f where
 (*) :: f (a - b) - f a - f b

 class (Applicative f) = Monad f where
 join :: f (f a) - f a

 This would be a great idea, for the sake of logic, first (a monad
 which is not a functor doesn't make sense), and also to eliminate
 redudancy (fmap = liftM, ap = (*), etc.)

 2010/5/20 Tony Morris tonymor...@gmail.com
 mailto:tonymor...@gmail.com

 Ivan Miljenovic wrote:
   On 20 May 2010 14:42, Tony Morris tonymor...@gmail.com
 mailto:tonymor...@gmail.com wrote:
  
   We all know that class (Functor f) = Monad f is preferable
 but its
   absence is a historical mistake. We've all probably tried once:
  
   instance (Functor f) = Monad f where
  
  
   Do you mean the reverse of this (instance (Monad m) = Functor m
 where) ?
  
 Yes.

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


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



 

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


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


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


[Haskell-cafe] Retrospective type-class extension

2010-05-19 Thread Tony Morris
We all know that class (Functor f) = Monad f is preferable but its
absence is a historical mistake. We've all probably tried once:

instance (Functor f) = Monad f where
...

However, is there a type system extension (even proposed but not
implemented) that allows me to retrospectively apply such a notion?

Ideally something like this would be handy if it could somehow be
retrospectively applied:
Monad - Applicative - Pointed - Functor


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


Re: [Haskell-cafe] What is the meaning of tilde (~) symbol

2010-02-14 Thread Tony Morris
Stephen Tetley wrote:
 Hi Evan

 Singleton (aka wrap) would be nice - isn't it called Pointed in the
 typeclassopedia but not otherwise existent? I suppose its missing by
 historical accident rather than design.

 I frequently use Semigroup (append but no zero) - there is one on
 Hackage without any instances:
 http://hackage.haskell.org/package/algebra
   
I do too. I also wish there was an associative: class F f where k :: f a
- f a - f a without the zero component.


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


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


[Haskell-cafe] Lazy language on JVM/CLR

2010-02-08 Thread Tony Morris
I have hypothesised a pure, lazy language on the JVM and perhaps the
.NET CLR with FFI to .NET/Java libraries. I foresee various problems but
none that are catastrophic; just often requiring a compromises,
sometimes very unattractive compromises. I have authored several
libraries in the same vain as pure, lazy programming to run on the JVM
in Java and Scala programming languages.

I expect others have forethought and perhaps even experimented with such
a language. Are there any dangers to be wary of that undo the entire
endeavour?

Thanks for any insights.

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

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


Re: [Haskell-cafe] Maybe, maybe not.

2010-01-26 Thread Tony Morris
It might be more obvious by giving:

fromMaybe :: a - (a - x, x) - x

Ivan Miljenovic wrote:
 2010/1/27 Edward Z. Yang ezy...@mit.edu:
   
 Excerpts from Daniel Peebles's message of Tue Jan 26 23:25:28 -0500 2010:
 
 There are actually only two (extensionally) possible total functions with
 that type, as far as I can see :)
   
 Is the other one... const?
 

 As far as I can tell, yes.

   


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


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


Re: [Haskell-cafe] Maybe, maybe not.

2010-01-26 Thread Tony Morris
Ivan Miljenovic wrote:
 2010/1/27 Tony Morris tonymor...@gmail.com:
   
 It might be more obvious by giving:

 fromMaybe :: a - (a - x, x) - x
 

 I actually found this more confusing, and am not sure of its validity:
 should that be Maybe a there at the beginning?

   

Sorry a mistake. Correction: fromMaybe :: a - ((a - x, x) - x) - x

{-# LANGUAGE RankNTypes #-}

data Maybe' a = M (forall x. (a - x, x) - x)

to :: Maybe' t - Maybe t
to (M f) = f (Just, Nothing)

from :: Maybe a - Maybe' a
from (Just a) = M (flip fst a)
from Nothing  = M snd


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


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


Re: [Haskell-cafe] Parse error

2010-01-17 Thread Tony Morris
No, but there's a specific reason why GHC consistently refuses to accept
your perfectly unreasonable code snippet :)

GHC accepts the following perfectly reasonable code snippet:

main = do
 putStrLn Line 1
 putStrLn Line 2

 let xs = do x - [1..10]
 y - [1..10]
 return (x+y)

 print xs

Andrew Coppin wrote:
 Is there a specific reason why GHC consistently refuses to accept the
 following perfectly reasonable code snippet?

 main = do
  putStrLn Line 1
  putStrLn Line 2

  let xs = do
x - [1..10]
y - [1..10]
return (x+y)

  print xs

 No matter which way I rearrange this, it *insists* that there's a
 parse error. This is very frustrating, given that it's utterly clear
 what I want...

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


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


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


Re: [Haskell-cafe] Language simplicity

2010-01-12 Thread Tony Morris
Andrew Coppin wrote:
 OK people, it's random statistics time!

 Haskell '98 apparently features 25 reserved words. (Not counting
 forall and mdo and so on, which AFAIK are not in Haskell '98.) So
 how does that compare to other languages?

 C: 32
 C++: 62
 Borland Turbo Pascal: ~50 [without the OOP extensions added later]
 Eiffel: 59
 VB: The source I checked listed in excess of 120 reserved words, but
 I'm dubious as to how reserved they really are. (Is CInt really
 reserved? I doubt it!) It also depends wildly on which of the
 bazillion VB dialects you mean.
 Java: 50
 JavaScript: 36
 Smalltalk: 0
 Lisp: AFAIK, there are no truly reserved words in Lisp, only
 predefined functions. (??)
 Python: 31
 Ruby: 38
 Tcl: Same analysis as for Lisp I believe.

 As you can see, this conclusively proves... something.

 Hmm, I wonder if there's some way to compare the size of the language
 specification documents? :-}

 PS. It comes as absolutely no surprise to me that C++ has the most
 keywords. But then, if I were to add AMOS Professional, that had well
 over 800 keywords at the last count...

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

Java has 53 reserved words.

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


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


[Haskell-cafe] ghc -e

2010-01-06 Thread Tony Morris
Can I import a module when using ghc -e?

e.g. ghc -e import Control.Monad; forM [[1,2,3]] reverse

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

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


Re: [Haskell-cafe] ghc -e

2010-01-06 Thread Tony Morris
Gwern Branwen wrote:
 On Wed, Jan 6, 2010 at 7:23 PM, Tony Morris tonymor...@gmail.com wrote:
   
 ghc -e import Control.Monad; forM [[1,2,3]] reverse
 

 As of 6.10.2, the bug whereby the GHC API lets you use functions from
 anywhere just by naming them (Java-style) has not been fixed:

 $ ghc -e Control.Monad.forM [[1,2,3]] reverse
 package flags have changed, resetting and loading new packages...

 interactive:1:25:
 Warning: Defaulting the following constraint(s) to type `Integer'
  `Num t' arising from the literal `3' at interactive:1:25
 In the expression: 3
 In the expression: [1, 2, 3]
 In the first argument of `forM', namely `[[1, 2, 3]]'

 interactive:1:25:
 Warning: Defaulting the following constraint(s) to type `Integer'
  `Num t' arising from the literal `3' at interactive:1:25
 In the expression: 3
 In the expression: [1, 2, 3]
 In the first argument of `forM', namely `[[1, 2, 3]]'
 [[3],[2],[1]]
 it :: [[Integer]]
 (0.01 secs, 1710984 bytes)

   
I see the same on GHC 6.10.4.
$ ghc -e Control.Monad.forM [[1,2,3]] reverse
[[3],[2],[1]]


What would it be fixed to? What is wrong with how it is?

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


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


[Haskell-cafe] (liftM join .) . mapM

2009-12-29 Thread Tony Morris
Can (liftM join .) . mapM be improved?
(Monad m) = (a - m [b]) - [a] - m [b]

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


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


[Haskell-cafe] Children elements with HXT

2009-12-22 Thread Tony Morris
I am trying to parse XML using HXT following
http://www.haskell.org/haskellwiki/HXT/Conversion_of_Haskell_data_from/to_XML

Here is my XML file (way.xml):

way id=27776903 visible=true timestamp=2009-05-31T13:39:15Z
version=3 changeset=1368552 user=Matt uid=70
  tag k=access v=private/
  tag k=highway v=service/
/way

The problem is when parsing, by reading the tag entries into the
list held by the Way data structure, I cannot get anything but an
empty list.

Here is my parsing code:

import Text.XML.HXT.Arrow

newtype Way = Way {
  tags :: [Tag]
} deriving (Eq, Show)

xpWay :: PU Way
xpWay = xpElem way (xpWrap (Way, tags) (xpList xpTag))

data Tag = Tag {
  k :: String,
  v :: String
} deriving (Eq, Show)

xpTag :: PU Tag
xpTag = xpElem tag (xpWrap (uncurry Tag, k  v) (xpPair (xpAttr
k xpText) (xpAttr v xpText)))

When I run, I get the following result:

Main run = runX (xunpickleDocument xpWay [] way.xml)
[Way {tags = []}]

Why is the tags list empty instead of holding two entries?


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


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


Re: [Haskell-cafe] Children elements with HXT

2009-12-22 Thread Tony Morris
Adding (a_remove_whitespace,v_1) as a parser option when running solves
it. Silly me.


Tony Morris wrote:
 I am trying to parse XML using HXT following
 http://www.haskell.org/haskellwiki/HXT/Conversion_of_Haskell_data_from/to_XML

 Here is my XML file (way.xml):

 way id=27776903 visible=true timestamp=2009-05-31T13:39:15Z
 version=3 changeset=1368552 user=Matt uid=70
   tag k=access v=private/
   tag k=highway v=service/
 /way

 The problem is when parsing, by reading the tag entries into the
 list held by the Way data structure, I cannot get anything but an
 empty list.

 Here is my parsing code:

 import Text.XML.HXT.Arrow

 newtype Way = Way {
   tags :: [Tag]
 } deriving (Eq, Show)

 xpWay :: PU Way
 xpWay = xpElem way (xpWrap (Way, tags) (xpList xpTag))

 data Tag = Tag {
   k :: String,
   v :: String
 } deriving (Eq, Show)

 xpTag :: PU Tag
 xpTag = xpElem tag (xpWrap (uncurry Tag, k  v) (xpPair (xpAttr
 k xpText) (xpAttr v xpText)))

 When I run, I get the following result:

 Main run = runX (xunpickleDocument xpWay [] way.xml)
 [Way {tags = []}]

 Why is the tags list empty instead of holding two entries?


   

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


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


Re: [Haskell-cafe] Finding HP

2009-12-03 Thread Tony Morris

 Furthermore, when someone offers feedback designed to improve a page, and 
 does so in a very non-threatening way:

 On Dec 2, 2009, at 2:26 PM, Andrew Coppin wrote:

   
 My suggestion is that if we really want people to grab the HP rather than 
 download GHC directly, maybe we could make the link slightly more prominent? 
 It also wouldn't hurt to mention it from the Implementations page, and 
 maybe the GHC homepage? Just a suggestion...
 

 ... then in my own humble opinion, snapping back with Are you sure this 
 isn't user error? is not a particularly nice response.

   
When someone asks a question after being offered feedback designed to
improve a page, and does so in a very non-threatening way:

 Are you sure this isn't user error?

... then in my own humble opinion, snapping back with \Are you sure
this isn't a user error?\ is not a particularly nice response is not a
particularly nice response.

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


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


Re: [Haskell-cafe] Implicit newtype unwrapping

2009-12-02 Thread Tony Morris
Isn't that the point of type-classes?

Martijn van Steenbergen wrote:
 So here's a totally wild idea Sjoerd and I came up with.

 What if newtypes were unwrapped implicitly?

 What advantages and disadvantages would it have?
 In what cases would this lead to ambiguous code?

 Thanks,

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


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


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


Re: [Haskell-cafe] Working with multiple projects

2009-11-11 Thread Tony Morris
I don't want to have to upload every time I make a minor change as I am
working. Surely there is an easier way.

Martijn van Steenbergen wrote:
 Tony Morris wrote:
 I have two projects that I intend to put on hackage soon. One depends
 on the other. I have cabaled both. I am wondering how others work
 with this kind of set up where changes are made to both libraries as
 they work.

 You just update and re-upload the packages as necessary. It really
 helps here if you follow the versioning guidelines:

 http://www.haskell.org/haskellwiki/Package_versioning_policy

 HTH,

 Martijn.



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


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


[Haskell-cafe] Working with multiple projects

2009-11-10 Thread Tony Morris
I have two projects that I intend to put on hackage soon. One depends
on the other. I have cabaled both. I am wondering how others work
with this kind of set up where changes are made to both libraries as
they work.



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


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


Re: [Haskell-cafe] Applicative but not Monad

2009-10-30 Thread Tony Morris
newtype Accy o a = Acc{acc :: o } -- Applicative Programming With Effects


Yusaku Hashimoto wrote:
 Hello cafe,
 Do you know any data-type which is Applicative but not Monad?

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

   

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


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


Re: [Haskell-cafe] Cal, Clojure, Groovy, Haskell, OCaml, etc.

2009-09-30 Thread Tony Morris
There is a significant difference between:

* A $ function without a type system
* A statically checked $ function
* A $ keyword without static checking

Curt Sampson wrote:
 On 2009-09-30 13:45 -0300 (Wed), namekuseijin wrote:

   
 The Perl call is spot on.  Specially because Haskell has been
 incorporating so much syntatic sugar that it's almost looking Perlish
 noise already: [examples deleted]
 

 No, I disagree with your particular examples; they're bog-standard
 Haskell that don't use any syntatic sugar (. and $ are just library
 functions), and I find them perfectly fine to read. Note that nothing
 in there is inconsistent or interpreted in any sort of exceptional way,
 unlike many things that look like that in Perl.

 It does take time to learn to read that sort of stuff, but once you've
 got it, simplifying this sort of thing would only make it harder to
 read, because it would be more verbose without saying anything more.
 Haskell's concision is one of its most important strengths.

 (Incidently, a good exercise for learning to understand stuff like that
 might be to go thorugh it and convert it to use parens instead of $,
 full application instead of ., and so on.)

 cjs
   

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


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


Re: [Haskell-cafe] Comments requested: succ Java

2009-09-29 Thread Tony Morris


John A. De Goes wrote:
   write them yourself (at a cost of several to dozens of man years),
Is that right?

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


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


Re: [Haskell-cafe] Cal, Clojure, Groovy, Haskell, OCaml, etc.

2009-09-28 Thread Tony Morris
I think one must distinguish what it means for a language to exist and
be practical. Counter-example: Java fails catastrophically at all
three and it most certainly exists; boy do I know it.

Casey Hawthorne wrote:
 I think a language needs the following to exist:

 - a community

 - good library

 - a package manager

 Thoughts?
 --
 Regards,
 Casey
 ___
 Haskell-Cafe mailing list
 Haskell-Cafe@haskell.org
 http://www.haskell.org/mailman/listinfo/haskell-cafe

   

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


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


Re: [Haskell-cafe] Library function for map+append

2009-08-18 Thread Tony Morris
Dusan Kolar wrote:
 Hello all,

  During a small project I'm trying to develop a small application. It
 becomes quite often that I need a function mapapp:

 mapapp _ [] ap = ap
 mapapp f (a:as) ap = f a : map f as ap

  I tried hoogle to find such a function with no success. Is there any
 function/functions built-in standard libraries that could easily
 satisfy the functionality with the same or even better (?) efficiency?

  Of course,
 (map f list) ++ append 
  would do the same as

 mapapp f list append

  but with less efficiency. Or am I wrong?

  Thanks

Dusan

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

mapapp = ((++) .) . map

Reasoning about efficiency in a pure lazy language is different.

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


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


Re: [Haskell-cafe] Monoid wants a (++) equivalent

2009-06-30 Thread Tony Morris


David Leimbach wrote:


 On Tue, Jun 30, 2009 at 11:54 AM, Brent Yorgey byor...@seas.upenn.edu
 mailto:byor...@seas.upenn.edu wrote:

 On Tue, Jun 30, 2009 at 09:45:45AM -0700, Bryan O'Sullivan wrote:
  I've thought for a while that it would be very nice indeed if
 the Monoid
  class had a more concise operator for infix appending than a
 `mappend` b.
  I wonder if other people are of a similar opinion, and if so,
 whether this
  is worth submitting a libraries@ proposal over.

 +1.

 IIRC Jules Bean has proposed using (+) for this purpose, which I
 like.  It has the advantages of (a) not clashing with any other
 (common) operators, (b) making more obvious the fact that mappend is
 not necessarily commutative, and (c) providing the obvious (+) for
 'flip mappend' which is sometimes useful.


 I actually think this proposal is pretty excellent.  
I happen to agree.

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


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


[Haskell-cafe] List spine traversal

2009-06-28 Thread Tony Morris
Is there a canonical function for traversing the spine of a list?

I could use e.g. (seq . length) but this feels dirty, so I have foldl'
(const . const $ ()) () which still doesn't feel right. What's the
typical means of doing this?


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


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


Re: [Haskell-cafe] I need a hint in list processing

2009-06-14 Thread Tony Morris
nub . concat ?

Richard O'Keefe wrote:

 On 14 Jun 2009, at 8:06 pm, Fernan Bolando wrote:

 Hi all

 If I have a number of list
 example
 list1 = [2,3]
 list2 = [1,2]
 list3 = [2,3,4]
 list4 = [1,2,3]

 I want to create a list from the list above with n elements,
 non-repeating and each elements index represents 1 of the elements
 from the corresponding list so for the above input I would get.

 a = [3,2,4,1]

 I have been staring at this off and on all day,
 and I haven't the faintest idea what you want.

 What is n.  What is it that doesn't repeat?
 How does the index of an element represent 1 element?
 Which list corresponds to what?

 I'm beginning to suspect that what you want is a choice
 function:
 f [s1,...,sn] = [x1,...,xn]
 when each xi is an element of the corresponding si
 and no two xs are the same.

 Instead of finding one answer, let's find them all.

 all_choices :: Eq a = [[a]] - [[a]]
 all_choices [] = [[]]
 all_choices (set:sets) =
   [x:xs | xs - all_choices sets, x  - set, not(x `elem` xs)]

 The test case

 all_choices [[2,3], [1,2], [2,3,4], [1,2,3]]

 has the answer

 [[3,2,4,1], [3,1,4,2], [2,1,4,3]]

 and you probably want to use it something like

 case all_choices sets of
   [] - there are no such choices
   (first_choice:_) - first_choice is one such choice

 For inputs like [[1,2],[2,1],[1]] there is of course no such
 choice function.


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


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


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


Re: [Haskell-cafe] I need a hint in list processing

2009-06-14 Thread Tony Morris
Just guessing. How do you know it's an accident?


Richard O'Keefe wrote:

 On 15 Jun 2009, at 4:26 pm, Tony Morris wrote:

 Prelude Data.List nub . concat $ [[2, 3], [1, 2], [2, 3, 4], [1, 2, 3]]
 [2,3,1,4]

 In this particular case.  But that's a lucky accident.\



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


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


Re: [Haskell-cafe] When folding is there a way to pick out the last point being processed?

2009-06-11 Thread Tony Morris
By swapping from foldl to foldr? Care to provide more detail?

Casey Hawthorne wrote:
 When folding is there a way to pick out the last point being
 processed?

 The first point can easily be picked out with (x:xs) but last xs
 crawls down the list.
 --
 Regards,
 Casey
 ___
 Haskell-Cafe mailing list
 Haskell-Cafe@haskell.org
 http://www.haskell.org/mailman/listinfo/haskell-cafe

   

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


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


Re: [Haskell-cafe] Re: Non Empty List?

2009-06-04 Thread Tony Morris
I note that you didn't address the suggestion of a zipper.


GüŸnther Schmidt wrote:
 Dan Weston schrieb:
 Unless I'm missing something in your description, why not

   data Container a = Single a | Many a a [a]


 Hi Dan,

 the above solution would still allow to construct, for instance,

 Many 5 42 [] :: Container Int

 The reason why I'm trying to find the design for a data structure in
 which this would not even be possible is to be able to avoid writing
 additional bookkeeping code into the functions that operate on the
 structure, ie. the lookups, inserts, delete etc.

 Günther

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


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


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


Re: [Haskell-cafe] instance Monad (Except err)

2009-05-04 Thread Tony Morris
Martijn van Steenbergen wrote:
 Hello,

 Mr. McBride and mr. Paterson define in their Applicative paper:

 data Except e a = OK a | Failed e
 instance Monoid e = Applicative (Except e) where ...

 Sometimes I'd still like to use = on Excepts but this feels wrong
 somehow, because it doesn't use monoids nicely like the Applicative
 instance does. Are there any good reasons such a Monad instance
 shouldn't be defined? Does it violate any laws, for example?

 Thanks,

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

I'm sure you could, but then ap /= (*).

This seems related to a question that I once asked
http://www.haskell.org/pipermail/haskell-cafe/2009-January/054139.html


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


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


Re: [Haskell-cafe] instance Monad (Except err)

2009-05-04 Thread Tony Morris
Yes, however, ap is not equal to (*) for the given Applicative. I
don't believe such a monad is possible.

Neil Brown wrote:
 Martijn van Steenbergen wrote:
 Hello,

 Mr. McBride and mr. Paterson define in their Applicative paper:

 data Except e a = OK a | Failed e
 instance Monoid e = Applicative (Except e) where ...

 Sometimes I'd still like to use = on Excepts but this feels wrong
 somehow, because it doesn't use monoids nicely like the Applicative
 instance does. Are there any good reasons such a Monad instance
 shouldn't be defined? Does it violate any laws, for example?
 Isn't the Except type just Either by another name?  OK = Right, Failed
 = Left.  Therefore the monad is just the same as the Either monad, and
 is useful as an error monad:

 instance Monad (Except e) where
  (OK x) = f = f x
  Failed e = _ = Failed e
  return = OK

 This obeys all the monad laws.

 Thanks,

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


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


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


Re: [Haskell-cafe] Combining computations

2009-05-03 Thread Tony Morris
michael rice wrote:
 If you look at this stuff long enough it almost begins to make sense.
 Maybe. ;-)

 I've been messing around with MonadPlus and I understand its usage
 with the Maybe and List monads. Since one use of Monads is combining
 computations, how can I combine a Maybe with a List?

 let m1 = Nothing
 let m2 = [1]
 let m3 = m1 `mplus` m2  == [1]--if the Maybe is Nothing, do nothing 

 let m1 = Just 1
 let m2 = []
 let m3 = m1 `mplus` m2  == [1]  --if the Maybe is not Nothing, add it
 to the list

 Or am I misunderstanding combining computations?

 Michael


 

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

Hi Michael,
You'll want the Data.Maybe.listToMaybe and Data.Maybe.maybeToList functions.

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


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


Re: [Haskell-cafe] name for monad-like structure?

2009-04-28 Thread Tony Morris
Michael Vanier wrote:
 I've stumbled upon a structure that is like a weaker version of a
 monad, one that supports return and  but not =.  Has anyone seen
 this before, and if so, does it have a standard name?

 Mike


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

Are you sure it supports
() :: m a - m b - m b

and not
mplus :: m a - m a - m a ?

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


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


Re: [Haskell-cafe] Getting the x out

2009-04-21 Thread Tony Morris
You mean, the x out of *Maybe* x even. In the very literal sense, the
assumption that there is an x in Maybe x is false -- there may not be
one since it is maybe, but not necessarily, x. IT's a bit like the use
of null that you might have seen in other languages where you might have
a value or you might have null. What you can do however, is say give me
the x if there is one, otherwise, use this value.

This is the fromMaybe function.

Prelude Data.Maybe let safeDivision x y = if y == 0 then Nothing else
Just (x/y)
Prelude Data.Maybe 3 + (42 `fromMaybe` safeDivision 10 5)
5.0
Prelude Data.Maybe 3 + (42 `fromMaybe` safeDivision 10 0)
45.0



michael rice wrote:
 How do I get the x out of Just x?

 Michael

 =

 safeDivision :: Float - Float - Maybe Float
 safeDivision x y = if y == 0 then Nothing else Just (x/y)

 *Main Data.List safeDivision 10 5
 Just 2.0
 *Main Data.List 3 + (safeDivision 10 5)

 interactive:1:0:
 No instance for (Num (Maybe Float))
   arising from a use of `+' at interactive:1:0-22
 Possible fix: add an instance declaration for (Num (Maybe Float))
 In the expression: 3 + (safeDivision 10 5)
 In the definition of `it': it = 3 + (safeDivision 10 5)
 *Main Data.List


 

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

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


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


Re: [Haskell-cafe] Monad explanation

2009-02-09 Thread Tony Morris
-BEGIN PGP SIGNED MESSAGE-
Hash: SHA1

Gregg Reynolds wrote:
 The point being that the metalanguage commonly used to describe IO
 in Haskell contains a logical contradiction.  A thing cannot be both
 a value and a function, but e,g, getChar behaves like a function and
 has the type signature of a value.
getChar has the signature RealWorld - (RealWorld, Char)

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

*
* Anteromedial Heterotopic Osseous Impingement Syndrome *
*

http://www.ajronline.org/cgi/content/full/178/3/601
can result in chronic ankle pain, especially in athletes and the
younger population (15-40 years old)

http://radiographics.rsnajnls.org/cgi/content/figsonly/22/6/1457
Soft-tissue and osseous impingement syndromes of the ankle can be an
important cause of chronic pain, particularly in the professional
athlete.

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

iD8DBQFJj/bcmnpgrYe6r60RAicqAJ9z3f+aM/k+gDv8d5yAaNSCFf9NVQCfX3Qo
ItFqQSWPDUE2h9WS+axAXV8=
=c8Nw
-END PGP SIGNATURE-

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


Re: [Haskell-cafe] Monad explanation

2009-02-09 Thread Tony Morris
-BEGIN PGP SIGNED MESSAGE-
Hash: SHA1

You're right - my statement is inaccurate.

Implementation details aside, I am referring specifically to the
statement getChar ... has the type signature of a value. It clearly
does not.

Lennart Augustsson wrote:
 Not it doesn't.  getChar has the type signature IO Char. The IO
 type is abstract.  GHC happens to implement it by a state monad.
 But in, e.g., hbc it is implemented in a totally different way,
 more like a continuation monad.

 Peeking inside an implementation of IO can be illuminating, but one
 must remember that IO is abstract.

 -- Lennart

 On Mon, Feb 9, 2009 at 10:26 AM, Tony Morris tmor...@tmorris.net
 wrote: Gregg Reynolds wrote:
 The point being that the metalanguage commonly used to
 describe IO in Haskell contains a logical contradiction.  A
 thing cannot be both a value and a function, but e,g, getChar
 behaves like a function and has the type signature of a
 value.
 getChar has the signature RealWorld - (RealWorld, Char)


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


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

S, K and I ought to be enough for anybody.

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

iEYEARECAAYFAkmQAfkACgkQmnpgrYe6r61tmQCcCx42Cz1iunkD7JGubla/z2Pg
uhAAoLk5rkjeHnrfc936IhYoBQYO/+0r
=6xWk
-END PGP SIGNATURE-

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


Re: [Haskell-cafe] Monad explanation

2009-02-09 Thread Tony Morris
-BEGIN PGP SIGNED MESSAGE-
Hash: SHA1

I also agree it is a value.
The original post was attempting to make a distinction that does not
exist. I deliberately avoided that topic.

A thing cannot be both a value and a function, but e,g, getChar

My original intent was to hope the poster reconsidered the whole post.
You've blown my cover :)


Lennart Augustsson wrote:
 But an (IO Char) is a value.  You can do all the things with it
 that you can do with values, e.g., pass it as an argument, stick it
 in a list, etc.  It is a special kind of value, since if it ever
 gets in contact with the top level it will be executed. But the
 fact that IO types also behave as values makes Haskell a very
 powerful imperative language.

 On Mon, Feb 9, 2009 at 11:14 AM, Tony Morris tmor...@tmorris.net
 wrote: You're right - my statement is inaccurate.

 Implementation details aside, I am referring specifically to the
 statement getChar ... has the type signature of a value. It
 clearly does not.

 Lennart Augustsson wrote:
 Not it doesn't.  getChar has the type signature IO Char. The
 IO type is abstract.  GHC happens to implement it by a state
 monad. But in, e.g., hbc it is implemented in a totally
 different way, more like a continuation monad.

 Peeking inside an implementation of IO can be illuminating,
 but one must remember that IO is abstract.

 -- Lennart

 On Mon, Feb 9, 2009 at 10:26 AM, Tony Morris
 tmor...@tmorris.net wrote: Gregg Reynolds wrote:
 The point being that the metalanguage commonly used to
 describe IO in Haskell contains a logical
 contradiction.  A thing cannot be both a value and a
 function, but e,g, getChar behaves like a function and
 has the type signature of a value.
 getChar has the signature RealWorld - (RealWorld, Char)

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


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

S, K and I ought to be enough for anybody.

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

iEYEARECAAYFAkmQB5EACgkQmnpgrYe6r60L5QCfffj1Vy2Yg25adZLsLBReOk/K
ZAoAoISEpzQH/9D0AzQOZdxJoxmoKeBj
=+ZZx
-END PGP SIGNATURE-

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


Re: [Haskell-cafe] Function const (Binding)

2009-02-07 Thread Tony Morris
-BEGIN PGP SIGNED MESSAGE-
Hash: SHA1

Maybe it will help with parentheses:
(const id 1) 2

(const id 1) ignores the second argument and yields the id function so
then
id 2

which is just 2.

TKM wrote:
 Hello,

 I've a small question about the function const. I'm a bit of
 confused about how it binds. Let me take the following expression
 as example:

 const id 1 2

 If I execute this expression, I will get as answer 2 with Helium.
 Now is my question, why doesn't it give me 1 as the answer? Because
  the type of id would be: a - a. So first it would execute id 1 in
  my opinion. That gives us 1. And after executing const 1 2 it
 should give us 1.

 Can somebody explain to me why it does not bind as I expect? (I
 know I can do: const (id 1) 2 to get what I want)

 Thank you for your answers.

 Greetz TKM

 --


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

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


* Anteromedial Osseous Impingement *


http://www.ajronline.org/cgi/content/full/178/3/601
can result in chronic ankle pain, especially in athletes and the
younger population (15-40 years old)

http://radiographics.rsnajnls.org/cgi/content/figsonly/22/6/1457
Soft-tissue and osseous impingement syndromes of the ankle can be an
important cause of chronic pain, particularly in the professional
athlete.

1. Take any person with soft tissue and osseous joint impingement from
trauma
2. Surgically tighten the joint ligaments particularly those in the
area of impingement.
3. When the patient complains of incredible and permanent pain, shrug
your shoulders.

Outcome
You'll find the patient at the mental hospital bordering psychosis.
-BEGIN PGP SIGNATURE-
Version: GnuPG v1.4.6 (GNU/Linux)
Comment: Using GnuPG with Mozilla - http://enigmail.mozdev.org

iD8DBQFJjhkomnpgrYe6r60RAmvtAKDBQxNAlc2tfN283vcvs5gkzXUEjwCgpw7s
CcGAha7L6AgHESzwLSoD2XU=
=szrP
-END PGP SIGNATURE-

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


[Haskell-cafe] Applicative/Monad for Either

2009-01-21 Thread Tony Morris
-BEGIN PGP SIGNED MESSAGE-
Hash: SHA1

In the code below, the Applicative instance accumulates on the Left
constructor using Monoid/mappend.
Is it possible to write an equivalent Monad such that ap = (*) ? I'm
finding difficulty in proving to myself either way.




import Control.Monad.Instances
import Control.Applicative
import Data.Monoid

newtype Z e a = Z {
  either :: Either e a
}

instance Functor (Z e) where
  fmap f (Z e) = Z (f `fmap` e)

instance (Monoid e) = Applicative (Z e) where
  pure = Z . Right
  (Z (Left e1)) * (Z (Left e2)) = Z (Left (e1 `mappend` e2))
  (Z (Left e1)) * (Z (Right _)) = Z (Left e1)
  (Z (Right _)) * (Z (Left e2)) = Z (Left e2)
  (Z (Right f)) * (Z (Right a)) = Z (Right (f a))

instance (Monoid e) = Monad (Z e) where
  return = pure
  (Z e) = f = error todo -- ?

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

S, K and I ought to be enough for anybody.

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

iD8DBQFJd5vImnpgrYe6r60RAoUNAJ4jn0GfC6zsP9giPGop1ILExiHrLQCfSoc2
0QXf533sWb3HyrL0pQNjMww=
=R36O
-END PGP SIGNATURE-

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


Re: [Haskell-cafe] Function composition

2008-12-26 Thread Tony Morris
-BEGIN PGP SIGNED MESSAGE-
Hash: SHA1

Check the type of (.)

Prelude :t (.)
(.) :: (b - c) - (a - b) - a - c

Then the type of (.) not

Prelude :t (.) not
(.) not :: (a - Bool) - a - Bool

Now try to apply (==)

Prelude :t (.) not (==) -- not going to happen

Won't happen. What do you want to happen?


Oscar Picasso wrote:
 Hi,

 I can write:
 *Main let yes = not . not
 *Main :t yes
 yes :: Bool - Bool

 But not:
 *Main let isNotEqual = not . (==)

 interactive:1:23:
 Couldn't match expected type `Bool'
against inferred type `a - Bool'
 Probable cause: `==' is applied to too few arguments
 In the second argument of `(.)', namely `(==)'
 In the expression: not . (==)

 Why?

 Oscar


 --

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

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

S, K and I ought to be enough for anybody.

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

iD8DBQFJVamwmnpgrYe6r60RAnerAKDAs4KKsGHN7/WnqUYAJcVJixQiCgCgkQTV
CgeAJDTFEeKdAl4Ep3ibG88=
=GcLE
-END PGP SIGNATURE-

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


Re: [Haskell-cafe] About do notation.

2008-10-14 Thread Tony Morris
-BEGIN PGP SIGNED MESSAGE-
Hash: SHA1

Magicloud wrote:
 Hi, As some articles say, do notation is expand to () and (=)
 when being compiled. So I want to know the details. Like: main = do
  a - getArgs b - getLine myFunc1 (head a) b myFunc2 b (head a)

 I cannot figure out what is the () and (=) way of this.

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



getArgs = (\a - getLine = (\b - myFunc1 (head a) b  myFunc2 b
(head a)))

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


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

iD8DBQFI9WqJmnpgrYe6r60RAhAEAKCNvJaxziyZ3g9wGUOoJpcx4/MrtwCfVnlL
ZflntZ5xrDOCv3kHgcuMP18=
=21PH
-END PGP SIGNATURE-

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


Re: [Haskell-cafe] Having trouble with zip12..

2008-07-06 Thread Tony Morris
-BEGIN PGP SIGNED MESSAGE-
Hash: SHA1

Michael Feathers wrote:


 I have some code that looks like this and I'm having trouble with
 it:


 zip12 ((tails . nub) flightPaths) wayPoints etopsPackets (hd
 geoCaches) groundSpeeds headings (map windShift headings)
 (regulations !! 2) (foldr (\|/) (tail pathDistances)) [ghy x | x -
 [1..], full x] (nub . nub) arrivalSchedule

Hi Michael,
Sorry to distract from your issue, but I note that (nub . nub) can be
replaced with just 'nub' since the function nub is idempotent (f . f
== f).

dibblego @check \x - (nub . nub) x == nub x -- is nub idempotent?
lambdabot  OK, passed 500 tests.

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

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

iD8DBQFIcS9LmnpgrYe6r60RAiDOAKCJlDaqNd5ssgxrUrrHee75WGzhbgCfftdn
70+4isXh4zaoYly0da2Gdk8=
=ryfF
-END PGP SIGNATURE-

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


Re: [Haskell-cafe] zlib, missing zlib.h

2008-05-30 Thread Tony Morris
-BEGIN PGP SIGNED MESSAGE-
Hash: SHA1

apt-get install zlib1g-dev

Tony Morris
http://tmorris.net/

Real-world problems are simply degenerate cases of pure mathematical
problems.



Thomas Hartman wrote:
 Tried to install
 
 http://hackage.haskell.org/cgi-bin/hackage-scripts/package/zlib
 
 which is required for
 
 http://darcs.haskell.org/cabal-branches/cabal-1.4
 
 which is required for cabal-install.
 
 Got the following error. apt-get installed zlibc on a stab in the
 dark, but same result. advice?
 
 [EMAIL 
 PROTECTED]:~/haskellInstalls/smallInstalls/cabal-install/zlib-0.4.0.4runghc
 Setup.hs configure
 Configuring zlib-0.4.0.4...
 
 [EMAIL 
 PROTECTED]:~/haskellInstalls/smallInstalls/cabal-install/zlib-0.4.0.4runghc
 Setup.hs build out
 
 [EMAIL 
 PROTECTED]:~/haskellInstalls/smallInstalls/cabal-install/zlib-0.4.0.4head
 out
 Preprocessing library zlib-0.4.0.4...
 
 Stream.hsc:74:18:  error: zlib.h: No such file or directory
 Stream.hsc: In function 'main':
 
 Stream.hsc:254:0:
  error: 'z_stream' undeclared (first use in this function)
 
 Stream.hsc:254:0:
  error: (Each undeclared identifier is reported only once
 [EMAIL PROTECTED]:~/haskellInstalls/smallInstalls/cabal-install/zlib-0.4.0.4
 ___
 Haskell-Cafe mailing list
 Haskell-Cafe@haskell.org
 http://www.haskell.org/mailman/listinfo/haskell-cafe
 
 
 
-BEGIN PGP SIGNATURE-
Version: GnuPG v1.4.6 (GNU/Linux)
Comment: Using GnuPG with Mozilla - http://enigmail.mozdev.org

iD8DBQFIP8GgmnpgrYe6r60RAjGGAKDCpiIE9IGv5Madf2jMhEZCDuuEhgCdGljK
ztH9XwTczFX7ABBrh3TuT8I=
=jR/y
-END PGP SIGNATURE-
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] lambdabot on GHC 6.8.2

2008-05-20 Thread Tony Morris
-BEGIN PGP SIGNED MESSAGE-
Hash: SHA1

So after some effort, I managed to get lambdabot installed on a ubuntu
machine using GHC 6.8.2, however, it fails when evaluating an expression:

 1 + 1
setResourceLimit: invalid argument (Invalid argument)

Googling around brings up a bug (#2038) against GHC 6.8.2. Am I hitting
this bug? If so, can I get around it to get a working lambdabot? Thanks
for any tips.


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

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

iD8DBQFIMnFnmnpgrYe6r60RAp7DAJ9JhFsWwL05eyrcECf6C9Z/ML+h0gCgt5/I
3E7eOjVMm+RSXumbYiCsgR8=
=bpjW
-END PGP SIGNATURE-
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] Test.QuickCheck.Gen

2008-05-01 Thread Tony Morris
-BEGIN PGP SIGNED MESSAGE-
Hash: SHA1

I am trying to understand the QuickCheck source in a bit of depth and
I have noted that a Gen x is a function Int - StdGen - x, however,
some of the combinators can at times, fail to ever produce a result by
throwing an error. I include an example using ghci:

*Test.QuickCheck (f 0 (mkStdGen 0)) :: Int
*** Exception: Prelude.(!!): negative index

It seems this can be alleviated by changing Gen x to Int - StdGen -
Maybe x and having the generator produce Nothing when a combinator
fails. However, now the function promote cannot be written (I have
tried and run into the conundrum of writing the function (a - Maybe
b) - Maybe (a - b)), which is used to generate functions. So, I'm
caught on the fence about whether there is a possible improvement here
(for example, should the elements function throw the error?), or if
the current scenario is acceptable.

I'm seeking comments about this, thanks!

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

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

iD8DBQFIGjO6mnpgrYe6r60RAtohAKCBsl1lHxuNrBaLHuqwCN58PBHCIACbBALk
YWkBkw9o9NUQbr+lgo0rXE0=
=JQlH
-END PGP SIGNATURE-

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


Re: [Haskell-cafe] haskellwiki and Project Euler

2008-02-23 Thread Tony Morris

Daniel Fischer wrote:

Hi all,
I try not to be too rude, although I'm rather disgusted.
I know there are several sites out on the web where solutions to PE problems 
are given. That is of course absolutely against the sporting spirit of 
Project Euler, but hey, not all people are sporting.
I've found http://www.haskell.org/haskellwiki/Euler_problems irritating for a 
while, but wasn't overly annoyed by it while it only contained code for 
solving a few dozen problems.

Today I learnt that it now contains code for all problems.
Really bad!

On top of that, the code for many problems isn't even Haskell, but C, WTF!
Other code was submitted without consent of the author, copied from the PE 
fora, which are restricted access and so, even if perhaps not legally, but in 
spirit, do not fall under the legitimate resources for haskellwiki:
You are also promising us that you wrote this yourself, or copied it from a 
public domain or similar free resource. DO NOT SUBMIT COPYRIGHTED WORK 
WITHOUT PERMISSION!


To make matters worse still, there was a page containing nothing but the 
answers. That was changed, but Cale chose to reintroduce that crap.

I just removed it again. Your turn, Cale.

I call on the Haskell community to vote for immediate removal of these pages 
from the wiki!

Show that you're a sporting bunch.

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





You're going the right way about having the answers published in more 
ways than just the Haskell wiki. I'm only making a prediction, not a threat.


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

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


  1   2   >