
Hello all, Quick one for you. I have a list of (<timestamp>,<value>) pairs, and I have defined lots of nice functions for doing various tricks with them. I'd like to define a custom data type which is an instance of 'Num' so I can conveniently do arithmetic on them. (I have written some tools for merging two time series etc...) e.g. t (x,y) = x v (x,y) = y mergeSkip _ [] = [] mergeSkip [] _ = [] mergeSkip (x:xs) (y:ys) | t x == t y = ( t x, (v x, v y) ) : (mergeSkip xs ys) | t x > t y = mergeSkip xs (y:ys) | t x < t y = mergeSkip (x:xs) ys binaryValueFunc f [] = [] binaryValueFunc f ((t,(a,b)):xs) = (t, f a b):binaryValueFunc f xs add xs = binaryValueFunc (+) xs addSkip xs ys = add $ mergeSkip xs ys So addSkip will nicely take two of my time series, merge them by throwing out any pairs which don't have a time stamp that exists in both and then add the values to return a new series. All is well. But how do I make it so that I can use the + operator to add two of them? Well of course, I tried making a custom data type: data Ts a b = Ts [(a,b)] intance Ts Num where <blaa blaa blaa> But then I have to rewrite all of my functions to pattern match on Ts instead of just the list. Worse, when I am writing recursive functions I have to construct a Ts again for the recursive call. I guess I could make my own 'list-like' datastructure data Ts a b = Empty | Cons ((a,b), Ts) But that seems rather clumsy. So I tried to make 'Ts' a type synonym for [(a,b)] which worked, but then I couldn't declare it an instance of 'Num'. So I guess the question is, is there any way of making a type synonym for a type which I can define as an instance of another class? So I can use my values of the type synonym for functions which expect the 'vanilla' type, but define 'extra' stuff my type synonym can do? Any help or advice greatly appreciated. - Philip

Well, let's begin by making some suggestions to your current code. Below I tell my answer to your question as well. :) On Sat, Nov 21, 2009 at 03:20:30PM +0000, Philip Scott wrote: ] t (x,y) = x ] v (x,y) = y
t = fst v = snd
] mergeSkip _ [] = [] ] mergeSkip [] _ = [] ] mergeSkip (x:xs) (y:ys) ] | t x == t y = ( t x, (v x, v y) ) : (mergeSkip xs ys) ] | t x > t y = mergeSkip xs (y:ys) ] | t x < t y = mergeSkip (x:xs) ys Using 't' and 'v' isn't very readable, so probably it would be better to just type two more characters and use 'fst' and 'snd':
mergeSkip (x:xs) (y:ys) | fst x == fst y = (fst x, (snd x, snd y)) : mergeSkip xs ys | fst x > fst y = mergeSkip xs (y:ys) | fst x < fst y = mergeSkip (x:xs) ys
Or, even better yet,
mergeSkip xss@((xa,xb):xs) yss@((ya,yb):ys) | xa == ya = (xa, (xb, yb)) : mergeSkip xs ys | xa > ya = mergeSkip xs yss | xa < ya = mergeSkip xss ys
] binaryValueFunc f [] = [] ] binaryValueFunc f ((t,(a,b)):xs) = (t, f a b):binaryValueFunc f xs
import Control.Arrow (second) binaryValueFunc f = map (second $ uncurry f)
Now, to your question! ] So addSkip will nicely take two of my time series, merge them by throwing out ] any pairs which don't have a time stamp that exists in both and then add the ] values to return a new series. All is well. But how do I make it so that I can ] use the + operator to add two of them? ] ] Well of course, I tried making a custom data type: ] ] data Ts a b = Ts [(a,b)] ] intance Ts Num where ] <blaa blaa blaa> ] ] But then I have to rewrite all of my functions to pattern match on Ts instead ] of just the list. Worse, when I am writing recursive functions I have to ] construct a Ts again for the recursive call. I guess I could make my own ] 'list-like' datastructure The common idiom is to write
newtype Ts a b = Ts {unTs :: [(a,b)]} deriving (Eq, Show)
We use a newtype just to guarantee that there will be no overhead in using this data type instead of just using a plain list (i.e. at runtime Ts and unTs will be striped out). We name the field as unTs to use it when composing functions (see below). So your definitions above will become:
mergeSkip' (T xs) (T ys) = T (mergeSkip xs ys)
if you want to keep the old definition, or
mergeSkip'' (T []) _ = T [] mergeSkip'' _ (T []) = T [] mergeSkip'' xss@(T ((xa,xb):xs)) yss@(T ((ya,yb):ys)) | xa == ya = T $ (xa, (xb, yb)) : mergeSkip'' xs ys | xa > ya = mergeSkip'' (T xs) yss | xa < ya = mergeSkip'' xss (T ys)
Not that bad, I think. Continuing, let's use unTs:
binaryValueFunc f = Ts . map (second $ uncurry f) . unTs
Not bad at all :). However we can just define:
instance Functor (Ts a) where fmap f = Ts . fmap (second f) . unTs
Using the Functor we can rewrite binaryValueFunc to just
binaryValueFunc' :: Functor f => (a -> b -> c) -> f (a,b) -> f c binaryValueFunc' f = fmap (uncurry f)
I've written the type explicitly to show how general we just got. However, I guess the following function is more useful for the Num instance:
liftBin f xs ys = fmap (uncurry f) $ mergeSkip xs ys
Now our Num instance is just
instance (Ord a, Num b) => Num (Ts a b) where (+) = liftBin (+) (-) = liftBin (-) (*) = liftBin (*) abs = fmap abs negate = fmap negate signum = fmap signum fromInteger = error "I don't know how you would define this :)"
I hope that helps! (Note that if you can implement the Applicative type class for your Ts data type and then get liftBin = liftA2 for free.) -- Felipe.

Well, let's begin by making some suggestions to your current code. Below I tell my answer to your question as well. :)
What a fantastic and comprehensive answer, thank you! I now need to sit down and digest it. There are so many little clever tricks you can do with Haskell, is there a collection of them somewhere? If you want to collect your obligatory cookie and are ever in and around Cambridge UK let me know :) - Philip

On Sat, Nov 21, 2009 at 05:57:45PM +0000, Philip Scott wrote:
What a fantastic and comprehensive answer, thank you!
No problem. :)
I now need to sit down and digest it. There are so many little clever tricks you can do with Haskell, is there a collection of them somewhere?
Lately people have been suggesting the Typeclassopedia[1] as a good place for begginners. It's a good reading and I recommend it, I just don't know if you'll find everything needed for my answer there. In general, however, you just need practice. Go code! =) [1] http://haskell.org/sitewiki/images/8/85/TMR-Issue13.pdf
If you want to collect your obligatory cookie and are ever in and around Cambridge UK let me know :)
Too bad I'm 8837 km away from Cambridge according to Alpha =(... Cheers, -- Felipe.

Hi ho,
In general, however, you just need practice. Go code! =)
Righto, I am getting stuck in with that. One last question; I've been trying to read up on Arrows and my mind is being boggled. Via experiment, I have worked out what 'second' was doing (the documentation is useless unless you already understand a lot of stuff I clearly don't) For the other newbies, 'second' takes a function and a tuple, it applies the function to the second thing in your tuple and returns a tuple with the first value unchanged, and the result of applying 'f' to the second:
second (\x -> "fish") (10,20) (10,"fish")
What I am struggling to understand is what on earth the type signature means: :t second second :: (Arrow a) => a b c -> a (d, b) (d, c) How can (\x -> "fish") be an 'a b c' when it really looks like this: :t (\x->"fish") (\x->"fish") :: t -> [Char] And I am pretty sure I never made any Arrpws... I feel I am on the verge of understanding something deep and fundamentally philosophical about the typesystem but I can't quite bend my mind around to it :) All the best, Philip

On Sat, Nov 21, 2009 at 9:33 PM, Philip Scott
For the other newbies, 'second' takes a function and a tuple, it applies the function to the second thing in your tuple and returns a tuple with the first value unchanged, and the result of applying 'f' to the second:
That's what it does on a specific arrow, though generally that's the idea.
What I am struggling to understand is what on earth the type signature means:
:t second second :: (Arrow a) => a b c -> a (d, b) (d, c)
How can (\x -> "fish") be an 'a b c' when it really looks like this:
:t (\x->"fish") (\x->"fish") :: t -> [Char]
Right, but you must understand that (->) is a type constructor, just like Maybe or Either or your Ts. It takes two types parameter and return a function type. So "a -> b" is the infix syntax, but you could write that "(->) a b" just like you can write "3 + 5" as "(+) 3 5". Once you've done that on your function you get "(->) t Char" which looks a bit more like "a b c"... The final piece is that (->) is an Arrow, the most basic one but still an Arrow, so if you replace a by (->) in the type of second, you get : second :: (->) b c -> (->) (d, b) (d, c) which is just second :: (b -> c) -> (d, b) -> (d, c) which corresponds exactly to the action of second you described (that's the only function that could have this type, except bottom of course). -- Jedaï

The final piece is that (->) is an Arrow, the most basic one but still an Arrow, so if you replace a by (->) in the type of second, you get : second :: (->) b c -> (->) (d, b) (d, c) which is just second :: (b -> c) -> (d, b) -> (d, c)
Ahh I see, very clever! There is method to the madness after all; I should never have doubted you Haskell. Thank you for taking the time to explain that :) Do you know of any good discussions/tutorials on Arrows? I've only managed to find little snippets here and there http://www.haskell.org/arrows/ Doesn't have a lot of detail and http://www.haskell.org/ghc/docs/latest/html/libraries/base/Control-Arrow.htm... ..would probably be useful once I actually understand what is going on but right now I think a slap in the face with a big wet fish might help me more ;) - Philip

On Sat, Nov 21, 2009 at 09:07:38PM +0000, Philip Scott wrote:
The final piece is that (->) is an Arrow, the most basic one but still an Arrow, so if you replace a by (->) in the type of second, you get : second :: (->) b c -> (->) (d, b) (d, c) which is just second :: (b -> c) -> (d, b) -> (d, c)
Ahh I see, very clever! There is method to the madness after all; I should never have doubted you Haskell. Thank you for taking the time to explain that :)
Do you know of any good discussions/tutorials on Arrows? I've only managed to find little snippets here and there
The two tutorials linked from the "Bibliogrphy" section of that page are very good: http://www.soi.city.ac.uk/~ross/papers/fop.html http://www.cs.chalmers.se/~rjmh/afp-arrows.pdf You may also be interested in reading the "Category" and "Arrow" sections of the Typeclassopedia: http://www.haskell.org/sitewiki/images/8/85/TMR-Issue13.pdf -Brent

Chaddaï Fouché wrote:
second :: (b -> c) -> (d, b) -> (d, c) which corresponds exactly to the action of second you described (that's the only function that could have this type, except bottom of course).
Nonsense! There are several perfectly good Haskell functions with that type. I count seven: second :: (b -> c) -> (d, b) -> (d, c) second = Control.Arrow.second second = undefined second = const undefined second = const (const undefined) second = const (const (undefined,undefined)) second f (d,b) = (undefined, f b) second f (d,b) = (d, undefined) Why I'm stickling on that point on the beginners list, however, is a mystery. I'll go write a more useful response, in contrition. John

On Sat, Nov 21, 2009 at 10:13 PM, John Dorsey
Chaddaï Fouché wrote:
second :: (b -> c) -> (d, b) -> (d, c) which corresponds exactly to the action of second you described (that's the only function that could have this type, except bottom of course).
Nonsense! There are several perfectly good Haskell functions with that type. I count seven:
second :: (b -> c) -> (d, b) -> (d, c) second = Control.Arrow.second second = undefined second = const undefined second = const (const undefined) second = const (const (undefined,undefined)) second f (d,b) = (undefined, f b) second f (d,b) = (d, undefined)
Right... Let's just say functions that may be evaluated to normal form if their parameters can be evaluated to normal form. Nitpicker !! :P -- Jedaï

Am Samstag 21 November 2009 22:13:49 schrieb John Dorsey:
Chaddaï Fouché wrote:
second :: (b -> c) -> (d, b) -> (d, c) which corresponds exactly to the action of second you described (that's the only function that could have this type, except bottom of course).
Nonsense! There are several perfectly good Haskell functions with that type. I count seven:
second :: (b -> c) -> (d, b) -> (d, c) second = Control.Arrow.second second = undefined second = const undefined second = const (const undefined) second = const (const (undefined,undefined)) second f (d,b) = (undefined, f b) second f (d,b) = (d, undefined)
I don't see second f (d,b) = (undefined, f undefined) second f (d,b) = (d, f undefined) in there.
Why I'm stickling on that point on the beginners list, however, is a mystery. I'll go write a more useful response, in contrition.
John

Am Samstag 21 November 2009 21:33:28 schrieb Philip Scott:
Hi ho,
In general, however, you just need practice. Go code! =)
Righto, I am getting stuck in with that. One last question; I've been trying to read up on Arrows and my mind is being boggled. Via experiment, I have worked out what 'second' was doing (the documentation is useless unless you already understand a lot of stuff I clearly don't)
For the other newbies, 'second' takes a function and a tuple, it applies the function to the second thing in your tuple and returns a tuple with the first
value unchanged, and the result of applying 'f' to the second:
second (\x -> "fish") (10,20)
(10,"fish")
What I am struggling to understand is what on earth the type signature means: :t second
second :: (Arrow a) => a b c -> a (d, b) (d, c)
How can (\x -> "fish") be an 'a b c' when it really looks like this: :t (\x->"fish") (\x->"fish") :: t -> [Char]
a is a type variable (restricted to be a member of the Arrow class). Now the type ghci reports for (\x -> "fish") is printed in infix form, in prefix form, it reads :t (\x -> "fish") (\x -> "fish") :: (->) t [Char] so we find a = (->) b = t c = [Char] and you're using the most widespread instance of Arrow, (->). Arrows are a generalisation of functions. Until you're more familiar with Arrows, I suggest replacing any (Arrow a) with (->) in the type signatures to understand what things mean in the familiar case. Next in line would probably be Kleisli arrows (Monad m => a -> m b; it's wrapped in a newtype for Control.Arrow), break at any level of abstraction you want and return later.
And I am pretty sure I never made any Arrpws...
There are a few others have made for you to use :)
I feel I am on the verge of understanding something deep and fundamentally philosophical about the typesystem but I can't quite bend my mind around to it
:)
All the best,
Philip

On Sat, Nov 21, 2009 at 08:33:28PM +0000, Philip Scott wrote:
Righto, I am getting stuck in with that. One last question; I've been trying to read up on Arrows and my mind is being boggled. Via experiment, I have worked out what 'second' was doing (the documentation is useless unless you already understand a lot of stuff I clearly don't)
For the other newbies, 'second' takes a function and a tuple, it applies the function to the second thing in your tuple and returns a tuple with the first value unchanged, and the result of applying 'f' to the second:
second (\x -> "fish") (10,20) (10,"fish")
What I am struggling to understand is what on earth the type signature means:
:t second second :: (Arrow a) => a b c -> a (d, b) (d, c)
How can (\x -> "fish") be an 'a b c' when it really looks like this:
:t (\x->"fish") (\x->"fish") :: t -> [Char]
And I am pretty sure I never made any Arrpws...
I feel I am on the verge of understanding something deep and fundamentally philosophical about the typesystem but I can't quite bend my mind around to it :)
The problem you're facing is that you have to think of the arrow operator (->) as a type constructor. IOW, to unify : a b c with t -> [Char] you have the following "assignments": a ~ (->) b ~ t c ~ [Char] In another other words, t -> [Char] is the same as (->) t [Char] Now it's easy to see whats happening. Note that (->) is an instance to Arrow, in GHCi: Prelude Control.Arrow> :i Arrow class (Control.Category.Category a) => Arrow a where arr :: (b -> c) -> a b c first :: a b c -> a (b, d) (c, d) second :: a b c -> a (d, b) (d, c) (***) :: a b c -> a b' c' -> a (b, b') (c, c') (&&&) :: a b c -> a b c' -> a b (c, c') -- Defined in Control.Arrow instance Arrow (->) -- Defined in Control.Arrow <<< HERE <<< instance (Monad m) => Arrow (Kleisli m) -- Defined in Control.Arrow Specializing those types to Arrow (->) and using the common infix notation we have that: arr :: (b -> c) -> (b -> c) first :: (b -> c) -> ((b, d) -> (c, d)) second :: (b -> c) -> ((d, b) -> (d, c)) (***) :: (b -> c) -> (b' -> c') -> ((b, b') -> (c, c')) (&&&) :: (b -> c) -> (b' -> c') -> (b -> (c, c')) Note that 'arr = id'. That's why we may use all Arrow functions on, err, plain functions without having wrap everything with 'arr' (as you would with any other arrow). It's a good exercise to try to reproduce the definition of the Arrow (->) instance by defining the functions above. Most definitions, if not all, are just the corresponding free theorems (meaning roughly that the definition follows from the type because that's the only definition that doesn't have undefined's). HTH! -- Felipe.

On Sat, Nov 21, 2009 at 21:08 Felipe Lessa wrote:
Most definitions, if not all, are just the corresponding free theorems (meaning roughly that the definition follows from the type because that's the only definition that doesn't have undefined's).
Question: Is it correct to paraphrase Felipe's description as follows: In Haskell the *term theorems for free* means roughly that the definition of a class, instance or a function follows from the supplied types because they are the only types that don’t have undefined argumens or undefined return types. Regards, Pat

On Sun, Nov 22, 2009 at 03:32:07PM +0000, pbrowne wrote:
On Sat, Nov 21, 2009 at 21:08 Felipe Lessa wrote:
Most definitions, if not all, are just the corresponding free theorems (meaning roughly that the definition follows from the type because that's the only definition that doesn't have undefined's).
Question: Is it correct to paraphrase Felipe's description as follows: In Haskell the *term theorems for free* means roughly that the definition of a class, instance or a function follows from the supplied types because they are the only types that don’t have undefined argumens or undefined return types.
That is a good way to paraphrase Felipe's description --- but I don't think Felipe's terminology is correct. Many types do indeed have only a small number, or even only one, possible "interesting" implementation that does not involve undefined anywhere. However, this is not what is meant by "free theorems". A "free theorem" is a *property* which is satisfied by any function with a particular type. For example, any function with the type foo :: [a] -> Maybe a necessarily satisfies foo (map f xs) = fmap f (foo xs) (or, in points-free form, foo . map f = fmap f . foo ) for any list xs and function f, no matter what the implementation of foo (as long as it does not involve undefined or unsafePerformIO or any "cheating" of that sort). -Brent

On Sun, Nov 22, 2009 at 03:32:07PM +0000, Brent Yorgey wrote:
A "free theorem" is a *property* which is satisfied by any function with a particular type. For example, any function with the type
foo :: [a] -> Maybe a
necessarily satisfies
foo (map f xs) = fmap f (foo xs)
A theorem is a statement which has been proved on the basis of previously established theorems or axiom. So, should the definition of the function not satisfy the signature? I may be confusing terminology here. I am coming of an OBJ2/Maude/CafeOBJ background to Haskell. In CafeOBJ a *property* of an operation could, for example, be associativity. I am having difficulty in adjusting to Haskells level of formality.
In Haskell the *theorems for free* means roughly that the definition of a class, instance or a function follows from the supplied types because they are the only types that don’t have undefined argumens or undefined return types.
Question: Is my generalization of applying the "free theorem" concept to classes and instances correct? Pat

On Sun, Nov 22, 2009 at 04:12:29PM +0000, pbrowne wrote:
On Sun, Nov 22, 2009 at 03:32:07PM +0000, Brent Yorgey wrote:
A "free theorem" is a *property* which is satisfied by any function with a particular type. For example, any function with the type
foo :: [a] -> Maybe a
necessarily satisfies
foo (map f xs) = fmap f (foo xs)
A theorem is a statement which has been proved on the basis of previously established theorems or axiom. So, should the definition of the function not satisfy the signature? I may be confusing terminology here. I am coming of an OBJ2/Maude/CafeOBJ background to Haskell. In CafeOBJ a *property* of an operation could, for example, be associativity. I am having difficulty in adjusting to Haskells level of formality.
I'm not quite sure what you're asking here. My point is just that a "free theorem" will be of the form "Any function f of type T, *no matter how f is implemented*, will always satisfy the following property: blah blah f blah = blah f blah " This has nothing to do with whether or not there is only one possible implementation of f that does not involve undefined, which is a different phenomenon.
In Haskell the *theorems for free* means roughly that the definition of a class, instance or a function follows from the supplied types because they are the only types that don’t have undefined argumens or undefined return types.
Question: Is my generalization of applying the "free theorem" concept to classes and instances correct?
Classes don't have types, so I'm not sure what you mean by including classes. Generalizing to instances makes sense; type class instances are just composed of a list of functions. However, again, this notion of there sometimes being only one possible implementation of a particular type has nothing to do with the concept of "free theorems". (At least, it has not much to do with it that I am aware of.)

Brent Yorgey wrote:
"free theorem" will be of the form
"Any function f of type T, *no matter how f is implemented*, will always satisfy the following property:
blah blah f blah = blah f blah "
This has nothing to do with whether or not there is only one possible implementation of f that does not involve undefined, which is a different phenomenon.
If it hasn't been mentioned, djinn turns type signatures into code, as has been discussed, although if f has multiple implementations, it will simply produce one of them. http://hackage.haskell.org/package/djinn The discussion on ltu helps flesh out the concept: http://lambda-the-ultimate.org/node/1178 This is, of course, as Brent pointed out, very different from free theorems. --S

On Nov 22, 2009, at 10:32 , pbrowne wrote:
On Sat, Nov 21, 2009 at 21:08 Felipe Lessa wrote:
Most definitions, if not all, are just the corresponding free theorems (meaning roughly that the definition follows from the type because that's the only definition that doesn't have undefined's).
Question: Is it correct to paraphrase Felipe's description as follows: In Haskell the *term theorems for free* means roughly that the definition of a class, instance or a function follows from the supplied types because they are the only types that don’t have undefined argumens or undefined return types.
Pretty much. It's not specific to Haskell, either; it's a result of the Curry-Howard correspondence between programs and mathematical proofs. http://homepages.inf.ed.ac.uk/wadler/papers/free/free.ps is the canonical paper on deriving free theorems from Hindley-Milner type systems. -- brandon s. allbery [solaris,freebsd,perl,pugs,haskell] allbery@kf8nh.com system administrator [openafs,heimdal,too many hats] allbery@ece.cmu.edu electrical and computer engineering, carnegie mellon university KF8NH

Hello Philip If you are wanting element-wise addition with two lists, you can do
instance Num a => Num [a] where (+) = zipWith (+) (-) = zipWith (-) (*) = zipWith (*) fromInteger = repeat . fromInteger abs = map abs signum = map signum
Plus as you are representing timestamped values as pairs you would need a Num instance for pairs...
instance (Num a,Num b) => Num (a,b) where (+) (a,b) (x,y) = (a+x,b+y) (-) (a,b) (x,y) = (a-x,b-y) (*) (a,b) (x,y) = (a*x,b*y) fromInteger a = (fromInteger a, fromInteger a) abs (a,b) = (abs a, abs b) signum (a,b) = (signum a, signum b)
But... these instances are somewhat arbitrary, and other people would no doubt disagree with their details: For Num on lists there is the problem of uneven length lists. Also fromInteger has a valid definintion as fromInteger a = a : repeat 0 Hence, there aren't instances in the Hierarchical Libraries. Uneven lists can be solved with Streams - see Ralf Hinze's Streams, but then you move to infinite lists... Oh well. http://hackage.haskell.org/packages/archive/hinze-streams/1.0/doc/html/Data-... As for your question, you can't use a type synonym to define different class instances, you have to use a newtype. Perhaps the best illustration is in Data.Monoid - Numbers have several useful monoids, two of them are: addition (0,+) multiplication (1,*) Data.Monoid uses the Sum newtype wrapper to define the addition monoid and the Product newtype wrapper to define the multiplication monoid. Best wishes Stephen

Hi Stephan,
instance Num a => Num [a] where (+) = zipWith (+) (-) = zipWith (-) (*) = zipWith (*) fromInteger = repeat . fromInteger abs = map abs signum = map signum
Oooh I had no idea you could do that with 'instance' I merge my lists into a list of pairs before I do anything with them so unevenness isn't a problem; I was just trying t convince haskell that I could use nice operators like '+' on my derived type. Thank you very much for your reply; between that and Felipe's I have enough to keep me busy all evening digesting the new toys you have demonstrated :) - Philip

Hi Philip
Aesthetics, taste, sanity, whatever... strongly suggest not doing it of course.
But there is (probably) little harm in trying it.
Best wishes
Stephen
2009/11/21 Philip Scott
Oooh I had no idea you could do that with 'instance'
instance Num a => Num [a] where (+) = zipWith (+) (-) = zipWith (-) (*) = zipWith (*) fromInteger = repeat . fromInteger abs = map abs signum = map signum

Philip,
I merge my lists into a list of pairs before I do anything with them so unevenness isn't a problem; I was just trying t convince haskell that I could use nice operators like '+' on my derived type.
There's another way to use nice operators like '+', in cases where the type you're using it with just doesn't make sense as an instance of Class Num. (I think there's an argument that your [(date,value)] type isn't a number and shouldn't be a Num, but I'm not going to go there.) Every module can have its own definition for each name, such as the operator (+). So in your module (eg. module Main, or module DateValueSeries), you can go ahead and define your own (+). The major caveat is making sure you don't conflict with the default (+), which lives in module Prelude, which is normally automatically brought into scope. So you could do this: -- file DateValueSeries.hs module DateValueSeries where import Prelude hiding ((+)) (+) :: [(Int,Int)] -> [(Int,Int)] -> [(Int,Int)] (+) = addSkip addSkip = ... -- file main.hs import Prelude hiding ((+)) import DateValueSeries dvlist1 = [(0,100)] dvlist2 = ... dvlist3 = dvlist1 + dvlist2 The code is incomplete and untested, of course. The basic idea is that you can use (+) for something that isn't exactly addition (although you're choosing that name because it's clearly related to addition). Unlike the examples using Class Num your (+) has nothing to do with the normal (+); it just has the same name. John

Thanks John,
Every module can have its own definition for each name, such as the operator (+). So in your module (eg. module Main, or module DateValueSeries), you can go ahead and define your own (+). The major caveat is making sure you don't conflict with the default (+), which lives in module Prelude, which is normally automatically brought into scope.
That actually quite nicely solves the problem... it feels almost a little too easy, after spending the evening getting my mind wrapped up with Arrows :) Thank you very much for your help. - Philip

Philip Scott wrote:
Thanks John,
Every module can have its own definition for each name, such as the operator (+). So in your module (eg. module Main, or module DateValueSeries), you can go ahead and define your own (+). The major caveat is making sure you don't conflict with the default (+), which lives in module Prelude, which is normally automatically brought into scope.
That actually quite nicely solves the problem... it feels almost a little too easy, after spending the evening getting my mind wrapped up with Arrows :)
why has no one mentioned: you most likely don't need to understand Arrows? I'm pretty good with Haskell, and Arrows are still somewhat confusing to me. Why? Most problems I've worked with in Haskell have had more-idiomatic solutions than Arrows. (examples include: Monad; Functor; Applicative; just plain functions; plain old lack of type-class abstraction.) It's not so easy or useful to understand any abstraction/class without using at least two or three useful examples/instances of it first. -Isaac

On Sat, Nov 21, 2009 at 05:43:29PM -0500, Isaac Dupree wrote:
why has no one mentioned: you most likely don't need to understand Arrows? I'm pretty good with Haskell, and Arrows are still somewhat confusing to me. Why? Most problems I've worked with in Haskell have had more-idiomatic solutions than Arrows. (examples include: Monad; Functor; Applicative; just plain functions; plain old lack of type-class abstraction.) It's not so easy or useful to understand any abstraction/class without using at least two or three useful examples/instances of it first.
In defence of my solution, I haven't really used the power of the arrows. The "problem" is that the quite useful functions first, second, (***) and (&&&) are defined within Control.Arrow. Cheers, :) -- Felipe.

If you don't yet understand Arrows, then what compels you to conclude that there are more idiomatic solutions (than what you don't yet understand)? Just sayin' Isaac Dupree wrote:
Philip Scott wrote:
Thanks John,
Every module can have its own definition for each name, such as the operator (+). So in your module (eg. module Main, or module DateValueSeries), you can go ahead and define your own (+). The major caveat is making sure you don't conflict with the default (+), which lives in module Prelude, which is normally automatically brought into scope.
That actually quite nicely solves the problem... it feels almost a little too easy, after spending the evening getting my mind wrapped up with Arrows :)
why has no one mentioned: you most likely don't need to understand Arrows? I'm pretty good with Haskell, and Arrows are still somewhat confusing to me. Why? Most problems I've worked with in Haskell have had more-idiomatic solutions than Arrows. (examples include: Monad; Functor; Applicative; just plain functions; plain old lack of type-class abstraction.) It's not so easy or useful to understand any abstraction/class without using at least two or three useful examples/instances of it first.
-Isaac _______________________________________________ Beginners mailing list Beginners@haskell.org http://www.haskell.org/mailman/listinfo/beginners
-- Tony Morris http://tmorris.net/

Sorry to take offense :-) maybe I was being too modest? What leads me to conclude that is... Reading several papers about uses of Arrows and Applicative and Monads for parsing and FRP, being on the mailing-lists for a few years listening to debates and people struggling with bits of code, getting a sense of the history of each abstraction and of how people who use that abstraction daily relate to it. (let's see if I can name names... Ross Paterson, Conor McBride, maybe Simon Peyton-Jones..). Experimenting a bit with my own code. Having a vague sense, through coding Haskell quite a bit, how much it's possible to condense a piece of code. It is not a conclusion of compulsion, just that I haven't seen it done better. It seems Arrows are a necessary abstraction for a couple very particular world-views/paradigms, and don't fit very well with a lot of other stuff. So far, I haven't used FRP for anything major, and I've done most parsing with Parsec (monad-based) and Happy (hmm, it's a preprocessor). Since I don't have lots of experience with the examples, I didn't want to claim to understand the abstraction(class) very well. :-) -Isaac Tony Morris wrote:
If you don't yet understand Arrows, then what compels you to conclude that there are more idiomatic solutions (than what you don't yet understand)? Just sayin'
Isaac Dupree wrote:
Philip Scott wrote:
Thanks John,
Every module can have its own definition for each name, such as the operator (+). So in your module (eg. module Main, or module DateValueSeries), you can go ahead and define your own (+). The major caveat is making sure you don't conflict with the default (+), which lives in module Prelude, which is normally automatically brought into scope. That actually quite nicely solves the problem... it feels almost a little too easy, after spending the evening getting my mind wrapped up with Arrows :) why has no one mentioned: you most likely don't need to understand Arrows? I'm pretty good with Haskell, and Arrows are still somewhat confusing to me. Why? Most problems I've worked with in Haskell have had more-idiomatic solutions than Arrows. (examples include: Monad; Functor; Applicative; just plain functions; plain old lack of type-class abstraction.) It's not so easy or useful to understand any abstraction/class without using at least two or three useful examples/instances of it first.
-Isaac _______________________________________________ Beginners mailing list Beginners@haskell.org http://www.haskell.org/mailman/listinfo/beginners

2009/11/22 Isaac Dupree
Sorry to take offense :-) maybe I was being too modest?
It seems Arrows are a necessary abstraction for a couple very particular world-views/paradigms, and don't fit very well with a lot of other stuff.
Hello All I wouldn't go quite as far as saying Arrows are misfits, but in Isaac's defence, if all you have are pure functions, then arrows are just a wee bit, erm, boring. In Philip's original message he happened to be representing his data as a pair, so second worked fine as a projection/application function, vis: *Arrows> second (\x -> "fish") (10,20) (10,"fish") But of course it doesn't work as a projection/application function for triples (sorry I lack a better term for projection/application): *Arrows> second (\x -> "chips") (10,20,30) <interactive>:1:0: Couldn't match expected type `(t, t1, t2)' against inferred type `(d, b)' In the expression: second (\ x -> "chips") (10, 20, 30) In the definition of `it': it = second (\ x -> "chips") (10, 20, 30) Nor would it work if Philip had defined his own data type. Also for pure functions the derived operators (>>^) and (^>>) become (.), and (<<^) & (^<<) are become reverse composition - which was sometimes called (##) but now seems categorized as (<<<) . The code below is a bit superfluous to the discussion, but it does define the arrow operations for pure functions with the type constructor simplified to (->), I occasionally do the Arrow combinators longhand when I can't remember which Arrow combinator does what. Best wishes Stephen
module ArrowLonghand where
import Control.Arrow
arr :: (b -> c) -> a b c fun_arr :: a b c -> (b -> c) where a = (->)
fun_arr :: (b -> c) -> (b -> c) fun_arr f = f
arr's definition is clearly identity, but specialized to functions
alt_fun_arr :: (b -> c) -> (b -> c) alt_fun_arr = id
first :: a b c -> a (b, d) (c, d) fun_first :: a b c -> a (b,d) (c,d) where a = (->)
fun_first :: (b -> c) -> (b,d) -> (c,d) fun_first f (x,y) = (f x, y)
second :: a b c -> a (d, b) (d, c) fun_second :: a b c -> a (d,b) (d,c) where a = (->)
fun_second :: (b -> c) -> (d,b) -> (d,c) fun_second f (x,y) = (x, f y)
(***) :: a b c -> a b' c' -> a (b, b') (c, c') fun_starstarstar :: a b c -> a b' c' -> a (b,b') (c,c') where a = (->)
fun_starstarstar :: (b -> c) -> (b' -> c') -> (b,b') -> (c,c') fun_starstarstar f g (x,y) = (f x, g y)
Funnily enough, (***) is not unlike prod from Jeremy Gibbons 'Pair Calculus': http://www.comlab.ox.ac.uk/oucl/work/jeremy.gibbons/publications/acmmpc-calc...
prod :: (b -> c) -> (b' -> c') -> (b,b') -> (c,c') prod f g = fork (f . fst, g . snd)
(&&&) :: a b c -> a b c' -> a b (c, c') fun_ampampamp :: a b c -> a b c' -> a b (c,c') where a = (->)
fun_ampampamp :: (b -> c) -> (b -> c') -> b -> (c,c') fun_ampampamp f g x = (f x, g x)
Funnily enough, (&&&) is not unlike fork from the Pair Calculus...
fork :: (b -> c, b -> c') -> b -> (c,c') fork (f,g) a = (f a, g a)
pair_first :: (b -> c) -> (b,d) -> (c,d) pair_first f = f `prod` id
pair_second :: (b -> c) -> (d,b) -> (d,c) pair_second g = id `prod` g
-------------------------------------------------------------------------------- (^>>) :: Arrow a => (b -> c) -> a c d -> a b d
preCompLR :: (b -> c) -> (c -> d) -> (b -> d) preCompLR f g = \x -> g (f x)
(>>^) :: Arrow a => a b c -> (c -> d) -> a b d
postCompLR :: (b -> c) -> (c -> d) -> (b -> d) postCompLR f g = \x -> g (f x)
(^>>) and (>>^) are the same for functions. -- reverse (<<^) :: Arrow a => a c d -> (b -> c) -> a b d
preCompRL :: (c -> d) -> (b -> c) -> (b -> d) preCompRL f g = \x -> f (g x)
(^<<) :: Arrow a => (c -> d) -> a b c -> a b d
postCompRL :: (c -> d) -> (b -> c) -> (b -> d) postCompRL f g = \x -> f (g x)

Stephen Tetley wrote:
2009/11/22 Isaac Dupree
: Sorry to take offense :-) maybe I was being too modest?
It seems Arrows are a necessary abstraction for a couple very particular world-views/paradigms, and don't fit very well with a lot of other stuff.
Hello All
I wouldn't go quite as far as saying Arrows are misfits, but in Isaac's defence, if all you have are pure functions, then arrows are just a wee bit, erm, boring.
:-) there are a few combinators in Arrow that would be nice to have for functions, without even that Arrow generalization, as people have noted now and then. I used to use them sometimes, but then I decided that it was a bit too confusing to the reader to involve a type-class (Arrow) that wasn't very relevant (and not ubiquitously well-known), even if a version with explicit lambdas is a bit longer.
participants (12)
-
Brandon S. Allbery KF8NH
-
Brent Yorgey
-
Chaddaï Fouché
-
Daniel Fischer
-
Felipe Lessa
-
Isaac Dupree
-
John Dorsey
-
pbrowne
-
Philip Scott
-
Stephen Tetley
-
sterl
-
Tony Morris