Re: [Haskell-cafe] Postdoctoral Fellowship in Functional Programming

2007-09-26 Thread Bryan Burgers
On 9/26/07, Graham Hutton [EMAIL PROTECTED] wrote:

 Salary  will be  within the  range 25,134  - 32,796  pounds  per year,
 depending  on qualifications  and experience.   The post  is available
 immediately, and will be offered on a fixed-term contract for 3 years.

I don't mean to diminish the seriousness of your message, but why is
the salary range so exact? Couldn't you have just rounded the upper
bound to 32,768 for the sake of readability?

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


Re: [Haskell-cafe] Basic question....

2007-08-17 Thread Bryan Burgers
On 8/17/07, rodrigo.bonifacio [EMAIL PROTECTED] wrote:
 Hi all.

 I want to create the following polymorphic type (EnvItem) that we can apply 
 two functions (envKey and envValue). I tried the following:

  type Key = String

  data EnvItem a = EnvItem (Key, a)

  envKey :: EnvItem (Key, a) - String
  envKey EnvItem (key, value) = key

  envValue :: EnvValue(Key, a) - a
  envValue EnvItem (key, value) = value

 But this is resulting in the error: [Constructor EnvItem must have exactly 
 1 argument in pattern]

 I think this is a very basic problem, but I don't know what is wrong.

 Regards,

 Rodrigo.

In addition to what others have already said, I'd like to point out
that you do not really need a tuple in your data item.

 data EnvItem a = EI Key a

 envKey :: EnvItem a - Key
 envKey (EI key _) = key

 envValue :: EnvValue a - a
 envValue (EI _ value) = value

Also, you made a distinction between 'Key' and 'String', which is
good. But then in 'envKey', you used 'String' in the signature instead
of 'Key'.That's a little confusing, and also should you ever want to
change the representation of 'Key', you would then have to change the
signature of envKey.

Just my two cents,

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


Re: [Haskell-cafe] Question about arrows

2007-08-04 Thread Bryan Burgers
On 8/3/07, Lewis-Sandy, Darrell [EMAIL PROTECTED] wrote:

 Is there a class property of the Control.Arrow class that represents the
 evaluatation of an arrow:

 eval :: (Arrow a)=a b c-b-c


You could always use the ArrowEval class. Granted, it doesn't exist,
so you'd have to write it, but it should serve your purposes.

class ArrowEval a where
  eval :: a b c - b - c

instance ArrowEval (-) where
  eval = ...

instance ArrowEval YourPartial where
  eval = ...


(That's off the cuff, so I probably didn't get the syntax correct.)
Does that fit your problem? But like Mr. Morris said, eval isn't valid
for every arrow, so you can only define instances of ArrowEval where
it is valid.

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


Re: [Haskell-cafe] Maintaining the community

2007-07-18 Thread Bryan Burgers

On 7/18/07, Martin Coxall [EMAIL PROTECTED] wrote:

On 7/18/07, Jon Harrop [EMAIL PROTECTED] wrote:
 On Tuesday 17 July 2007 23:26:08 Hugh Perkins wrote:
  Am I the only person who finds it interesting/worrying that there are few
  to no people in the group who are ex-C# programmers.  I mean, you could
  argue that C# programmers are simply too stupid to do Haskell, but ... you
  know, there is another explanation ;-)

 To understand this, I think you must look at the number of technical users for
 each language. There are a huge number of technical C++ and Java programmers
 but a tiny number of technical C# programmers in comparison. The few
 technical C# programmers are migrating to F# because it is next door and F#
 programmers are better looking.

Most C# programmers are (a) GUI programmers and (b) former VB
programmers. This means they are *guaranteed* to be less attractive
that the average C++ developer. I have proof. But it's too big to be
contained in this margin.

Martin


I heard that Fermat didn't even actually have a proof. You wouldn't be
trying to hoodwink us in the same way, would you? :)

I haven't been paying attention to the subject, but I suppose I should
pipe in now. I really enjoy Haskell. I'm probably like most people
here in that I like learning new languages: I've given Scheme a fair
shot; F# captured my interest for a while, and right now I'm toying
with Erlang. I've tried Python, used Perl for a job, determined after
an hour that PHP wasn't for me, and even looked at Ruby. The list goes
on. (Always, of course, I keep GHC on my computer.) But for work, I
use C#. And I, for one, am looking forward to C#3.0, because it will
be easier to apply my FP experience to problems when FP is the better
way to solve a problem. (You've heard the maxim that when all you have
is a hammer, everything looks like a nail; the flip side of it is that
when you've got a whole tool set including a screwdriver and you see a
screw, but your company only lets you use your hammer, it can be
frustrating to beat on the screw with the hammer.) And since I'm fresh
out of college with no experience, I'm neither in a position to even
suggest a language change in my company, nor do I have the experience
to move to the occassional Scheme or Erlang job opening I see (I don't
know if I've ever seen a Haskell job opening, and I'm guessing if I
did it would get snatched up by a more qualified programmer quite
quickly).

I guess the point being made is that there are a smaller percentage of
attractive programmers in C#; but it looked to me that people were
implying that there are /no/ knowledgeable programmers in C#; and I'd
just like to assert that maybe there are some that don't really have a
choice right now. :)

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


Re: [Haskell-cafe] Help with IO and randomR

2007-07-16 Thread Bryan Burgers

On 7/16/07, Niko Korhonen [EMAIL PROTECTED] wrote:

I'm writing some code to generate a dither (=noise) signal. I'm trying
to generate an infinite series of noise with triangular distribution but
my code hangs into an infinite loop. The problem is that I'm not very
good with Haskell IO yet and I can't figure out how to write this piece
of IO code without it looping infinitely.

So, in short, how do I do this without getting into an infinite loop:

tpdfs :: (Int, Int) - IO [Int]
tpdfs (low, high) = do
  first - getStdRandom (randomR (low, high))
  second - getStdRandom (randomR (low, high))
  let r = (first + second) `div` 2
  rest - tpdfs (low, high)
  return (r : rest)

Caller site:

do
  nums - tpdfs (2, 12)
  let ns = take 7 nums

Niko


I did not look at it long enough to tell you why there is an infinite
loop. However, think about it on a high level with me.

You want a stream of these random numbers (I'm not sure what a
triangular distribution is, but that's okay). To get one of these, you
take two random numbers and perform a combination function (\x y - (x
+ y) `div` 2 ) on them.

So you can lift this from one random numbers to a stream of random
numbers if you have have two streams of random numbers instead of just
two random numbers. zipWith is the function that brings us from one
number to a stream of numbers.

tpdfs range = do
  g - newStdGen   -- get a random generator
  (g1, g2) - return $ split g   -- make two random generators out of it
  return $ zipWith combine (randomRs range g1) (randomRs range g2)
-- get two streams of random numbers, and combine them elementwise.

combine x y = (x + y) `div` 2

Uh, I know that's a very poor explanation, but hopefully it gives you
an alternate way to look at the problem.
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Messing around with types [newbie]

2007-06-21 Thread Bryan Burgers

On 6/21/07, Cristiano Paris [EMAIL PROTECTED] wrote:

Hi,

I'm making my way through Haskell which seems to me one of the languages
with steepest learning curve around.

Now, please consider this snippet:

{-# OPTIONS_GHC -fglasgow-exts #-}
module Main where


class FooOp a b where
  foo :: a - b - IO ()

instance FooOp Int Double where
  foo x y = putStrLn $ (show x) ++  Double  ++ (show y)

partialFoo = foo (10::Int)

bar = partialFoo (5.0::Double)

I hope the indentation looks ok in your email client. I'm experimenting with
currying and typeclasses at the moment.

 If I try to import this in ghci, it works flawlessy. Now, if I remove the
type signature from 10 and 5.0, ghci complaints saying:

example.hs:12:6:
Ambiguous type variable `t' in the constraint:
  `Num t' arising from use of `partialFoo' at example.hs:12:6-19
Probable fix: add a type signature that fixes these type variable(s)

example.hs:12:6:
Ambiguous type variables `t', `t1' in the constraint:
  `FooOp t t1' arising from use of `partialFoo' at example.hs:12:6-19
Probable fix: add a type signature that fixes these type variable(s)

example.hs:12:17:
Ambiguous type variable `t1' in the constraint:
  `Fractional t1'
arising from the literal `5.0' at example.hs:12:17-19
Probable fix: add a type signature that fixes these type variable(s)

I switched off the monomorphism restriction (btw, is this bad? No flame war
please :D) otherwise it'd have complained louder.

Can you explain how to fix the code (if possible) and give some explanation?


Here's a quick transcript of a GHCi session:

Prelude :t 10
10 :: (Num t) = t
Prelude :t 5.0
5.0 :: (Fractional t) = t


From this you can see that 10 is not necessarily an Int, and 5.0 is

not necessarily a Double. So the typechecker does not know, given just
10 and 5.0, which instance of 'foo' to use. But when you explicitly
told the typechecker that 10 is an Int and 5.0 is a Double, then the
type checker was able to choose which instance of 'foo' it should use.

Does that make sense? (I hope it makes sense, and I also hope it is correct!)

And I do not really know how to fix it, maybe somebody else can write
about that.

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


Re: [Haskell-cafe] To yi or not to yi, is this really the question? A plea for a cooperative, ubiquitous, distributed integrated development system.

2007-06-18 Thread Bryan Burgers

On 6/18/07, Pasqualino 'Titto' Assini [EMAIL PROTECTED] wrote:

Having just presented a case for the possible rationality of the irrational
decision of creating an Emacs-like IDE in Haskell, I wonder if we should not
be even more irrational and contemplate the possibility of using Haskell to
create a radically different kind of IDE.

[...]



Up to you now, what is your dream?


I just did a quick read through of your dream and I'm not going to say
either way with it. But I would like to point out, just to make sure
you've considered it, that my dream--or maybe my reality--involves
being able to code without the requirement of a network connection.

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


Re: [Haskell-cafe] Re: [Haskell] Who pays for *.haskell.org machines?

2007-06-13 Thread Bryan Burgers

 is its funding will be reliable? for example, if we don't get money
 from Google in 2008 year?

in irc some time ago i brought up the topic of something like the
freebsd or wikimedia foundations, but for haskell. if you can give me
a secure and trustworthy method of payment, and as a bonus, a tax
receipt (what is known as 501-c-3 status in the US), i will gladly
start writing checks on a yearly basis. i am sure others would join
me.


Similarly, the Perl community has a foundation, and I believe giving
to it is tax-deductible. You could look in to how they do it.

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


Re: [Haskell-cafe] Mathematics in Haskell Re: Why the Prelude must die

2007-04-02 Thread Bryan Burgers

Jacques Carette wrote:

 perhaps i was mistaken in thinking that there is a group of
 math-interested
 haskellers out there discussing, developing, and documenting the area? or
 perhaps that group needs introductory tutorials presenting its work?
 My guess is that there are a number of people waiting in the wings,
 waiting for a critical mass of features to show up before really diving
 in.  See
 http://www.cas.mcmaster.ca/plmms07/
 for my reasons for being both interested and wary).

 Probably the simplest test case is the difficulties that people are
 (still) encountering doing matrix/vector algebra in Haskell.  One either
 quickly encounters efficiency issues (although PArr might help), or
 typing issues (though many tricks are known, but not necessarily
 simple).  Blitz++ and the STL contributed heavily to C++ being taken
 seriously by people in the scientific computation community.  Haskell
 has even more _potential_, but it is definitely unrealised potential.


I am one of those mathematicians waiting in the wings.  Haskell looked
very appealing at first, and the type system seems perfect, especially for
things like multilinear algebra where currying and duality is fundamental.
I too was put off by the Num issues though--strange mixture of sophisticated
category theory and lack of a sensible hierarchy of algebraic objects.

However, I've decided I'm more interested in helping to fix it than wait;
so count me in on an effort to make Haskell more mathematical.  For me that
probably starts with the semigroup/group/ring setup, and good
arbitrary-precision as well as approximate linear algebra support.


I've been watching this thread for quite a while now, and it seems to
me that there is quite a bit of interest in at least working on a new
Prelude. I've also noticed a 'The Other Prelude' page on the wiki
[http://haskell.org/haskellwiki/The_Other_Prelude] and they seem to
have a start on this. So it seems that we should actually start this,
because people will contribute. Can somebody with good Cabal skills
and maybe access to darcs.haskell.org start a new library for people
to start patching?

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


Re: [Haskell-cafe] Unresolved overloading error

2007-03-31 Thread Bryan Burgers

On 3/31/07, Scott Brown [EMAIL PROTECTED] wrote:


It's working now, thank you.
I changed the definition to

 binom n j = div (fac n) ((fac j)*(fac (n - j)))

 bernoulli n p j = fromIntegral(binom n j)*(p ^ j) * ((1 - p)^(n - j))


As a matter of style suggestion, it might make 'binom' more clear if
you use 'div' as an infix operator:


binom n j = (fac n) `div` ( fac j * fac (n - j) )

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


Re: [Haskell-cafe] newbie concatenating monad question

2007-03-24 Thread Bryan Burgers

My idea is to have a monad with a concatenating , so that I can:

bulidStuff = do
  func1
  func2
  func3
  func4



Leandro Penz


I actually did this recently for a project I have been working on.
First, an example:


output label a@(I.Add a1 a2 a3) = do
  comment (show a)
  mov' label eax a1
  add eax a2
  mov a3 eax


My monad in this example has a Writer or a WriterT in it somewhere. I
of course had to include the 'tell' that you mention somewhere, but I
hid it in the 'comment', 'mov', and 'add' functions in an attempt to
make my own personal assembly DSL. Obviously, you would have to either
include 'tell' in your func1, func2, etc., or create wrappers for them
that include a 'tell'.

Just my two cents.

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


Re: [Haskell-cafe] flip fix and iterate (was: Lazy IO and closing of file handles)

2007-03-19 Thread Bryan Burgers

On the topic of 'fix', is there any good tutorial for fix? I searched
google, but mostly came up with pages including things like 'bug fix'.
It's hard for me to get an intuition about it when 'fix' always stack
overflows on me because I don't really know how to use it.
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Recursion

2007-03-06 Thread Bryan Burgers

On 3/6/07, [EMAIL PROTECTED] [EMAIL PROTECTED] wrote:

Does the following code increase the level of recursion
once for each input line or is the recursive construct
converted to an iteration?

Thanks,
Dave Feustel

main :: IO ()
main = do
  line - getLine
  processIt line
  main

processIt   :: String - IO ()
processIt s = do
  print (length s)


Dave,

I would imagine it does not, but I will let somebody more
knowledgeable tell you for sure. My thought, though, is that if this
is your whole code and not a simplified version (eg, one that
terminates on certain input), then you could consider using the
Prelude's 'interact'[1] function, which performs a transformation on
standard input. In your case, the code would simplify to:

main = interact (unlines . map (show . length) . lines)

The unlines/lines combo breaks up the whole input into a list of lines
of input, and the (show . length) is the heart of your 'processIt'
function.

Alternately, you could also use something like:

main = getContents = mapM_ processIt . lines

Which takes everything from standard in, splits it up into lines, and
then performs processIt for each line.

[1] 
http://haskell.org/ghc/docs/latest/html/libraries/base/Prelude.html#v%3Ainteract

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


[Haskell-cafe] Pulling a monad out of a functor

2007-03-05 Thread Bryan Burgers

Haskellers,

Recently, I have come across a couple of situations in which I need to
pull a monad out of a functor so to speak. The first time it was
needed, I didn't think much of it, but the second time started me
thinking whether there is already an existing construct for this. The
type signatures I have in mind are:

pull :: (Monad m, Functor f) = f (m a) - m (f a)
fmapM :: (Monad m, Functor f) = (a - m b) - f a - m (f b)
fmapM f = pull . fmap f

You may notice that these are already defined for the List functor as
'sequence' and 'mapM'. It seems to me that if this were a class, the
implementor would be defining a traversing order by defining pull; in
the list case this traversing sequence is clearly defined as head to
tail.

I am wondering if there is already a construct for this that I am not
aware of (a class, a way to defined it using monads and functors that
I am not aware of, an idiom)? Is this something that frequently
happens for others, or is it a sign a few of my designs have been
flawed recently?

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


Re: [Haskell-cafe] Pulling a monad out of a functor

2007-03-05 Thread Bryan Burgers

http://haskell.org/ghc/dist/current/docs/libraries/base/Data-Traversable.html

pull is sequence, fmapM is mapM (also see the sequenceA, traverse
functions for the more general case of applicative functors vs. monads)


Stefan


Ah yes, thank you! Saying It seems to me that if this were a class, the
implementor would be defining a traversing order by defining pull
should have tipped me off to check out the 'Traversable' class before
asking (but, having probably only seen that class once or twice before
in passing, it was probably too deep in my head for quick retrieval).

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


Re: [Haskell-cafe] Memoisation

2007-02-25 Thread Bryan Burgers

On 2/25/07, Tony Morris [EMAIL PROTECTED] wrote:

I have a backtracking algorithm that I need to memoise with. Rather than
go into the intricacies of the algorithm, I figure (and hope) the
factorial function is trivial enough to point out my problem.

Simply, suppose I wish to calculate the factorial of 10, then later
the factorial of 5. I have already calculated the factorial of 5, but
now I must do it again. I have thought of various ways of preventing
this; perhaps passing an Array in a state monad. I'm wondering if there
is a general solution for this kind of problem.

Thanks for any tips.

--
Tony Morris


You may be able to glean some ideas from a previous discussion at:
http://comments.gmane.org/gmane.comp.lang.haskell.cafe/19623

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


[Haskell-cafe] Summer of Code

2007-02-12 Thread Bryan Burgers

Hello,

Yes, I realize it's mid-February right now and the summer is still
months away, but it's probably not too early to think about the
future.

I am wondering if there are any Summer of Code projects that I would
be able to do for the Haskell community. I will be graduating from my
undergrad program this semester and am hoping to go on to graduate
school in the fall, and I think a good Haskell project would be the
perfect way to spend my transitional summer.

I looked at 
http://hackage.haskell.org/trac/summer-of-code/query?status=newstatus=assignedstatus=reopenedgroup=topictype=proposed-projectorder=priority
to see if there was anything that people already had in mind, but that
page looks old and unkempt (judging by the abundance of
advertisements) so I am not sure which of those are still available or
needed.

So, are there any projects that will need a student for the summer? If
this is not the place to ask, where should I be asking?

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


[Haskell-cafe] It matters how Type Synonyms are defined?

2007-02-02 Thread Bryan Burgers

Today, I was plugging away on a program and I ran into a problem. It
seems that ErrorT can or can not take a type synonym as its monad,
depending on how the type synonym was defined. For example, consider
this GHCi interactive run:


:k Maybe

Maybe :: * - *

let { a :: ErrorT String Maybe Bool; a = undefined }
:t a

a :: ErrorT String Maybe Bool


:k State (Scope VVar)

State (Scope VVar) :: * - *

let { a :: ErrorT String (State (Scope VVar)) Bool; a = undefined }
:t a

a :: ErrorT String (State (Scope VVar)) Bool

ScopeState is defined in a file as:

type ScopeState a = State (Scope VVar) a



:k ScopeState

ScopeState :: * - *

let { a :: ErrorT String ScopeState Bool; a = undefined }


interactive:1:6:
   Type synonym `ScopeState' should have 1 argument, but has been given 0
   In the type signature: a :: ErrorT String ScopeState Bool

Now, I was going to ask something like, How can I define my type
synonym so I can do this, but I figured out while writing this email
that if I define ScopeState a different way:

type ScopeState = State (Scope VVar)



:k ScopeState

ScopeState :: * - *

let { a :: ErrorT String ScopeState Bool; a = undefined }
:t a

a :: ErrorT String ScopeState Bool

So, my new question is: Why does it matter how ScopeState is defined?

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


Re: [Haskell-cafe] Combine list of sorted lists

2006-12-29 Thread Bryan Burgers

 I am not sure how to express f1 with map?  how do I say
 (lambda (ls)
 (map (lambda (x) (list x))
 ls))
 in Haskell?  map ([])  ?

map (:[]), :[] takes a single element and puts it into a list. Some
people refer to this as box


Another way to express f1 with map is:

f1 xs = map (\x - [x]) xs

The (\x - [x]) is a lambda that takes an x and puts it in a list.
This is semantically the same as (\x - x:[]), where (:) puts x at the
front of the empty list ([]). So, this is where Niel gets his method
(:[]) -- ie, just like (\x - x+1) is semantically the same as (+1),
so (\x - x:[]) is semantically the same as (:[]).

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


Re: [Haskell-cafe] constant functions

2006-12-27 Thread Bryan Burgers

I'm trying to learn Haskell and translating some Lisp
functions as exercises.

How would I write a Haskell function named ALWAYS that
behaves like this:

one = always 1
bozo = always clown

 map one [2,3,4,5,6]
[1,1,1,1,1]

 one 62
1

 map bozo [2,3,4,5,6]
[clown,clown ,clown, clown, clown]

 bozo 62
clown

i.e. ALWAYS returns a function with a single parameter
that is ignored, returning instead the value given to
ALWAYS when the function was created.

This is what I've been trying:

always :: (a - a) - a - a
always x = (\y - x)

one = always 1

Michael


First, you want 'one' to take an integer and return 1. So,


one :: Integer - Integer


since one = always 1, then


always 1 :: Integer - Integer


So, 'always' takes an Integer and returns an Integer - Integer


always :: Integer - (Integer - Integer)


But that's the same as


always :: Integer - Integer - Integer


You actually have the implementation correct, you just didn't have the
right type signature.


always first = (\second - first)


Of course, neither of these implementations need to be tied to
Integers; they can be polymorphic. So, we end up with:

always :: a - b - a  -- no reason the second parameter has to be the
same type as the first, so use 'b' instead of 'a'.
always first = (\_ - first)   -- replace 'second' with '_', because
we don't need to bind anything to the second parameter.

Does that makes sense?

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


Re: [Haskell-cafe] Haskell Side Effect

2006-12-20 Thread Bryan Burgers

On 12/20/06, Jason Dagit [EMAIL PROTECTED] wrote:

Am I the only one that doesn't get it?

Jason


No, you are not the only one that doesn't get it.
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] I'd like start with Haskell, but...

2006-12-16 Thread Bryan Burgers

That said, if I was writing a GUI+database thing, which doesn't do a
lot of substantial processing (more just Add/Edit/Delete buttons), I'd
definately use C# over Haskell. Haskell can do this, but you are
walking a relatively new path. On the other hand C# developers do this
day in, day out, and the language is optimised towards it.


I agree with Neil here. I've been working with Haskell for a while and
I wouldn't have the foggiest idea of how to start a GUI / Database
project. After working with C# for about a week, I had a substantial
GUI / Database program going for a company I interned with last
summer. Haskell is good for a lot of things, and I'm sure somebody
someday will show me that Haskell is even great for GUI/Database, but
you should always use the right tool for the job, and for your job,
I'd say C# is the right tool.

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


Re: [Haskell-cafe] Name that function =)

2006-12-12 Thread Bryan Burgers

On 12/12/06, Louis J Scoras [EMAIL PROTECTED] wrote:

I have some IO actions that I want to map over a list of pairs --
these are just directory names and their down-cased versions.  It
wasn't difficult to actually get the right behavior by just doing mapM
twice.

-- putDirs just outputs something like mv fst snd
mapM_ putDirs pairs
mapM_ (uncurry renameFile) pairs

This bothered me though, because I suspected that this could be done
in one pass.  Naively I proceeded to this.

mapM_ (putDirs  (uncurry renameFile)) pairs

Which didn't work.  I thought about it a little more before realizing
that putDirs wouldn't get any parameters this way: I needed some way
to distribute the pair over both operations.  Here's the higher-order
function I needed:

foo h f g i = h (f i) (g i)

which could then be curried and we get:

mapM_ (foo () putDirs $ uncurry renameFile) pairs

Works great.  So my question: is there a established name for foo?
What about foo partially applied to ()?  This was a fun exercise,
but I'd like to use the standard implementations if they exist.


Before we get too far down the obfuscation road, I'd like to offer
what I think is more readable than a liftM2 solution:

  mapM_ (\p - putDirs p  uncurry renameFile p) pairs

I haven't tested it, but I hope that does the same thing. To me, this
explicitely shows what each is doing, moreso than with a point-free
'foo' combinator.

The way my mind worked to get to this solution:

  mapM_ putDirs pairs
  mapM_ (uncurry renameFile) pairs

==

  mapM_ (\p - putDirs p) pairs
  mapM_ (\p - uncurry renameFile p) pairs

==

  mapM_ (\p - putDirs p  uncurry renameFile p) pairs

Is that a reasonable solution?

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


Re: [Haskell-cafe] smallest double eps

2006-09-30 Thread Bryan Burgers

 Hang on, hang on, now I'm getting confused.
 First you asked for the smallest (positive) x such that
1+x /= x
 which is around x=4.5e15.

 1 + 0 /= 0

 0 is smaller than 4.5e15

 So I don't understand this at all...

 But then 0 isn't positive.

Why not?
In any case every positive number nust satisfy the above inequation so what
about 0.1, which is certainly smaller than 4500?


In math, every positive number must satisfy the above inequation, that
is true. But as Chad said, the smallest number in Haskell (at least
according to my GHC, it could be different with different processors,
right?) that satisfies the equation is 2.2e-16.


1 + 2.2e-16 /= 1

True

1 + 2.2e-17 /= 1

False

This is because the Double type only holds so much precision. After
getting small enough, the type just can't hold any more precision, and
the value is essentially 0.


last $ takeWhile (\x - 1 + x /= 1) (iterate (/2) 1)

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


Re: [Haskell-cafe] Re: Numeric type classes

2006-09-12 Thread Bryan Burgers

It seems we are at a point, where we have to define what is a 'number'.
More precisely: Can you tell me the difference between numbers and more
complex mathematical objects? Is a complex number a number? Is a
quaternion a number? Is a residue class a number? We can calculate with
integers modulo some other integer like with integers - is that considered
computation with numbers? Shall we distinguish between matrices of numbers
and matrices of more complex mathematical objects? In signal theory
matrices of polynomials are very common.


My question would be why is it so important to determine what is or
isn't a number? Whether something is a number or not does not
determine what operations and properties it has. Rather, we should try
to determine what is a field, a ring, a group, etc. If we know that
matrices of polynomials form a group, then we can perform the
operations of the group on those objects.

That being said, I'll have to play the other side of the coin: it
would probably be a little bit of a pain to have to define instances
of each data declaration (Integer, Int, Float, Matrix, Complex, etc.)
on each of these seperate classes--especially when being in a certain
class usually implies being in another (ie, the definition of a set
being a field requires that that set is a group, right?) And another
problem I can see is that, for example, the Integers are a group over
addition, and also a group over multiplication; and in my small bit of
thinking about this, it seems that having to keep track of all of this
might get a bit unruly.

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


Re: Re[2]: class [] proposal Re: [Haskell-cafe] One thought: Num to 0 as ? to list?

2006-08-22 Thread Bryan Burgers

On 8/22/06, Bulat Ziganshin [EMAIL PROTECTED] wrote:

what i propose is not full replacement of existing syntax - quite the
contrary it is just a syntax sugar for most frequent cases of using
classes in function signatures. the key idea is that in most cases we
use only one type class for each type variable, and the same type for
each occurrence of type class in the type:

(+) :: Num - Num - Num

[...]

so, while this proposal is rather minor, i think that it is Good thing


I disagree. As a new learner to Haskell, I already have a hard time
keeping Constructors, Types, and Classes straight. I know what they
all are and what they all do, but sometimes I really have to think
hard to remember which is which in a piece of code. What helps my
understanding is that each has a specific place in the type signature
(which I guess includes 'nowhere' regarding constructors). Being able
to put Classes where Types go would just serve to muddle that
understanding.

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


Re: [Haskell-cafe] REALLY simple STRef examples

2006-07-21 Thread Bryan Burgers

On 7/21/06, S C Kuo [EMAIL PROTECTED] wrote:

Not totally relevant to what the discussion has evolved to, but I wrote
a factorial function using STRefs (in the spirit of the Evolution of a
Haskell programmer) and I think it qualifies as a really simple example.
Code follows:

import Data.STRef
import Control.Monad.ST

foreach :: (Monad m) = [a] - (a - m b) - m ()
foreach = flip mapM_
-- Bryn Keller's foreach, but with type restrictions

fac :: (Num a, Enum a) = a - a
fac n   = runST (fac' n)

fac':: (Num a, Enum a) = a - ST s a
fac' n  = dor - newSTRef 1
foreach [1..n] (\x - modifySTRef r (*x))
x - readSTRef r
return x


Forgive me for not understanding, but I was hoping you would explain a
choice you made in your code. Why did you define foreach and then use


foreach [1..n] (\x - modifySTRef r (*x))


Instead of simply using


mapM_ (\x - modifySTRef r (*x)) [1..n]


? I tried it out in GHCi, and it worked fine, and I have seen code
that has been defined as a flip to take advantage of partial
application. But your code doesn't seem to take advantage of partial
application, so why did you define 'foreach' and then use it instead
of using 'mapM_'? I am just curious, and have always been interested
in reasons behind coding style.

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


Re: [Haskell-cafe] do we have something like isDefined or isNull in Haskell?

2006-06-15 Thread Bryan Burgers

On 6/15/06, Vladimir Portnykh [EMAIL PROTECTED] wrote:

Suppose there is a data definition in Haskell:
data MyType = MyType { date :: Double,
   weight   :: Double,
  height:: Double
} deriving (Eq, Ord, Show)

Is it possible to check if the field height, for example, is filled
in(defined)? Can we give default values in Haskell?

Many thanks and sorry fro so sily questions. Vladimir


You could make date, weight, and height Maybe Doubles, then
isDefined = isJust and isNull = isNothing.

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


Re: [Haskell-cafe] do we have something like isDefined or isNull in Haskell?

2006-06-15 Thread Bryan Burgers

Vladimir,

I think you forgot to put Haskell-cafe as a recipient of this email,
so first I'll repost what you wrote.

On 6/15/06, Vladimir Portnykh [EMAIL PROTECTED] wrote:

many thanks. i have the follwoing code:

module MyType (DataContainer(..)) where
import Maybe
data DataContainer =
MyType {
date :: [Maybe Double],
weight ::[Maybe Double],
height ::[Maybe Double]
   }
deriving (Eq, Ord, Show)

myType =  MyType {
date =
[38548,38562,38576,38590,38604,38618,38632,38646,38660,38674],
weight = [],
height = []
}

reportProblem = if isJust (height myType  !! (length (date myType) - 1))
then 0 else 1


it failed to compiled saying No instance for (Num (Maybe Double)) arising
from the literal 38674 .


After reading your code for a while, I still don't know if I quite
understand.  Can you explain exactly what you are trying to do?

My thought is that maybe you just want a list of objects, since you
are indexing height at the same index as date.  Then you just want a
list of the structures that Duncan described.

myObjects = [default {weight = 3.2}, default {weight = 7.9, date=38458},...]

If not, hopefully somebody a little more knowledgable than I can help you.

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


Re: [Haskell-cafe] elementsinlist

2006-06-13 Thread Bryan Burgers

On 6/13/06, Jenny678 [EMAIL PROTECTED] wrote:


Hallo
I search a code for

elements_in_List([1,2],[1,2]).
True
elements_in_List([1,8],[1,2,3,4,8]).
True
elements_in_List([2,1],[1,2]).
True
elements_in_List([1,1],[1]).
False

I have a code
elements_in_List :: Eq a = [a] - [a] - Bool
elements_in_List [] _ = True
elements_in_List _ [] = False
elements_in_List (x:xs) (y:ys)
 | x == y = elements_in_List xs ys
 | True = elements_in_List (x:xs) ys

but it failed at
elements_in_List([2,1],[1,2]).
True

I hope somebody can help me
Please don't use built-in-Functions.

Thanks for Help


I haven't looked too far into this, but how about something like this:

elements_in_list a b = and $ map (\x - element_in_list x b) a
  where element_in_list = ...

Maybe if you don't want to use built-in functions, define your own
'and' as well.

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


[Haskell-cafe] Library Repository?

2006-06-03 Thread Bryan Burgers

Recently, I have seen a few messages to Haskell Cafe (Like Marc
Weber's Is there any url lib? and Ferenc Wagner's LDIF output
library, as well as many replies like oh, you can find that library
at this link...) that have prodded me to ask what I've been wondering
for a long time.

What are the pros and cons of having a library repository for Haskell
libraries.  At current, I'm thinking of Perl's CPAN, which many Perl
experts claim is the most important aspect of Perl (Don't reinvent
the wheel is a common reply at Perlmonks.org), and I believe Ruby has
something similar (RubyGems?).  It seems to me that with the emergence
of Cabal as a standard way to package Haskell libraries, this could be
possible.

Here's a short, non-exhaustive list of pros and cons I came up with.

Pros:
* Localized place to find libraries.  If I want to know if a urllib
exists, I can go to the server and search for 'url' and come up with
relevant libraries.
* Encourages programmers to share their libraries.  If there's a
place to put libraries, I would imagine that some people who have good
libraries lying around might put them there.  Or if they have
something close, they might generalize it into a library and put it
there.

Cons:
* It obviously needs a server, which costs money, and other things
like that cost money.
* Personel.  It would take a bit of initiative to start a project
like this, as well as continued upkeep.  That would either require
some knowledgable volunteers, or, once again, money.

I'd love to hear the thoughts of the community on this.

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