Re: [Haskell-cafe] Comments from OCaml Hacker Brian Hurt

2009-01-19 Thread George Pollard
On Thu, 2009-01-15 at 18:10 -0500, Cale Gibbard wrote:
> My personal preference would be:
> 
> class Monoid m where
>zero :: m
>(++) :: m -> m -> m
> 
> (in the Prelude of course)
> 
>  - Cale

I've tried doing this (and making more widespread use of typeclassed
operations) by writing my own AltPrelude. Unfortunately there is still a
lot of 'unrebindable' syntax (list comprehensions, 'error' forced to
exist in Monad, if-then-else not using nearest Bool, etc) which makes
this hard to achieve.


signature.asc
Description: This is a digitally signed message part
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Re: Haskell and C++ program

2009-01-19 Thread Derek Elkins
On Mon, 2009-01-19 at 22:12 -0500, S. Doaitse Swierstra wrote:
> On 17 jan 2009, at 22:22, Derek Elkins wrote:
> 
> > On Thu, 2009-01-15 at 13:40 +0100, Apfelmus, Heinrich wrote:
> >> Eugene Kirpichov wrote:
> >>> Well, your program is not equivalent to the C++ version, since it
> >>> doesn't bail on incorrect input.
> >>
> >> Oops. That's because my assertion
> >>
> >>   show . read = id
> >>
> >> is wrong. We only have
> >>
> >>   read . show  = id
> >>   show . read <= id  (in the "less defined than" sense)
> >
> > No, you only have
> > read . show = id which often doesn't hold in practice.
> > show . read  
> You do not even have that; the read may remove surplus parentheses  
> which will not be reinserted by the show.
> 
>   Doaitse
> 

My notation is show . read is not less than or equal to id.  That covers
that case.  The particular example I was thinking of was actually simply
whitespace.

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


Re: [Haskell-cafe] Re: Haskell and C++ program

2009-01-19 Thread S. Doaitse Swierstra


On 17 jan 2009, at 22:22, Derek Elkins wrote:


On Thu, 2009-01-15 at 13:40 +0100, Apfelmus, Heinrich wrote:

Eugene Kirpichov wrote:

Well, your program is not equivalent to the C++ version, since it
doesn't bail on incorrect input.


Oops. That's because my assertion

  show . read = id

is wrong. We only have

  read . show  = id
  show . read <= id  (in the "less defined than" sense)


No, you only have
read . show = id which often doesn't hold in practice.
show . read 

You do not even have that; the read may remove surplus parentheses  
which will not be reinserted by the show.


 Doaitse





Assuming the first identity holds, you do of course have show . read .
show = show and this probably holds even in most cases where read .  
show

= id does not hold.


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


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


Re: [Haskell-cafe] Re: Improved documentation for Bool

2009-01-19 Thread ajb

G'day all.

I wrote:


- Intuitionistic logic systems.

- The "truth values" of an arbitrary topos (i.e. the points of the
subobject classifier).


Sorry, I misread the question.  These are _not_ instances of Boolean
(or at least the latter isn't an instance in general).

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


Re: [Haskell-cafe] Re: Improved documentation for Bool

2009-01-19 Thread ajb

G'day all.

Quoting David Menendez :


Are there any instances of Boolean that aren't isomorphic to Bool?


Sure.  Two obvious examples:

- The lattice of subsets of a "universe" set, where "or" is union
"and" is intersection and "not" is complement with respect to the
universe.

- Many-valued logic systems.

- Intuitionistic logic systems.

- The "truth values" of an arbitrary topos (i.e. the points of the
subobject classifier).

Look up "Heyting algebra" for examples.

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


Re: [Haskell-cafe] Re: Improved documentation for Bool

2009-01-19 Thread Dan Piponi
On Mon, Jan 19, 2009 at 6:25 PM, David Menendez  wrote:

> Are there any instances of Boolean that aren't isomorphic to Bool?

a->Bool for any a. I think.

Though I think it should be called GeorgeBoolean otherwise we might
confuse it for something his father might have invented.
--
Dan
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Employment

2009-01-19 Thread Andrew Wagner
> Such a database would help me counter by boss's
> argument that "it's impossible to find and hire Haskell programmers."
>

Err, people actually say such things? And they say _we're_ out of touch with
the real world?
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Re: Improved documentation for Bool

2009-01-19 Thread David Menendez
On Mon, Jan 19, 2009 at 7:22 PM,   wrote:
>
> And perhaps more to the point, "Boolean" is an adjective, not a noun.
> Therefore, it would be better reserved for a typeclass.

There's also John Meacham's Boolean package.



> class (Heyting a) => Boolean a where
>{- the additional axiom that x || not x == top -}

Are there any instances of Boolean that aren't isomorphic to Bool?

(I'm assuming that (||) and (&&) are intended to be idempotent,
commutative, and associative.)

-- 
Dave Menendez 

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


Re: [Haskell-cafe] Employment

2009-01-19 Thread Tom Hawkins
On Mon, Jan 19, 2009 at 3:04 PM, Andrew Coppin
 wrote:
>
> Like many people I'm sure, I'd like to get paid to code stuff in Haskell.
> But I can't begin to imagine how you go about doing that...

At Eaton, we're using Haskell to design automotive control systems
(see http://cufp.galois.com/).  In a 3 month span we went from 98K
lines of Simulink, Matlab, and VisualBasic to 4K lines of Haskell.
The system is now in vehicle testing and is going to production mid
this year.  In addition to tuning control laws and fault monitors,
other fun things we are using Haskell for is to integrate our
environment with an SMT solver for infinite state, bounded model
checking.

Unfortunately, due to economic conditions, all new openings have been
temporarily put on hold.  However, we expect new reqs to open as soon
as conditions improve.  When this happens, it would be nice if we had
a single source to find qualified people.

Maybe the community should consider building a database to help people
who want to write Haskell for a living get in touch with employers who
want to hire them.  Such a database would help me counter by boss's
argument that "it's impossible to find and hire Haskell programmers."

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


[Haskell-cafe] GHCi Memory Leak in Windows Vista

2009-01-19 Thread spam . andir
Hi all!

Environment: Windows Vista + SP1, GHC 6.10.1.

Description: If use ghci.exe and run separate ghc.exe compiler
process, memory leak in ghci occurred.  After exhausting available
memory Vista has no responding.

Steps for reproduce:
1)  After run GHCi, process list has 2 processes: ghci.exe (a), ghc.exe (b),
2)  Then I run separated compilation process 20 times:

Command Line:
for /L %i in (1,1,20) do ghc -fforce-recomp -O --make "problem.hs" -o
"problem.exe"

Sample Haskell Program listing (problem.hs):
main :: IO ()
main = do
print $ [x | x <- [1..]]
putStrLn "Hello, world!"

3)  In process list (taskmgr.exe) I can see some processor
activity and increasing value of "Memory (Private Working Set)" for
process (b).
4)  After run "Memory (Private Working Set)" increased about 100Mb.

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


Re: [Haskell-cafe] know a workaround for greedy context reduction?

2009-01-19 Thread Nicolas Frisby
I revisited the Strongly typed Heterogeneous Lists paper and read
about the import hierarchy technique. The basic idea is to delay
importing the instances until as late as possible, which prevents the
context simplification. The instances are effectively imported in the
top, Main module.

I'm thinking of exporting a MyLibrary.Main or MyLibrary.Instances module.

Anyone have experience with this approach in a library design? Is it
worth the user's extra import? Any pitfalls?

On Sun, Dec 7, 2008 at 4:57 PM, Nicolas Frisby  wrote:
> Seems I got ahead of myself with the bug search. I was thinking bug
> because when I ascribe a type, I expect the compiler to check and then
> respect it. With the "most general type" specification of the ":type"
> command in mind, this does make sense. Thanks for improving my
> internal notion of ":type".
>
> My grumble may seem more legitimate from a library perspective. I
> implement a type-level function Append with three (preferably hidden)
> ancillary classes and a single instance in order to support the
> multiple modalities (in the Mercury sense) of the Append logic
> function. When a user defines another function that uses the append
> method, it's obfuscating for the user to see the internal classes in
> the inferred type. That's what I would like to workaround.
>
> If we consider class C the internal and consider class D and the
> function f the library's exposed interface, then I'd like to see C
> instead of D in the context of f and any function the user defines
> with f, especially when I have supplied a preferred type for f.
>
>> f :: D a => () -> a
>> f () = d
>
>> *> :t f
>> f :: (C a) => () -> a
>
> No dice?
>
> Thanks again,
> Nick
>
> On Sun, Dec 7, 2008 at 2:34 PM, Simon Peyton-Jones
>  wrote:
>> This is perfectly reasonable behavior I'm afraid.  If you do ":info d" 
>> you'll get d's original type signature.  But ":type" takes an *arbitrary 
>> expression* (in this case a single variable 'd', and figures out its most 
>> general type.  You could have said ":t (3*3)" for example.
>>
>> In this case, when inferring the most general type of the expression "d", 
>> GHC tries to simplify the context (D a), and uses the instance declaration 
>> to reduce it to (C a).  And then it can't simplify it further.  But you 
>> *might* have had
>>instance C a
>> somewhere, in which case it'd have been able to simplify the (C a) away.  So 
>> GHC must try that route.  If it fails, you want it to "back up" to a 
>> notationally more convenient type, but GHC can't do that, I'm afraid
>>
>> Simon
>>
>> | -Original Message-
>> | From: haskell-cafe-boun...@haskell.org [mailto:haskell-cafe-
>> | boun...@haskell.org] On Behalf Of Nicolas Frisby
>> | Sent: 06 December 2008 03:23
>> | To: haskell Cafe
>> | Subject: [Haskell-cafe] know a workaround for greedy context reduction?
>> |
>> | With these three declarations
>> |
>> |   {-# LANGUAGE FlexibleInstances #-}
>> |   {-# LANGUAGE UndecidableInstances #-}
>> |
>> |   class C a where c :: a
>> |   class C a => D a where d :: a
>> |   instance C a => D a where d = c
>> |
>> | ghci exhibits this behavior:
>> |
>> |   *> :t d
>> |   d :: (C a) => a
>> |
>> | Where I would prefer "d :: (D a) => a". In my actual examples, the
>> | context is much larger and I can't involve overlapping instances. Is
>> | there a known workaround? I didn't find a related bug on the GHC trac,
>> | and I don't know if other compilers behave in the same way.
>> | ___
>> | Haskell-Cafe mailing list
>> | Haskell-Cafe@haskell.org
>> | http://www.haskell.org/mailman/listinfo/haskell-cafe
>>
>>
>
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] LinuxFest Northwest 2009

2009-01-19 Thread Thomas DuBuisson
I might go - I'll certainly keep an eye on the page.  It would be more
likely if I could find a group driving from Portland.

Tom

On Mon, Jan 19, 2009 at 9:25 PM, Shachaf Ben-Kiki  wrote:
> LFNW 2009 () is going to be at the end of
> April, and I was wondering if anyone here is going to be there, or possibly a
> Haskell-related presentation.
>
> Last year I met ac from #haskell there, but it would be nice if more people
> came, especially with the (relatively) big group in Oregon and such. Perhaps
> someone here has plans already?
>
>Shachaf
> ___
> Haskell-Cafe mailing list
> Haskell-Cafe@haskell.org
> http://www.haskell.org/mailman/listinfo/haskell-cafe
>
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Re: Improved documentation for Bool

2009-01-19 Thread ajb

G'day all.

On Mon, 2009-01-19 at 19:33 +, Andrew Coppin wrote:


My only problem with it is that it's called Bool, while every other
programming language on Earth calls it Boolean. (Or at least, the
languages that *have* a name for it...)


Jonathan Cast commented:


Except C++?


And perhaps more to the point, "Boolean" is an adjective, not a noun.
Therefore, it would be better reserved for a typeclass.

class (PartialOrder a) => JoinSemilattice a where
(||) :: a -> a -> a

class (MeetSemilattice a) => BoundedJoinSemilattice a where
bottom :: a

class (PartialOrder a) => MeetSemilattice a where
(&&) :: a -> a -> a

class (MeetSemilattice a) => BoundedMeetSemilattice a where
top :: a

class (BoundedJoinSemilattice a, BoundedMeetSemilattice a) => Heyting a where
implies :: a -> a -> a

not :: a -> a
not x = x `implies` bottom

class (Heyting a) => Boolean a where
{- the additional axiom that x || not x == top -}

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


Re: [Haskell-cafe] Employment

2009-01-19 Thread Thomas DuBuisson
> Hmm, interesting... So lots happening in Portland, Oregon. Lots in
> Cambridge, MA. A few things in Europe. And nothing at all in the UK...

Nothing in the UK?  Lets not forget MSR and Well-Typed!
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] MonadTrans lift implementation

2009-01-19 Thread ajb

G'day all.

Quoting Jonathan Cast :


(By the way, you *do* have the equations

lift (return x) = return x

[...]

Right.  And you could, at least in principle, implement "return" this
way in all monad transformers.

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


[Haskell-cafe] Current research on overlapping/closed type families?

2009-01-19 Thread Ryan Ingram
What's the status of overlapping/closed type families?  I'm interested
in something like the following, which can currently be implemented in
GHC with Oleg-magic using functional dependencies, but cannot, to my
knowledge, be implemented with type families:

data HTrue = HTrue
data HFalse = HFalse

type family IsFunction f

{- not legal in GHC6.10 -}
type instances
   IsFunction (a -> b) = HTrue
   IsFunction a = HFalse

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


Re: [Haskell-cafe] Re: How to make code least strict?

2009-01-19 Thread Ryan Ingram
Actually, I see a nice pattern here for unamb + pattern matching:

> zip xs ys = foldr unamb undefined [p1 xs ys, p2 xs ys, p3 xs ys] where
> p1 [] _ = []
> p2 _ [] = []
> p3 (x:xs) (y:ys) = (x,y) : zip xs ys

Basically, split each pattern out into a separate function (which by
definition is _|_ if there is no match), then use unamb to combine
them.

The invariant you need to maintain is that potentially overlapping
pattern matches (p1 and p2, here) must return the same result.

With a little typeclass hackery you could turn this into

> zip = unambPatterns [p1,p2,p3] where {- p1, p2, p3 as above -}

Sadly, I believe the performance of "parallel-or"-style operations is
pretty hideous right now.  Conal?

  -- ryan

On Mon, Jan 19, 2009 at 2:42 PM, Conal Elliott  wrote:
> I second Ryan's recommendation of using unamb [1,2,3] to give you unbiased
> (symmetric) laziness.
>
> The zip definition could also be written as
>
> zip xs@(x:xs') ys@(y:ys') =
>   assuming (xs == []) [] `unamb`
>   assuming (ys == []) [] `unamb`
>   (x,y) : zip xs' ys'
>
> The 'assuming' function yields a value if a condition is true and otherwise
> is bottom:
>
> assuming :: Bool -> a -> a
> assuming True  a = a
> assuming False _ = undefined
>
> This zip definition is a special case of the annihilator pattern, so
>
> zip = parAnnihilator (\ (x:xs') (y:ys') -> (x,y) : zip xs' ys') []
>
> where 'parAnnihilator' is defined in Data.Unamb (along with other goodies)
> as follows:
>
> parAnnihilator :: Eq a => (a -> a -> a) -> a -> (a -> a -> a)
> parAnnihilator op ann x y =
>   assuming (x == ann) ann `unamb`
>   assuming (y == ann) ann `unamb`
>   (x `op` y)
>
> [1] http://haskell.org/haskellwiki/Unamb
> [2]
> http://hackage.haskell.org/packages/archive/unamb/latest/doc/html/Data-Unamb.html
> [3] http://conal.net/blog/tag/unamb/
>
>- conal
>
> On Mon, Jan 19, 2009 at 12:27 PM, Ryan Ingram  wrote:
>>
>> On Mon, Jan 19, 2009 at 9:10 AM, ChrisK 
>> wrote:
>> > Consider that the order of pattern matching can matter as well, the
>> > simplest
>> > common case being zip:
>> >
>> > zip xs [] = []
>> > zip [] ys = []
>> > zip (x:xs) (y:ys) = (x,y) : zip xs ys
>>
>> If you are obsessive about least-strictness and performance isn't a
>> giant concern, this seems like a perfect use for Conal's unamb[1]
>> operator.
>>
>> zipR xs [] = []
>> zipR [] ys = []
>> zipR (x:xs) (y:ys) = (x,y) : zip xs ys
>>
>> zipL [] ys = []
>> zipL xs [] = []
>> zipL (x:xs) (y:ys) = (x,y) : zip xs ys
>>
>> zip xs ys = unamb (zipL xs ys) (zipR xs ys)
>>
>> This runs both zipL and zipR in parallel until one of them gives a
>> result; if neither of them is _|_ they are guaranteed to be identical,
>> so we can "unambiguously choose" whichever one gives a result first.
>>
>>  -- ryan
>>
>> [1]
>> http://conal.net/blog/posts/functional-concurrency-with-unambiguous-choice/
>> ___
>> Haskell-Cafe mailing list
>> Haskell-Cafe@haskell.org
>> http://www.haskell.org/mailman/listinfo/haskell-cafe
>
>
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] xhtml + bytestring

2009-01-19 Thread Eugene Kirpichov
I think that your instance is too specific, although useful for the
particular case of escaping.

I've done my own implementation for fun:

concatMap' :: (Word8 -> L.ByteString) -> L.ByteString -> L.ByteString
concatMap' f s = L.unfoldr p x0
where x0 = (LI.Empty, s, 0, 0)
  p (LI.Empty, LI.Empty, _, _) = Nothing
  p (LI.Empty, c@(LI.Chunk s s'), _, ns) | ns==S.length s = p
(LI.Empty, s', 0, 0)
 | otherwise  = p
(f (S.index s ns), c, 0, ns+1)
  p (c@(LI.Chunk s s'), bs, nf, ns) | nf==S.length s = p (s', bs, 0, ns)
| otherwise  = Just
(S.index s nf, (c, bs, nf+1, ns))

It turns out to be both a lot slower (don't know why) and with greater
memory residence (because it's not lazy) than the built-in concatMap
for bytestrings in my synthetic tests. However, it produces a
bytestring with few chunks (due to a good implementation of unfoldr)
in an asymptotically optimal time. I also noticed that for a case like
unescaping, where 'f' produces a small string (5) and the source
bytestring is large (10mln), my version spends 24% in GC whereas the
standard version spends 68%.
A drawback is that the resulting bytestring is not lazy at all.

I wonder how one might optimize it. It looks like a function that a
compiler should optimize very well without my help, although I didn't
read the core etc.

2009/1/20 Joachim Breitner :
> Hi Bjorn, hi list,
>
> the darcswatch instance I'm running is getting quite big, and it
> periodically slows down my server. I managed to get quite an improvement
> with this simple patch to my parsing:
> http://darcs.nomeata.de/cgi-bin/darcsweb.cgi?r=darcswatch;a=commitdiff;h=20090119181919-23c07-140f8deb91a52a423a2984dce2d22f4a48999aaf.gz
>
> Since the new HTTP library, my code runs completely on ByteStrings, only
> the xhtml library expects me to feed strings. I tried to fix this and
> created a patch against xhtml-3000.2.0.1 to work internally with lazy
> ByteStrings. It's API-compatible to the normal xhtml library, it just
> adds showHtml', renderHtml' and prettyHtml' that output lazy
> ByteStrings, and that has Html instances for strict any lazy
> ByteStrings.
>
> There were some speed and space improvements, but none horrific (at
> least for DarcsWatch, most of the time goes into parsing the
> repositories and mails, and into sorting that data). Unfortunately, I
> can't use it in the live installation until I upgrade the machine from
> Debian etch to lenny, as the bundled bytestring library in ghc-6.6' base
> is too old.
>
> Nevertheless, I'm sharing my patch here, maybe it's useful for some, or
> maybe it can be the base for an official xhtml release with bytestrings
> inside.
>
> To speed things up even more one should probably create a type analogous
> to ShowS, i.e. (L.ByteString -> L.ByteString), that allows you to
> concatenate ByteString chunks cheaply.
>
> I also noted that the current version of bytestring implements
> "concatMap" in a way that is guaranteed to rip apart the string into
> very small chunks, even if the mapped function returns the same
> character most times (as it is the case for the Html escaping function).
> Therefore, I wrote this function:
>
> -- | More efficient variant of 'L.concatMap'
> concatMapL' :: (Char -> String) -> L.ByteString -> L.ByteString
> concatMapL' f s = go s
>  where go s = let (unmodified, modified) = L.span (\c -> f c == [c]) s
>   in case L.uncons modified of
> Nothing   -> unmodified
> Just (c,rest) -> L.pack (f c) `L.append` go rest
>
> Does this make sense? Should it maybe replace the function in the
> library?
>
> Greetings,
> Joachim
>
> [1] http://darcswatch.nomeata.de/
>
> --
> Joachim "nomeata" Breitner
>  mail: m...@joachim-breitner.de | ICQ# 74513189 | GPG-Key: 4743206C
>  JID: nome...@joachim-breitner.de | http://www.joachim-breitner.de/
>  Debian Developer: nome...@debian.org
>
> ___
> Haskell-Cafe mailing list
> Haskell-Cafe@haskell.org
> http://www.haskell.org/mailman/listinfo/haskell-cafe
>
>
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Re: Improved documentation for Bool

2009-01-19 Thread Jonathan Cast
On Mon, 2009-01-19 at 20:55 +, Andrew Coppin wrote:
> Dan Piponi wrote:
> > On Mon, Jan 19, 2009 at 11:33 AM, Andrew Coppin
> >  wrote:
> >
> >   
> >> My only problem with it is that it's called Bool, while every other
> >> programming language on Earth calls it Boolean. (Or at least, the languages
> >> that *have* a name for it...)
> >> 
> >
> > Python: bool
> > ocaml: bool
> > C++: bool
> > C99: bool
> > C#: bool
> >   
> 
> Versus Java, Pascal,

Again, we don't want to imitate these two!

> Smalltalk and Eiffel who all call it Boolean. Oh 
> well. At least it's pretty obvious what it means.

> >> But I'm far more perturbed by names like Eq, Ord, Num, Ix (??), and so on.
> >> The worst thing about C is the unecessary abbriviations; let's not copy
> >> them, eh?
> >> 
> >
> > They're short so they're quick to parse (for a human) and read.
> > They're easy to type. If you have a constraint like (Eq a,Num a,Ord
> > a,Show a,Ix a) you can see all five type classes at a single glance
> > without having to scan your eye across the line. They're highly
> > mnemonic in the sense that once I'd learnt what they meant it became
> > hard to forget them again. What exactly is wrong with them?
> >   
> 
> Would it really hurt to type a few more keystrokes and say "Equal"? 
> "Ordered"? "Index"? I don't think so.

Constantly?  Yeah.  Commonly used names should be short, or abbreviated.
You can't abbreviate type classes.

> Sure, we don't especially want to end up with classes like 
> StrictlyOrderedAssociativeSet or something, but a few more characters 
> wouldn't exactly kill you.
> 
> But, again, this is too difficult to change now, so we're stuck with it.
> 
> PS. Ord implies Eq, so you don't need both in the same constraint. Num 
> implies Show, so you don't need that either. So actually, (Ord a, Num a, 
> Ix a) - or rather, (Ordered a, Number a, Index a) - would do just fine.

newtype MyFoo = MyWrapsWhatever
  deriving (Eq, Ord, Read, Show, Num, Ix, Data, Typeable)

vs.

newtype MyFoo = MyWrapsWhatever
  deriving (Equality, Order, Read, Show, Number, Index, Data, Typeable)

Yeah.  Count me out.

jcc


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


Re: [Haskell-cafe] Employment

2009-01-19 Thread Jonathan Cast
On Mon, 2009-01-19 at 21:04 +, Andrew Coppin wrote:
> Erik de Castro Lopo wrote:
> > Its proabably a little harder to find a company that wants a
> > Haskell hacker than  it is to find a company where Haskell and
> > other sane languages can be worked  in over time.
> >   
> 
> I think you're probably right about that. ;-)
> 
> I mean, heck, *I* use Haskell at work - and I'm not even supposed to be 
> coding things!

/me feels slightly relieved, if you'll forgive my saying so :)  Also, if
you don't mind my asking, what *is* your job title?

jcc


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


Re: [Haskell-cafe] Re: How to make code least strict?

2009-01-19 Thread Conal Elliott
I second Ryan's recommendation of using unamb [1,2,3] to give you unbiased
(symmetric) laziness.

The zip definition could also be written as

zip xs@(x:xs') ys@(y:ys') =
  assuming (xs == []) [] `unamb`
  assuming (ys == []) [] `unamb`
  (x,y) : zip xs' ys'

The 'assuming' function yields a value if a condition is true and otherwise
is bottom:

assuming :: Bool -> a -> a
assuming True  a = a
assuming False _ = undefined

This zip definition is a special case of the annihilator pattern, so

zip = parAnnihilator (\ (x:xs') (y:ys') -> (x,y) : zip xs' ys') []

where 'parAnnihilator' is defined in Data.Unamb (along with other goodies)
as follows:

parAnnihilator :: Eq a => (a -> a -> a) -> a -> (a -> a -> a)
parAnnihilator op ann x y =
  assuming (x == ann) ann `unamb`
  assuming (y == ann) ann `unamb`
  (x `op` y)

[1] http://haskell.org/haskellwiki/Unamb
[2]
http://hackage.haskell.org/packages/archive/unamb/latest/doc/html/Data-Unamb.html
[3] http://conal.net/blog/tag/unamb/

   - conal

On Mon, Jan 19, 2009 at 12:27 PM, Ryan Ingram  wrote:

> On Mon, Jan 19, 2009 at 9:10 AM, ChrisK 
> wrote:
> > Consider that the order of pattern matching can matter as well, the
> simplest
> > common case being zip:
> >
> > zip xs [] = []
> > zip [] ys = []
> > zip (x:xs) (y:ys) = (x,y) : zip xs ys
>
> If you are obsessive about least-strictness and performance isn't a
> giant concern, this seems like a perfect use for Conal's unamb[1]
> operator.
>
> zipR xs [] = []
> zipR [] ys = []
> zipR (x:xs) (y:ys) = (x,y) : zip xs ys
>
> zipL [] ys = []
> zipL xs [] = []
> zipL (x:xs) (y:ys) = (x,y) : zip xs ys
>
> zip xs ys = unamb (zipL xs ys) (zipR xs ys)
>
> This runs both zipL and zipR in parallel until one of them gives a
> result; if neither of them is _|_ they are guaranteed to be identical,
> so we can "unambiguously choose" whichever one gives a result first.
>
>  -- ryan
>
> [1]
> http://conal.net/blog/posts/functional-concurrency-with-unambiguous-choice/
> ___
> Haskell-Cafe mailing list
> Haskell-Cafe@haskell.org
> http://www.haskell.org/mailman/listinfo/haskell-cafe
>
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


RE: [Haskell-cafe] Employment

2009-01-19 Thread Sittampalam, Ganesh
Andrew Coppin wrote:
> Andrew Wagner wrote:
>> http://www.haskell.org/haskellwiki/Haskell_in_industry could be of
>> interest to you
> 
> Hmm, interesting... So lots happening in Portland, Oregon. Lots in
> Cambridge, MA. A few things in Europe. And nothing at all in the
> UK...  

We (Credit Suisse) have Haskell developers in both London and NY,
although the page only listed NY (I've now corrected it).

Two other companies without locations listed - Barclays Capital and
Standard Chartered - also have at least some Haskell development in
the UK, and I think that's where Amgen's development is based too.

Ganesh

==
Please access the attached hyperlink for an important electronic communications 
disclaimer: 

http://www.credit-suisse.com/legal/en/disclaimer_email_ib.html
==

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


Re: [Haskell-cafe] GLUT (glutGet undefined reference)

2009-01-19 Thread Felipe Lessa
2009/1/19 Paul Keir :
> I was hoping to introduce my old pal OpenGL
> with my new chum, Haskell. I used cabal to
> install GLUT on my 64-bit Ubuntu machine with
> GHC 6.8.2 (installed via apt-get/synaptic).

I'm sorry, I can't help you with your problem. But I'd recommend you
using GLFW, it's a lot easier to build and use on Linux and on Windows
(I never managed to install GLUT on Windows). There are some functions
from GLUT that it doesn't have, but most of the time you don't use
them anyway.

HTH,

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


Re: [Haskell-cafe] Employment

2009-01-19 Thread Andrew Coppin

Andrew Wagner wrote:
http://www.haskell.org/haskellwiki/Haskell_in_industry could be of 
interest to you


Hmm, interesting... So lots happening in Portland, Oregon. Lots in 
Cambridge, MA. A few things in Europe. And nothing at all in the UK...


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


Re: [Haskell-cafe] Employment

2009-01-19 Thread Andrew Coppin

Erik de Castro Lopo wrote:

Its proabably a little harder to find a company that wants a
Haskell hacker than  it is to find a company where Haskell and
other sane languages can be worked  in over time.
  


I think you're probably right about that. ;-)

I mean, heck, *I* use Haskell at work - and I'm not even supposed to be 
coding things!


Like many people I'm sure, I'd like to get paid to code stuff in 
Haskell. But I can't begin to imagine how you go about doing that...


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


Re: [Haskell-cafe] Re: Improved documentation for Bool

2009-01-19 Thread Andrew Coppin

Dan Piponi wrote:

On Mon, Jan 19, 2009 at 11:33 AM, Andrew Coppin
 wrote:

  

My only problem with it is that it's called Bool, while every other
programming language on Earth calls it Boolean. (Or at least, the languages
that *have* a name for it...)



Python: bool
ocaml: bool
C++: bool
C99: bool
C#: bool
  


Versus Java, Pascal, Smalltalk and Eiffel who all call it Boolean. Oh 
well. At least it's pretty obvious what it means.



But I'm far more perturbed by names like Eq, Ord, Num, Ix (??), and so on.
The worst thing about C is the unecessary abbriviations; let's not copy
them, eh?



They're short so they're quick to parse (for a human) and read.
They're easy to type. If you have a constraint like (Eq a,Num a,Ord
a,Show a,Ix a) you can see all five type classes at a single glance
without having to scan your eye across the line. They're highly
mnemonic in the sense that once I'd learnt what they meant it became
hard to forget them again. What exactly is wrong with them?
  


Would it really hurt to type a few more keystrokes and say "Equal"? 
"Ordered"? "Index"? I don't think so.


Sure, we don't especially want to end up with classes like 
StrictlyOrderedAssociativeSet or something, but a few more characters 
wouldn't exactly kill you.


But, again, this is too difficult to change now, so we're stuck with it.

PS. Ord implies Eq, so you don't need both in the same constraint. Num 
implies Show, so you don't need that either. So actually, (Ord a, Num a, 
Ix a) - or rather, (Ordered a, Number a, Index a) - would do just fine.


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


[Haskell-cafe] xhtml + bytestring

2009-01-19 Thread Joachim Breitner
Hi Bjorn, hi list,

the darcswatch instance I’m running is getting quite big, and it
periodically slows down my server. I managed to get quite an improvement
with this simple patch to my parsing:
http://darcs.nomeata.de/cgi-bin/darcsweb.cgi?r=darcswatch;a=commitdiff;h=20090119181919-23c07-140f8deb91a52a423a2984dce2d22f4a48999aaf.gz

Since the new HTTP library, my code runs completely on ByteStrings, only
the xhtml library expects me to feed strings. I tried to fix this and
created a patch against xhtml-3000.2.0.1 to work internally with lazy
ByteStrings. It’s API-compatible to the normal xhtml library, it just
adds showHtml', renderHtml' and prettyHtml' that output lazy
ByteStrings, and that has Html instances for strict any lazy
ByteStrings.

There were some speed and space improvements, but none horrific (at
least for DarcsWatch, most of the time goes into parsing the
repositories and mails, and into sorting that data). Unfortunately, I
can’t use it in the live installation until I upgrade the machine from
Debian etch to lenny, as the bundled bytestring library in ghc-6.6’ base
is too old.

Nevertheless, I’m sharing my patch here, maybe it’s useful for some, or
maybe it can be the base for an official xhtml release with bytestrings
inside.

To speed things up even more one should probably create a type analogous
to ShowS, i.e. (L.ByteString -> L.ByteString), that allows you to
concatenate ByteString chunks cheaply.

I also noted that the current version of bytestring implements
"concatMap" in a way that is guaranteed to rip apart the string into
very small chunks, even if the mapped function returns the same
character most times (as it is the case for the Html escaping function).
Therefore, I wrote this function:

-- | More efficient variant of 'L.concatMap'
concatMapL' :: (Char -> String) -> L.ByteString -> L.ByteString
concatMapL' f s = go s 
  where go s = let (unmodified, modified) = L.span (\c -> f c == [c]) s
   in case L.uncons modified of
 Nothing   -> unmodified
 Just (c,rest) -> L.pack (f c) `L.append` go rest

Does this make sense? Should it maybe replace the function in the
library? 

Greetings,
Joachim

[1] http://darcswatch.nomeata.de/

-- 
Joachim "nomeata" Breitner
  mail: m...@joachim-breitner.de | ICQ# 74513189 | GPG-Key: 4743206C
  JID: nome...@joachim-breitner.de | http://www.joachim-breitner.de/
  Debian Developer: nome...@debian.org
Nur in xhtml-bytestring/: dist.
diff -aur xhtml-3000.2.0.1/Text/XHtml/Debug.hs xhtml-bytestring/Text/XHtml/Debug.hs
--- xhtml-3000.2.0.1/Text/XHtml/Debug.hs	2008-09-17 16:19:47.0 +0200
+++ xhtml-bytestring/Text/XHtml/Debug.hs	2009-01-19 22:04:32.0 +0100
@@ -7,6 +7,7 @@
 import Text.XHtml.Table
 import Text.XHtml.Strict.Elements
 import Text.XHtml.Strict.Attributes
+import qualified Data.ByteString.Lazy.Char8 as L
 
 --
 -- * Tree Displaying Combinators
@@ -84,7 +85,7 @@
 
   debug :: HtmlElement -> HtmlTree
   debug (HtmlString str) = HtmlLeaf (spaceHtml +++
-  linesToHtml (lines str))
+  linesToHtml (lines (L.unpack str)))
   debug (HtmlTag {
   markupTag = markupTag,
   markupContent = markupContent,
diff -aur xhtml-3000.2.0.1/Text/XHtml/Extras.hs xhtml-bytestring/Text/XHtml/Extras.hs
--- xhtml-3000.2.0.1/Text/XHtml/Extras.hs	2008-09-17 16:19:47.0 +0200
+++ xhtml-bytestring/Text/XHtml/Extras.hs	2009-01-19 22:03:57.0 +0100
@@ -13,11 +13,11 @@
 -- | Convert a 'String' to 'Html', converting
 --   characters that need to be escaped to HTML entities.
 stringToHtml :: String -> Html
-stringToHtml = primHtml . stringToHtmlString 
+stringToHtml = primHtml' . stringToHtmlString 
 
 -- | This converts a string, but keeps spaces as non-line-breakable.
 lineToHtml :: String -> Html
-lineToHtml = primHtml . concatMap htmlizeChar2 . stringToHtmlString 
+lineToHtml = primHtml' . concatMapL' htmlizeChar2 . stringToHtmlString 
where 
   htmlizeChar2 ' ' = " "
   htmlizeChar2 c   = [c]
diff -aur xhtml-3000.2.0.1/Text/XHtml/Frameset.hs xhtml-bytestring/Text/XHtml/Frameset.hs
--- xhtml-3000.2.0.1/Text/XHtml/Frameset.hs	2008-09-17 16:19:47.0 +0200
+++ xhtml-bytestring/Text/XHtml/Frameset.hs	2009-01-19 22:35:55.0 +0100
@@ -11,6 +11,7 @@
  primHtml, 
  -- * Rendering
  showHtml, renderHtml, prettyHtml, 
+ showHtml', renderHtml', prettyHtml',
  showHtmlFragment, renderHtmlFragment, prettyHtmlFragment,
  module Text.XHtml.Strict.Elements,
  module Text.XHtml.Frameset.Elements,
@@ -19,7 +20,7 @@
  module Text.XHtml.Extras
   ) where
 
-import Text.XHtml.Internals
+import Text.XHtml.Internals hiding (showHtml', renderHtml', prettyHtml')
 
 import Text.XHtml.Strict.Elements
 import Text.XHtml.Frameset.Elements
@@ -28,7 +29,9 @@
 
 import Text.XHtml.Extras
 
-docType =
+import qualified Data.ByteString.Lazy.Char8 as L
+
+

Re: [Haskell-cafe] Factoring into type classes

2009-01-19 Thread Derek Elkins
On Mon, 2009-01-19 at 12:10 -0800, Iavor Diatchki wrote:
> Hi,
> 
> On Mon, Jan 19, 2009 at 11:06 AM, Jonathan Cast
>  wrote:
> > On Mon, 2009-01-19 at 10:59 -0800, Iavor Diatchki wrote:
> >> Hello,
> >> The multitude of newtypes in the Monoid module are a good indication
> >> that the Monoid class is not a good fit for the class system
> >
> > I would say rather that the class system is not a good fit for Monoid.
> > Proposals for local instances, multiple instances, instance
> > import/export control, etc. come up quite frequently on this list; the
> > phenomena in question are not restricted to Monoid.
> 
> I disagree with you but that is a moot point because we are discussing
> Haskell, which does not have any of these features.  Also, I find that
> in many situations where people want to use them, simpler solutions
> (like some of the ideas I mentioned in my  previous post) suffice.
> That is not to say that we should stop trying to figure out how to
> improve the class system, but language changes require a lot more work
> than improving the design of the libraries.
> 
> >> I usually
> >> avoid using the "newtype" trick as I find it inconvenient:  usually
> >> the newtype does not have the same operations as the underlying type
> >> and so it cannot be used directly, and if you are going to wrap thing
> >> just when you use the class methods,
> >
> > OTOH, I think you mean here `when you use class methods and when you use
> > overloaded functions'.
> 
> Sure, the point is that you are essentially adding a type annotation,
> which is like using a non-overloaded function.  Compare, for example:
> "mappend add x y"  and "getSum (mappend (Sum x) (Sum y))".  I think
> that the first one is quite a bit more readable but, of course, this
> is somewhat subjective.

data Iso a b = Iso { to :: a -> b, from :: b -> a }

under :: Iso a b -> (b -> b) -> (a -> a)
under iso = to iso ~> from iso

under2 :: Iso a b -> (b -> b -> b) -> (a -> a -> a)
under2 iso = to iso ~> under iso

sumIso = Iso Sum getSum

(+) = under2 sumIso mappend

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


Re: [Haskell-cafe] MonadTrans lift implementation

2009-01-19 Thread Jonathan Cast
On Mon, 2009-01-19 at 21:31 +, Ross Paterson wrote:
> On Mon, Jan 19, 2009 at 01:13:37PM -0800, Jonathan Cast wrote:
> > (On the other hand, your hunch that lift = return is correct --- so you
> > get a cookie for that; it's just that return here is neither the return
> > of the monad for m nor the return of the monad for ReaderT m.  It is,
> > instead, the return of the *applicative functor* --- on the category of
> > monads and monad homomorphisms --- associated to the monad transformer
> > ReaderT.)
> 
> It's also a monad in the category of monads, as are ErrorT, StateT and
> WriteT (see Moggi, An Abstract View of Programming Languages, 1989, s4).

Nice!  I really haven't studied monad transformers nearly as much as I
should have.  (I also really need to read more Moggi :)

jcc


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


Re: [Haskell-cafe] GLUT (glutGet undefined reference)

2009-01-19 Thread Eugene Kirpichov
Ouch. Sorry, I misread your post: I thought you were having troubles on Windows.

2009/1/20 Eugene Kirpichov :
> Have you tried 
> http://netsuperbrain.com/blog/posts/freeglut-windows-hopengl-hglut/
> ?
>
> 2009/1/20 Paul Keir :
>> Hi all,
>>
>> I was hoping to introduce my old pal OpenGL
>> with my new chum, Haskell. I used cabal to
>> install GLUT on my 64-bit Ubuntu machine with
>> GHC 6.8.2 (installed via apt-get/synaptic).
>>
>> I followed the wiki OpenGLTutorial1 until:
>> ghc -package GLUT HelloWorld.hs -o HelloWorld
>> at which point my screen is filled with errors.
>> The errors begin with:
>>
>> /home/paul/.cabal/lib/GLUT-2.1.1.2/ghc-6.8.2/libHSGLUT-2.1.1.2.a(Begin.o):
>> In function `szEn_info':
>> (.text+0x26c): undefined reference to `glutGet'
>>
>> This surprised me a little because I've already
>> seen these same errors recently on two separate
>> Windows boxes. Somehow I'd got the idea it was
>> (on Windows) due to installing from a binary; though
>> I guess the story is the same with apt-get. Should
>> I look for an apt-get switch to reinstall GHC from
>> source instead?
>>
>> Regards,
>> Paul
>>
>>
>> ___
>> Haskell-Cafe mailing list
>> Haskell-Cafe@haskell.org
>> http://www.haskell.org/mailman/listinfo/haskell-cafe
>>
>>
>
>
>
> --
> Евгений Кирпичев
> Разработчик Яндекс.Маркета
>
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] GLUT (glutGet undefined reference)

2009-01-19 Thread Eugene Kirpichov
Have you tried 
http://netsuperbrain.com/blog/posts/freeglut-windows-hopengl-hglut/
?

2009/1/20 Paul Keir :
> Hi all,
>
> I was hoping to introduce my old pal OpenGL
> with my new chum, Haskell. I used cabal to
> install GLUT on my 64-bit Ubuntu machine with
> GHC 6.8.2 (installed via apt-get/synaptic).
>
> I followed the wiki OpenGLTutorial1 until:
> ghc -package GLUT HelloWorld.hs -o HelloWorld
> at which point my screen is filled with errors.
> The errors begin with:
>
> /home/paul/.cabal/lib/GLUT-2.1.1.2/ghc-6.8.2/libHSGLUT-2.1.1.2.a(Begin.o):
> In function `szEn_info':
> (.text+0x26c): undefined reference to `glutGet'
>
> This surprised me a little because I've already
> seen these same errors recently on two separate
> Windows boxes. Somehow I'd got the idea it was
> (on Windows) due to installing from a binary; though
> I guess the story is the same with apt-get. Should
> I look for an apt-get switch to reinstall GHC from
> source instead?
>
> Regards,
> Paul
>
>
> ___
> Haskell-Cafe mailing list
> Haskell-Cafe@haskell.org
> http://www.haskell.org/mailman/listinfo/haskell-cafe
>
>



-- 
Евгений Кирпичев
Разработчик Яндекс.Маркета
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] GLUT (glutGet undefined reference)

2009-01-19 Thread Paul Keir
Hi all,

I was hoping to introduce my old pal OpenGL
with my new chum, Haskell. I used cabal to
install GLUT on my 64-bit Ubuntu machine with
GHC 6.8.2 (installed via apt-get/synaptic).

I followed the wiki OpenGLTutorial1 until:
ghc -package GLUT HelloWorld.hs -o HelloWorld
at which point my screen is filled with errors.
The errors begin with:

/home/paul/.cabal/lib/GLUT-2.1.1.2/ghc-6.8.2/libHSGLUT-2.1.1.2.a(Begin.o): In 
function `szEn_info':
(.text+0x26c): undefined reference to `glutGet'

This surprised me a little because I've already
seen these same errors recently on two separate
Windows boxes. Somehow I'd got the idea it was
(on Windows) due to installing from a binary; though
I guess the story is the same with apt-get. Should
I look for an apt-get switch to reinstall GHC from
source instead?

Regards,
Paul

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


Re: [Haskell-cafe] MonadTrans lift implementation

2009-01-19 Thread Ross Paterson
On Mon, Jan 19, 2009 at 01:13:37PM -0800, Jonathan Cast wrote:
> (On the other hand, your hunch that lift = return is correct --- so you
> get a cookie for that; it's just that return here is neither the return
> of the monad for m nor the return of the monad for ReaderT m.  It is,
> instead, the return of the *applicative functor* --- on the category of
> monads and monad homomorphisms --- associated to the monad transformer
> ReaderT.)

It's also a monad in the category of monads, as are ErrorT, StateT and
WriteT (see Moggi, An Abstract View of Programming Languages, 1989, s4).
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] LinuxFest Northwest 2009

2009-01-19 Thread Shachaf Ben-Kiki
LFNW 2009 () is going to be at the end of
April, and I was wondering if anyone here is going to be there, or possibly a
Haskell-related presentation.

Last year I met ac from #haskell there, but it would be nice if more people
came, especially with the (relatively) big group in Oregon and such. Perhaps
someone here has plans already?

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


Re: [Haskell-cafe] MonadTrans lift implementation

2009-01-19 Thread Jonathan Cast
On Mon, 2009-01-19 at 13:03 -0800, Daryoush Mehrtash wrote:
> Is there a reason why the lift function in ReaderT's MonadTrans instance is 
> implemented as:
> 
> instance MonadTrans (ReaderT r) where
> 
> lift m = ReaderT $ \_ -> m
> 
> 
> 
> Instead of just using the monad's return function? Could  "lift m" be 
> implemented as "return m"?

No:

Prelude> :m + Control.Monad.Reader
Prelude Control.Monad.Reader> :t \ m -> ReaderT $ \ _ -> m
\ m -> ReaderT $ \ _ -> m :: m a -> ReaderT r m a
Prelude Control.Monad.Reader> :t \ m -> ReaderT $ \ _ -> return m
\ m -> ReaderT $ \ _ -> return m :: (Monad m) => a -> ReaderT r m a

Your first clue that something's wrong should be that the types don't
work out.

(On the other hand, your hunch that lift = return is correct --- so you
get a cookie for that; it's just that return here is neither the return
of the monad for m nor the return of the monad for ReaderT m.  It is,
instead, the return of the *applicative functor* --- on the category of
monads and monad homomorphisms --- associated to the monad transformer
ReaderT.)

(By the way, you *do* have the equations

lift (return x) = return x

and

lift (a >>= f) = lift a >>= lift . f
)

jcc


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


Re: [Haskell-cafe] MonadTrans lift implementation

2009-01-19 Thread Brent Yorgey
On Mon, Jan 19, 2009 at 01:03:55PM -0800, Daryoush Mehrtash wrote:

> lift m   = ReaderT $ \_ -> m
> return a = ReaderT $ \_ -> return a

If you look carefully you will see that these are not the same.

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


[Haskell-cafe] MonadTrans lift implementation

2009-01-19 Thread Daryoush Mehrtash
Is there a reason why the lift function in ReaderT's MonadTrans
instance is implemented as:

instance MonadTrans (ReaderT r) where
lift m = ReaderT $ \_ -> m


Instead of just using the monad's return function? Could  "lift m"
be implemented as "return m"?


instance (Monad m) => Monad (ReaderT r m) where
   * return a = ReaderT $ \_ -> return a*
m >>= k  = ReaderT $ \r -> do
a <- runReaderT m r
runReaderT (k a) r
fail msg = ReaderT $ \_ -> fail msg


Thanks,

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


Re: [Haskell-cafe] Employment

2009-01-19 Thread John Goerzen
Andrew Coppin wrote:
> Is it possible to earn money using Haskell? Does anybody here actually 
> do this?
> 
> Inquiring minds want to know... ;-)

I work for a company that designs, builds, and sells lawn mowers
(hustlerturf.com).  We use quite a bit of Haskell, especially as a "glue
language" for tying together data from different manufacturing-related
systems.  We also use it for some web apps that are deployed to our
dealer network.  There are also some uses for it doing sysadmin
automation, such as adding/removing people from LDAP servers and the like.

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


Re: [Haskell-cafe] Factoring into type classes

2009-01-19 Thread Miguel Mitrofanov

I'd prefer something like

Sum :: Monoid Integer
Sum = Monoid {mappend = (+), mempty = 0}

Prod :: Monoid Integer
Prod = Monoid {mappend = (*), mempty = 1}

instance Sum in [some code using mempty and mappend]

On 19 Jan 2009, at 23:18, Alberto G. Corona wrote:

This is one of the shortcomings of haskell not to mention other  
programming languages. Mathemathicist would find it very annoying.


Instead of

instance Monoid Integer where
mappend = (+)
mempty = 0
instance Monoid Integer where
mappend = (*)
mempty = 1

which is not legal and the workaround
Num a => Monoid (Sum a)
Num a => Monoid (Product a)

wich is cumbersome
A mathematician  would say something like:
instance Monoid Integer with operation + where
mappend = (+)
mempty = 0
and
instance Monoid Integer with operation * where

mappend = (*)
mempty = 1

But talking about shortcomings, personally I prefer to implement  
first a form of assertion that permits the checking of the  class  
properties automatically for each new instance.


This is far more important in práctical terms.


2009/1/19 Thomas DuBuisson 
2009/1/19 Luke Palmer :
> On Mon, Jan 19, 2009 at 3:58 AM, Patai Gergely >

> wrote:
>>
>> However, there are other type classes that are too general to  
assign
>> such concrete uses to. For instance, if a data structure can have  
more

>> than one meaningful (and useful) Functor or Monoid instance,
>
> As a side curiosity, I would love to see an example of any data  
structure
> which has more than one Functor instance.  Especially those which  
have more

> than one useful functor instance.
> Luke

The recent, and great, blog post about moniods [1] discusses the fact
that (Num a) could be one of several different monoids and how that
was handled.

[1] http://sigfpe.blogspot.com/2009/01/haskell-monoids-and-their-uses.html
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe

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


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


Re: [Haskell-cafe] Employment

2009-01-19 Thread Jeff Heard
Haskell's all I use at work, although no-one requires it.  I know that
Ravi Nanavati's company uses Haskell pretty exclusively, and there's
also Galois and a couple of financial houses.  I was pretty impressed
with the professional turnout for ICFP 2008.

-- Jeff

On Mon, Jan 19, 2009 at 2:34 PM, Andrew Coppin
 wrote:
> Is it possible to earn money using Haskell? Does anybody here actually do
> this?
>
> Inquiring minds want to know... ;-)
>
> ___
> Haskell-Cafe mailing list
> Haskell-Cafe@haskell.org
> http://www.haskell.org/mailman/listinfo/haskell-cafe
>
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] Haskell Weekly News: Issue 101 - January 19, 2009

2009-01-19 Thread Brent Yorgey
---
Haskell Weekly News
http://sequence.complete.org/hwn/20090119
Issue 101 - January 19, 2009
---

   Welcome to issue 101 of HWN, a newsletter covering developments in the
   [1]Haskell community.

   Gee whiz, people, stop being so darn productive or you're going to burn
   me out. Seriously.

Announcements

   curl-1.3.4. Sigbjorn Finne [2]announced that a new version of [3]curl,
   a complete Haskell binding to the libcurl API, is now available and
   have been uploaded to Hackage. The most notable change is the
   overloading of representation of response buffers (and headers),
   allowing for the use of ByteStrings.

   Turbinado V0.4. Alson Kemp [4]announced the release of version 0.4 of
   [5]Turbinado, an easy to use Model-View-Controller-ish web framework
   for Haskell. Highlights for the 0.4 release include a dramatically
   improved ORM which handles foreign keys, and improved documentation.

   Hackage about to reach 1000 releases. Don Stewart [6]announced that
   Hackage is about to reach the 1000 release mark, 2 years after it went
   live. Some pretty charts [7]can be seen here.

   leapseconds-announced-2009. Bjorn Buckwalter [8]announced the release
   of the [9]leapseconds-announced package, which contains a single module
   and a single function implementing the
   Data.Time.Clock.TAI.LeapSecondTable interface.

   zipper-0.1. Andres Loeh [10]announced [11]zipper-0.1, a library
   offering a generic zipper for systems of recursive datatypes.

   multirec-0.2. Andres Loeh [12]announced [13]multirec-0.2, a library
   which provides a mechanism to talk about fixed points of systems of
   datatypes that may be mutually recursive. On top of these
   representations, generic functions such as the fold or the Zipper can
   then be defined.

   ghci-haskeline 0.1. Judah Jacobson [14]announced the first release of
   [15]ghci-haskeline. This package uses the GHC API to reimplement ghci
   with the [16]Haskeline library as a backend. Haskeline is a library for
   line input in command-line programs, similar to readline or editline,
   which is written in Haskell and thus (hopefully) more easily integrated
   into other Haskell programs.

   The Monad.Reader (13) - Call for copy. Wouter Swierstra [17]announced a
   Call for Copy for Issue 13 of [18]The Monad.Reader. The submission
   deadline is February 13, 2009. Please get in touch with Wouter if you
   intend to submit something.

   Cabal 2.0. Duncan Coutts [19]announced that he has started a [20]wiki
   page to collect ideas for Cabal 2. The basic idea for Cabal 2 is to
   learn lessons from our how the existing design has fared and how we can
   make a better design to tackle an expanded set of goals.

   Announcing Haskell protocol-buffers 1.4.0 (the smashing recursive
   edition). Chris Kuklewicz [21]announced version 1.4.0 (the smashing
   recursive edition) of [22]protocol-buffers, a Haskell interface to
   Google's "..language-neutral, platform-neutral, extensible way of
   serializing structured data for use in communications protocols, data
   storage, and more."

   Haskell WikiProject. Robin Green [23]asked: is anyone else interested
   in forming a Haskell WikiProject on Wikipedia, to collaborate on
   improving and maintaining the coverage and quality of articles on
   Haskell-related software and topics (broadly defined)?

   darcs 2.2.0. Petr Rockai [24]announced the release of darcs 2.2.0, with
   both a [25]source tarball and a [26]cabalized tarball available. This
   version features many improvements and bug fixes; see Petr's original
   announcement for a list.

   hledger 0.3. Simon Michael [27]announced the release of [28]hledger
   0.3, a partial haskell clone of John Wiegley's "ledger" text-based
   accounting tool. It generates transaction and balance reports from a
   plain text ledger file, and demonstrates a functional implementation of
   ledger.

   language-sh-0.0.3.1. Stephen Hicks [29]announced the [30]language-sh
   package, a set of modules for parsing, manipulating, and printing
   sh-style shell scripts. It's being developed alongside shsh, the
   [31]Simple Haskell Shell.

   Coadjute 0.0.1, generic build tool. Matti Niemenmaa [32]announced
   version 0.0.1 of [33]Coadjute, a generic build tool intended as an
   easier to use and more portable replacement for make.

   dataenc 0.12. Magnus Therning [34]announced version 0.12 of
   [35]dataenc, a data encoding library currently providing Uuencode,
   Base64, Base64Url, Base32, Base32Hex, Base16, Base85, and (new in 0.12)
   yEncoding.

   3 applications of "indexed composition" as a language design principle.
   Greg Meredith [36]announced that he has found a way to generalize the
   LogicT transformer, and calculated it's [37]application to three fairl

Re: [Haskell-cafe] Factoring into type classes

2009-01-19 Thread Derek Elkins
On Mon, 2009-01-19 at 21:18 +0100, Alberto G. Corona wrote:
> This is one of the shortcomings of haskell not to mention other
> programming languages. Mathemathicist would find it very annoying.
> 
> 
> Instead of 
> 
> 
> instance Monoid Integer where
> mappend = (+)
> mempty = 0
> 
> instance Monoid Integer where
> mappend = (*)
> mempty = 1
> 
> 
> which is not legal and the workaround
> 
> Num a => Monoid (Sum a)
> Num a => Monoid (Product a)
> 
> wich is cumbersome
> A mathematician  would say something like:
> instance Monoid Integer with operation + where
> mappend = (+)
> mempty = 0
> and
> 
> instance Monoid Integer with operation * where
> 
> mappend = (*)
> mempty = 1

Check out the OBJ family of languages, particularly OBJ3 and (I think)
Maude.

> 
> 
> But talking about shortcomings, personally I prefer to implement first
> a form of assertion that permits the checking of the  class properties
> automatically for each new instance. 
>  
> This is far more important in práctical terms.
> 
> 
> 
> 2009/1/19 Thomas DuBuisson 
> 2009/1/19 Luke Palmer :
> 
> 
> > On Mon, Jan 19, 2009 at 3:58 AM, Patai Gergely
> 
> > wrote:
> >>
> >> However, there are other type classes that are too general
> to assign
> >> such concrete uses to. For instance, if a data structure
> can have more
> >> than one meaningful (and useful) Functor or Monoid
> instance,
> >
> > As a side curiosity, I would love to see an example of any
> data structure
> > which has more than one Functor instance.  Especially those
> which have more
> > than one useful functor instance.
> > Luke
> 
> 
> The recent, and great, blog post about moniods [1] discusses
> the fact
> that (Num a) could be one of several different monoids and how
> that
> was handled.
> 
> [1]
> http://sigfpe.blogspot.com/2009/01/haskell-monoids-and-their-uses.html
> 
> ___
> Haskell-Cafe mailing list
> Haskell-Cafe@haskell.org
> http://www.haskell.org/mailman/listinfo/haskell-cafe
> 
> 
> ___
> Haskell-Cafe mailing list
> Haskell-Cafe@haskell.org
> http://www.haskell.org/mailman/listinfo/haskell-cafe

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


Re: [Haskell-cafe] Factoring into type classes

2009-01-19 Thread Jonathan Cast
On Mon, 2009-01-19 at 12:10 -0800, Iavor Diatchki wrote:
> >> I usually
> >> avoid using the "newtype" trick as I find it inconvenient:  usually
> >> the newtype does not have the same operations as the underlying type
> >> and so it cannot be used directly, and if you are going to wrap thing
> >> just when you use the class methods,
> >
> > OTOH, I think you mean here `when you use class methods and when you use
> > overloaded functions'.
> 
> Sure, the point is that you are essentially adding a type annotation,
> which is like using a non-overloaded function.  Compare, for example:
> "mappend add x y"  and "getSum (mappend (Sum x) (Sum y))".  I think
> that the first one is quite a bit more readable but, of course, this
> is somewhat subjective.

Right.  Of course, this issue comes up quite frequently; even

sort :: Ord alpha => [alpha] -> [alpha]

Needs to be specialized to non-standard Ord instances.  I think that, if
we're going to restrict type classes to only those cases where we never
want to specialize an overloaded function to a non-standard instance,
that we're going to end up with Eq, Num, and maybe Functor as classes.
I'm not sure a general language mechanism is really needed just for
those three.

jcc


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


Re: [Haskell-cafe] Re: Improved documentation for Bool

2009-01-19 Thread Dan Piponi
On Mon, Jan 19, 2009 at 11:33 AM, Andrew Coppin
 wrote:

> My only problem with it is that it's called Bool, while every other
> programming language on Earth calls it Boolean. (Or at least, the languages
> that *have* a name for it...)

Python: bool
ocaml: bool
C++: bool
C99: bool
C#: bool

> But I'm far more perturbed by names like Eq, Ord, Num, Ix (??), and so on.
> The worst thing about C is the unecessary abbriviations; let's not copy
> them, eh?

They're short so they're quick to parse (for a human) and read.
They're easy to type. If you have a constraint like (Eq a,Num a,Ord
a,Show a,Ix a) you can see all five type classes at a single glance
without having to scan your eye across the line. They're highly
mnemonic in the sense that once I'd learnt what they meant it became
hard to forget them again. What exactly is wrong with them?
--
Dan
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Re: How to make code least strict?

2009-01-19 Thread Ryan Ingram
On Mon, Jan 19, 2009 at 9:10 AM, ChrisK  wrote:
> Consider that the order of pattern matching can matter as well, the simplest
> common case being zip:
>
> zip xs [] = []
> zip [] ys = []
> zip (x:xs) (y:ys) = (x,y) : zip xs ys

If you are obsessive about least-strictness and performance isn't a
giant concern, this seems like a perfect use for Conal's unamb[1]
operator.

zipR xs [] = []
zipR [] ys = []
zipR (x:xs) (y:ys) = (x,y) : zip xs ys

zipL [] ys = []
zipL xs [] = []
zipL (x:xs) (y:ys) = (x,y) : zip xs ys

zip xs ys = unamb (zipL xs ys) (zipR xs ys)

This runs both zipL and zipR in parallel until one of them gives a
result; if neither of them is _|_ they are guaranteed to be identical,
so we can "unambiguously choose" whichever one gives a result first.

  -- ryan

[1] http://conal.net/blog/posts/functional-concurrency-with-unambiguous-choice/
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Factoring into type classes

2009-01-19 Thread Alberto G. Corona
This is one of the shortcomings of haskell not to mention other programming
languages. Mathemathicist would find it very annoying.
Instead of

instance Monoid Integer where
mappend = (+)
mempty = 0

instance Monoid Integer where
mappend = (*)
mempty = 1


which is not legal and the workaround

Num a => Monoid (Sum a)

Num a => Monoid (Product a)

wich is cumbersome

A mathematician  would say something like:

instance Monoid Integer with operation + where
mappend = (+)
mempty = 0

and

instance Monoid Integer with operation * where
mappend = (*)
mempty = 1


But talking about shortcomings, personally I prefer to implement first a
form of assertion that permits the checking of the  class properties
automatically for each new instance.

This is far more important in práctical terms.


2009/1/19 Thomas DuBuisson 

> 2009/1/19 Luke Palmer :
> > On Mon, Jan 19, 2009 at 3:58 AM, Patai Gergely <
> patai_gerg...@fastmail.fm>
> > wrote:
> >>
> >> However, there are other type classes that are too general to assign
> >> such concrete uses to. For instance, if a data structure can have more
> >> than one meaningful (and useful) Functor or Monoid instance,
> >
> > As a side curiosity, I would love to see an example of any data structure
> > which has more than one Functor instance.  Especially those which have
> more
> > than one useful functor instance.
> > Luke
>
> The recent, and great, blog post about moniods [1] discusses the fact
> that (Num a) could be one of several different monoids and how that
> was handled.
>
> [1] http://sigfpe.blogspot.com/2009/01/haskell-monoids-and-their-uses.html
> ___
> Haskell-Cafe mailing list
> Haskell-Cafe@haskell.org
> http://www.haskell.org/mailman/listinfo/haskell-cafe
>
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Factoring into type classes

2009-01-19 Thread Iavor Diatchki
Hi,

On Mon, Jan 19, 2009 at 11:06 AM, Jonathan Cast
 wrote:
> On Mon, 2009-01-19 at 10:59 -0800, Iavor Diatchki wrote:
>> Hello,
>> The multitude of newtypes in the Monoid module are a good indication
>> that the Monoid class is not a good fit for the class system
>
> I would say rather that the class system is not a good fit for Monoid.
> Proposals for local instances, multiple instances, instance
> import/export control, etc. come up quite frequently on this list; the
> phenomena in question are not restricted to Monoid.

I disagree with you but that is a moot point because we are discussing
Haskell, which does not have any of these features.  Also, I find that
in many situations where people want to use them, simpler solutions
(like some of the ideas I mentioned in my  previous post) suffice.
That is not to say that we should stop trying to figure out how to
improve the class system, but language changes require a lot more work
than improving the design of the libraries.

>> I usually
>> avoid using the "newtype" trick as I find it inconvenient:  usually
>> the newtype does not have the same operations as the underlying type
>> and so it cannot be used directly, and if you are going to wrap thing
>> just when you use the class methods,
>
> OTOH, I think you mean here `when you use class methods and when you use
> overloaded functions'.

Sure, the point is that you are essentially adding a type annotation,
which is like using a non-overloaded function.  Compare, for example:
"mappend add x y"  and "getSum (mappend (Sum x) (Sum y))".  I think
that the first one is quite a bit more readable but, of course, this
is somewhat subjective.

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


Re: [Haskell-cafe] Employment

2009-01-19 Thread Don Stewart
And of course, there's at least half a dozen people on this list at
working at Galois.

And all documented on the wiki,

http://haskell.org/haskellwiki/Haskell_in_industry

See you guys at CUFP 09!

http://cufp.galois.com/

-- Don

pbeadling:
> Barclays Capital use it for Equity Derivative modeling and pricing - it's a
> small team at the moment, but the whole project is in Haskell.
> 
> I don't work on it myself so I couldn't give you any details (plus I would
> get fired for blabbing!), I work in an adjacent group.  Haskell certainly
> lends itself to complex financial maths simulation tho, so I think they've
> made a good choice.
> 
> 
> On 19/01/2009 19:34, "Andrew Coppin"  wrote:
> 
> > Is it possible to earn money using Haskell? Does anybody here actually
> > do this?
> > 
> > Inquiring minds want to know... ;-)
> > 
> > ___
> > Haskell-Cafe mailing list
> > Haskell-Cafe@haskell.org
> > http://www.haskell.org/mailman/listinfo/haskell-cafe
> 
> ___
> Haskell-Cafe mailing list
> Haskell-Cafe@haskell.org
> http://www.haskell.org/mailman/listinfo/haskell-cafe
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Employment

2009-01-19 Thread Erik de Castro Lopo
Erik de Castro Lopo wrote:

> Monad Reader  7 article helped). Fortunately my manager is a really
> bright byg, was open to new ideas and already trusted my judgement.

Ooops, typo. He's a "really bright guy".

Erik
-- 
-
Erik de Castro Lopo
-
"Hey, I've re-dorkulated." -- Prof. Frink (The Simpsons)
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Employment

2009-01-19 Thread Erik de Castro Lopo
Andrew Coppin wrote:

> Is it possible to earn money using Haskell? Does anybody here actually 
> do this?

Its proabably a little harder to find a company that wants a
Haskell hacker than  it is to find a company where Haskell and
other sane languages can be worked  in over time.

I work for a small venture capital funded started. My early work
was all C and C++. However we did have problems where these two 
langauges were not a good fit (too much reinventing the wheel and
boilerplate required) and I made the case for Ocaml (Yaron  Minsky's
Monad Reader  7 article helped). Fortunately my manager is a really
bright byg, was open to new ideas and already trusted my judgement.

We now hae a number of vital components of our flagship product
written in Ocaml. I am currently learning Haskell and intend to
introduce that as well.

HTH,
Erik
-- 
-
Erik de Castro Lopo
-
"life is too long to be an expert at harmful things, including
such evilness as C++ and perl." -- Erik Naggum
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Employment

2009-01-19 Thread Phil
Barclays Capital use it for Equity Derivative modeling and pricing - it's a
small team at the moment, but the whole project is in Haskell.

I don't work on it myself so I couldn't give you any details (plus I would
get fired for blabbing!), I work in an adjacent group.  Haskell certainly
lends itself to complex financial maths simulation tho, so I think they've
made a good choice.


On 19/01/2009 19:34, "Andrew Coppin"  wrote:

> Is it possible to earn money using Haskell? Does anybody here actually
> do this?
> 
> Inquiring minds want to know... ;-)
> 
> ___
> Haskell-Cafe mailing list
> Haskell-Cafe@haskell.org
> http://www.haskell.org/mailman/listinfo/haskell-cafe

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


Re: [Haskell-cafe] Haskell WikiProject

2009-01-19 Thread Gwern Branwen
-BEGIN PGP SIGNED MESSAGE-
Hash: SHA512

On Mon, Jan 19, 2009 at 1:46 PM, Robin Green  wrote:
> Is anyone else interested in forming a Haskell WikiProject on Wikipedia,
> to collaborate on improving and maintaining the coverage and quality of
> articles on Haskell-related software and topics (broadly defined)? Not
> just programming topics specific to Haskell, but also ones of interest
> to the Haskell community.
>
> Some of you might already be doing this from time to time, but forming
> an explicit WikiProject might help to:
>
> * Highlight things that could use some attention
> * Divide up tasks (based on expertise or interest)
> * Recruit more editors (sticking a banner on article Talk pages can let
>  editors know the WikiProject exists)
> * Eventually (something for the future, maybe!) work together on a
>  Wikipedia Haskell Portal
> * And of course, improve the visibility of Haskell on Wikipedia, which
>  should help our community
>
> Here's a good example to start with. The article on Eager evaluation
> could do with some improvement - and possibly should be merged into the
> Lazy evaluation article, I'm not sure:
>
> http://en.wikipedia.org/wiki/Eager_evaluation
>
> We could also probably create some more articles on projects written
> in Haskell, and add more references to Haskell research papers.
> Software projects don't have to be polished to be covered in Wikipedia -
> or even working! - they essentially just have to be "notable", as the
> Wikipedia guidelines define it.
>
> By the way (getting a bit offtopic here) an annoying limitation of the
> Wikipedia category system, that you couldn't run queries like "Give me
> all the articles in the Haskell category that are also in the
> Unreferenced category" has now been partially addressed by the
> experimental prototype of Category Intersection:
>
> http://toolserver.org/~dschwen/intersection/
>
> This is slightly better than Googling, because crucially, it searches
> *recursively* through categories. That means it will turn up articles
> that are in a subcategory of "Category:Haskell programming language" but
> don't explicitly mention Haskell. Don't know if there any such articles
> yet, but it's worth bearing in mind that you can do this. I think it
> will, in principle, make topic-specific maintenance a bit more
> convenient - and it's what I've been waiting for before getting
> involved in topic-specific maintenance.
>
> If you want to just express interest in signing up for such a
> WikiProject (no commitment required whatsoever!), please reply
> privately via email or publicly on my User Talk page (User talk:Greenrd)
> - to avoid clogging up this mailing list.

As a longtime Wikipedian (almost as long as you), I'm not too
enthusiastic about this. More than once I've seen some editor
enthusiastically going around, saying "Hey, you know what this
neglected area of Wikipedia needs? A Wikiproject! That'll solve all
our problems!" And then they go form the Star Wars wikiproject or the
Evangelion workgroup, and things go along as before. (Meet the new
project banner, same as the old banner...)

What would solve all that area's problem is a lot of hard work by a
lot of people over months and years. A wikiproject does little to help
out with this, and in fact, is liable to suck up the effort of the few
people who would otherwise be out actually improving articles.

- ---

To avoid sounding *too* bitter and curmudgeonly and burnt-out, I'd
like to make a counter-suggestion.

Instead of a Wikiproject, why don't you draw up a list of volunteers
and set up a weekly cleanup drive? It would work like this:

1) Every Sunday, you pick some neglected FP topic - preferably
manageable in scope like datastructures are eg. [[Rope (computer
science)]] or [[Finger tree]].
2) You track down all the academic and realworld references, download
all the PDFs, and plop them down on some website where everyone can
access them. You'll remove them after a few days of course.
3) Then you use one of the many notification-bot programs to contact
everyone on the list, saying 'Here is this week's article, here are
the references. Go to!'
4) For good measure, you'll email Haskell-cafe and post a link to the
- -cafe email on Reddit.

This is all perfectly doable on a weekly basis, and I can basically
guarantee you tgat this will do more to clean up FP articles than any
Project-space page of templates and banners would.

- --
gwern
-BEGIN PGP SIGNATURE-
Version: GnuPG v1.4.9 (GNU/Linux)

iEYEAREKAAYFAkl02nUACgkQvpDo5Pfl1oLT9QCeLCqvec+3xyWSkguWXnAHLZJB
7/sAnihxxosIYf7++geo/bCTfYPPe+t8
=nXc3
-END PGP SIGNATURE-
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Employment

2009-01-19 Thread David Leimbach
On Mon, Jan 19, 2009 at 11:34 AM, Andrew Coppin  wrote:

> Is it possible to earn money using Haskell? Does anybody here actually do
> this?
>
> Inquiring minds want to know... ;-)
>

I'm using it at work in simulations... not shipping anything with it yet,
but we do ship Erlang :-)

Haskell may work it's way in eventually too.


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


Re: [Haskell-cafe] Re: Improved documentation for Bool

2009-01-19 Thread Jonathan Cast
On Mon, 2009-01-19 at 19:33 +, Andrew Coppin wrote:
> rocon...@theorem.ca wrote:
> > I noticed the Bool datatype isn't well documented.  Since Bool is not 
> > a common English word, I figured it could use some haddock to help 
> > clarify it for newcomers.
> 
> My only problem with it is that it's called Bool, while every other 
> programming language on Earth calls it Boolean. (Or at least, the 
> languages that *have* a name for it...)

Except C++?  But then again:

> But I'm far more perturbed by names like Eq, Ord, Num, Ix (??), and so 
> on. The worst thing about C is the unecessary abbriviations; [sic] let's not 
> copy them, eh?

I agree.  I've always felt that 

class EqualsClass randomTypeSelectedByTheUser => TotalOrderClass
randomTypeSelectedByTheUser where
  compareXToY :: randomTypeSelectedByTheUser ->
randomTypeSelectedByTheUser -> OrderingValue
  lessThanOrEqualTo :: randomTypeSelectedByTheUser ->
randomTypeSelectedByTheUser -> Boolean
  lessThan :: randomTypeSelectedByTheUser -> randomTypeSelectedByTheUser
-> Boolean

was both more understandable to the reader, and easier to remember and
reproduce for the writer.

Or, in other words, leave well enough alone; we should always err in the
direction of being like C, to avoid erring in the direction of being
like Java.

jcc


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


Re: [Haskell-cafe] Employment

2009-01-19 Thread Andrew Wagner
http://www.haskell.org/haskellwiki/Haskell_in_industry could be of interest
to you

On Mon, Jan 19, 2009 at 2:34 PM, Andrew Coppin
wrote:

> Is it possible to earn money using Haskell? Does anybody here actually do
> this?
>
> Inquiring minds want to know... ;-)
>
> ___
> Haskell-Cafe mailing list
> Haskell-Cafe@haskell.org
> http://www.haskell.org/mailman/listinfo/haskell-cafe
>
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] Employment

2009-01-19 Thread Andrew Coppin
Is it possible to earn money using Haskell? Does anybody here actually 
do this?


Inquiring minds want to know... ;-)

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


[Haskell-cafe] Re: Improved documentation for Bool

2009-01-19 Thread Andrew Coppin

rocon...@theorem.ca wrote:
I noticed the Bool datatype isn't well documented.  Since Bool is not 
a common English word, I figured it could use some haddock to help 
clarify it for newcomers.


My only problem with it is that it's called Bool, while every other 
programming language on Earth calls it Boolean. (Or at least, the 
languages that *have* a name for it...)


But I'm far more perturbed by names like Eq, Ord, Num, Ix (??), and so 
on. The worst thing about C is the unecessary abbriviations; let's not 
copy them, eh?


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


Re: [Haskell-cafe] Expect module?

2009-01-19 Thread Erik de Castro Lopo
Donn Cave wrote:

> Quoth Neil Mitchell :
> 
> >> Is there a Haskell-Expect module? Something that would allow me to
> >> control an external Unix program via its stdin/stdout/stderr?
> >
> > System.Process does what you want, I think:
> 
> It might not.  Expect uses pseudottys (cf. openpty()), and select().

Yep, I definitely need the pty as the program I need to run asks for
a password. Pipes won't work.

Erik
-- 
-
Erik de Castro Lopo
-
"The earth is degenerating these days. Bribery and corruption abound.
Children no longer mind parents ...and it is evident that the end of
the world is approaching fast." -- Assyrian Tablet Engraved in 2800 B.C.
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Open unqualified imports

2009-01-19 Thread Ian Lynagh
On Fri, Jan 16, 2009 at 06:42:46AM -0800, eyal.lo...@gmail.com wrote:
> 
> Closed-unqualified import:
> import Data.Map(Map, lookup)

One problem with this style is that you can get lots of conflicts from
your VCS if you have multiple people working on the same module.


Thanks
Ian

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


Re: [Haskell-cafe] Factoring into type classes

2009-01-19 Thread Jonathan Cast
On Mon, 2009-01-19 at 10:59 -0800, Iavor Diatchki wrote:
> Hello,
> The multitude of newtypes in the Monoid module are a good indication
> that the Monoid class is not a good fit for the class system

I would say rather that the class system is not a good fit for Monoid.
Proposals for local instances, multiple instances, instance
import/export control, etc. come up quite frequently on this list; the
phenomena in question are not restricted to Monoid.

> I usually
> avoid using the "newtype" trick as I find it inconvenient:  usually
> the newtype does not have the same operations as the underlying type
> and so it cannot be used directly, and if you are going to wrap thing
> just when you use the class methods,

OTOH, I think you mean here `when you use class methods and when you use
overloaded functions'.

jcc


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


Re: [Haskell-cafe] Haskell WikiProject

2009-01-19 Thread Roman Cheplyaka
* Robin Green  [2009-01-19 18:46:43+]
> Here's a good example to start with. The article on Eager evaluation
> could do with some improvement - and possibly should be merged into the
> Lazy evaluation article, I'm not sure:
> 
> http://en.wikipedia.org/wiki/Eager_evaluation

I was also disappointed with the article on Typed lambda calculus (compare
it with the article on (untyped) Lambda calculus).

http://en.wikipedia.org/wiki/Typed_lambda_calculus
http://en.wikipedia.org/wiki/Lambda_calculus

-- 
Roman I. Cheplyaka :: http://ro-che.info/
"Don't let school get in the way of your education." - Mark Twain
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] Re: some ideas for Haskell', from Python

2009-01-19 Thread ChrisK

Manlio Perillo wrote:

Brandon S. Allbery KF8NH ha scritto:
 >
...in theory. In practice GHC needs help with circular imports, and 
some cycles might be impossible to resolve.




This is interesting.
Where can I find some examples?

Is this explained in the Real World Haskell book?



I have no idea about RWH, but there are certainly mutual import cycles that 
cannot be resolved by using hs-boot files with GHC.


Consider three modules A and B and C, which are A-B-C permutations of


module A(A,AKBC, AKCB)
import B(B,BKAC)
import C(C,CKAB)

data A
AKBC :: Either B C
AKCB :: Either C B

>
> instance Show (A,BKAC,CKAB) where ...

There is no way to break the ?K?? import cycle with just hs-boot files.  I had 
to solve this by generating "helper" modules.


Call the "data A" the rank-1 declarations.  Then the ?K?? are built on rank-1 
types such as "B" and "C" and are rank-2 declarations.  The rank-1 declarations 
can all be put in hs-boot files but the rank-2 declaration import cycle cannot 
be broken with the same hs-boot files.  Some of these need to be put in separate 
modules.


It may be possible to make a useful definition of rank-3 and higher 
declarations.

--
Chris

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


Re: [Haskell-cafe] Factoring into type classes

2009-01-19 Thread Iavor Diatchki
Hello,
The multitude of newtypes in the Monoid module are a good indication
that the Monoid class is not a good fit for the class system (it is
ironic that discussing it resulted in such a huge thread recently :-).
   How I'd approach the situation that you describe would depend on
the context (did I design the class, or am I just using it?  am I
writing a library that is to be used by other people, or is the class
just used in an internal part of my program?, etc.) but, in general,
here are some ideas:
1. If one type can be made into an instance of a class in multipe ways
and I have no control over the class:
   - I would provide non-overloaded versions for each implementation
   - if there is a "natural" one (something that is quite commonly
used) I would use it for an instance
   - if most uses are equally likely to be useful, then I would not
provide an instance but just use the non-overloaded functions.  If I
did provide an instance, then I would be careful to document the
choice I made.
2. If I have control over the class I may consider changing it:
  - Consider using a different class, that has operations that are
more specific to what I am doing (e.g., use a PrettyPrint class
instead of Show class)
  - If many types are members of the same classes, then it may be
useful to combine them (i.e., add multiple methods that perform the
different operations).

I think that I have done all of the above in different situations, and
so I don't think that there is a single correct answer.  I usually
avoid using the "newtype" trick as I find it inconvenient:  usually
the newtype does not have the same operations as the underlying type
and so it cannot be used directly, and if you are going to wrap thing
just when you use the class methods, then you may as well use the
non-overloaded operations.

Hope that this helps,
Iavor


On Mon, Jan 19, 2009 at 9:40 AM, Patai Gergely
 wrote:
>> As a side curiosity, I would love to see an example of any data structure
>> which has more than one Functor instance.  Especially those which have
>> more than one useful functor instance.
>
> data Record a b = R { field1 :: a, field2 :: b }
>
> If I want to use fmap to transform either field, I have to declare the
> type to have the corresponding type variable at the end, i.e. choosing
> "Record a b" or "Record b a" is already a design decision, and it is
> driven by the standard Functor class in this case. I can define custom
> functions fmap1 and fmap2 manually, but then I don't get the advantages
> of overloading, like fmapping over a data structure containing my
> records.
>
> Now I understand that I can't get everything, and my question is mainly
> what to do when such a dilemma comes up. Those who have already
> encountered such a dilemma: how did it come up and what did you do to
> solve it?
>
> Gergely
>
> --
> http://www.fastmail.fm - Same, same, but different...
>
> ___
> Haskell-Cafe mailing list
> Haskell-Cafe@haskell.org
> http://www.haskell.org/mailman/listinfo/haskell-cafe
>
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Haskell WikiProject

2009-01-19 Thread Don Stewart
greenrd:
> Is anyone else interested in forming a Haskell WikiProject on Wikipedia,
> to collaborate on improving and maintaining the coverage and quality of
> articles on Haskell-related software and topics (broadly defined)? Not
> just programming topics specific to Haskell, but also ones of interest
> to the Haskell community.
> 
> Some of you might already be doing this from time to time, but forming
> an explicit WikiProject might help to:
> 
> * Highlight things that could use some attention
> * Divide up tasks (based on expertise or interest)
> * Recruit more editors (sticking a banner on article Talk pages can let
>   editors know the WikiProject exists)
> * Eventually (something for the future, maybe!) work together on a
>   Wikipedia Haskell Portal
> * And of course, improve the visibility of Haskell on Wikipedia, which
>   should help our community
> 
> Here's a good example to start with. The article on Eager evaluation
> could do with some improvement - and possibly should be merged into the
> Lazy evaluation article, I'm not sure:
> 
> http://en.wikipedia.org/wiki/Eager_evaluation
> 
> We could also probably create some more articles on projects written
> in Haskell, and add more references to Haskell research papers.
> Software projects don't have to be polished to be covered in Wikipedia -
> or even working! - they essentially just have to be "notable", as the
> Wikipedia guidelines define it.
> 
> By the way (getting a bit offtopic here) an annoying limitation of the
> Wikipedia category system, that you couldn't run queries like "Give me
> all the articles in the Haskell category that are also in the
> Unreferenced category" has now been partially addressed by the
> experimental prototype of Category Intersection:
> 
> http://toolserver.org/~dschwen/intersection/
> 
> This is slightly better than Googling, because crucially, it searches
> *recursively* through categories. That means it will turn up articles
> that are in a subcategory of "Category:Haskell programming language" but
> don't explicitly mention Haskell. Don't know if there any such articles
> yet, but it's worth bearing in mind that you can do this. I think it
> will, in principle, make topic-specific maintenance a bit more
> convenient - and it's what I've been waiting for before getting
> involved in topic-specific maintenance.
> 
> If you want to just express interest in signing up for such a
> WikiProject (no commitment required whatsoever!), please reply
> privately via email or publicly on my User Talk page (User talk:Greenrd)
> - to avoid clogging up this mailing list.

Yes!

Also, we have many good writers who've written extensively on topics on
blogs who I'm sure would be happy to donate content.

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


Re: [Haskell-cafe] How to make code least strict?

2009-01-19 Thread Robin Green
On Mon, 19 Jan 2009 17:36:30 +
"Thomas DuBuisson"  wrote:

> On Mon, Jan 19, 2009 at 4:48 PM, Robin Green 
> wrote:
> > What guidelines should one follow to make Haskell code least-strict?
> 
> There was a great Cafe discussion started by Henning on just this.  He
> provided this link:
> 
> http://www.haskell.org/haskellwiki/Maintaining_laziness

Thanks - wow, my memory is terrible! I submitted this page to the
Haskell reddit myself 20 days ago! I had a sneaking feeling of deja
vu after I asked the question. :-D
-- 
Robin
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] Haskell WikiProject

2009-01-19 Thread Robin Green
Is anyone else interested in forming a Haskell WikiProject on Wikipedia,
to collaborate on improving and maintaining the coverage and quality of
articles on Haskell-related software and topics (broadly defined)? Not
just programming topics specific to Haskell, but also ones of interest
to the Haskell community.

Some of you might already be doing this from time to time, but forming
an explicit WikiProject might help to:

* Highlight things that could use some attention
* Divide up tasks (based on expertise or interest)
* Recruit more editors (sticking a banner on article Talk pages can let
  editors know the WikiProject exists)
* Eventually (something for the future, maybe!) work together on a
  Wikipedia Haskell Portal
* And of course, improve the visibility of Haskell on Wikipedia, which
  should help our community

Here's a good example to start with. The article on Eager evaluation
could do with some improvement - and possibly should be merged into the
Lazy evaluation article, I'm not sure:

http://en.wikipedia.org/wiki/Eager_evaluation

We could also probably create some more articles on projects written
in Haskell, and add more references to Haskell research papers.
Software projects don't have to be polished to be covered in Wikipedia -
or even working! - they essentially just have to be "notable", as the
Wikipedia guidelines define it.

By the way (getting a bit offtopic here) an annoying limitation of the
Wikipedia category system, that you couldn't run queries like "Give me
all the articles in the Haskell category that are also in the
Unreferenced category" has now been partially addressed by the
experimental prototype of Category Intersection:

http://toolserver.org/~dschwen/intersection/

This is slightly better than Googling, because crucially, it searches
*recursively* through categories. That means it will turn up articles
that are in a subcategory of "Category:Haskell programming language" but
don't explicitly mention Haskell. Don't know if there any such articles
yet, but it's worth bearing in mind that you can do this. I think it
will, in principle, make topic-specific maintenance a bit more
convenient - and it's what I've been waiting for before getting
involved in topic-specific maintenance.

If you want to just express interest in signing up for such a
WikiProject (no commitment required whatsoever!), please reply
privately via email or publicly on my User Talk page (User talk:Greenrd)
- to avoid clogging up this mailing list.

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


Re: [Haskell-cafe] Expect module?

2009-01-19 Thread Brandon S. Allbery KF8NH

On 2009 Jan 19, at 3:47, Neil Mitchell wrote:

Is there a Haskell-Expect module? Something that would allow me to
control an external Unix program via its stdin/stdout/stderr?


System.Process does what you want, I think:

http://hackage.haskell.org/packages/archive/process/1.0.1.1/doc/html/System-Process.html



I don't see any pty stuff in there offhand.

--
brandon s. allbery [solaris,freebsd,perl,pugs,haskell] allb...@kf8nh.com
system administrator [openafs,heimdal,too many hats] allb...@ece.cmu.edu
electrical and computer engineering, carnegie mellon universityKF8NH


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


Re: [Haskell-cafe] plugins can not be installed in ghc 6.10.1

2009-01-19 Thread Don Stewart
agocorona:
>Do really pluigins needs Cabal (>=1.4 && <1.5) ???
>C:\Documents and Settings\Administrator>cabal install plugins
>Resolving dependencies...
>cabal: dependencies conflict: ghc-6.10.1 requires Cabal ==1.6.0.1 however
>Cabal-1.6.0.1 was excluded because plugins-1.3.1 requires Cabal ==1.4.*


Patches welcome. Probably switching to the 1.6 API won't be too hard.
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] Re: ANN: hledger 0.3 released

2009-01-19 Thread Sebastian Sylvan
The cabal file still includes the vty dependency, but simply removing it 
made it compile.


--
From: "Simon Michael" 
Sent: Sunday, January 18, 2009 7:04 PM
To: "Sebastian Sylvan" 
Cc: ; 
Subject: Re: ANN: hledger 0.3 released

I've pushed a patch which should omit the vty dependency and ui  command 
on windows. Sebastian, could you darcs get the latest code  from 
http://joyful.com/repos/hledger and see if cabal configure and  build 
works for you on windows ?



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


Re: [Haskell-cafe] Expect module?

2009-01-19 Thread Donn Cave
Quoth Neil Mitchell :

>> Is there a Haskell-Expect module? Something that would allow me to
>> control an external Unix program via its stdin/stdout/stderr?
>
> System.Process does what you want, I think:

It might not.  Expect uses pseudottys (cf. openpty()), and select().

System.Process supports what you might think of as the "naive" model,
using pipes for the I/O device and making some simplifying assumptions
about the behavior of the external program.  It's more portable and
works for many common cases, at least the popen() and system() usages
that probably account for 98 percent of process invocations.

But once you need output from a process _before_ it exits, you will
encounter the problem with pipes:  output to a pipe is normally block
buffered, so it doesn't reliably get to the pipe on time.  The C I/O
library treats a pty device like a tty and line buffers output.
(But unfortunately, a pty device is not just a pipe with that single
property - I wouldn't replace pipes with ptys just as a matter of course,
because depending on the OS they may do things like discard date on
overflow, or they may be a severely limited system resource.)

select() also helps with another potential problem, when the same
process is writing to two or more pipes, which are fixed size devices.
In GHC, I suppose the potential deadlock might similarly be avoided
using threads.  I don't know if GHC supports openpty() - having a
little trouble getting data from its web site this morning.  But of
course there's more to Expect than just the raw system calls.

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


Re: [Haskell-cafe] Factoring into type classes

2009-01-19 Thread Patai Gergely
> As a side curiosity, I would love to see an example of any data structure
> which has more than one Functor instance.  Especially those which have
> more than one useful functor instance.

data Record a b = R { field1 :: a, field2 :: b }

If I want to use fmap to transform either field, I have to declare the
type to have the corresponding type variable at the end, i.e. choosing
"Record a b" or "Record b a" is already a design decision, and it is
driven by the standard Functor class in this case. I can define custom
functions fmap1 and fmap2 manually, but then I don't get the advantages
of overloading, like fmapping over a data structure containing my
records.

Now I understand that I can't get everything, and my question is mainly
what to do when such a dilemma comes up. Those who have already
encountered such a dilemma: how did it come up and what did you do to
solve it?

Gergely

-- 
http://www.fastmail.fm - Same, same, but different...

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


Re: [Haskell-cafe] How to make code least strict?

2009-01-19 Thread Thomas DuBuisson
On Mon, Jan 19, 2009 at 4:48 PM, Robin Green  wrote:
> What guidelines should one follow to make Haskell code least-strict?

There was a great Cafe discussion started by Henning on just this.  He
provided this link:

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


Re: [Haskell-cafe] plugins can not be installed in ghc 6.10.1

2009-01-19 Thread Gwern Branwen
-BEGIN PGP SIGNED MESSAGE-
Hash: SHA512

2009/1/19 Alberto G. Corona :
-BEGIN PGP SIGNATURE-
Version: GnuPG v1.4.9 (GNU/Linux)

iEYEAREKAAYFAkl0uKYACgkQvpDo5Pfl1oJ30wCfQzX80TulZxyyLLyaAcU/LPVc
PPMAoJl8tjhfrlWwoQ9yVGXlXStMDs+O
=lf6T
-END PGP SIGNATURE-

>
> Do really pluigins needs Cabal (>=1.4 && <1.5) ???
>
> C:\Documents and Settings\Administrator>cabal install plugins
> Resolving dependencies...
> cabal: dependencies conflict: ghc-6.10.1 requires Cabal ==1.6.0.1 however
> Cabal-1.6.0.1 was excluded because plugins-1.3.1 requires Cabal ==1.4.*
>
> ___
> Haskell-Cafe mailing list
> Haskell-Cafe@haskell.org
> http://www.haskell.org/mailman/listinfo/haskell-cafe
>
>

Yes. Suppose you change the deps:

hunk ./plugins.cabal 42
-  Cabal >= 1.4 && < 1.5,
+  Cabal >= 1.4,

And then try to compile, you'll see (at least for me):

[ 3 of 16] Compiling System.Plugins.ParsePkgConfCabal (
src/System/Plugins/ParsePkgConfCabal.hs,
dist/build/System/Plugins/ParsePkgConfCabal.o )

src/System/Plugins/ParsePkgConfCabal.hs:287:34:
Ambiguous occurrence `depends'
It could refer to either
`Distribution.InstalledPackageInfo.depends', imported from
Distribution.InstalledPackageInfo at
src/System/Plugins/ParsePkgConfCabal.hs:8:0-39
  or `Distribution.Package.depends', imported
from Distribution.Package at
src/System/Plugins/ParsePkgConfCabal.hs:9:0-26

src/System/Plugins/ParsePkgConfCabal.hs:300:36:
Ambiguous occurrence `depends'
It could refer to either
`Distribution.InstalledPackageInfo.depends', imported from
Distribution.InstalledPackageInfo at
src/System/Plugins/ParsePkgConfCabal.hs:8:0-39
  or `Distribution.Package.depends', imported
from Distribution.Package at
src/System/Plugins/ParsePkgConfCabal.hs:9:0-26

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


[Haskell-cafe] plugins can not be installed in ghc 6.10.1

2009-01-19 Thread Alberto G. Corona
Do really pluigins needs Cabal (>=1.4 && <1.5) ???

C:\Documents and Settings\Administrator>cabal install plugins
Resolving dependencies...
cabal: dependencies conflict: ghc-6.10.1 requires Cabal ==1.6.0.1 however
Cabal-1.6.0.1 was excluded because plugins-1.3.1 requires Cabal ==1.4.*
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] runghc Setup.hs doitall

2009-01-19 Thread Alberto G. Corona
C:\Documents and Settings\Administrator>cabal install plugins
Resolving dependencies...
cabal: dependencies conflict: ghc-6.10.1 requires Cabal ==1.6.0.1 however
Cabal-1.6.0.1 was excluded because plugins-1.3.1 requires Cabal ==1.4.*

2009/1/19 Alberto G. Corona 

>
>
> I finally installed cabal-install in windows.. I had a copy of sh.exe for
> windows time ago so I could use bootstrap. The only additional thing needed
> is wget(http://users.ugent.be/~bpuype/wget/).
> finally I moved the resulting cabal.exe to ghc/bin
>
> 2009/1/19 Duncan Coutts 
>
> On Mon, 2009-01-19 at 01:36 +0100, Alberto G. Corona wrote:
>> > The problem with Windows can be solved once and for all when CygWIN
>> > will be considered  for Windows instead of MinGW. Is that possible?
>>
>> The standard Windows build of GHC does not use Cygwin. So all the
>> programs built with GHC (like cabal) are native Windows programs and do
>> not understand Cygwin paths etc.
>>
>> If you want to build GHC for Cygwin then there is quite a bit of work
>> for you to do to update GHC to build that way.
>>
>> I get the general impression that most users would prefer not to have to
>> install Cygwin or MinGW at all.
>>
>> Duncan
>>
>>
>
>
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] Re: How to make code least strict?

2009-01-19 Thread ChrisK

Robin Green wrote:

What guidelines should one follow to make Haskell code least-strict?


Obviously the use of "seq" and bang-patterns make code more strict.

Code is strict when it evaluates values to determine a pattern match.  So 
avoiding that makes code lazier.  Values are evaluated when decisions have to be 
make in order to choose what an expression will evaluate to.  Avoiding "case" 
statements and things that de-sugar to case statements such as "if then else" 
and pattern matching.  Put off examining the input values.  Occasionally the use 
of "lazy" patterns, preceded by ~, can help make code both more compact and less 
strict.


Consider that the order of pattern matching can matter as well, the simplest 
common case being zip:


zip xs [] = []
zip [] ys = []
zip (x:xs) (y:ys) = (x,y) : zip xs ys

The order of the first two lines of zip's definition affects whether
zip [] (error "boom")
or
zip (error "bam") []
will be an error.  This shows that "least-strict" is not a unique goal.

For the choice I just made the "zip [] (error "boom")" will cause an error 
because the first definition line of zip checks the second argument, while "zip 
(error "bam") []" will evaluate to [].


The other way to reduce strictness is to be more polymorphic because this 
reduces what can be sensibly done with the arguments.


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


[Haskell-cafe] How to make code least strict?

2009-01-19 Thread Robin Green
What guidelines should one follow to make Haskell code least-strict?
-- 
Robin
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Factoring into type classes

2009-01-19 Thread Lennart Augustsson
The desugaring of (, a) would involve some type level lambda, and
that's not something that is available (yet).

  -- Lennart

On Mon, Jan 19, 2009 at 1:49 PM, Holger Siegel  wrote:
> Am Montag, den 19.01.2009, 14:47 +0100 schrieb Daniel Fischer:
>> Am Montag, 19. Januar 2009 14:31 schrieb Antoine Latter:
>> > 2009/1/19 Luke Palmer :
>> > > As a side curiosity, I would love to see an example of any data structure
>> > > which has more than one Functor instance.  Especially those which have
>> > > more than one useful functor instance.
>> >
>> > (,)  ?
>> >
>> > -Antoine
>>
>> Wrong kind. And
>> (,) a
>> has only one useful instance.
>
>
> What about
>
> instance Functor ((,) a) where
>fmap f (x,y) = (x, f y)
>
> and
>
> instance Functor (, a) where
>fmap f (x, y) = (f x, y)
>
> ? Of course, the latter is not legal Haskell. But if it was, then it
> might be useful.
>
> Is there any way to declare this Functor instance, possibly with some
> GHC extensions?
>
>
>
> ___
> Haskell-Cafe mailing list
> Haskell-Cafe@haskell.org
> http://www.haskell.org/mailman/listinfo/haskell-cafe
>
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] Re: ANNOUNCE: Coadjute 0.0.1, generic build tool

2009-01-19 Thread Matti Niemenmaa

Nicolas Pouillard wrote:

Excerpts from Matti Niemenmaa's message of Sun Jan 18 19:47:46 +0100 2009:

   3. Coadjute keeps track of command line arguments (see docs for
  details): for me this is really a killer feature, I don't know of
  anything else which does this.


ocamlbuild does this.


   4. hake always uses timestamps, Coadjute can use MD5 hashes as well.
   5. Coadjute can have arbitrary path specifications, hake's rules seem
  to be based on file extensions only, thus applying only to the
  current directory. Peter Miller's "Recursive Make Considered
  Harmful" comes to mind: http://miller.emu.id.au/pmiller/books/rmch/


[...]

Moreover, it seems that Coadjute and ocamlbuild share a fair number of design
choices, maybe having a look at it could be fruitful.


Thanks, I hadn't heard of that one. It seems to be somewhat oriented 
towards OCaml but I'll take a look.


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


Fwd: [Haskell-cafe] runghc Setup.hs doitall

2009-01-19 Thread Alberto G. Corona
I finally installed cabal-install in windows.. I had a copy of sh.exe for
windows time ago so I could use bootstrap. The only additional thing needed
is wget(http://users.ugent.be/~bpuype/wget/).
finally I moved the resulting cabal.exe to ghc/bin

2009/1/19 Duncan Coutts 

On Mon, 2009-01-19 at 01:36 +0100, Alberto G. Corona wrote:
> > The problem with Windows can be solved once and for all when CygWIN
> > will be considered  for Windows instead of MinGW. Is that possible?
>
> The standard Windows build of GHC does not use Cygwin. So all the
> programs built with GHC (like cabal) are native Windows programs and do
> not understand Cygwin paths etc.
>
> If you want to build GHC for Cygwin then there is quite a bit of work
> for you to do to update GHC to build that way.
>
> I get the general impression that most users would prefer not to have to
> install Cygwin or MinGW at all.
>
> Duncan
>
>
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Re: ANNOUNCE: Coadjute 0.0.1, generic build tool

2009-01-19 Thread Nicolas Pouillard
Excerpts from Matti Niemenmaa's message of Sun Jan 18 19:47:46 +0100 2009:
> Henning Thielemann wrote:
> > Matti Niemenmaa schrieb:
> >> Announcing the release of Coadjute, version 0.0.1!
> >>
> >> Web site: http://iki.fi/matti.niemenmaa/coadjute/
> >> Hackage:
> >> http://hackage.haskell.org/cgi-bin/hackage-scripts/package/Coadjute
> 
> > How does it compare to
> >http://hackage.haskell.org/cgi-bin/hackage-scripts/package/hake
> 
> Short answer: the question that comes to mind is "how does hake compare 
> to make?" Coadjute seems to be more capable, in general, but then I 
> don't know pretty much anything about hake.
> 
> Somewhat longer answer:
> 
> Coadjute is better in that:
>1. hake's documentation is rather sparse. I have no idea what most
>   functions do, or even what exactly the main program does.
>2. hake doesn't seem to do parallel builds, but I'm not sure because
>   of point 1.
>3. Coadjute keeps track of command line arguments (see docs for
>   details): for me this is really a killer feature, I don't know of
>   anything else which does this.

ocamlbuild does this.

>4. hake always uses timestamps, Coadjute can use MD5 hashes as well.
>5. Coadjute can have arbitrary path specifications, hake's rules seem
>   to be based on file extensions only, thus applying only to the
>   current directory. Peter Miller's "Recursive Make Considered
>   Harmful" comes to mind: http://miller.emu.id.au/pmiller/books/rmch/

[...]

Moreover, it seems that Coadjute and ocamlbuild share a fair number of design
choices, maybe having a look at it could be fruitful.

Best regards,

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


Re: [Haskell-cafe] Factoring into type classes

2009-01-19 Thread Holger Siegel
Am Montag, den 19.01.2009, 14:47 +0100 schrieb Daniel Fischer:
> Am Montag, 19. Januar 2009 14:31 schrieb Antoine Latter:
> > 2009/1/19 Luke Palmer :
> > > As a side curiosity, I would love to see an example of any data structure
> > > which has more than one Functor instance.  Especially those which have
> > > more than one useful functor instance.
> >
> > (,)  ?
> >
> > -Antoine
> 
> Wrong kind. And 
> (,) a
> has only one useful instance.


What about

instance Functor ((,) a) where
fmap f (x,y) = (x, f y)

and

instance Functor (, a) where
fmap f (x, y) = (f x, y)

? Of course, the latter is not legal Haskell. But if it was, then it
might be useful.

Is there any way to declare this Functor instance, possibly with some
GHC extensions?



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


Re: [Haskell-cafe] Factoring into type classes

2009-01-19 Thread Daniel Fischer
Am Montag, 19. Januar 2009 14:31 schrieb Antoine Latter:
> 2009/1/19 Luke Palmer :
> > As a side curiosity, I would love to see an example of any data structure
> > which has more than one Functor instance.  Especially those which have
> > more than one useful functor instance.
>
> (,)  ?
>
> -Antoine

Wrong kind. And 
(,) a
has only one useful instance.
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Factoring into type classes

2009-01-19 Thread Thomas DuBuisson
2009/1/19 Luke Palmer :
> On Mon, Jan 19, 2009 at 3:58 AM, Patai Gergely 
> wrote:
>>
>> However, there are other type classes that are too general to assign
>> such concrete uses to. For instance, if a data structure can have more
>> than one meaningful (and useful) Functor or Monoid instance,
>
> As a side curiosity, I would love to see an example of any data structure
> which has more than one Functor instance.  Especially those which have more
> than one useful functor instance.
> Luke

The recent, and great, blog post about moniods [1] discusses the fact
that (Num a) could be one of several different monoids and how that
was handled.

[1] http://sigfpe.blogspot.com/2009/01/haskell-monoids-and-their-uses.html
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Factoring into type classes

2009-01-19 Thread Antoine Latter
2009/1/19 Luke Palmer :
> As a side curiosity, I would love to see an example of any data structure
> which has more than one Functor instance.  Especially those which have more
> than one useful functor instance.

(,)  ?

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


[Haskell-cafe] Re: Bug in Text.Regex.PCRE - do not accept national symbol in pattern

2009-01-19 Thread ChrisK

Alexandr,

  Thanks for sending me this question about unicode and regex-pcre.  I will 
share with the mailing list. This is an encoding issue.


From the haddock documentation for regex-pcre:

http://hackage.haskell.org/packages/archive/regex-pcre/0.94.1/doc/html/Text-Regex-PCRE.html

"Using the provided CompOption and ExecOption values and if configUTF8 is
True, then you might be able to send UTF8 encoded ByteStrings to PCRE and get
sensible results. This is currently untested."


This is a literate Haskell post so you can save with file extension
".lhs" and pass this to ghci.

The answer is a combination of "man 3 pcre" and the haddock
documentation for haskell-pcre and using makeRegexOpts.  I show one
possible way to use utf8 below, via the 'utf8-string' package from
hackage.  There are other ways to use the same package and other
packages available.

> {-# LANGUAGE FlexibleContexts #-}
> import Text.Regex.PCRE hiding ((=~))
> --import Text.Regex.PCRE.Wrap(configUtf8)
> import qualified Data.ByteString.UTF8 as U
> import qualified System.IO.UTF8 as U
> import Data.Bits((.|.))
>

Here I copied the original source for (=~) from
http://hackage.haskell.org/packages/archive/regex-pcre/0.94.1/doc/html/Text-Regex-PCRE-Wrap.html#v%3A%3D~
I then editied it to create a custom (=~) that defines its own
options.  You can add compNoUTF8Check for performance/safety tradeoff
(see man 3 pcre).

> makeRegexUtf8 :: (RegexMaker Regex CompOption ExecOption source) => source -> 
Regex
> makeRegexUtf8 r = let co = defaultCompOpt .|. compUTF8 -- need compUTF8 flag 
when using makeRegexOpts

>   -- co = defaultCompOpt .|. compUTF8 .|. compNoUTF8Check 
 --
>   in makeRegexOpts co defaultExecOpt r

> (=~)  :: (RegexMaker Regex CompOption ExecOption source,RegexContext Regex 
source1 target)

>   => source1 -> source -> target
> (=~) x r = let q = makeRegexUtf8 r
>in match q x

If you are going to use the same pattern against many different texts
then you should NOT use (=~).  Instead you should call makeRegexUtf8
and reuse the resulting Regex value.  Otherwise you have to recompile
the pattern for each match performed.

Below, 're_test' was changed internally to convert the [Char] into a
ByteString holding a utf8 encoded representation.  The 'makeRegexOpts'
and 'match' calls will then run the libpcre routines directly on the
the memory that backs the ByteString.  This is an optimal was to use
the library.

> re_test :: String -> String -> Bool
> re_test re str = (U.fromString str) =~ (U.fromString re)
>
> -- test for national symbols
> main = do
>   putStrLn $ "If this line ends with True then your libpcre has UTF8 support: 
" ++ show configUTF8

>   let pattern1,pattern2,pattern3,text :: String
>   pattern1 = "^п.*"
>   pattern2 = "^..ив.*"
>   pattern3 = "^..$"
>   text = "привет"
>   U.putStrLn $ "The 3 patterns are: " ++ pattern1 ++ ", " ++ pattern2 ++ ", 
and "++pattern3

>   U.putStrLn $ "The text to be matched is " ++ text
>   putStrLn $ "The length of the text to be matched is "++show (length text)
>   putStrLn "All three lines below should print True"
>   print $ re_test pattern1 text
>   print $ re_test pattern2 text
>   print $ re_test pattern3 text

The output when I run this on my machine is

If this line ends with True then your libpcre has UTF8 support: True
The 3 patterns are: ^п.*, ^..ив.*, and ^..$
The text to be matched is привет
The length of the text to be matched is 6
All three lines below should print True
True
True
True

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


[Haskell-cafe] Re: ANNOUNCE: Coadjute 0.0.1, generic build tool

2009-01-19 Thread Matti Niemenmaa

Paul Moore wrote:

2009/1/18 Matti Niemenmaa :

Announcing the release of Coadjute, version 0.0.1!

[...]

 Portability is striven towards in two ways:


Is it intended to work on Windows? (I don't want to spend time
downloading and trying to set it up if it was never intended to be
Windows-compatible.)


Yes, all my software is unless I explicitly say it isn't. :-)

In fact, I've both developed and used it mostly on Windows.

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


[Haskell-cafe] Re: Different return type?

2009-01-19 Thread Chung-chieh Shan
John Ky  wrote in article 
 in 
gmane.comp.lang.haskell.cafe:
> data Person = Person { name :: String, ... }
> data Business = Business { business_number :: Int, ...}
>
> key person = name person
> key business = business_number business

Let's make this concrete:

  data Person = Person { name :: String, age :: Integer }
  data Business = Business { business_number :: Int, revenue :: Double }

  key person = name person
  key business = business_number business

Even without dependent types, you can do the following (but of course,
you lose some syntactic sugar for records):

  data Individual k v = Individual { key :: k, value :: v }
  type Person = Individual String Integer
  type Business = Individual Int Double

  name :: Person -> String
  name = key

  age :: Person -> Integer
  age = value

  business_number :: Business -> Int
  business_number = key

  revenue :: Business -> Double
  revenue = value

-- 
Edit this signature at http://www.digitas.harvard.edu/cgi-bin/ken/sig
May all beings be well and happy!~

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


Re: [Haskell-cafe] Factoring into type classes

2009-01-19 Thread Luke Palmer
On Mon, Jan 19, 2009 at 3:58 AM, Patai Gergely wrote:

> However, there are other type classes that are too general to assign
> such concrete uses to. For instance, if a data structure can have more
> than one meaningful (and useful) Functor or Monoid instance,


As a side curiosity, I would love to see an example of any data structure
which has more than one Functor instance.  Especially those which have more
than one useful functor instance.

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


Re: [Haskell-cafe] ANNOUNCE: Coadjute 0.0.1, generic build tool

2009-01-19 Thread Paul Moore
2009/1/18 Matti Niemenmaa :
> Announcing the release of Coadjute, version 0.0.1!
[...]
>  Portability is striven towards in two ways:

Is it intended to work on Windows? (I don't want to spend time
downloading and trying to set it up if it was never intended to be
Windows-compatible.)

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


[Haskell-cafe] Re: ANNOUNCE: Coadjute 0.0.1, generic build tool

2009-01-19 Thread Matti Niemenmaa

Brandon S. Allbery KF8NH wrote:

On 2009 Jan 18, at 13:47, Matti Niemenmaa wrote:

 3. Coadjute keeps track of command line arguments (see docs for
details): for me this is really a killer feature, I don't know of
anything else which does this.


It's been done many times before; it never seems to catch on.  My 
personal favorite was Shape (http://user.cs.tu-berlin.de/~shape/) which 
I used for a few local projects in the late 80s.  SCons is perhaps the 
most popular tool in this class (and itself a Pythonization of the 
original Perl Cons; maybe it's time for HCons?), followed by Apache's 
Ant (I don't think that actually caches command lines or binaries 
though), then Jam and successors.


Actually, you're right, and I misspoke: I know about SCons and didn't 
like it (see below for brief rant)—Coadjute is the only truly /generic/ 
build tool I knew of which does it.


The main thing I'll mention that turned me off SCons was that it tries 
to do too much stuff automatically: it's very much built around the idea 
that you just give it a filename and it figures out what to do. E.g. 
"foo.hs" and it detects what files it depends on, what Haskell compilers 
you've got, picks one (arbitrarily?), and compiles all the sources into 
a binary.


(On my Windows machine this meant fun delays of multiple seconds prior 
to every build, as it scanned all the directories in PATH for several 
binaries which it never found: looking for various C compilers while I 
haven't even specified C dependencies.)


I found it quite difficult (verbose and non-obvious) and probably 
against its philosophies to just say "here is foo.hs, it depends on 
foo.c, don't do anything else with them and just run the following 
command if foo.hs needs to be built."


To be completely honest I don't like the idea of SCons in itself: it 
seems to be something in between platform-specific tools like Cabal and 
generic ones like make or Coadjute. Maybe I'm just too dense, or maybe 
it's a documentation problem, but it's just not something I'd use for 
pretty much anything. (C/C++ don't really have tools geared specifically 
for them (CMake?) so that might be one case where I would.)


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


Re: [Haskell-cafe] Factoring into type classes

2009-01-19 Thread Eugene Kirpichov
As for multiple Monoid or Functor instances, simply define a newtype,
as it is done in Data.Monoid.
What part of your question does that answer and what part doesn't it?

2009/1/19 Patai Gergely :
> Hi everyone,
>
> I have a general program design question, but I can't really think of
> good examples so it will be a bit vague. There was a discussion on Show
> not long ago which brought up the problem that there are several ways to
> "show" a data structure, and it depends on the context (or should I call
> it a use case?) which of these we actually want, e.g. human readable
> form, debug information, serialisation for later reading and so on, and
> one of the solutions was to propose a family of show functions that
> carry the intended use in their name.
>
> However, there are other type classes that are too general to assign
> such concrete uses to. For instance, if a data structure can have more
> than one meaningful (and useful) Functor or Monoid instance, what should
> one do? Should one refrain from instantiating these classes altogether
> and just use the names of operations directly? If one still decides to
> pick a certain set of operations as an instance, what are the factors
> that should guide this decision? What about designing libraries, how
> much should one prefer standard classes for their interfaces?
>
> It seems to me that there is practically no literature on design issues
> like these, and it would be nice to hear some opinions from experienced
> Haskellers.
>
> Gergely
>
> --
> http://www.fastmail.fm - The way an email service should be
>
> ___
> Haskell-Cafe mailing list
> Haskell-Cafe@haskell.org
> http://www.haskell.org/mailman/listinfo/haskell-cafe
>
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] Factoring into type classes

2009-01-19 Thread Patai Gergely
Hi everyone,

I have a general program design question, but I can't really think of
good examples so it will be a bit vague. There was a discussion on Show
not long ago which brought up the problem that there are several ways to
"show" a data structure, and it depends on the context (or should I call
it a use case?) which of these we actually want, e.g. human readable
form, debug information, serialisation for later reading and so on, and
one of the solutions was to propose a family of show functions that
carry the intended use in their name.

However, there are other type classes that are too general to assign
such concrete uses to. For instance, if a data structure can have more
than one meaningful (and useful) Functor or Monoid instance, what should
one do? Should one refrain from instantiating these classes altogether
and just use the names of operations directly? If one still decides to
pick a certain set of operations as an instance, what are the factors
that should guide this decision? What about designing libraries, how
much should one prefer standard classes for their interfaces?

It seems to me that there is practically no literature on design issues
like these, and it would be nice to hear some opinions from experienced
Haskellers.

Gergely

-- 
http://www.fastmail.fm - The way an email service should be

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


[Haskell-cafe] Re: Different return type?

2009-01-19 Thread Jon Fairbairn
"John Ky"  writes:

> Hi,
>
> Possibly a silly question but is it possible to have a function that has a
> different return type based on it's first argument?

Are you sure that's what you really want?

> For instance
>
> data Person = Person { name :: String, ... }
> data Business = Business { business_number :: Int, ...}

data Entity = Person {...} | Business {...}

> key person = name person
> key business = business_number business

data Key = PersonKey String | BusinessKey Int

It seems likely that you are at least sometimes going to
want to pass the result of key to some other function.

...?

-- 
Jón Fairbairn jon.fairba...@cl.cam.ac.uk
http://www.chaos.org.uk/~jf/Stuff-I-dont-want.html  (updated 2008-04-26)

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


Re: [Haskell-cafe] Different return type?

2009-01-19 Thread Miran Lipovaca

Hello!
I wouldn't use either. It seems like it complicates things quite a lot and it 
looks like this could be solved more simply by setting up the data types or 
organizing functions differently.
Is there a specific problem that you're solving or are you just curious about 
different return types based on input types?


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


Re: [Haskell-cafe] Graham-Scan Algorithm exercise from Chapter 3 Real World Haskell

2009-01-19 Thread Daniel Fischer
Am Montag, 19. Januar 2009 10:17 schrieb Daniel Fischer:
> Am Montag, 19. Januar 2009 09:32 schrieb Michael Litchard:
> > I have started the Graham Scan Algorithm exercise. I'm getting tripped
> > up by the sortByCotangent* function.
> > Here's what I have so far
> >
> > data Direction = DStraight
> >
> >| DLeft
> >| DRight
> >
> >  deriving (Eq,Show)
> > type PointXY = (Double,Double)
> >
> > calcTurn :: PointXY -> PointXY -> PointXY -> Direction
> > calcTurn a b c
> >
> > | crossProduct == 0 = DStraight
> > | crossProduct > 0  = DLeft
> > | otherwise = DRight
> >
> >where crossProduct = ((fst b - fst a) * (snd c - snd a)) -
> > ((snd b - snd a) * (fst c - fst a))
> >
> >
> > calcDirectionList :: [PointXY] -> [Direction]
> > calcDirectionList (x:y:z:zs) = (calcTurn x y z) : (calcDirectionList
> > (y:z:zs)) calcDirectionList _ = []
> >
> > sortListByY :: [PointXY] -> [PointXY]
> > sortListByY [] = []
> > sortListByY [a] = [a]
> > sortListByY (a:as) = insert (sortListByY as)
> >where insert [] = [a]
> >  insert (b:bs) | snd a <= snd b = a : b : bs
> >
> >| otherwise  = b : insert bs
>
> I think it would be easier to see what the code does if you had it
>
> sortListByY [] = []
> sortListByY (a:as) = insertByY a (sortListByY as)
>   where
>   insertByY a (b:bs)
>
>   | snd a <= snd b = a:b:bs
>   | otherwise = b:insertByY a bs
>
>   insertByY a [] = [a]
>
> analogously for sortListByCoTangent.
>
> > sortListByCoTangent :: [PointXY] -> [PointXY]
> > sortListByCoTangent [] = []
> > sortListByCoTangent [a] = [a]
> > sortListByCoTangent (a:as) = a : insert (sortListByCoTangent as)
> >  where insert :: [PointXY] -> [PointXY]
> >insert [] = [a]
>
>   ^^
> shouldn't that be insert [] = [], if at all? However, this will never be
> encountered, so you can delete it.
>
> >insert [b] = [b]
> >insert (b:c:cs) | (myCoTan a b) >= (myCoTan a
> > c) =  b : c : cs
> >
> >| otherwise
> >
> >  =  c : b : insert cs
>
> There's the oops. You can only pass one point at a time, so it should be
> ... b:insert (c:cs)
> resp.
> ... c:insert (b:cs)
>
> >  where myCoTan :: PointXY -> PointXY ->
> > Double myCoTan p1 p2 = (fst p2 - fst p1) / (snd p2 - snd p1)
> >
> > test data
> > *Main> sortListByCoTangent (sortListByY
> > [(1,2),(2,6),(3,10),(4,9),(5,10),(2,20),(6,15)])
> > [(1.0,2.0),(5.0,10.0),(2.0,6.0),(4.0,9.0),(6.0,15.0),(3.0,10.0),(2.0,20.0
> >)]
> >
> > (1,0,2.0) is correct. That's the pivot point. It screws up from there.
> >
> > I suspect my insert is hosed, but I'm having difficulty analyzing the
> > logic of the code. I'd like hints/help but with the following
> > boundaries.
> >
> > (1) I want to stick with the parts of the language that's been
> > introduced in the text so far. I know there are solutions that make
> > this problem trivial, however using those misses the point.
> > (2) I'd prefer going over the logic of my code, versus what is
> > supposed to happen. I'm trying to learn how to troubleshoot haskell
> > code, more than implement the graham scan algorithm.
>
> Walk through your code by hand for very small inputs (say four or five
> vertices in several orders). Then you see how exactly it works, and find
> more easily what's wrong (and what to rewrite in a clearer fashion).
>
> > I appreciate any help/hints

Another thing, your sortListByCoTangent is inefficient because you 
unnecessarily sort all tails of the list according to their first element, 
while you only want to sort according to the very first element of the entire 
list. Also, you recompute the cotangent of all segments, it would probably be 
better to calculate it only once.

sortListByCoTangent [] = []
sortListByCoTangent [a] = [a]
sortListByCoTangent (a:bs) = a:map point (sortBC (map addCT bs))
  where
addCT b = (fst b - fst a, snd b - snd a, b)
point (dx,dy,p) = p
sortBC [] = []
sortBC (t:ts) = insert t (sortBC ts)
insert t [] = [t]
insert (dx1,dy1,p1) ((dx2,dy2,p2):ts)
| dx1*dy2 < dx2*dy1 = (dx2,dy2,p2):insert (dx1,dy1,p1) ts
| otherwise = (dx1,dy1,p1):(dx2,dy2,p2):ts

sorts only once. However, it is still an insertion sort, which is not the most 
efficient sorting method.
> >
> >
> > Michael Litchard
> >
> > *It seems the wikipedia page on the graham scan algorithm is wrong
> > concerning the following part of the algorithm.
> > "...instead, it suffices to calculate the tangent of this angle, which
> > can be done with simple arithmetic."
> > Someone from #haskell said that it's the cotangent I want, and my math
> > tutor confirmed. If this is the case, I suppose we should submit a
> > correction.
>
> Actual

[Haskell-cafe] Re: Comments from OCaml Hacker Brian Hurt

2009-01-19 Thread Heinrich Apfelmus
david48 wrote:
> Apfelmus, Heinrich wrote:
>
>> Hm, what about the option of opening Bird's "Introduction on Functional
>> Programming using Haskell" in the section about fold? Monoid is on page
>> 62 in the translated copy I've got here.
>
>> I don't think that I would try to learn a programming language, for
>> example Python, without obtaining a paper book on it.
> 
> I would, if the online documentation makes it possible, and then I
> would buy a paper book later, to go further or for reference.
> That's how I learned Haskell, and much later I've bought my first book.

Interesting, I wouldn't want to miss actual paper when learning
difficult topics. Also, some great resources like the contents of Bird's
book just aren't available online ;). I'd recommend to borrow it from a
library, though, the current amazon price is quite outrageous.


Regards,
apfelmus

-- 
http://apfelmus.nfshost.com

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


Re: [Haskell-cafe] Graham-Scan Algorithm exercise from Chapter 3 Real World Haskell

2009-01-19 Thread Daniel Fischer
Am Montag, 19. Januar 2009 09:32 schrieb Michael Litchard:
> I have started the Graham Scan Algorithm exercise. I'm getting tripped
> up by the sortByCotangent* function.
> Here's what I have so far
>
> data Direction = DStraight
>
>| DLeft
>| DRight
>
>  deriving (Eq,Show)
> type PointXY = (Double,Double)
>
> calcTurn :: PointXY -> PointXY -> PointXY -> Direction
> calcTurn a b c
>
> | crossProduct == 0 = DStraight
> | crossProduct > 0  = DLeft
> | otherwise = DRight
>
>where crossProduct = ((fst b - fst a) * (snd c - snd a)) -
> ((snd b - snd a) * (fst c - fst a))
>
>
> calcDirectionList :: [PointXY] -> [Direction]
> calcDirectionList (x:y:z:zs) = (calcTurn x y z) : (calcDirectionList
> (y:z:zs)) calcDirectionList _ = []
>
> sortListByY :: [PointXY] -> [PointXY]
> sortListByY [] = []
> sortListByY [a] = [a]
> sortListByY (a:as) = insert (sortListByY as)
>where insert [] = [a]
>  insert (b:bs) | snd a <= snd b = a : b : bs
>
>| otherwise  = b : insert bs

I think it would be easier to see what the code does if you had it

sortListByY [] = []
sortListByY (a:as) = insertByY a (sortListByY as)
  where
insertByY a (b:bs)
| snd a <= snd b = a:b:bs
| otherwise = b:insertByY a bs
insertByY a [] = [a]

analogously for sortListByCoTangent.
>
> sortListByCoTangent :: [PointXY] -> [PointXY]
> sortListByCoTangent [] = []
> sortListByCoTangent [a] = [a]
> sortListByCoTangent (a:as) = a : insert (sortListByCoTangent as)
>  where insert :: [PointXY] -> [PointXY]
>insert [] = [a]
^^
shouldn't that be insert [] = [], if at all? However, this will never be 
encountered, so you can delete it.

>insert [b] = [b]
>insert (b:c:cs) | (myCoTan a b) >= (myCoTan a
> c) =  b : c : cs
>
>| otherwise
>
>  =  c : b : insert cs

There's the oops. You can only pass one point at a time, so it should be
... b:insert (c:cs)
resp.
... c:insert (b:cs)


>  where myCoTan :: PointXY -> PointXY -> Double
>myCoTan p1 p2 = (fst p2 - fst p1) /
> (snd p2 - snd p1)
>
> test data
> *Main> sortListByCoTangent (sortListByY
> [(1,2),(2,6),(3,10),(4,9),(5,10),(2,20),(6,15)])
> [(1.0,2.0),(5.0,10.0),(2.0,6.0),(4.0,9.0),(6.0,15.0),(3.0,10.0),(2.0,20.0)]
>
> (1,0,2.0) is correct. That's the pivot point. It screws up from there.
>
> I suspect my insert is hosed, but I'm having difficulty analyzing the
> logic of the code. I'd like hints/help but with the following
> boundaries.
>
> (1) I want to stick with the parts of the language that's been
> introduced in the text so far. I know there are solutions that make
> this problem trivial, however using those misses the point.
> (2) I'd prefer going over the logic of my code, versus what is
> supposed to happen. I'm trying to learn how to troubleshoot haskell
> code, more than implement the graham scan algorithm.

Walk through your code by hand for very small inputs (say four or five 
vertices in several orders). Then you see how exactly it works, and find more 
easily what's wrong (and what to rewrite in a clearer fashion).

>
> I appreciate any help/hints
>
>
> Michael Litchard
>
> *It seems the wikipedia page on the graham scan algorithm is wrong
> concerning the following part of the algorithm.
> "...instead, it suffices to calculate the tangent of this angle, which
> can be done with simple arithmetic."
> Someone from #haskell said that it's the cotangent I want, and my math
> tutor confirmed. If this is the case, I suppose we should submit a
> correction.

Actually, both will do. Using the tangent requires a little sophistication in 
sorting, though (first positive tangent in increasing order, then infinity if 
it appears, finally negative tangent in decreasing order), so it's not 
technically wrong, but the cotangent is better.

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


[Haskell-cafe] Re: walking a directory tree efficiently

2009-01-19 Thread Paolo Losi

Massimiliano Gubinelli wrote:

Hi,
 what about avoid the use of the unfold over the tree and construct it
directly (e.g. see http://hpaste.org/13919#a3)? 


Nice solution!


I wonder if there is (an
easy) possibility to construct the tree lazily so that output start
immediately for large trees.


I think the modular approach would be that of using
a fold-left enumerator that produces the list of paths
and navigation operations by traversing the dir hierarchy "Depth First":

data DirTraversalInfo = Path String
  | DirUp
  | DirDown

I guess you know:
http://okmij.org/ftp/papers/LL3-collections-talk.pdf


best,
Massimiliano Gubinelli


Ciao
Paolo

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


Re: [Haskell-cafe] Expect module?

2009-01-19 Thread Neil Mitchell
Hi Erik,

> Is there a Haskell-Expect module? Something that would allow me to
> control an external Unix program via its stdin/stdout/stderr?

System.Process does what you want, I think:

http://hackage.haskell.org/packages/archive/process/1.0.1.1/doc/html/System-Process.html

Thanks

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


  1   2   >