Re: [Haskell-cafe] on finding abstractions ...

2010-02-14 Thread Alexander Solla
On Feb 14, 2010, at 4:38 AM, Günther Schmidt wrote: I've got a problem, in short my haskell code sucks. While it does work and I do manage to use higher-orderish aspects quite extensively to make my code more concise it still is nowhere abstract, always concrete and thus always with lots o

Re: [Haskell-cafe] Category Theory woes

2010-02-16 Thread Alexander Solla
On Feb 16, 2010, at 9:43 AM, Gregg Reynolds wrote: I've looked through at least a dozen. For neophytes, the best of the bunch BY FAR is Goldblatt, Topoi: the categorial analysis of logic . Don't be put off by the title. He not only explains the stuff, but he explains the problems that mo

Re: [Haskell-cafe] Heterogeneous Data Structures - Nested Pairs and functional references

2010-02-16 Thread Alexander Solla
On Feb 16, 2010, at 12:14 PM, Günther Schmidt wrote: Let's say there was some clever monad ... someMonad = do h1 <- add "twenty" h2 <- add False h3 <- add 16 . modify h2 True and get a ("twenty",(True, 16)) back. And while *in* the monad some a

Re: [Haskell-cafe] Heterogeneous Data Structures - Nested Pairs and functional references

2010-02-16 Thread Alexander Solla
On Feb 16, 2010, at 12:48 PM, Alexander Solla wrote: (Accumulator String)s are (Accumulator value)s for any value. So you can build things like: Sorry, I made a typo. I meant "StringAccumulator String"s are "Accumulator value&

Re: [Haskell-cafe] Heterogeneous Data Structures - Nested Pairs and functional references

2010-02-16 Thread Alexander Solla
On Feb 16, 2010, at 2:11 PM, Stephen Tetley wrote: Your monad looks equivalent to the Identity monad but over a much bigger syntax. What advantages do you get from it being a monad, rather than just a functor? I replied to Stephen, but forgot to include the list. I took the liberty of mak

Re: [Haskell-cafe] Re: Heterogeneous Data Structures - Nested Pairs and functional references

2010-02-18 Thread Alexander Solla
sry for being a bit thick, but how would this code be used? I'm unable to figure out the application yet. Could you give some examples how you use it? Günther So, the type (View view) -- ignoring class instances -- is basically isomorphic to this (slightly simpler) type: data View =

Re: [Haskell-cafe] Category Theory woes

2010-02-18 Thread Alexander Solla
On Feb 18, 2010, at 10:19 AM, Nick Rudnick wrote: Back to the case of open/closed, given we have an idea about sets -- we in most cases are able to derive the concept of two disjunct sets facing each other ourselves, don't we? The only lore missing is just a Bool: Which term fits which ide

Re: [Haskell-cafe] Category Theory woes

2010-02-18 Thread Alexander Solla
On Feb 18, 2010, at 1:28 PM, Hans Aberg wrote: It is a powerful concept. I think of a function closure as what one gets when adding all an expression binds to, though I'm not sure that is why it is called a closure. Its because a monadic morphism into the same type carrying around data i

Re: [Haskell-cafe] Category Theory woes

2010-02-18 Thread Alexander Solla
On Feb 18, 2010, at 2:08 PM, Nick Rudnick wrote: my actual posting was about rename refactoring category theory; closed/open was just presented as an example for suboptimal terminology in maths. But of course, bordered/unbordered would be extended by e.g. «partially bordered» and the same

Re: [Haskell-cafe] Category Theory woes

2010-02-18 Thread Alexander Solla
On Feb 18, 2010, at 4:49 PM, Nick Rudnick wrote: Why does the opposite work well for computing science? Does it? I remember a peer trying to convince me to use "the factory pattern" in a language that supports functors. I told him I would do my task my way, and he could change it later

Re: [Haskell-cafe] Restricted categories

2010-02-20 Thread Alexander Solla
On Feb 20, 2010, at 10:29 AM, Sjoerd Visscher wrote: I don't understand this, as I thought the constraints the error is complaining about is just what withConstraintsOf g should provide. I guess there's something about the Suitable trick that I don't understand, or possibly the type families

Re: [Haskell-cafe] Re: Heterogeneous Data Structures - Nested Pairs and functional references

2010-02-20 Thread Alexander Solla
On Feb 20, 2010, at 10:25 AM, Heinrich Apfelmus wrote: But isn't the line renderXHtml (ConcatView l r) = fold $ renderXHtml (ConcatViews l r) a type error? I'm assuming Data.Foldable.fold :: (Foldable m, Monoid t) => m t -> t being applied to the result type of renderXHtml which is

Re: [Haskell-cafe] Restricted categories

2010-02-20 Thread Alexander Solla
On Feb 20, 2010, at 6:32 PM, Nick Rudnick wrote: A simple example: class Show el=> ExceptionNote el where comment:: Show exception=> exception-> el-> String instance ExceptionNote Int where comment exception refId = show refId ++ ": " ++ show exception Here you don't need to constrain «ex

Re: [Haskell-cafe] Re: Heterogeneous Data Structures - Nested Pairs and functional references

2010-02-25 Thread Alexander Solla
On Feb 24, 2010, at 10:15 AM, Heinrich Apfelmus wrote: Namely, let's assume we are already given a "magic" type constructor |- (so magic that it's not even legal Haskell syntax) with the property that A |- B somehow denotes an expression of type B with free variables of type A .

Re: [Haskell-cafe] Re: [Haskell] Recursive definition of fibonacci with Data.Vector

2010-03-07 Thread Alexander Solla
On Mar 7, 2010, at 12:56 PM, Don Stewart wrote: In fact, infinite vectors make no sense, as far as I can tell -- these are fundamentally bounded structures. Fourier analysis? Functional analysis? Hamel bases in Real analysis? There are lots of infinite dimensional vector spaces out the

Re: [Haskell-cafe] Re: [Haskell] Recursive definition of fibonacci with Data.Vector

2010-03-07 Thread Alexander Solla
On Mar 7, 2010, at 5:22 PM, Don Stewart wrote: Sorry for the overloading, I mean 'vector' in the sense of Data.Vector. Being strict in the length, its unclear to me that you can do much with infinite ones :-) Yeah, fair enough. I studied mathematics, not Haskell's Data.* hierarchy. T

Re: [Haskell-cafe] how to listen on a specific IP using the network library

2010-03-16 Thread Alexander Solla
On Mar 15, 2010, at 12:09 PM, Jeremy Shaw wrote: In happstack we use a really horrible trick involving template haskell where we see if the SockAddrInet6 constructor exists at compile time and conditionally compile different versions of the code that way. But it is really ugly. Maybe a

Re: [Haskell-cafe] How to improve its performance ?

2010-03-17 Thread Alexander Solla
On Mar 17, 2010, at 6:14 PM, Daniel Fischer wrote: I found it surprisingly not-slow (code compiled with -O2, as usual). There are two points where you waste time. I found one big point where time is wasted: in computing the powerset of a list. He's making 2^n elements, and then iterating

Re: [Haskell-cafe] How to improve its performance ?

2010-03-17 Thread Alexander Solla
On Mar 17, 2010, at 8:33 PM, zaxis wrote: `allPairs list = [(x,y) | x <- list, y <- list] ` is not what `combination` does ! let allPairs list = [(x,y) | x <- list, y <- list] allPairs [1,2,3] [(1,1),(1,2),(1,3),(2,1),(2,2),(2,3),(3,1),(3,2),(3,3)] Yeah, I know that. I said so specifi

Re: [Haskell-cafe] Abstraction in data types

2010-03-17 Thread Alexander Solla
I wrote this to Darrin, but didn't CC cafe: On Mar 17, 2010, at 9:20 PM, Darrin Chandler wrote: type Cartesian_coord = Float type Latitude = Float type Longitude = Float data Point = Cartesian (Cartesian_coord, Cartesian_coord) | Spherical (Latitude, Longitude) type Cen

Re: [Haskell-cafe] Abstraction in data types

2010-03-17 Thread Alexander Solla
On Mar 17, 2010, at 9:56 PM, Alexander Solla wrote: But your "spherical" points don't really form a basis in three- space, or even over all of two-space. I'll take this back. Lattitude and longitude is enough to "form a basis" on R^2, by taking a basis fo

Re: [Haskell-cafe] Abstraction in data types

2010-03-17 Thread Alexander Solla
On Mar 17, 2010, at 10:27 PM, Darrin Chandler wrote: Let's go back to your original code: data Point = Cartesian (Cartesian_coord, Cartesian_coord) | Spherical (Latitude, Longitude) type Center = Point type Radius = Float data Shape = Circle Center Radius

Re: [Haskell-cafe] Re: instance Eq (a -> b)

2010-04-14 Thread Alexander Solla
On Apr 14, 2010, at 12:16 PM, Ashley Yakeley wrote: They are distinct Haskell functions, but they represent the same moral function. If you're willing to accept that distinct functions can represent the same "moral function", you should be willing to accept that different "bottoms" repre

[Haskell-cafe] Re: instance Eq (a -> b)

2010-04-14 Thread Alexander Solla
On Apr 14, 2010, at 1:24 PM, Ashley Yakeley wrote: Bottoms should not be considered values. They are failures to calculate values, because your calculation would never terminate (or similar condition). And yet you are trying to recover the semantics of comparing bottoms. ___

Re: [Haskell-cafe] Re: instance Eq (a -> b)

2010-04-14 Thread Alexander Solla
On Apr 14, 2010, at 5:10 PM, Ashley Yakeley wrote: Worse, this rules out values of types that are not Eq. In principle, every type is an instance of Eq, because every type satisfies the identity function. Unfortunately, you can't DERIVE instances in general. As you are finding out... O

Re: [Haskell-cafe] Re: instance Eq (a -> b)

2010-04-15 Thread Alexander Solla
On Apr 15, 2010, at 12:53 AM, rocon...@theorem.ca wrote: I'd call them disrespectful functions, or maybe nowadays I might call them improper functions. The "good" functions are respectful functions or proper functions. There's no need to put these into a different class. The IEEE defined

Re: [Haskell-cafe] Bulk Synchronous Parallel

2010-04-20 Thread Alexander Solla
On Apr 20, 2010, at 11:05 AM, Jason Dusek wrote: Thanks for the link; my ultimate interest, though, is in an architecture that could scale to multiple machines rather than multiple cores with shared memory on a single machine. Has there been any interest and/or progress in making DPH ru

[Haskell-cafe] Build problems (hsp, trhsx, ultimately Happstack)

2010-04-22 Thread Alexander Solla
Consider the following bash session: [ a...@kizaru:~/ ]$ which trhsx /home/ajs/.cabal/bin/trhsx [ a...@kizaru:~/ ]$ trhsx Usage: trhsx [] [ a...@kizaru:~/ ]$ cabal install hsp Resolving dependencies... Configuring hsp-0.4.5... Preprocessing library hsp-0.4.5... Building hsp-0.4.5... ghc: could

Re: [Haskell-cafe] Build problems (hsp, trhsx, ultimately Happstack)

2010-04-26 Thread Alexander Solla
On Apr 23, 2010, at 2:59 PM, Thomas Hartman wrote: So, you might need to -- upgrade hsx -- make sure that the upgraded trhsx executable is the one being executed by cabal install hsx (maybe deleting/temporarily moving other trhsx exes) Unfortunately, this suggestion didn't work out for me. I

Re: [Haskell-cafe] Build problems (hsp, trhsx, ultimately Happstack)

2010-04-26 Thread Alexander Solla
On Apr 26, 2010, at 12:30 PM, Jeremy Shaw wrote: Does trying to install hsp-0.5.1 work any better? I hadn't tried it, since it forces hsx-0.7 to install. But I gave it a shot, and it fails the same way: [ a...@kizaru:~/ ]$ cabal install hsp-0.5.1 Resolving dependencies... Configuring hs

Re: [Haskell-cafe] Build problems (hsp, trhsx, ultimately Happstack)

2010-04-26 Thread Alexander Solla
On Apr 26, 2010, at 1:23 PM, Gregory Collins wrote: Is "$HOME/.cabal/bin" on your $PATH? Argh. I had "~/.cabal/bin" in my $PATH instead of "$HOME/.cabal/bin". I'm still not sure what the semantic difference is in this use case, but one ($HOME) works and the other (~/) doesn't. Thanks

Re: [Haskell-cafe] Build problems (hsp, trhsx, ultimately Happstack)

2010-05-01 Thread Alexander Solla
On Apr 30, 2010, at 11:28 PM, Warren Harris wrote: $ cabal install happstack Resolving dependencies... cabal: cannot configure HJScript-0.5.0. It requires hsx >=0.7.0 For the dependency on hsx >=0.7.0 there are these packages: hsx-0.7.0. However none of them are available. hsx-0.7.0 was excl

Re: [Haskell-cafe] Build problems (hsp, trhsx, ultimately Happstack)

2010-05-01 Thread Alexander Solla
On May 1, 2010, at 10:54 AM, Warren Harris wrote: I think I'll have to wait for Jeremy's update. On the plus side, the comments/source in the tutorial are pretty good to follow the source along as an example, even if you don't compile and run them. I didn't bother installing happstack-tu

Re: [Haskell-cafe] ANNOUNCE: happstack 0.5.0

2010-05-03 Thread Alexander Solla
On May 3, 2010, at 10:57 AM, Jeremy Shaw wrote: - hide IxSet constructor. use ixSet instead. - improved efficiency of gteTLE, getGTE, and getRange - get rid of Dynamic, just use Data.Typeable (internal change) - added deleteIx - Eq and Ord instances for IxSet - removed a

Re: [Haskell-cafe] forall (What does it do)

2010-05-06 Thread Alexander Solla
On May 5, 2010, at 9:52 PM, John Creighton wrote: I've seen forall used in a few places related to Haskell. I know their is a type extension call "explicit forall" but by the way it is documnted in some places, the documentation makes it sound like it does nothing usefull. However on Page 27 o

Re: [Haskell-cafe] Re: GADTs and Scrap your Boilerplate

2010-05-18 Thread Alexander Solla
On May 18, 2010, at 3:27 PM, John Creighton wrote: I looked again at the paper (page 27): Haskell's Overlooked object system. http://homepages.cwi.nl/~ralf/OOHaskell/paper.pdf Is there any particular reason why you like that paper so much? Object orientation is nice, when you're dealing wi

Re: [Haskell-cafe] Re: Proof question -- (==) over Bool

2010-05-22 Thread Alexander Solla
On May 22, 2010, at 1:32 AM, Jon Fairbairn wrote: Since Bool is a type, and all Haskell types include ⊥, you need to add conditions in your proofs to exclude it. Not really. Bottom isn't a value, so much as an expression for computations that don't refer to "real" values. It's close enoug

Re: [Haskell-cafe] Re: Proof question -- (==) over Bool

2010-05-23 Thread Alexander Solla
On May 23, 2010, at 1:35 AM, Jon Fairbairn wrote: It seems to me relevant here, because one of the uses to which one might put the symmetry rule is to replace an expression “e1 == e2” with “e2 == e1”, which can turn a programme that terminates into a programme that does not. I don't see how t

Re: [Haskell-cafe] Re: Proof question -- (==) over Bool

2010-05-24 Thread Alexander Solla
On May 23, 2010, at 2:53 AM, Lennart Augustsson wrote: BTW, the id function works fine on bottom, both from a semantic and implementation point of view. Yes, but only because it doesn't work at all. Consider that calling > id undefined requires evaluating undefined before you can call id.

Re: [Haskell-cafe] Difference between div and /

2010-06-01 Thread Alexander Solla
On Jun 1, 2010, at 12:20 PM, Aaron D. Ball wrote: The underlying object here is a Unix file descriptor, which is just a number. In that sense, stdin is 0, stdout is 1, and stderr is 2, so this would be (0 + 2) (mod 1) = 0 Every integer is 0 (mod 1). __

Re: [Haskell-cafe] ANN: random-fu 0.1.0.0

2010-06-03 Thread Alexander Solla
On Jun 3, 2010, at 6:34 AM, mo...@deepbondi.net wrote: Announcing the 0.1.0.0 release of the "random-fu" library for random number generation[1]. This release hopefully stabilizes the core interfaces (those exported from the base module "Data.Random"). Great work, I'm upgrading now. The on

Re: [Haskell-cafe] ANN: random-fu 0.1.0.0

2010-06-03 Thread Alexander Solla
On Jun 3, 2010, at 4:19 PM, mo...@deepbondi.net wrote: I don't think I understand. My familiarity with probability theory is fairly light. Are you referring to the fact that the PDF of the sum of random variables is the convolution of their PDFs? If so, the sum of random variables can alr

Re: [Haskell-cafe] ANN: random-fu 0.1.0.0

2010-06-03 Thread Alexander Solla
On Jun 3, 2010, at 6:40 PM, mo...@deepbondi.net wrote: If anyone knows a way this could be done while still allowing general functions to be mapped over RVars, I'd love to hear about it. My suspicion though is that it is not possible. It would be a very similar problem to computing the inve

Re: [Haskell-cafe] How to name a mapped function?

2010-06-07 Thread Alexander Solla
On Jun 6, 2010, at 11:22 AM, Martin Drautzburg wrote: If I have a function, say "compute" whose last parameter is some value ... and I create another function, which applies "compute" to a list of values, how would I call this function? computeF is my natural inclination. F is for Functo

Re: [Haskell-cafe] is there a way to prove the equivalence of these two implementations of (Prelude) break function?

2010-06-07 Thread Alexander Solla
On Jun 5, 2010, at 8:10 PM, Thomas Hartman wrote: Is there a way to prove they are identical mathematically? What are the techniques involved? Or to transform one to the other? Typically, the easiest way to prove that functions f g are equivalent is to (1) show that their domains are the sa

Re: [Haskell-cafe] is there a way to prove the equivalence of these two implementations of (Prelude) break function?

2010-06-07 Thread Alexander Solla
On Jun 7, 2010, at 4:10 PM, Alexander Solla wrote: For exposition, I'll do the analysis for the Prelude function. You might note how much like evaluating the function Correction: You might note how much like evaluating the function generating the analys

Re: [Haskell-cafe] is there a way to prove the equivalence of these two implementations of (Prelude) break function?

2010-06-08 Thread Alexander Solla
On Jun 8, 2010, at 2:38 AM, Alberto G. Corona wrote: This is`t a manifestation of the Curry-Howard isomorphism? Yes, basically. If we rephrase the isomorphism as "a proof is a program, the formula it proves is a type for the program" (as Wikipedia states it), we can see the connection.

Re: [Haskell-cafe] Vague: Assembly line process

2010-06-14 Thread Alexander Solla
On Jun 14, 2010, at 4:40 PM, Luke Palmer wrote: So hang on, what is the problem? You have described something like a vague model, but what information are you trying to get? Say, perhaps, a set of possible output lists from a given input list? I think he's trying to construct a production p

Re: [Haskell-cafe] Terminology

2010-06-15 Thread Alexander Solla
On Jun 15, 2010, at 1:42 PM, wren ng thornton wrote: Generally these sorts of things are called homomorphisms. It's a terribly general term, but that's the one I've always seen to describe that pattern. g is a "list homomorphism", if you want to get specific. Equivalently, it is the "li

Re: [Haskell-cafe] Mapping a list of functions

2010-06-17 Thread Alexander Solla
On Jun 17, 2010, at 12:02 PM, Martin Drautzburg wrote: The standard map function applies a single function to a list of arguments. But what if I want to apply a list of functions to a single argument. I can of course write such a function, but I wonder if there is a standard way of doing

Re: [Haskell-cafe] What is Haskell unsuitable for?

2010-06-18 Thread Alexander Solla
On Jun 17, 2010, at 9:44 PM, Michael Snoyman wrote: While we're on the topic, does anyone else get funny looks when they say "monads"? Yes, almost every time. They seem to catch on if I say "monadic" when I mean "able to syntactically transformed so as to be put in a sequence". ___

Re: [Haskell-cafe] The functional-object style seems to be gaining momentum.

2010-06-18 Thread Alexander Solla
On Jun 17, 2010, at 10:47 AM, cas...@istar.ca wrote: The functional-object style seems to be gaining momentum. Is there any way to convert monads into objects, so that beginners have an easier time with the syntax and thus we can attract more people to the language? I think you're a littl

Re: [Haskell-cafe] The functional-object style seems to be gaining momentum.

2010-06-18 Thread Alexander Solla
On Jun 18, 2010, at 2:36 PM, Alexander Solla wrote: Package Number; sub new { my $class = shift; my $self = shift; bless $self, $class; return $self; } sub plus arg { return $self + arg; } sub minus arg { return $self - arg } Syntax errors in my Perl (sorry, the last time I did Perl

Re: [Haskell-cafe] new recursive do notation (ghc 6.12.x) spoils layout

2010-06-20 Thread Alexander Solla
On Jun 21, 2010, at 10:18 AM, John Lask wrote: do rec a <- getChar b <- f c c <- g b putChar c return b I don't particularly care that the only recursive statements are #2,#3 - I just want my nice neat layout back. I have just spent an inordinate amount of time updating cod

Re: [Haskell-cafe] new recursive do notation (ghc 6.12.x) spoils layout

2010-06-20 Thread Alexander Solla
On Jun 20, 2010, at 6:24 PM, Alexander Solla wrote: do a <- getChar let b = c >>= return . f let c = b >>= return . g c >>= putChar b Correction: by your construction, f and g are already in the Kliesli category, so you don't need t

Re: [Haskell-cafe] When the unknown is unknown

2010-06-23 Thread Alexander Solla
On Jun 23, 2010, at 1:50 PM, Martin Drautzburg wrote: I said that a rhythm is a series of Moments (or Beats), each expressed as fractions of a bar. But each Moment also has volume. So I could model rhythm as Pairs of (Moment, Volume). However I certanly do not want to specify both the Mom

Re: [Haskell-cafe] When the unknown is unknown

2010-06-24 Thread Alexander Solla
On Jun 24, 2010, at 11:14 AM, Martin Drautzburg wrote: Another question is: how much past and future knowledge do I need. (I believe the fundamental property of music is that things are ordered). In order to compute Volumes from Moments I can get pretty much away without the past, but com

Re: [Haskell-cafe] Type-Level Programming

2010-06-26 Thread Alexander Solla
On Jun 26, 2010, at 4:33 AM, Andrew Coppin wrote: It's a bit like trying to learn Prolog from somebody who thinks that the difference between first-order and second-order logic is somehow "common knowledge". A first order logic quantifies over values, and a second order logic quantifies

Re: [Haskell-cafe] Type-Level Programming

2010-06-26 Thread Alexander Solla
On Jun 26, 2010, at 11:21 AM, Andrew Coppin wrote: A first order logic quantifies over values, and a second order logic quantifies over values and sets of values (i.e., types, predicates, etc). The latter lets you express things like "For every property P, P x". Notice that this expressi

Re: [Haskell-cafe] Construction of short vectors

2010-06-27 Thread Alexander Solla
On Jun 27, 2010, at 12:29 PM, Alexey Khudyakov wrote: This is of course faster but what I really want is vectors with length parametrized by type. This way I can write generic code. Uniform representation is requirement for that. You're going to need dependent types, or a similar construction

Re: [Haskell-cafe] How easy is it to hire Haskell programmers

2010-07-02 Thread Alexander Solla
On Jul 2, 2010, at 7:08 PM, Ivan Lazar Miljenovic wrote: Knowing about something /= knowing how to use it. I own and have read RWH, but I've never had to use hsc2hs, or Applicative, etc. Applicative is nice. I had to Google for hsc2hs. This is what I get for learning Haskell from the Hask

Re: [Haskell-cafe] bug in ghci ?

2010-07-09 Thread Alexander Solla
On Jul 9, 2010, at 5:46 PM, Kevin Quick wrote: That's probably an interesting assertion that one of the category theorists around here could prove or disprove. ;-) It's not too hard. I don't like thinking about it in terms of category theory, though. It's easier to think about it in ter

Re: [Haskell-cafe] Handling absent maintainers

2010-07-15 Thread Alexander Solla
On Jul 15, 2010, at 6:49 PM, Jason Dagit wrote: Everyone has their own branch of everything they contribute to, listed right on the website? This is inline with another idea I've heard where we'd have a 'stable' hackage and 'unstable/dev' versions. But, how does this work for resolving

Re: [Haskell-cafe] On documentation

2010-07-21 Thread Alexander Solla
On Jul 20, 2010, at 10:28 PM, Richard O'Keefe wrote: What I don't see is "HOW DO I USE THIS STUFF?" I think tutorials are the best way to do that (i.e., example normal forms for the computations the library intends to expose). Perl's package archive (the cpan) traditionally uses a "Synop

Re: [Haskell-cafe] Heavy lift-ing

2010-07-23 Thread Alexander Solla
On Jul 23, 2010, at 4:35 PM, michael rice wrote: Why is it called "lift"-ing? Basically, because mathematicians like enlightening metaphors. It is a mathematical term. A "monadic value" has an "underlying" value. To turn a function that works on the underlying value into one that work

Re: [Haskell-cafe] default function definitions

2010-07-24 Thread Alexander Solla
On Jul 24, 2010, at 10:59 AM, Patrick Browne wrote: class C1 c1 where age :: c1 -> Integer -- add default impl, can this be defined only once at class level? -- Can this function be redefined in a *class* lower down the heirarchy? age(c1) = 1 Yes, but keep in mind that the hierarchy is o

Re: [Haskell-cafe] Suggestions For An Intro To Monads Talk.

2010-08-03 Thread Alexander Solla
On Aug 3, 2010, at 2:51 PM, aditya siram wrote: I am looking for suggestions on how to introduce the concept and its implications. I'd also like to include a section on why monads exist and why we don't really see them outside of Haskell. Start with functors (things that attach values/func

Re: [Haskell-cafe] Why is toRational a method of Real?

2010-08-04 Thread Alexander Solla
On Aug 4, 2010, at 11:30 AM, Omari Norman wrote: Why is toRational a method of Real? I thought that real numbers need not be rational, such as the square root of two. Wouldn't it make more sense to have some sort of Rational typeclass with this method? Thanks. You can't build the real num

Re: [Haskell-cafe] ATs vs FDs

2010-08-14 Thread Alexander Solla
On Aug 14, 2010, at 9:01 AM, Antoine Latter wrote: What's wrong with fun-deps? The associated type synonym syntax is prettier, but I didn't tknow that fun-deps were evil. Do you have any links? They're not "evil", they are "tricky" and can lead to non-termination, inconsistency, etc. ht

Re: [Haskell-cafe] Hackage on Linux

2010-08-24 Thread Alexander Solla
On Aug 22, 2010, at 3:41 AM, Andrew Coppin wrote: It looks as if it's automated for Arch, however. Either that or somebody is spending an absurd amount of time keeping it manually up to date. It probably is automated. There's a tool out there called "cabal2arch", which turns a cabal fil

Re: [Haskell-cafe] On to applicative

2010-08-26 Thread Alexander Solla
On Aug 26, 2010, at 12:34 AM, michael rice wrote: A lot of stuff to get one's head around. Was aware of liftM2, liftM3, etc., but not liftA2, liftA3, etc. liftM and liftA are essentially equivalent (and are both essentially equivalent to fmap) Same for the liftAn = liftMn functions (whe

Re: [Haskell-cafe] On to applicative

2010-08-26 Thread Alexander Solla
On Aug 26, 2010, at 1:29 AM, Alexander Solla wrote: The other function is pure :: (a -> b) -> f (a -> b). It takes a function and lifts it into the functor, without applying it to anything. In other words, given an f :: a -> b, My mistake, though if you got the rest of i

Re: [Haskell-cafe] On to applicative

2010-08-26 Thread Alexander Solla
On Aug 26, 2010, at 9:27 AM, michael rice wrote: Some functions just happen to map to other functions. <$> is flip fmap. f <$> functor = fmap f functor Brent Yorgey's post noted. "map to"? Take as arguments? "maps to" as in "outputs". pure f <*> functor = f <$> functor

Re: [Haskell-cafe] On to applicative

2010-08-31 Thread Alexander Solla
On Aug 31, 2010, at 12:03 PM, michael rice wrote: I tried creating an instance earlier but *Main> :t (->) Int Char :1:1: parse error on input `->' Try: Prelude> :info (->) data (->) a b-- Defined in GHC.Prim If you want type-information about values, use :t. If you want informa

Re: [Haskell-cafe] Projects that could use student contributions?

2010-08-31 Thread Alexander Solla
On Aug 31, 2010, at 1:52 PM, Brent Yorgey wrote: This fall I'll be teaching a half-credit introduction to Haskell to some undergrads. As a final project I am thinking of giving them the option of (instead of developing some program/project of their own) contributing to an existing open-source

Re: [Haskell-cafe] On to applicative

2010-09-02 Thread Alexander Solla
On Sep 2, 2010, at 11:30 AM, michael rice wrote: In each case, what does the notation show:: ... and undefined:: ... accomplish? They're type annotations. show is a function in "many" types: Prelude> :t show show :: (Show a) => a -> String If you want to see the type of a "specific" sh

Re: [Haskell-cafe] Unnecessarily strict implementations

2010-09-02 Thread Alexander Solla
On Sep 2, 2010, at 9:10 AM, Stephen Sinclair wrote: Sorry to go a bit off topic, but I find it funny that I never really noticed you could perform less-than or greater-than comparisons on Bool values. What's the semantic reasoning behind allowing relative comparisons on booleans? In what cont

Re: [Haskell-cafe] Unnecessarily strict implementations

2010-09-03 Thread Alexander Solla
On Sep 2, 2010, at 11:35 PM, Henning Thielemann wrote: But in the lattice example the roles of 0 and 1 are interchangeable, aren't they? Sort of. If you try to interchange the roles of 0 and 1, you are interchanging the roles of the meet and join operations. In short, you are constructi

Re: [Haskell-cafe] help me evangelize haskell.

2010-09-05 Thread Alexander Solla
On Sep 5, 2010, at 7:46 PM, Mathew de Detrich wrote: Another thing you can say is that Perl is a very extreme language in design where as Haskell is more "general". This means the one thing Perl does, it does very well (expressing programming problems in the most concise/short possible way

Re: [Haskell-cafe] Ultra-newbie Question

2010-09-18 Thread Alexander Solla
On Sep 18, 2010, at 12:51 AM, Christopher Tauss wrote: I am a professional programmer with 11 years experience, yet I just do not seem to be able to get the hang of even simple things in Haskell. I am trying to write a function that takes a list and returns the last n elements. Note

Re: [Haskell-cafe] A model theory question

2010-09-26 Thread Alexander Solla
On 09/26/2010 01:32 PM, Patrick Browne wrote: Hi, Below is an assumption (which could be wrong) and two questions. ASSUMPTION 1 Only smaller models can be specified using the sub-class mechanism. For example if we directly make a subclass A => B then every instance of B must also be an instanc

Re: [Haskell-cafe] Coding conventions for Haskell?

2010-09-26 Thread Alexander Solla
On 09/25/2010 02:24 AM, Petr Pudlak wrote: Hi, sometimes I have doubts how to structure my Haskell code - where to break lines, how much to indent, how to name functions and variables etc. Are there any suggested/recommended coding conventions? I searched a bit and I found a few articles and

Re: [Haskell-cafe] A model theory question

2010-09-27 Thread Alexander Solla
On 09/27/2010 12:25 AM, Patrick Browne wrote: Alexander Solla wrote: On 09/26/2010 01:32 PM, Patrick Browne wrote: / Bigger how? Under logical implication and its computational analogue? That is to say, do you want the model to be more SPECIFIC, describing a smaller class of objects more

Re: [Haskell-cafe] A model theory question

2010-09-28 Thread Alexander Solla
On 09/28/2010 03:03 AM, Patrick Browne wrote: I had a look at the types of a and a’. *Main> :t a a :: forall a obj. (Uneditable obj) => a -> obj *Main> :t a' a' :: forall witness a obj. (Refactored obj witness) => Maybe (a -> obj) Could you explain the example a little more. This is going

Re: [Haskell-cafe] Re: Monad instance for partially applied type constructor?

2010-09-29 Thread Alexander Solla
On 09/29/2010 02:15 PM, DavidA wrote: instance Monad (\v -> Vect k (Monomial v)) > Yes, that is exactly what I am trying to say. And since I'm not allowed to say it like that, I was trying to say it using a type synonym parameterised over v instead. Why not: instance Monad ((->) Vect k (M

Re: [Haskell-cafe] Re: Monad instance for partially applied type constructor?

2010-09-29 Thread Alexander Solla
On 09/29/2010 09:13 PM, Alexander Solla wrote: On 09/29/2010 02:15 PM, DavidA wrote: instance Monad (\v -> Vect k (Monomial v)) > Yes, that is exactly what I am trying to say. And since I'm not allowed to say it like that, I was trying to say it using a type synonym parameter

Re: [Haskell-cafe] Ordering vs. Order

2010-10-07 Thread Alexander Solla
On Oct 7, 2010, at 1:02 AM, Christian Sternagel wrote: Hi all, I'm not a native English speaker and recently I was wondering about the two words "order" and "ordering" (the main reason why I write this to the Haskell mailing list, is that the type class "Ordering" does exist). My dicti

Re: [Haskell-cafe] A model theory question

2010-10-07 Thread Alexander Solla
On Sep 30, 2010, at 1:39 AM, Patrick Browne wrote: I think my original question can be rephrased as: Can type classes preserve satisfaction under the the expansion sentences (signature/theory morphisms inducing a model morphism). According to [1] expansion requires further measures (program

Re: [Haskell-cafe] Ordering vs. Order

2010-10-08 Thread Alexander Solla
On Oct 7, 2010, at 1:15 AM, Alexander Solla wrote: For example, a set with three elements can be ordered in three different ways. Six ways. I hate making such basic math mistakes. ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http

Re: [Haskell-cafe] Re: Re-order type

2010-10-09 Thread Alexander Solla
On Oct 9, 2010, at 4:17 PM, André Batista Martins wrote: If i want compose f and f1, i need to do a correct input to f1 from the output of f. So i want one function to convert the output of "f" to input off "f!". In this case, we do f1 fst (snd (t,(t1,t2))) snd (snd (t, (t1,t2)))

[Haskell-cafe] Static computation/inlining

2010-10-10 Thread Alexander Solla
Hi everybody, I'm working on a module that encodes "static" facts about "the real world". For now, I'm working on an ISO 3166 compliant list of countries, country names, and country codes. I've run into a bit of an optimization issue. There is a static bijective correspondence between c

Re: [Haskell-cafe] Client-extensible heterogeneous types

2010-10-12 Thread Alexander Solla
On Oct 12, 2010, at 4:24 AM, Jacek Generowicz wrote: I can't see a Haskell solution which combines both of these orthogonal features without losing the benefits of the type system. (For example, I could create my own, weak, type system with tags to identify the type and maps to do the dispatch.

Re: [Haskell-cafe] Client-extensible heterogeneous types

2010-10-13 Thread Alexander Solla
On Oct 13, 2010, at 2:18 PM, Jacek Generowicz wrote: Is there any particular reason why you want to actually to mirror Python code? I don't want to: I merely have a situation in which an OO solution (not necessarily a good one) immediately springs to mind, while I didn't see any obvious

[Haskell-cafe] ANNOUNCE: Facts

2010-10-13 Thread Alexander Solla
The Facts hierarchy is meant to contain commonly used, relatively static facts about the "real world". The facts are meant to be encoded using relatively simple Haskell constructs. However, we do make some promises: every data type our modules export will have instances of Data, Eq, Ord, Sh

Re: Who is afraid of arrows, was Re: [Haskell-cafe] ANNOUNCE: Haskell XML Toolbox Version 9.0.0

2010-10-14 Thread Alexander Solla
On Oct 11, 2010, at 11:48 AM, Gregory Crosswhite wrote: No, but there is no point in using a formalism that adds complexity without adding functionality. Arrows are more awkward to use than monads because they were intentionally designed to be less powerful than monads in order to cover s

Re: [Haskell-cafe] ANNOUNCE: Facts

2010-10-14 Thread Alexander Solla
On Oct 14, 2010, at 3:00 PM, Henk-Jan van Tuyl wrote: The list of countries is maybe less static then you would think; since last Sunday, the Netherlands Antilles does not exist anymore; instead there are two new countries: Curaçao and St. Maarten [0] Thanks for the update. I'l put it in

Re: [Haskell-cafe] In what language...?

2010-10-15 Thread Alexander Solla
On Oct 15, 2010, at 1:36 PM, Andrew Coppin wrote: Does anybody have any idea which particular dialect of pure math this paper is speaking? (And where I can go read about it...) It's some kind of typed logic with lambda abstraction and some notion of witnessing, using Gertzen (I think!) sty

Re: [Haskell-cafe] In what language...?

2010-10-25 Thread Alexander Solla
On Oct 25, 2010, at 2:10 PM, Andrew Coppin wrote: Hypothesis: The fact that the average Haskeller thinks that this kind of dense cryptic material is "pretty garden-variety" notation possibly explains why normal people think Haskell is scary. Maybe, but the notation is still clearer than mo

Re: [Haskell-cafe] In what language...?

2010-10-25 Thread Alexander Solla
On Oct 25, 2010, at 2:10 PM, Andrew Coppin wrote: Type theory doesn't actually interest me, I just wandered what the hell all the notation means. Sorry for the double email. I recommend "Language , Proof, and Logic", by Barwise and Etchemendy. It doesn't go into type theory (directly).

Re: [Haskell-cafe] In what language...?

2010-10-26 Thread Alexander Solla
On Oct 26, 2010, at 12:43 PM, Andrew Coppin wrote: Propositional logic is quite a simple logic, where the building blocks are atomic formulae and the usual logical connectives. An example of a well-formed formula might be "P → Q". It tends to be the first system taught to undergraduates,

  1   2   3   >