Re: [Haskell-cafe] do

2007-10-13 Thread Luke Palmer
On 10/13/07, PR Stanley [EMAIL PROTECTED] wrote: Hi do, what's its role? I know a few uses for it but can't quite understand the semantics - e.g. do putStrLn bla bla So, what does do, do? In this example, do doesn't do anything. do doesn't do anything to a single expression (well, I think

Re: [Haskell-cafe] do

2007-10-13 Thread Luke Palmer
Disclaimer: I'm explaining all of this in terms of actions, which are only one way of looking at monads, and the view only works for certain ones (IO, State, ...). Without futher ado... An action does two things: it has a side-effect and then it has a return value. The type IO Int is an I/O

Re: [Haskell-cafe] Pixel plotter

2007-10-14 Thread Luke Palmer
YEEESSS!! W00t11 I've been looking for that for a long time. I get so sick of glut... Thanks. Luke On 10/14/07, Roel van Dijk [EMAIL PROTECTED] wrote: I say someone binds SDL[1]. (If it hasn't been done already.) Ask and you shall receive: http://darcs.haskell.org/~lemmih/hsSDL/ I

Re: [Haskell-cafe] haskell-curry, classical logic, excluded middle

2007-10-14 Thread Luke Palmer
On 10/14/07, Tim Newsham [EMAIL PROTECTED] wrote: I've been struggling with this for the last day and a half. I'm trying to get some exercise with the type system and with logic by playing with the curry-howard correspondence. I got stuck on the excluded-middle, and I think now I got it

Re: [Haskell-cafe] Strange subtract operator behavior - and lazy naturals

2007-10-20 Thread Luke Palmer
On 10/19/07, Yitzchak Gale [EMAIL PROTECTED] wrote: So why not make the laziness available also for cases where 1 - 2 == 0 does _not_ do the right thing? data LazyInteger = IntZero | IntSum Bool Integer LazyInteger or data LazyInteger = LazyInteger Bool Nat I think data LazyInteger

Re: [Haskell-cafe] Type vs TypeClass duality

2007-10-23 Thread Luke Palmer
On 10/23/07, TJ [EMAIL PROTECTED] wrote: What I find strange is, if we can have functions with hidden parameters, why can't we have the same for, say, elements of a list? Suppose that I have a list of type Show a = [a], I imagine that it would not be particularly difficult to have GHC insert

Re: [Haskell-cafe] Disjunctive Normal Form

2007-11-01 Thread Luke Palmer
A good way to approach this is data-structure-driven programming. You want a data structure which represents, and can _only_ represent, propositions in DNF. So: data Term = Pos Var | Neg Var type Conj = [Term] type DNF = [Conj] Then write: dnf :: LS - DNF The inductive definition of dnf is

Re: [Haskell-cafe] Disjunctive Normal Form

2007-11-01 Thread Luke Palmer
On 11/2/07, Luke Palmer [EMAIL PROTECTED] wrote: On 11/1/07, Arnar Birgisson [EMAIL PROTECTED] wrote: dnf :: LS - DNF dnf (Var s) = [[Pos s]] dnf (Or l1 l2) = (dnf l1) ++ (dnf l2) dnf (And l1 l2) = [t1 ++ t2 | t1 - dnf l1, t2 - dnf l2] dnf (Not (Not d)) = dnf d dnf (Not (And l1 l2

Re: [Haskell-cafe] Disjunctive Normal Form

2007-11-01 Thread Luke Palmer
On 11/1/07, Arnar Birgisson [EMAIL PROTECTED] wrote: I'm learning too and found this an interesting problem. Luke, is this similar to what you meant? Heh, your program is almost identical to the one I wrote to make sure I wasn't on crack. :-) data LS = Var String | Not LS | And LS LS | Or LS

Re: [Haskell-cafe] Re: Why can't Haskell be faster?

2007-11-02 Thread Luke Palmer
On 11/2/07, Isaac Gouy [EMAIL PROTECTED] wrote: Ketil Malde wrote: [LOC vs gz as a program complexity metric] Do either of those make sense as a program /complexity/ metric? You're right! We should be using Kolmogorov complexity instead! I'll go write a program to calculate it for the

Re: [Haskell-cafe] Please help from a newby

2007-11-02 Thread Luke Palmer
On 11/2/07, karle [EMAIL PROTECTED] wrote: type Address = Int data Port = C | D deriving(Eq,Show) data Payload = UP[Char] | RTDP(Address,Port) deriving(Eq,Show) data Pkgtype = RTD | U deriving(Eq,Show) type Pkg = (Pkgtype,Address,Payload) type Table = [(Address,Port)]

Re: [Haskell-cafe] Monte Carlo Pi calculation (newbie learnings)

2007-11-05 Thread Luke Palmer
On Nov 5, 2007 1:30 PM, Jonathan Cast [EMAIL PROTECTED] wrote: main = do Get two standard generators (one per dimension) g0 - newStdGen g1 - newStdGen Get an infinite list of pairs let pairs = [ (x, y) | x - randoms (-1, 1) g0, y - randoms (-1, 1) g1

Re: [Haskell-cafe] Strange Type Inference

2007-11-05 Thread Luke Palmer
On Nov 5, 2007 2:37 PM, C.M.Brown [EMAIL PROTECTED] wrote: Hi, I was given a quandary this evening, suppose I have the following code: module Test1 where import qualified Data.Map as Map testFunction :: Ord a = Map.Map a b - Map.Map a b - a - (Maybe b, Maybe b) testFunction m0 m1 k =

Re: [Haskell-cafe] type/class question: toString

2007-11-06 Thread Luke Palmer
I'm assuming you're not fond of the way the print function handles Strings? With GHC you can do this: {-# OPTIONS -fallow-overlapping-instances #-} {-# OPTIONS -fallow-undecidable-instances #-} class Show a = MyShow a where show_ :: a - String instance MyShow String where show_ s =

Re: [Haskell-cafe] Monte Carlo Pi calculation (newbie learnings)

2007-11-06 Thread Luke Palmer
On Nov 5, 2007 8:11 PM, Alex Young [EMAIL PROTECTED] wrote: {--} module Main where import Random import System.Environment import List import Monad randMax = 32767 unitRadius = randMax * randMax rand :: IO Int rand = getStdRandom

Re: [Haskell-cafe] FW: please help... small problem

2007-11-09 Thread Luke Palmer
I'm not sure what you mean by not use auxillary functions. This code is about as compact as it is going to get if you don't want to use library functions. wordToInt is not necessary at all, of course; you could just replace wordToInt everywhere with read, and type inference will figure out the

Re: [Haskell-cafe] can someone explain monad transformers to me, or how do you combine maybe and IO?

2007-11-12 Thread Luke Palmer
On Nov 12, 2007 11:59 PM, Anatoly Yakovenko [EMAIL PROTECTED] wrote: works just like I want it to. But isn't this something that a monad transformer should be able to do? Yes. And I have rewritten MaybeT several times for use in my own projects. We want MaybeT! Luke

Re: [Haskell-cafe] Problems with do notation

2007-11-22 Thread Luke Palmer
On Nov 22, 2007 8:19 AM, Peter Verswyvelen [EMAIL PROTECTED] wrote: worksFine = if True then putStrLn True else putStrLn False This is just an expression, the indentation is inconsequential. worksNOT = do if True then putStrLn True else putStrLn False The first line,

Re: [Haskell-cafe] Re: Composing monads

2007-11-23 Thread Luke Palmer
On Nov 23, 2007 6:24 PM, Jules Bean [EMAIL PROTECTED] wrote: ...i.e. I wouldn't be afraid of a lambda in a case like that. IME it's moderately common to have to do: mapM_ (\a - some stuff something_with a some stuff) ll This has terrible endweight. In this imperativesque case, I'd write:

Re: [Haskell-cafe] been scouring through the Haskell prelude to no avail ...

2007-11-24 Thread Luke Palmer
Word16 from the Data.Word module. Luke On Nov 24, 2007 11:47 PM, Galchin Vasili [EMAIL PROTECTED] wrote: Hello, Is there any predefined datatype that can be used to represent a two byte value? Kind regards, Vasili ___ Haskell-Cafe mailing

Re: [Haskell-cafe] about GADTs on ghci

2007-11-27 Thread Luke Palmer
On Nov 27, 2007 12:57 PM, Yu-Teh Shen [EMAIL PROTECTED] wrote: i have seen the documents in http://www.haskell.org/haskellwiki/Generalised_algebraic_datatype but i can not run the following code on ghci ex: data Term x where K :: Term (a - b - a) S :: Term ((a - b - c) - (a - b)

Re: [Haskell-cafe] St. Petersburg Game

2007-11-27 Thread Luke Palmer
On Nov 27, 2007 1:27 PM, [EMAIL PROTECTED] wrote: Hello, I'm trying to program an implementation of the St. Petersburg game in Haskell. There is a coin toss implied, and the random-number generation is driving me quite mad. So far, I've tried this: Yeah, random number generation is one of

Re: [Haskell-cafe] Hit a wall with the type system

2007-11-28 Thread Luke Palmer
On Nov 29, 2007 4:02 AM, Chris Smith [EMAIL PROTECTED] wrote: I was talking to a few people about this on #haskell, and it was suggested I ask here. I should say that I'm playing around here; don't mistake this for an urgent request or a serious problem. Suppose I wanted to implement

Re: [Haskell-cafe] Hit a wall with the type system

2007-11-28 Thread Luke Palmer
On Nov 29, 2007 4:31 AM, Luke Palmer [EMAIL PROTECTED] wrote: On Nov 29, 2007 4:02 AM, Chris Smith [EMAIL PROTECTED] wrote: I was talking to a few people about this on #haskell, and it was suggested I ask here. I should say that I'm playing around here; don't mistake this for an urgent

Re: [Haskell-cafe] What is the role of $!?

2007-11-28 Thread Luke Palmer
On Nov 29, 2007 4:23 AM, PR Stanley [EMAIL PROTECTED] wrote: PRS: You would also get different results - e.g. let a = 3, b = 7, c = 2 therefore 20 = strict ( ( (a+(b*c)) ) therefore 17 = non-strict ( (a+(b*c)) ) or am I misunderstanding the

Re: [Haskell-cafe] Optimizing cellular automata evaluation (round 2)

2007-11-30 Thread Luke Palmer
On Nov 30, 2007 6:03 PM, Justin Bailey [EMAIL PROTECTED] wrote: On Nov 29, 2007 9:11 PM, Jon Harrop [EMAIL PROTECTED] wrote: Mathematica uses a single arbitrary-precision integer to represent each generation of a 1D automaton. The rules to derive the next generation are compiled into

[Haskell-cafe] Design of a Physics Interface

2007-11-30 Thread Luke Palmer
I'm currently working on idioms for game programming using FRP. After going through several representations of physics as arrows[1] I decided that physics objects must not be implemented as arrows, because introducing new arrows in the middle of a computation[2] leads to ugly pain. So far the

Re: [Haskell-cafe] Rigid type-var unification failure in existentials used with parametrically polymorphic functions

2007-11-30 Thread Luke Palmer
On Nov 30, 2007 12:20 PM, Pablo Nogueira [EMAIL PROTECTED] wrote: A question about existential quantification: Given the existential type: data Box = forall a. B a [...] I cannot type-check the function: mapBox :: forall a b. (a - b) - Box - Box --:: forall a b. (a - b) -

Re: [Haskell-cafe] Design of a Physics Interface

2007-11-30 Thread Luke Palmer
On Nov 30, 2007 7:26 PM, Dan Weston [EMAIL PROTECTED] wrote: There seems to be three salient benefits of using arrows, as I read the Abstract and Introduction of Benjamin Lerner, Arrow Laws and Efficiency in Yampa, 2003, http://zoo.cs.yale.edu/classes/cs490/03-04a/benjamin.lerner/ 1) The

Re: [Haskell-cafe] Re: do

2007-12-04 Thread Luke Palmer
On Dec 4, 2007 11:39 AM, Jules Bean [EMAIL PROTECTED] wrote: Ben Franksen wrote: I don't buy this. As has been noted by others before, IO is a very special case, in that it can't be defined in Haskell itself, and there is no evaluation function runIO :: IO a - a. This is a straw man. Most

Re: [Haskell-cafe] Re: Why is this strict in its arguments?

2007-12-05 Thread Luke Palmer
On Dec 5, 2007 12:16 AM, Aaron Denney [EMAIL PROTECTED] wrote: we (the FPSIG group) defined: data BTree a = Leaf a | Branch (BTree a) a (BTree a) Totally avoiding your question, but I'm curious as to why you deliberately exclude empty trees. Come to think of it, how can you

Re: [Haskell-cafe] Why is this strict in its arguments?

2007-12-05 Thread Luke Palmer
On Dec 5, 2007 11:56 AM, Andrew Coppin [EMAIL PROTECTED] wrote: I was merely noting that questions of the form is X decidable? are usually undecidable. (It's as if God himself wants to tease us...) I take issue with your definition of usually then. Whenever X is decidable is undecidable, 'X is

Re: [Haskell-cafe] Why is this strict in its arguments?

2007-12-05 Thread Luke Palmer
On Dec 5, 2007 12:30 PM, Andrew Coppin [EMAIL PROTECTED] wrote: Luke Palmer wrote: On Dec 5, 2007 11:56 AM, Andrew Coppin [EMAIL PROTECTED] wrote: I was merely noting that questions of the form is X decidable? are usually undecidable. (It's as if God himself wants to tease us...) I

Re: [Haskell-cafe] matching

2007-12-05 Thread Luke Palmer
Just remove that if. What comes after | is already a conditional. Luke On Dec 6, 2007 7:03 AM, Ryan Bloor [EMAIL PROTECTED] wrote: hi I have a matching problem... I am wanting to identify whether or not a string is an opening substring of another (ignoring leading spaces). I have this:

Re: [Haskell-cafe] matching

2007-12-05 Thread Luke Palmer
AM, Luke Palmer [EMAIL PROTECTED] wrote: Just remove that if. What comes after | is already a conditional. Luke On Dec 6, 2007 7:03 AM, Ryan Bloor [EMAIL PROTECTED] wrote: hi I have a matching problem... I am wanting to identify whether or not a string is an opening substring

Re: [Haskell-cafe] Why is this strict in its arguments?

2007-12-06 Thread Luke Palmer
On Dec 6, 2007 9:30 AM, Alistair Bayley [EMAIL PROTECTED] wrote: Use of isNothing and fromJust and a cascade of ifs is generally a poor sign, much better to use case: findAllPath pred (Branch lf r rt) | pred r = case (findAllPath pred lf,findAllPath pred rt) of

Re: [Haskell-cafe] Re: distinguish functions from non-functions in a class/instances

2007-12-07 Thread Luke Palmer
On Dec 7, 2007 6:27 AM, Victor Nazarov [EMAIL PROTECTED] wrote: Cool solution and not so complicated and ad-hoc. But I'd like to ask isn't the following definition is more natural and simple? nary 0 x [] = x nary n f (x:xs) | n 0 = nary (n-1) (f $ read x) xs Sometimes it helps to write type

Re: [Haskell-cafe] Re: distinguish functions from non-functions in a class/instances

2007-12-07 Thread Luke Palmer
On Dec 7, 2007 6:21 PM, Dan Weston [EMAIL PROTECTED] wrote: This is great! Two questions: 1) I want to make sure the function arity matches the list length (as a runtime check). I think I can do this with an arity function using Data.Typeable. I came up with: arity f = a (typeOf f) where

Re: [Haskell-cafe] Re: Re: type class question

2007-12-07 Thread Luke Palmer
On Dec 7, 2007 5:57 PM, Peter Padawitz [EMAIL PROTECTED] wrote: type Block = [Command] data Command = Skip | Assign String IntE | Cond BoolE Block Block | Loop BoolE Block data IntE= IntE Int | Var String | Sub IntE IntE | Sum [IntE] | Prod [IntE] data BoolE = BoolE Bool | Greater

Re: [Haskell-cafe] Re: distinguish functions from non-functions in a class/instances

2007-12-07 Thread Luke Palmer
On Dec 7, 2007 8:39 PM, Dan Weston [EMAIL PROTECTED] wrote: compose f g = f . g compose' f g x = f (g x) Are you saying that these two exactly equivalent functions should have different arity? If not, then is the arity 2 or 3? Prelude :t let compose f g = f . g in compose let

Re: [Haskell-cafe] Re: distinguish functions from non-functions in a class/instances

2007-12-07 Thread Luke Palmer
On Dec 7, 2007 7:57 PM, Luke Palmer [EMAIL PROTECTED] wrote: On Dec 7, 2007 7:41 PM, Dan Weston [EMAIL PROTECTED] wrote: Luke Palmer wrote: You can project the compile time numbers into runtime ones: Yes, that works well if I know a priori what the arity of the function is. But I want

Re: [Haskell-cafe] Re: distinguish functions from non-functions in a class/instances

2007-12-07 Thread Luke Palmer
On Dec 7, 2007 7:41 PM, Dan Weston [EMAIL PROTECTED] wrote: Luke Palmer wrote: You can project the compile time numbers into runtime ones: Yes, that works well if I know a priori what the arity of the function is. But I want to be able to have the compiler deduce the arity of the function

Re: [Haskell-cafe] general

2007-12-08 Thread Luke Palmer
On Dec 8, 2007 7:41 PM, Ryan Bloor [EMAIL PROTECTED] wrote: hi I have a problem. Function A is a function that passes its input into B Function B is a function that does something once. What do you mean by that? B does something once. More details! (Type signatures at least will give

Re: [Haskell-cafe] IO is a bad example for Monads

2007-12-10 Thread Luke Palmer
On Dec 10, 2007 7:09 PM, Wolfgang Jeltsch [EMAIL PROTECTED] wrote: there's the fear that laziness can impact performance, Hmm, tell them that performance isn't all and that laziness helps you to write more modular programs. Nah, in this case I've found it's better to realistically compare

Re: [Haskell-cafe] class default method proposal

2007-12-12 Thread Luke Palmer
On Dec 11, 2007 3:19 PM, David Menendez [EMAIL PROTECTED] wrote: On Dec 11, 2007 9:20 AM, Duncan Coutts [EMAIL PROTECTED] wrote: So my suggestion is that we let classes declare default implementations of methods from super-classes. snip. Does this proposal have any unintended

Re: [Haskell-cafe] Implementing a MUD server in haskell

2007-12-16 Thread Luke Palmer
On Dec 16, 2007 1:45 PM, Jules Bean [EMAIL PROTECTED] wrote: This needs to stand up to concurrent modification of a shared world structure, but I think I'll set up the concurrency controls after I get my head around this.t The simplest way to do this is to bundle all your big shared mutable

Re: [Haskell-cafe] Re: OOP'er with (hopefully) trivial questions.....

2007-12-17 Thread Luke Palmer
There was a thread about this recently. In any case, if you load the code interpreted (which happens if there is no .o or .hi file of the module lying around), then you can look inside all you want. But if it loads compiled, then you only have access to the exported symbols. The reason is

Re: [Haskell-cafe] New to Haskell

2007-12-18 Thread Luke Palmer
On Dec 18, 2007 7:31 AM, Cristian Baboi [EMAIL PROTECTED] wrote: Here is some strange example: module Hugs where aa::Int aa=7 cc:: (Int-Int)-(Int-Int-Int)-Int-(Int-Int) cc a op b = \x- case x of { _ | x==aa - x+1 ; _- a x `op` b } f::Int-Int f(1)=1 f(2)=2 f(_)=3 g::Int-Int

Re: [Haskell-cafe] Knowledge

2007-12-19 Thread Luke Palmer
On Dec 19, 2007 7:26 PM, jlw501 [EMAIL PROTECTED] wrote: I'm new to functional programming and Haskell and I love its expressive ability! I've been trying to formalize the following function for time. Given people and a piece of information, can all people know the same thing? Anyway, this is

Re: [Haskell-cafe] New to Haskell

2007-12-19 Thread Luke Palmer
On Dec 20, 2007 1:23 AM, Jake McArthur [EMAIL PROTECTED] wrote: On Dec 19, 2007, at 6:25 PM, John Meacham wrote: On Tue, Dec 18, 2007 at 01:58:00PM +0300, Miguel Mitrofanov wrote: I just want the sistem to be able to print one of these expressions ! Its this too much to ask ? Yes,

Re: [Haskell-cafe] type trickery

2007-12-20 Thread Luke Palmer
On Dec 20, 2007 9:34 AM, Adrian Neumann [EMAIL PROTECTED] wrote: Hello haskell-cafe! After making data Number = Zero | Succ Number an instance of Integral, I wondered how I could do the same with galois fields. So starting with Z mod p, I figured I'd need something like this data GF = GF

Re: [Haskell-cafe] Smart Constructor Puzzle

2007-12-20 Thread Luke Palmer
On Dec 21, 2007 4:39 AM, Ronald Guida [EMAIL PROTECTED] wrote: Finally, I tried to define vecLength, but I am getting an error. vecLength :: (Peano s) = Vec s t - Int vecLength _ = pToInt (pGetValue :: s) The s in (pGetValue :: s) is different from the s in (Peano s). Use the scoped type

Re: [Haskell-cafe] Why does this blow the stack?

2007-12-22 Thread Luke Palmer
On Dec 22, 2007 12:06 AM, Stefan O'Rear [EMAIL PROTECTED] The explicit loop you're talking about is: enumDeltaInteger :: Integer - Integer - [Integer] enumDeltaInteger x d = x : enumDeltaInteger (x+d) d That code isn't very complicated, and I would hope to be able to write code

Re: [Haskell-cafe] Re: Wikipedia on first-class object

2007-12-28 Thread Luke Palmer
On Dec 28, 2007 5:58 AM, Cristian Baboi [EMAIL PROTECTED] wrote: Here is how I want print to be in Haskell print :: (a-b) - (a-b) with print = id, but the following side effect: - I want to call the print function today, and get the value tomorrow. You might be interested in the standard

Re: [Haskell-cafe] what does @ mean?.....

2007-12-28 Thread Luke Palmer
On Dec 28, 2007 9:35 AM, Jules Bean [EMAIL PROTECTED] wrote: In particular, adding sharing can stop something being GCed, which can convert an algorithm which runs in linear time and constant space to one which runs in linear space (and therefore, perhaps, quadratic time). I've heard of this

Re: [Haskell-cafe] Doing some things right

2007-12-28 Thread Luke Palmer
On Dec 28, 2007 2:55 PM, Miguel Mitrofanov [EMAIL PROTECTED] wrote: I thought Lisp and Erlang were both infinitely more popular and better known. Certainly not infinitely. Lisp isn't entirely functional, and while Erlang is an industrial success story, I think Haskell is seeing a

Re: [Haskell-cafe] Doing some things right

2007-12-29 Thread Luke Palmer
On Dec 29, 2007 10:32 AM, Andrew Coppin [EMAIL PROTECTED] wrote: Luke Palmer wrote: OO is orthogonal to functional. Erlang is pure functional, Lisp is a bastard child... 1. Wasn't Lisp here first? (I mean, from what I've read, Lisp is so old it almost predates electricity...) Before

Re: [Haskell-cafe] Sending bottom to his room

2007-12-29 Thread Luke Palmer
On Dec 29, 2007 11:14 AM, Cristian Baboi [EMAIL PROTECTED] wrote: In The Implementation of Functional Programming Languages by S.P. Jones, section 2.5.3, page 32 it is written: Eval [[*]] a b = a x b Eval [[*]] _|_ b = _|_ Eval [[*]] a _|_ = _|_ but in section 2.5.2 it is said that _|_ is

Re: [Haskell-cafe] More newbie typeclass confusion...

2007-12-29 Thread Luke Palmer
On Dec 30, 2007 3:43 AM, Jonathan Cast [EMAIL PROTECTED] wrote: On 29 Dec 2007, at 9:31 PM, alex wrote: Hi there. If someone can tell me why I am getting type ambiguity in the following code: class (Ord s, Num s) = Scalar s where zero :: s class Metric m where

Re: [Haskell-cafe] Re: Web server (Was: Basic question concerning data constructors)

2007-12-31 Thread Luke Palmer
On Dec 30, 2007 6:24 PM, Joost Behrends [EMAIL PROTECTED] wrote: I've already browsed through the docomentation of all that. Sorry, but i will not use WASH. I like things to be direct, to write p { ... } or similar things instead of p ... /p is worsening things for me. Haskell is not a good

Re: [Haskell-cafe] Basic question concerning data constructors

2008-01-01 Thread Luke Palmer
On Jan 1, 2008 3:43 PM, Yitzchak Gale [EMAIL PROTECTED] wrote: The classical definition of general recursive function refers to functions in Integer - Integer to begin with, so there can only be countably many values by construction. Except that there are uncountably many (2^Aleph_0)

Re: [Haskell-cafe] confusion about 'instance'....

2008-01-10 Thread Luke Palmer
On Jan 10, 2008 1:03 PM, Nicholls, Mark [EMAIL PROTECTED] wrote: Should be straight forwardsimplest example is... class A a data D = D1 instance A D fine.D is declared to be a member of type class A what about. class A a type T = (forall x.Num x=x) instance A T

Re: [Haskell-cafe] confusion about 'instance'....

2008-01-10 Thread Luke Palmer
On Jan 10, 2008 1:25 PM, Nicholls, Mark [EMAIL PROTECTED] wrote: Thanks for your response, I think you helped me on one of my previous abberations. Hmmmthis all slightly does my head inon one hand we have typesthen type classes (which appear to be a relation defined on

Re: Re[2]: [Haskell-cafe] confusion about 'instance'....

2008-01-10 Thread Luke Palmer
On Jan 10, 2008 2:04 PM, Nicholls, Mark [EMAIL PROTECTED] wrote: I can translate OO into mathematical logic pretty easily, I was trying to do the same thing (informally of course) with Haskellbut things are not quite what they appearnot because of some OO hang up (which I probably have

Re: Re[2]: [Haskell-cafe] confusion about 'instance'....

2008-01-10 Thread Luke Palmer
On Jan 10, 2008 1:36 PM, Bulat Ziganshin [EMAIL PROTECTED] wrote: Hello Mark, Thursday, January 10, 2008, 4:25:20 PM, you wrote: instance Num a = A a Mean the same thing as instance A (forall a.Num a=a) programmers going from OOP world always forget that classes in Haskell doesn't

[Haskell-cafe] \_ - not equivalent to const $

2008-01-10 Thread Luke Palmer
In attempting to devise a variant of cycle which did not keep its argument alive (for the purpose of cycle [1::Int..]), I came across this peculiar behavior: import Debug.Trace cycle' :: (a - [b]) - [b] cycle' xs = xs undefined ++ cycle' xs take 20 $ cycle' (const $ 1:2:3:4:trace x 5:[])

Re: [Haskell-cafe] \_ - not equivalent to const $

2008-01-10 Thread Luke Palmer
On Jan 10, 2008 11:11 PM, Felipe Lessa [EMAIL PROTECTED] wrote: On Jan 10, 2008 8:54 PM, Luke Palmer [EMAIL PROTECTED] wrote: Can someone explain what the heck is going on here? AFAICT, nothing is wrong. You see, both returned the very same values. What you saw was in fact the problem

Re: [Haskell-cafe] \_ - not equivalent to const $

2008-01-10 Thread Luke Palmer
On Jan 10, 2008 11:15 PM, Victor Nazarov [EMAIL PROTECTED] wrote: On Jan 11, 2008 2:11 AM, Felipe Lessa [EMAIL PROTECTED] wrote: On Jan 10, 2008 8:54 PM, Luke Palmer [EMAIL PROTECTED] wrote: Can someone explain what the heck is going on here? AFAICT, nothing is wrong. You see, both

Re: [Haskell-cafe] Re: Why purely in haskell?

2008-01-10 Thread Luke Palmer
On Jan 11, 2008 12:09 AM, [EMAIL PROTECTED] wrote: 1. Indirect black holes that are not expressible in a strict language. You generally have to be doing something bizarre for this to occur, and it doesn't take too long before you can accurately predict when they constitute a likely risk.

Re: [Haskell-cafe] Re: Why purely in haskell?

2008-01-11 Thread Luke Palmer
On Jan 11, 2008 9:27 AM, Wolfgang Jeltsch [EMAIL PROTECTED] wrote: However, the fact that (0 / 0) == (0 / 0) yields False is quite shocking. It doesn't adhere to any meaningful axiom set for Eq. So I think that this behavior should be changed. Think of a set implementation which uses (==) to

Re: [Haskell-cafe] type questions again....

2008-01-11 Thread Luke Palmer
2008/1/11 Nicholls, Mark [EMAIL PROTECTED]: Can someone explain (in simple terms) what is meant by existential and universal types. Preferably illustrating it in terms of logic rather than lambda calculus. Well, I don't know about logic. While they are certainly related to existential and

Re: [Haskell-cafe] type questions again....

2008-01-11 Thread Luke Palmer
On Jan 11, 2008 5:47 PM, Nicholls, Mark [EMAIL PROTECTED] wrote: If you wrap an existential type up in a constructor, not much changes: If you wrap a what?should this read existential or universal? Whoops, right, universal. newtype ID = ID (forall a. a - a) ID can hold any value

Re: [Haskell-cafe] Re: Not to load Prelude

2008-01-11 Thread Luke Palmer
On Jan 11, 2008 8:13 PM, Jeremy Shaw [EMAIL PROTECTED] wrote: At Thu, 10 Jan 2008 22:16:27 -0200, Maurí­cio wrote: I tried google and ghc homepage, but could not find elsewhere :) Can you give me a link or somewhere to start from? No. What I meant to say was, I'm not really sure myself,

Re: [Haskell-cafe] Solving a geometry problem with Haskell

2008-01-12 Thread Luke Palmer
On Jan 12, 2008 9:19 PM, Rafael Almeida [EMAIL PROTECTED] wrote: After some profiling I found out that about 94% of the execution time is spent in the ``isPerfectSquare'' function. That function is quite inefficient for large numbers. You might try something like this: isPerfectSquare n =

Re: [Haskell-cafe] Solving a geometry problem with Haskell

2008-01-12 Thread Luke Palmer
speed boost. Luke On Jan 12, 2008 9:48 PM, Luke Palmer [EMAIL PROTECTED] wrote: On Jan 12, 2008 9:19 PM, Rafael Almeida [EMAIL PROTECTED] wrote: After some profiling I found out that about 94% of the execution time is spent in the ``isPerfectSquare'' function. That function is quite

Re: [Haskell-cafe] [newbie question] Memoization automatic in Haskell?

2008-01-12 Thread Luke Palmer
On Jan 12, 2008 11:30 PM, David Benbennick [EMAIL PROTECTED] wrote: On 1/12/08, Henning Thielemann [EMAIL PROTECTED] wrote: Caching is not the default, but you can easily code this by yourself: Define an array and initialize it with all function values. Because of lazy evaluation the

Re: [Haskell-cafe] the trivial monad- thoughts and a question

2008-01-12 Thread Luke Palmer
On Jan 13, 2008 12:47 AM, Brian Hurt [EMAIL PROTECTED] wrote: So, I've been playing around with what I call the trivial monad: module TrivialMonad where data TrivialMonad a = M a Better to use newtype here; then it really is operationally equivalent to using just a, except that it's possible

Re: [Haskell-cafe] Comments and suggestions on code

2008-01-12 Thread Luke Palmer
On Jan 13, 2008 12:42 AM, Andre Nathan [EMAIL PROTECTED] wrote: On Sat, 2008-01-12 at 16:00 -0800, Jonathan Cast wrote: Wait, the last entry? If you're just printing out the values, then no --- those should have been garbage collected already. Won't they be garbage collected only after the

Re: [Haskell-cafe] Parsec monad transformer with IO?

2010-03-18 Thread Luke Palmer
On Thu, Mar 18, 2010 at 10:37 AM, Stefan Klinger all-li...@stefan-klinger.de wrote: Hello! Nice, Parsec 3 comes with a monad transformer [1]. So I thought I could use IO as inner monad, and perform IO operations during parsing. But I failed. Monad transformers still bend my mind. My problem:

Re: [Haskell-cafe] Abstraction in data types

2010-03-18 Thread Luke Palmer
On Thu, Mar 18, 2010 at 12:17 PM, John Meacham j...@repetae.net wrote: On Wed, Mar 17, 2010 at 09:20:49PM -0700, Darrin Chandler wrote: data Point    = Cartesian (Cartesian_coord, Cartesian_coord)               | Spherical (Latitude, Longitude) Just a quick unrelated note, though you are

Re: [Haskell-cafe] Are there any female Haskellers?

2010-03-27 Thread Luke Palmer
On Sat, Mar 27, 2010 at 2:22 PM, Peter Verswyvelen bugf...@gmail.com wrote: So the first computer nerd was a women??!!! ;-) ;-) ;-) Yeah, and she was so attractive that the entire male gender spent the next 50 years trying to impress her. Luke On Sat, Mar 27, 2010 at 9:06 PM, John Van Enk

Re: [Haskell-cafe] Re: Are there any female Haskellers?

2010-03-28 Thread Luke Palmer
2010/3/28 Pekka Enberg penb...@cs.helsinki.fi: 2010/3/28 Günther Schmidt gue.schm...@web.de: This is definately a point where we will continue to disagree. I found myself assuming that there are no female haskellers and wanted to verify it by asking for data. So what exactly is off-topic for

[Haskell-cafe] Announce: hothasktags

2010-04-01 Thread Luke Palmer
Hi, I'd like to draw attention to a little script I wrote. I tend to use qualified imports and short names like new and filter. This makes hasktags pretty much useless, since it basically just guesses which one to go to. hothasktags is a reimplementation of hasktags that uses haskell-src-exts

Re: [Haskell-cafe] Re: Hackage accounts and real names

2010-04-05 Thread Luke Palmer
On Mon, Apr 5, 2010 at 9:18 PM, Ertugrul Soeylemez e...@ertes.de wrote: David House dmho...@gmail.com wrote: * Reputation. Using a RealName is the most credible way to build a combined online and RealLife identity. (Some people don't want this, for whatever reasons.) I agree that the

Re: [Haskell-cafe] Announce: hothasktags

2010-04-07 Thread Luke Palmer
On Wed, Apr 7, 2010 at 1:23 AM, Evan Laforge qdun...@gmail.com wrote: On Thu, Apr 1, 2010 at 1:46 PM, Luke Palmer lrpal...@gmail.com wrote: Hi, I'd like to draw attention to a little script I wrote.  I tend to use qualified imports and short names like new and filter.  This makes hasktags

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

2010-04-14 Thread Luke Palmer
On Wed, Apr 14, 2010 at 4:41 AM, rocon...@theorem.ca wrote: As ski noted on #haskell we probably want to extend this to work on Compact types and not just Finite types instance (Compact a, Eq b) = Eq (a - b) where ... For example (Int - Bool) is a perfectly fine Compact set that isn't

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

2010-04-14 Thread Luke Palmer
On Wed, Apr 14, 2010 at 5:13 AM, Luke Palmer lrpal...@gmail.com wrote: On Wed, Apr 14, 2010 at 4:41 AM,  rocon...@theorem.ca wrote: As ski noted on #haskell we probably want to extend this to work on Compact types and not just Finite types instance (Compact a, Eq b) = Eq (a - b) where

Re: [Haskell-cafe] FRP for game programming / artifical life simulation

2010-04-21 Thread Luke Palmer
On Wed, Apr 21, 2010 at 4:47 PM, Ben Christy ben.chri...@gmail.com wrote: I have an interest in both game programming and artificial life. I have recently stumbled on Haskell and would like to take a stab at programming a simple game using FRP such as YAMPA or Reactive but I am stuck. I am not

Re: [Haskell-cafe] I need help getting started

2010-04-24 Thread Luke Palmer
On Sat, Apr 24, 2010 at 10:34 PM, mitch...@kaplan2.com wrote: Hi, I’m just starting to learn, or trying to learn Haskell.  I want to write a function to tell me if a number’s prime.  This is what I’ve got: f x n y = if n=y   then True   else   if gcd x n ==

Re: [Haskell-cafe] singleton types

2010-04-25 Thread Luke Palmer
2010/4/25 Günther Schmidt gue.schm...@web.de: Hello, HaskellDB makes extensive use of Singleton Types, both in its original version and the more recent one where it's using HList instead of the legacy implementation. I wonder if it is possible, not considering feasibility for the moment, to

Re: [Haskell-cafe] Re: Learning about Programming Languages (specifically Haskell)

2010-05-03 Thread Luke Palmer
On Mon, May 3, 2010 at 9:17 AM, Kyle Murphy orc...@gmail.com wrote: Reasons to learn Haskell include: Lazy evaluation can make some kinds of algorithms possible to implement that aren't possible to implement in other languages (without modification to the algorithm). One could say the reverse

Re: [Haskell-cafe] Strict type system allows for a maximum number of programming errors to be caught at compile time.

2010-05-03 Thread Luke Palmer
On Mon, May 3, 2010 at 9:34 AM, Casey Hawthorne cas...@istar.ca wrote: Strict type system allows for a maximum number of programming errors to be caught at compile time. I keep hearing this statement but others would argue that programming errors caught at compile time only form a minor subset

Re: [Haskell-cafe] Strict type system allows for a maximum number of programming errors to be caught at compile time.

2010-05-03 Thread Luke Palmer
On Mon, May 3, 2010 at 11:07 AM, Kyle Murphy orc...@gmail.com wrote: The problem with dynamic typing is that it has a much higher chance of having a subtle error creep into your code that can go undetected for a long period of time. A strong type system forces the code to fail early where it's

Re: [Haskell-cafe] Strict type system allows for a maximum number of programming errors to be caught at compile time.

2010-05-03 Thread Luke Palmer
On Mon, May 3, 2010 at 10:13 PM, Ivan Miljenovic ivan.miljeno...@gmail.com wrote: On 4 May 2010 13:30, Luke Palmer lrpal...@gmail.com wrote: Here is a contrived example of what I am referring to: prefac f 0 = 1 prefac f n = n * f (n-1) fac = (\x - x x) (\x - prefac (x x)) I can't work out

Re: [Haskell-cafe] ANN: has-0.4 Entity based records

2010-05-04 Thread Luke Palmer
On Tue, May 4, 2010 at 10:18 AM, HASHIMOTO, Yusaku nonow...@gmail.com wrote: Hello, I'm pleased to announce the release of my new library, named has, written to aim to ease pain at inconvinience of Haskell's build-in records. Hmm, nice work, looks interesting. With the has, You can reuse

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

2010-05-21 Thread Luke Palmer
2010/5/21 R J rj248...@hotmail.com: I'm trying to prove that (==) is reflexive, symmetric, and transitive over the Bools, given this definition: (==)                       :: Bool - Bool - Bool x == y                     =  (x y) || (not x not y) My question is:  are the proofs below for

Re: [Haskell-cafe] How to Show an Operation?

2010-06-09 Thread Luke Palmer
On Wed, Jun 9, 2010 at 12:33 PM, Martin Drautzburg martin.drautzb...@web.de wrote: So far so good. However my Named things are all functions and I don't see I ever want to map over any of them. But what I'd like to do is use them like ordinary functions as in: f::Named (Int-Int) f x Is

Re: [Haskell-cafe] Thread scheduling

2010-06-10 Thread Luke Palmer
On Thu, Jun 10, 2010 at 11:50 AM, Andrew Coppin andrewcop...@btinternet.com wrote: Control.Concurrent provides the threadDelay function, which allows you to make the current thread sleep until T=now+X. However, I can't find any way of making the current thread sleep until T=X. In other words, I

Re: [Haskell-cafe] Thread scheduling

2010-06-10 Thread Luke Palmer
Say, using System.Time.getClockTime. Luke On Thu, Jun 10, 2010 at 11:31 PM, Luke Palmer lrpal...@gmail.com wrote: On Thu, Jun 10, 2010 at 11:50 AM, Andrew Coppin andrewcop...@btinternet.com wrote: Control.Concurrent provides the threadDelay function, which allows you to make the current

Re: [Haskell-cafe] Re: How to Show an Operation?

2010-06-10 Thread Luke Palmer
On Thu, Jun 10, 2010 at 10:43 PM, Brandon S. Allbery KF8NH allb...@ece.cmu.edu wrote: On Jun 10, 2010, at 17:38 , Martin Drautzburg wrote: instance Applicative Named where   pure x = Named x   (Named s f) * (Named t v) = Named (s ++ ( ++ t ++ )) (f v) Applicative. Need to study that The

  1   2   3   4   5   6   7   >