Re: [Haskell-cafe] I love purity, but it's killing me.

2008-02-08 Thread Bulat Ziganshin
Hello Tom,

Friday, February 8, 2008, 9:33:35 AM, you wrote:

 The process of converting an expression tree to a graph uses either Eq
 or Ord (either derived or a custom instance) to search and build a set
 of unique nodes to be ordered for execution.

in similar situation, i've added hash field to each node, initialized
by smart constructor:

data Expression = Add Hash Expression Expression | ...
type Hash=Int

add x y = Add (x*y+1234567) x y
...


-- 
Best regards,
 Bulatmailto:[EMAIL PROTECTED]

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


Re: [Haskell-cafe] I love purity, but it's killing me.

2008-02-08 Thread Henning Thielemann

On Fri, 8 Feb 2008, Tom Hawkins wrote:

 I've been programming with Haskell for a few years and love it.  One
 of my favorite applications of Haskell is using for domain specific
 languages.  However, after designing a handful of DSLs, I continue to
 hit what appears to be a fundamental hurdle -- or at least I have yet
 to find an adequate solution.

It seems to become a FAQ. I think all DSLs suffer from the same problems:
sharing and recursion. I've used wrappers for CSound, SuperCollider,
MetaPost, they all have these problems.
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] FP and Quality

2008-02-08 Thread Dougal Stanton
On 07/02/2008, Benjamin L. Russell [EMAIL PROTECTED] wrote:

 - text follows immediately after this line -
 Haskell vs. Ada vs. C++ vs. Awk vs. ... An Experiment
 in Software Prototyping Productivity (1994),
 by Paul Hudak and Mark P. Jones:
 http://citeseer.ist.psu.edu/41732.html

This one's quite interesting but refers to the much longer report. In
the bibliography it is listed as unpublished, but during the text the
authors suggest you read it anyway. Does anyone have a source for this
document. (A quick search has only produced further citations in other
places.)

J.A.N. Lee, B. Blum, P. Kanellakis, H. Crisp, and J.A. Caruso.
ProtoTech HiPer-D Joint Prototyping Demonstration Project, February
1994. Unpublished; 400 pages.


Cheers,

D

-- 
Dougal Stanton
[EMAIL PROTECTED] // http://www.dougalstanton.net
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] I love purity, but it's killing me.

2008-02-08 Thread Matthew Naylor
Hi,

(Warning: longish message!)

There is some concern, and rightly so, that observable sharing is
dangerous, and that your Haskell program will explode if you use it,
and perhaps even that anyone who uses it is dirty and should be sent
to matron's for a good scrubbing!  However, when used safely, it is
not a hack, nor even dirty, but a nice, simple solution to an
otherwise nasty problem.  Below I define what I mean by safely.

First consider the circumstances under which obserevable sharing is
useful.  Typically we have some Haskell function f that produces a
symbolic representation of an expression.  For whatever reason, we'd
like to *generate a program* that computes the value of this
expression, rather that computing it in Haskell.  For example, in
Lava, we want to generate a VHDL program so that the expression can be
computed on, say, an FPGA.  In Tom's case, he wants to generate a C
program to compute the expression.  All perfectly reasonable, and in
my opinion, a very powerfull way to use Haskell.

Now recall that referential transparency lets you replace equals with
equals without changing the *value produced* by a program.  Note that
it says nothing about preserving *runtime behaviour*.  Sharing, for
example, may be lost.  So if you do equational reasoning on function
f (above), and loose some sharing, then you can only expect that the
same sharing will also be also lost in the generated program.  As long
as the generated program computes the same result as it did before,
referential transparency will be, overall, preserved; it would only be
lost intermediately.  This is what I mean by safe.

Now, there remains the concern that Haskell's semantics does not
enforce sharing.  A Haskell compiler is free to change the sharing a
program at a whim, unknowingly to the programmer who may be relying on
it in for an efficient program.  However, to my knowledge, it is an
unwritten rule of Haskell compilers that sharing *is* preserved, and
that they do perform *graph* reduction.  Clean, a similar language to
Haskell, indeed has a semantics based on graphs.  So I don't believe
Haskell being non-strict (not necessarily lazy) is a good reason for
not using observable sharing.  Though I do feel better when I compile
without -O. :-)

Finally, when I say observable sharing, I don't necessarily mean it
as defined by Koen Claessen and David Sands.  I simply mean the use of
unsafePerformIO to detect sharing, whether or not this is done by an
eq predicate on Refs. (I say this because I think there are simpler
ways to detect sharing, though these will probably not have the nice
semantic properties of observable sharing.)

Sorry for the somewhat long exposition. :-)

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


Re: [Haskell-cafe] Draft chapters of Real World Haskell now publicly available

2008-02-08 Thread Wolfgang Jeltsch
Am Donnerstag, 7. Februar 2008 18:33 schrieben Sie:
 Interesting. Thanks for the reply.

 It might be nice to have some performance benchmarks for all these
 experimental systems, so we can compare them.

I think, the most important thing is the asymptotical time behavior, e.g., 
whether the time of a certain task is linear, logarithmic or constant in the 
number of widgets.  Constant factors can always be improved.  So performance 
benchmarks don’t seem so important to me in the current early state of FRP 
GUI libraries.

 I could understand that performance might be an issue for games, but for
 GUIs? I mean many imperative GUI systems use rather slow message
 dispatching systems, and we use those every day. Look at the new Windows
 Presentation Foundation system found in VISTA. Here events are broadcasted
 and routed through the whole element tree. This is also rather slow I
 guess.

Are they rooted through every node of the tree (linear time) or are they 
routed down the tree to a leaf (not more than logarithmic time, probably).  
The latter would be acceptable, the former not.  The problem I noted on the 
Grapefruit talk page might result in a Yampa-based GUI taking linear time for 
handling a single event (but I’m not completely sure about that).

Does Vista’s event handling really have linear behavior as your statement 
seems to suggest?

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


[Haskell-cafe] Re: threads + IORefs = Segmentation fault?

2008-02-08 Thread Simon Marlow

David Roundy wrote:


I'm working on some new progress-reporting code for darcs, and am getting
segmentation faults!  :( The code uses threads + an IORef global variable
to do this (with lots of unsafePerformIO).  So my question for the gurus
who know more about this than I do:  is this safe? I thought it would be,
because only one thread ever modifies the IORef, and the others only read
it.  I don't really care if they read a correct value, as long as they
don't segfault.

The code (to summarize) looks like:

{-# NOINLINE _progressData #-}
_progressData :: IORef (Map String ProgressData)
_progressData = unsafePerformIO $ newIORef empty

updateProgressData :: String - (ProgressData - ProgressData) - IO ()
updateProgressData k f = when (progressMode) $ modifyIORef _progressData 
(adjust f k)

setProgressData :: String - ProgressData - IO ()
setProgressData k p = when (progressMode) $ modifyIORef _progressData (insert k 
p)

getProgressData :: String - IO (Maybe ProgressData)
getProgressData k = if progressMode then lookup k `fmap` readIORef _progressData
else return Nothing


(I'm a bit behind with haskell-cafe, sorry for not seeing this sooner...)

Yes, that should all be fine, because the IORef is only modified from one 
thread, and read from the other(s).   If you were modifying the IORef from 
more than one thread you would need to use atomicallyModifyIORef, or MVars.


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


Re: [Haskell-cafe] Best practice for embedding files in a GHC-compiled tool?

2008-02-08 Thread Reinier Lamers


Op 7-feb-2008, om 13:53 heeft Dave Bayer het volgende geschreven:


Under this extreme hypothesis, how do I embed a compressed tar file  
into a single file command line tool written in Haskell and  
compiled by GHC?
Hack up a shell script or a small Haskell program to automatically  
generate a Haskell file of the form:


 module TarFile where

 import Data.ByteString as B

 myTarFile = B.pack [tar file as list of Word8s here]

You could also do that using Template Haskell, as you already hinted,  
but this sounds less like rocket science :-)


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


Re: [Haskell-cafe] question concerning ANSI void *

2008-02-08 Thread Adam Langley
On Feb 8, 2008 9:13 AM, Galchin Vasili [EMAIL PROTECTED] wrote:
 Let's take a concrete but made up case .. suppose we want to call through
 to pthread_create and pass the (void *) argument to pthread_create which in
 turn gets interpreted by the pthread that is launched. How would one
 populate the C struct that is passed to the launched pthread keeping in mind
 that this C struct is variable in length? From the FFI how would one model
 this C struct?

It tough to be helpful with such a generic request. Here are some
options that you can consider:

1) Write a wrapper function in C which has a nicer FFI interface to
call from Haskell. Using cabal this is pretty painless and, if the
interface suits it, it probably the easiest solution.
2) Call pthread_create directly with the FFI. You can give the FFI
function a Haskell type with 'Ptr ()' or 'Ptr X', it doesn't really
matter. However the type system serves you best, do it that way. This
means that you need to populate the struct yourself in Haskell. The
issue with this is that the local system defines lots of things like
padding and alignment which mean that the layout of the structure in
memory is complex and platform specific. Tools like hsc2hs[1] or c2hs
will be very helpful here. Dealing with the variable length probably
isn't an issue. Usually variable length structures have a fixed header
and a variable tail, where the tail is an array of primitives. You can
malloc the correct sized region, use one of the previous tools to fill
in the fixed header and then use poke to complete the tail.

I might be able to be more helpful if you give the actual struct and
function prototype that you're trying to wrap.

Cheers



[1] http://therning.org/magnus/archives/tag/hsc2hs
[2] http://www.cse.unsw.edu.au/~chak/haskell/c2hs/

-- 
Adam Langley  [EMAIL PROTECTED]
http://www.imperialviolet.org   650-283-9641
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] question concerning ANSI void *

2008-02-08 Thread Galchin Vasili
Let's take a concrete but made up case .. suppose we want to call through
to pthread_create and pass the (void *) argument to pthread_create which in
turn gets interpreted by the pthread that is launched. How would one
populate the C struct that is passed to the launched pthread keeping in mind
that this C struct is variable in length? From the FFI how would one model
this C struct?

Thanks, Vasili


On 2/7/08, Adam Langley [EMAIL PROTECTED] wrote:

 2008/2/7 Galchin Vasili [EMAIL PROTECTED]:
   Ok .. I am writing a Haskell function that will call down into the
 ANSI
  C library .. blah ::  - Ptr Word8 -  The underlying C
 function
  that blah is calling has a void * so I am using Ptr Word  8 to
 model
  the void *.

 Depending on the context, void * is generally either taken as a Ptr
 () (for an opaque pointer) or Ptr Word8 (for calls like memcpy).

  I propose to have the callers of function blah to populate a
  data structure something like Ptr Buz where data Buz = { }
 and
  then do a recast :: Ptr Word 8 - Ptr Buz when invoking function
 blah.
  Does this seem reasonable? Is there a better way?

 Generally, Ptr x is only used where x is either a shadow type or a
 Bits type. Having a Ptr Baz where Baz is an ADT seems a little odd. If
 you need to translate a structure from Haskell to C code, probably you
 are better off having callers pass in a Baz then, internal to the
 wrapping, fill out the C structure and call the FFI function with a
 Ptr CBaz (where CBaz is a shadow type).


 AGL

 --
 Adam Langley  [EMAIL PROTECTED]
 http://www.imperialviolet.org   650-283-9641

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


Re: [Haskell-cafe] Re: Implementing fixed-sized vectors (using datatype algebra?)

2008-02-08 Thread Wolfgang Jeltsch
Am Donnerstag, 7. Februar 2008 16:31 schrieben Sie:
 On Feb 7, 2008 4:16 PM, Wolfgang Jeltsch [EMAIL PROTECTED] wrote:
 […]

  You seem to write 12 as 1 :+ 2 instead of () :+ 1 :+ 2.  But I think, the
  latter representation should probably be prefered.  With it, :+ always
  has a number as its left argument and a digit as its right.  Without the
  () :+ we get ugly exceptional cases.
  You can see this, for example, in the instance
  declarations for Compare.  With the second representation, we could
  reduce the number of instances dramatically.  We would define a
  comparison of digits (verbose) and than a comparison of numbers based on
  the digit comparison (not verbose).

 Even if () would be preferred from the programmers point of view (I'm
 not sure how much we could reduce the number of instances though), it
 makes the representation less attractive on the user-side. Anyone
 using the library would find it annoying and would wonder why is it
 neccessary.

I wouldn’t wonder.  Leaving out the () :* part just works because our 
type-level “values” are not typed, i.e., there aren’t different kinds Digit 
and Number but only kind *.  If :+ would be a data constructor (on the value 
level), it would take a number and a digit argument which would forbid using 
a digit as its left argument.  So I consider using a digit on the left 
as “unclean”.  It’s similar to using a number as the second part of a cons 
cell in LISP.

 […]

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


Re: [Haskell-cafe] Re: Implementing fixed-sized vectors (using datatype algebra?)

2008-02-08 Thread Brandon S. Allbery KF8NH


On Feb 8, 2008, at 11:14 , Stefan Monnier wrote:

You seem to write 12 as 1 :+ 2 instead of () :+ 1 :+ 2.  But I  
think, the

latter representation should probably be prefered.
(...)
How 'bout treating :+ as similar to `append' rather than similar to  
`cons'?

Basically treat :+ as taking 2 numbers (rather than a number and
a digit).


Dumb questions department:  why not define e.g. D'0 .. D'9 as () :*  
0 .. () :* 9?  Programmers then get D'1 :* 2, but the library sees  
() :* 1 :* 2.


--
brandon s. allbery [solaris,freebsd,perl,pugs,haskell] [EMAIL PROTECTED]
system administrator [openafs,heimdal,too many hats] [EMAIL PROTECTED]
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] question concerning ANSI void *

2008-02-08 Thread Galchin Vasili
a couple of concrete examples:

typedef struct {char a; int b; char str[8]} type1;

typedef struct {long c; char d} type2;

So to pthread_create (just an example function) we could be passing a struct
of type1 or a struct of type2 .. i.e. arbitrary length and content ... I am
trying to better understand this. I see some of the poke functions mentioned
in the FFI. Which one are you alluding to?

Regards, Vasili


On 2/8/08, Adam Langley [EMAIL PROTECTED] wrote:

 On Feb 8, 2008 9:13 AM, Galchin Vasili [EMAIL PROTECTED] wrote:
  Let's take a concrete but made up case .. suppose we want to call
 through
  to pthread_create and pass the (void *) argument to pthread_create which
 in
  turn gets interpreted by the pthread that is launched. How would one
  populate the C struct that is passed to the launched pthread keeping in
 mind
  that this C struct is variable in length? From the FFI how would one
 model
  this C struct?

 It tough to be helpful with such a generic request. Here are some
 options that you can consider:

 1) Write a wrapper function in C which has a nicer FFI interface to
 call from Haskell. Using cabal this is pretty painless and, if the
 interface suits it, it probably the easiest solution.
 2) Call pthread_create directly with the FFI. You can give the FFI
 function a Haskell type with 'Ptr ()' or 'Ptr X', it doesn't really
 matter. However the type system serves you best, do it that way. This
 means that you need to populate the struct yourself in Haskell. The
 issue with this is that the local system defines lots of things like
 padding and alignment which mean that the layout of the structure in
 memory is complex and platform specific. Tools like hsc2hs[1] or c2hs
 will be very helpful here. Dealing with the variable length probably
 isn't an issue. Usually variable length structures have a fixed header
 and a variable tail, where the tail is an array of primitives. You can
 malloc the correct sized region, use one of the previous tools to fill
 in the fixed header and then use poke to complete the tail.

 I might be able to be more helpful if you give the actual struct and
 function prototype that you're trying to wrap.

 Cheers



 [1] http://therning.org/magnus/archives/tag/hsc2hs
 [2] http://www.cse.unsw.edu.au/~chak/haskell/c2hs/

 --
 Adam Langley  [EMAIL PROTECTED]
 http://www.imperialviolet.org   650-283-9641

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


Re: [Haskell-cafe] User groups meeting all over the world

2008-02-08 Thread njbartlett
Hi Neil,

London HUG is not on the list because we're not meeting in the next
two weeks. Rest assured we are on the wiki page though.

On that note, I am looking again for topics and speaker for the next
full meeting at City University. It will likely be in the middle of
March. If anybody has ideas for talks, please let me know. Also talk
to me if there is something in particular you would like to *hear*
about... then we'll do our best to find somebody who can talk about
it.

Thanks,
Another Neil

On 2/8/08, Neil Mitchell [EMAIL PROTECTED] wrote:
 Hi

   Fun in the afternoonLondon/UKFebruary 12

 Fun in the afternoon is great, but its not really a user group - it is
 still primarily an academic event, although is open to everyone. There
 is LUG, which is the London Haskell Users Group, which should
 definately be on this list.

 Thanks

 Neil
 ___
 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] :i and :t give different types

2008-02-08 Thread Chad Scherrer
On Feb 8, 2008 9:55 AM, Simon Peyton-Jones [EMAIL PROTECTED] wrote:
 I have not been following closely but if Don thinks there's a bug there 
 probably is.  Can someone submit a bug report pls?  Better still a patch! :-)

 Simon

Ok, I filed a bug report.
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] question concerning ANSI void *

2008-02-08 Thread Galchin Vasili
basically I am trying to implement ioctl for the Posix library .. so a
possible signtaure would be:

fdIoctl :: Fd - Int - Ptr Word 8 - IO( Ptr Word8) 


Vasili

On 2/8/08, Galchin Vasili [EMAIL PROTECTED] wrote:

 a couple of concrete examples:

 typedef struct {char a; int b; char str[8]} type1;

 typedef struct {long c; char d} type2;

 So to pthread_create (just an example function) we could be passing a
 struct of type1 or a struct of type2 .. i.e. arbitrary length and content
 ... I am trying to better understand this. I see some of the poke functions
 mentioned in the FFI. Which one are you alluding to?

 Regards, Vasili


  On 2/8/08, Adam Langley [EMAIL PROTECTED] wrote:
 
  On Feb 8, 2008 9:13 AM, Galchin Vasili [EMAIL PROTECTED] wrote:
   Let's take a concrete but made up case .. suppose we want to call
  through
   to pthread_create and pass the (void *) argument to pthread_create
  which in
   turn gets interpreted by the pthread that is launched. How would one
   populate the C struct that is passed to the launched pthread keeping
  in mind
   that this C struct is variable in length? From the FFI how would one
  model
   this C struct?
 
  It tough to be helpful with such a generic request. Here are some
  options that you can consider:
 
  1) Write a wrapper function in C which has a nicer FFI interface to
  call from Haskell. Using cabal this is pretty painless and, if the
  interface suits it, it probably the easiest solution.
  2) Call pthread_create directly with the FFI. You can give the FFI
  function a Haskell type with 'Ptr ()' or 'Ptr X', it doesn't really
  matter. However the type system serves you best, do it that way. This
  means that you need to populate the struct yourself in Haskell. The
  issue with this is that the local system defines lots of things like
  padding and alignment which mean that the layout of the structure in
  memory is complex and platform specific. Tools like hsc2hs[1] or c2hs
  will be very helpful here. Dealing with the variable length probably
  isn't an issue. Usually variable length structures have a fixed header
  and a variable tail, where the tail is an array of primitives. You can
  malloc the correct sized region, use one of the previous tools to fill
  in the fixed header and then use poke to complete the tail.
 
  I might be able to be more helpful if you give the actual struct and
  function prototype that you're trying to wrap.
 
  Cheers
 
 
 
  [1] http://therning.org/magnus/archives/tag/hsc2hs
  [2] http://www.cse.unsw.edu.au/~chak/haskell/c2hs/
 
  --
  Adam Langley  [EMAIL PROTECTED]
  http://www.imperialviolet.org   650-283-9641
 


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


Re: [Haskell-cafe] Re: threads + IORefs = Segmentation fault?

2008-02-08 Thread David Roundy
On Fri, Feb 08, 2008 at 10:46:25AM +, Simon Marlow wrote:
 (I'm a bit behind with haskell-cafe, sorry for not seeing this sooner...)

No problem!

 Yes, that should all be fine, because the IORef is only modified from one 
 thread, and read from the other(s).   If you were modifying the IORef from 
 more than one thread you would need to use atomicallyModifyIORef, or MVars.

If I did modify the IORef from more than one thread (e.g. if a bug were
introduced), would this cause any trouble other than occasional missed
updates or reads of wrong data?
-- 
David Roundy
Department of Physics
Oregon State University
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Create a list without duplicates from a list with duplicates

2008-02-08 Thread Dan Weston
As noted, (Data.Set.toList . Data.Set.fromList) is the best traditional 
solution if you don't care about order (or Data.Set.toAscList for a 
sorted result).


If order is important, the new bijective Data.Bimap class
http://code.haskell.org/~scook0/haddock/bimap/Data-Bimap.html
may be your best bet (I haven't yet tried it myself).

Meanwhile, here is a hand-rolled solution to order-preserving nubbing:

 import Data.List(groupBy,sortBy,sort)
 import Data.Maybe(listToMaybe)

 efficientNub :: (Ord a) = [a] - [a]
 efficientNub  = flip zip [0..]-- carry along index
  sort  -- sort by value, then index
  groupBy equalFsts -- group adjacent equal values
  map head  -- keep only primus inter pares
  sortBy compareSnds-- sort by index
  map fst   -- discard index

   where equalFsts   (x1,y1) (x2,y2) = x1 == x2
 compareSnds (x1,y1) (x2,y2) = compare y1 y2
 x  y = y . x

There is a hidden proof obligation here:

Exercise: Prove that (groupBy equalFsts  map head) is a total 
function, using the defintion of groupBy from Data.List:


groupBy   :: (a - a - Bool) - [a] - [[a]]
groupBy _  []  =  []
groupBy eq (x:xs)  =  (x:ys) : groupBy eq zs
   where (ys,zs) = span (eq x) xs

Felipe Lessa wrote:

2008/2/8 Jed Brown [EMAIL PROTECTED]:

Look at Data.List:

nub :: (Eq a) = [a] - [a]
nub = nubBy (==)

nubBy :: (a - a - Bool) - [a] - [a]
nubBy eq [] = []
nubBy eq (x:xs) = x : nubBy eq (filter (\ y - not (eq x y)) xs)


And then there's also

sort :: (Ord a) = [a] - [a]

which should have better performance, O(n log n) against O(n²) I
guess, but of course will change the order of the elements. If you
really don't mind the order at all, you could also use Data.Set in the
first place.

Cheers,





___
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] Fwd: [pdxfunc] pdxfunc meeting: Monday, February 11, 7pm, CubeSpace (Portland, OR)

2008-02-08 Thread Justin Bailey
-- Forwarded message --
From: Igal Koshevoy [EMAIL PROTECTED]
Date: Feb 8, 2008 12:01 PM
Subject: [pdxfunc] pdxfunc meeting: Monday, February 11, 7pm, CubeSpace
To: Igal Koshevoy [EMAIL PROTECTED]


Join us at the next meeting of pdxfunc, the Portland Functional
Programming Study Group. We'll have presentations, demos and
discussions. We welcome programmers interested in all functional
languages and our meetings have content for coders of all skill levels.
If interested, please also subscribe to our mailing list at
http://groups.google.com/group/pdxfunc

PRESENTATIONS

(1) Kevin Scaldeferri: Effortless Concurrent Programming with Erlang

Abstract: Erlang is a dynamic functional programming language designed
for concurrent programming. After a quick introduction to the syntax and
primitives, we'll dive into some code to see example of how you can
easily write programs that take advantage of multiple CPUs, and that
even scale effortlessly to clusters of machines. (You are highly
encouraged to download and install Erlang from
http://erlang.org/download.html before the meeting.)

Speaker: Kevin Scaldeferri has spent the last 6 years building
high-volume, high-reliability systems at Yahoo. His interests include
programming languages, the interaction between online and real-life
communities, and techniques for making the development process more
reliable, more successful, and more fun.

(2) Tim Chevalier: Towards a GraphicsMagick Binding for Haskell

Abstract: I will discuss my work in progress on implementing a Haskell
Foreign Function Interface (FFI) binding for the C-based GraphicsMagick
image manipulation library. I will introduce portions of the FFI through
examples, as well as tools for simplifying FFI use. I will also explain
how I have begun to use Haskell's type system to develop a simplified
yet equally powerful interface (as compared to the C version) to the
GraphicsMagick library. Given the ongoing nature of my work, I will
conclude by soliciting comments on what *you* would like to see in a
Haskell image manipulation library.

Speaker: Tim Chevalier is a PhD student at Portland State University,
where he thinks about alternative back-ends for Haskell and languages
like it. He has been programming in Haskell for seven years, the first
six of which he spent trying to understand monads.
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Re: Implementing fixed-sized vectors (using datatype algebra?)

2008-02-08 Thread Dan Weston

Brandon S. Allbery KF8NH wrote:


On Feb 8, 2008, at 11:14 , Stefan Monnier wrote:

You seem to write 12 as 1 :+ 2 instead of () :+ 1 :+ 2.  But I 
think, the

latter representation should probably be prefered.
(...)
How 'bout treating :+ as similar to `append' rather than similar to 
`cons'?

Basically treat :+ as taking 2 numbers (rather than a number and
a digit).


Dumb questions department:  why not define e.g. D'0 .. D'9 as () :* 0 .. 
() :* 9?  Programmers then get D'1 :* 2, but the library sees () :* 1 :* 2.




No, D'0 should be (), not () :* D0. If you allow () :* D0, then you 
introduce redundant types for the same number:


In the first case, D'0 :* D'3 == D'3, and D'0 :* D'0 has no instance. In 
your example, D'3 and D'0 :* D'3 are equivalent, but no longer unify.


Dan


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


Re: [Haskell-cafe] Re: Implementing fixed-sized vectors (using datatype algebra?)

2008-02-08 Thread Dan Weston

Dan Weston wrote:

Brandon S. Allbery KF8NH wrote:


On Feb 8, 2008, at 11:14 , Stefan Monnier wrote:

You seem to write 12 as 1 :+ 2 instead of () :+ 1 :+ 2.  But I 
think, the

latter representation should probably be prefered.
(...)
How 'bout treating :+ as similar to `append' rather than similar to 
`cons'?

Basically treat :+ as taking 2 numbers (rather than a number and
a digit).


Dumb questions department:  why not define e.g. D'0 .. D'9 as () :* 0 
.. () :* 9?  Programmers then get D'1 :* 2, but the library sees () :* 
1 :* 2.




No, D'0 should be (), not () :* D0. If you allow () :* D0, then you 
introduce redundant types for the same number:


In the first case, D'0 :* D'3 == D'3, and D'0 :* D'0 has no instance. In 
your example, D'3 and D'0 :* D'3 are equivalent, but no longer unify.


Dan


On second thought, how would you write D'3 :* D0 ? I think maybe using 
the () makes it fundamentally difficult to restrict multiple types for 
the same number.


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


Re: [Haskell-cafe] question concerning ANSI void *

2008-02-08 Thread Adam Langley
On Feb 8, 2008 10:57 AM, Galchin Vasili [EMAIL PROTECTED] wrote:
 basically I am trying to implement ioctl for the Posix library .. so a
 possible signtaure would be:

 fdIoctl :: Fd - Int - Ptr Word 8 - IO( Ptr Word8) 

Ah, ok. You could cover many of the ioctls (the ones which only take a
single primitive) by using the Storable class and the types CInt etc.
Define the FFI call to ioctl with a type of CInt - Int - Ptr () -
IO CInt and then

ioctlCInt :: CInt - CInt - CInt - IO CInt
ioctlCInt fd call arg = do
  allocaBytes $ \ptr - do
poke ptr arg
result - ioctl fd call (cast ptr)
when (result  0) $ fail ioctl error
peek ptr

(untested, might work ;)

... and likewise for the other C types. However, for those ioctls which take a
complex structure (e.g. many of the networking ones), you'll need to marshal
yourself:

data SomeIOCtlStruct = CInt CInt CInt

ioctlSomeIOCtlStruct :: CInt - CInt - SomeIOCtlStruct - IO ()
ioctlSomeIOCtlStruct = do
  ...  (see the above linked to pointers to hsc2hs and c2hs about how to write
  this function)



AGL

--
Adam Langley  [EMAIL PROTECTED]
http://www.imperialviolet.org   650-283-9641
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Create a list without duplicates from a list with duplicates

2008-02-08 Thread Tillmann Rendel

Dan Weston wrote:

Meanwhile, here is a hand-rolled solution to order-preserving nubbing:

  import Data.List(groupBy,sortBy,sort)
  import Data.Maybe(listToMaybe)
 
  efficientNub :: (Ord a) = [a] - [a]
  efficientNub  = flip zip [0..]-- carry along index
   sort  -- sort by value, then index
   groupBy equalFsts -- group adjacent equal values
   map head  -- keep only primus inter pares
   sortBy compareSnds-- sort by index
   map fst   -- discard index
 
where equalFsts   (x1,y1) (x2,y2) = x1 == x2
  compareSnds (x1,y1) (x2,y2) = compare y1 y2
  x  y = y . x


I would try something like

  efficientNub = catMaybes . snd . mapAccumR f empty where
f s x | member x s = (s, Nothing)
  | otherwise = (insert x s, x)

that is, threading the Set of already given results through.

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


[Haskell-cafe] Re: question concerning ANSI void *

2008-02-08 Thread Ben Franksen
Galchin Vasili wrote:

 Let's take a concrete but made up case .. suppose we want to call
 through to pthread_create and pass the (void *) argument to pthread_create
 which in turn gets interpreted by the pthread that is launched. How would
 one populate the C struct that is passed to the launched pthread keeping
 in mind that this C struct is variable in length? From the FFI how would
 one model this C struct?

In this case I'd use

  Storable a = Ptr a

and provide an instance Storable for the actual type you want to marshal.
You can allocate the struct with Foreign.Marshal.Alloc.malloc and marshall
it from Haskell to C with Foreign.Storable.poke.

Cheers
Ben

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


Re: [Haskell-cafe] Mutable arrays

2008-02-08 Thread Chaddaï Fouché
Après avoir un peu manipulé la solution de John pour qu'elle fasse la même
chose que la mienne, je peux affirmer qu'elle est légèrement moins rapide
(c'est infime et normal vu que ses leftFold passent plus d'informations),
mais que les deux solutions ont au moins cet avantage d'être rapides (2s sur
10M de Double) et en mémoire parfaitement constante :


import Data.Array.MArray
import Control.Monad
import Data.Array.IO
import System

maxArr a = liftM (foldl1' max) (getElems a)

foldlA :: (MArray a e m, Ix i) = (r - e - r) - r - a i e - m r
foldlA f a arr = getBounds arr =
 foldM (\a-a `seq` liftM $ f a) a
   . map (readArray arr) . range

foldl1A :: (MArray a e m, Ix i) = (e - e - e) - a i e - m e
foldl1A f arr = flip (foldlA f) arr = readArray arr . fst = getBounds
arr

foldMA :: (MArray a e m, Ix i) = (r - e - m r) - r - a i e - m r
foldMA f a arr = getBounds arr =
 foldM (\a-a `seq` (= f a)) a
   . map (readArray arr) . range

modifyArray :: (MArray a e m, Ix i) = (e - e) - a i e - m ()
modifyArray f arr = mapM_ (modifyElement f arr) . range = getBounds arr

modifyElement :: (MArray a e m, Ix i) = (e - e) - a i e - i - m ()
modifyElement f arr i = writeArray arr i . f = readArray arr i

main = do
  [n] - getArgs
  a - (newListArray (0, 10 ^ read n) [1..] :: IO (IOUArray Int Double))
  maxE - foldl1A max a
  modifyArray (* (1/maxE)) a
  print = readArray a (10 ^ read n)


En tout cas il serait agréable d'avoir quelques unes de ces fonctions dans
les librairies standards, vu qu'elles sont généralement utiles et très
efficace. Je n'utilise pas les langages fonctionnels pour avoir à écrire des
boucles explicites sur mes structures de données !! ;-)
(et comme on l'a vu, pour un débutant, l'écriture d'une généralisation
efficace de ces boucles n'est pas si triviale qu'il y paraît).

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


[Haskell-cafe] Create a list without duplicates from a list with duplicates

2008-02-08 Thread [EMAIL PROTECTED]
Hallo!

Let's suppose I have a list [a,b,c,d,c,d]. I'd like to write
a function that returns a new list without duplicates (in
the example [a,b,c,d]). How can I do that? What is the most
general way? I'd like to use the same function for a list of
Int or String or some other user defined data type.

Thank for your attention!
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Create a list without duplicates from a list with duplicates

2008-02-08 Thread Jed Brown
On  8 Feb 2008, [EMAIL PROTECTED] wrote:

 Hallo!

 Let's suppose I have a list [a,b,c,d,c,d]. I'd like to write
 a function that returns a new list without duplicates (in
 the example [a,b,c,d]). How can I do that? What is the most
 general way? I'd like to use the same function for a list of
 Int or String or some other user defined data type.

Look at Data.List:

nub :: (Eq a) = [a] - [a]
nub = nubBy (==)

nubBy :: (a - a - Bool) - [a] - [a]
nubBy eq [] = []
nubBy eq (x:xs) = x : nubBy eq (filter (\ y - not (eq x y)) xs)

Jed


pgpBXoyoGoA2i.pgp
Description: PGP signature
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Haskell maximum stack depth

2008-02-08 Thread Neil Mitchell
Hi

 Yes, though testing stackGobbler with a large enough data set could
 be problematic for the very reason we've been discsussing.

Yes you are sure, or yes you tested and the results show than
neilGobbler is x% slower and consume y% more memory on specific test
n?

 But let's say your hypothesis was correct.

My hypothesis isn't that the stack is slow.

 AFAICT neilGobbler isn't even entirely safe as an implementation of
 an eager take. There's nothing the Haskell standard to stop it being
 transformed into..

 neilGobbler :: Int - [x] - [x]
 neilGobbler n xs = length (take n xs) `seq` take n xs

Yes, but so much in the Haskell standard is also missing. I think in
this case you could reasonably argue that any compiler violating this
_is_ violating the Haskell standard as it was intended (albeit not as
it was written). You'll also find that the space behaviour of CAF's
isn't documented in Haskell, but if people changed it you'd break
quite a bit of the nofib suite.

Thanks

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


Re: [Haskell-cafe] Create a list without duplicates from a list with duplicates

2008-02-08 Thread Felipe Lessa
2008/2/8 Jed Brown [EMAIL PROTECTED]:
 Look at Data.List:

 nub :: (Eq a) = [a] - [a]
 nub = nubBy (==)

 nubBy :: (a - a - Bool) - [a] - [a]
 nubBy eq [] = []
 nubBy eq (x:xs) = x : nubBy eq (filter (\ y - not (eq x y)) xs)

And then there's also

sort :: (Ord a) = [a] - [a]

which should have better performance, O(n log n) against O(n²) I
guess, but of course will change the order of the elements. If you
really don't mind the order at all, you could also use Data.Set in the
first place.

Cheers,

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


Re: [Haskell-cafe] User groups meeting all over the world

2008-02-08 Thread Neil Mitchell
Hi

  Fun in the afternoonLondon/UKFebruary 12

Fun in the afternoon is great, but its not really a user group - it is
still primarily an academic event, although is open to everyone. There
is LUG, which is the London Haskell Users Group, which should
definately be on this list.

Thanks

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


[Haskell-cafe] Re: Implementing fixed-sized vectors (using datatype algebra?)

2008-02-08 Thread Stefan Monnier
  You seem to write 12 as 1 :+ 2 instead of () :+ 1 :+ 2.  But I think, the
  latter representation should probably be prefered.  With it, :+ always
  has a number as its left argument and a digit as its right.  Without the
  () :+ we get ugly exceptional cases.
  You can see this, for example, in the instance
  declarations for Compare.  With the second representation, we could
  reduce the number of instances dramatically.  We would define a
  comparison of digits (verbose) and than a comparison of numbers based on
  the digit comparison (not verbose).
 
 Even if () would be preferred from the programmers point of view (I'm
 not sure how much we could reduce the number of instances though), it
 makes the representation less attractive on the user-side. Anyone
 using the library would find it annoying and would wonder why is it
 neccessary.

 I wouldn’t wonder.  Leaving out the () :* part just works because our 
 type-level “values” are not typed, i.e., there aren’t different kinds Digit 
 and Number but only kind *.  If :+ would be a data constructor (on the value 
 level), it would take a number and a digit argument which would forbid using 
 a digit as its left argument.  So I consider using a digit on the left 
 as “unclean”.  It’s similar to using a number as the second part of a cons 
 cell in LISP.

How 'bout treating :+ as similar to `append' rather than similar to `cons'?
Basically treat :+ as taking 2 numbers (rather than a number and
a digit).


Stefan

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


Re: [Haskell-cafe] Mutable arrays

2008-02-08 Thread Chaddaï Fouché
Sorry for the french, I was a little bit confused...

On 08/02/08, Chaddaï Fouché [EMAIL PROTECTED] wrote :
After I changed John's code so that it worked on the same dataset as mine, I
could benchmark both of them :
My solution is a bit faster (but that's a very tiny difference and to be
expected since John's fold are more general than mine), but in any case,
both solution are reasonably fast (2s on a 10M Double array (unboxed)) and
don't eat any more memory than necessary :

Anyway it would be nice to have some version of those function in the
standard library (MArray) since they are pretty useful and efficient. I
don't use functional language in order to have to code explicit loops on my
data structures !! ;-)
(And as we saw, to write an efficient generalisation of those loops isn't as
easy as it might seems)

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


[Haskell-cafe] Re: Implementing fixed-sized vectors (using datatype algebra?)

2008-02-08 Thread Aaron Denney
On 2008-02-05, Alfonso Acosta [EMAIL PROTECTED] wrote:
 On Feb 5, 2008 4:10 PM, Henning Thielemann
[EMAIL PROTECTED] wrote:

 On Fri, 1 Feb 2008, Aaron Denney wrote:

  On 2008-02-01, Bjorn Buckwalter [EMAIL PROTECTED] wrote:
   If Naturals had been sufficient for me I wouldn't have done my own
   implementation (I'm unaware of any other implementation of Integers).
   And there is certainly a lot of value to the clearer error messages
   from a decimal representation.
 
  I did a balanced-base-three (digits are 0, and +- 1) representation to
  get negative decimals.

 Nice. In German the digit values are sometimes called eins, keins, meins. 
 :-)

 I'm almost done with the decimal library but it would be nice to check
 some Integer implementations for future inclusion. So, Aaron, Björn,
 are your implementations available somewhere?

http://ofb.net/~wnoise/repos/dimensional/

-- 
Aaron Denney
--

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


Re: [Haskell-cafe] I love purity, but it's killing me.

2008-02-08 Thread Tom Hawkins
On 2/8/08, Emil Axelsson [EMAIL PROTECTED] wrote:
 I know of a few of ways to express sharing in a pure language:

 1) Observable sharing, which, in general, is unsafe.
 2) Using Template Haskell
 3) Matthew Naylor has done some work on expressible sharing, which has
 4) Use a monad (but I'm sure this is what you're trying to avoid).

Or...

5) Forget embedding the DSL, and write a direct compiler.

In addition to the sharing problem, another shortcoming of Haskell
DSLs is they can not fully exploit the benefits of algebraic
datatypes.  Specifically, pattern matching ADTs can only be used to
control the compile-time configuration of the target, it can't be used
to describe the target's behavior -- at least for DSLs that generate
code that executes outside of Haskell's runtime.

Writing a real compiler would solve both of these problems.  Is there
any Haskell implementation that has a clean cut-point, from which I
can start from a fully type-checked, type-annotated intermediate
representation?

And thanks for the link to John's paper describing Hydra's use of
Template Haskell.  I will definiately consider TH.

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


Re: [Haskell-cafe] Re: problem with collection (container) class

2008-02-08 Thread Daniel Fischer
Am Freitag, 8. Februar 2008 22:14 schrieb Ben Franksen:
 If it's a bug then it is probably in 6.6.1 too, it just gets hidden by the
 fact that in 6.6.1 the -fglasgow-exts extensions cannot be activated
 separately. If you enable one of them, you get them all.

Thanks for the info, didn't know that. 

The problem was the error message, which didn't mention that each type 
variable may appear only once in an instance head, which I had temporarily 
forgotten. Then the message

Leandro.hs:32:0:
Illegal instance declaration for `Container (Abb a b) a b'
(All instance types must be of the form (T a1 ... an)
 where a1 ... an are distinct type *variables*
 Use -XFlexibleInstances if you want to disable this.)
In the instance declaration for `Container (Abb a b) a b'

looks rather confusing :)

 Cheers
 Ben

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


Re: [Haskell-cafe] I love purity, but it's killing me.

2008-02-08 Thread Tim Chevalier
On 2/8/08, Matthew Naylor [EMAIL PROTECTED] wrote:
 it in for an efficient program.  However, to my knowledge, it is an
 unwritten rule of Haskell compilers that sharing *is* preserved, and
 that they do perform *graph* reduction.  Clean, a similar language to

I'm not sure that programmers ought to be relying on this rule. Sure,
all Haskell compilers I know of preserve sharing and do graph
reduction. But conventional wisdom is not the same thing as an
unwritten rule. Someday, someone might come along and write a Haskell
compiler that isn't based on graph reduction and doesn't preserve
sharing at the implementation level (while still preserving the
informal semantics of Haskell). A programmer who had written code that
failed to compile correctly under this hypothetical compiler would be
a very naughty Haskell programmer indeed.

 Haskell, indeed has a semantics based on graphs.  So I don't believe

Haskell doesn't have a semantics, graph-based or not... or at least
not a formal one, and if not a formal one, I don't know what you mean
:-)

Cheers,
Tim

-- 
Tim Chevalier * http://cs.pdx.edu/~tjc * Often in error, never in doubt
There are no sexist decisions to be made. There are antisexist
decisions to be made. And they require tremendous energy and
self-scrutiny, as well as moral stamina... -- Samuel R. Delany
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] Re: problem with collection (container) class

2008-02-08 Thread Ben Franksen
Daniel Fischer wrote:
 {-# LANGUAGE MultiParamTypeClasses #-}
 {-# LANGUAGE FunctionalDependencies #-}
 {- # LANGUAGE FlexibleInstances # -}
 module Leandro where
 
 data Abb a b = Branch a b (Abb a b) (Abb a b) | Leaf
 
 data ListAssoc a b = Node a b (ListAssoc a b) | Empty
 
 class Container c a b |c - a, c - b where
 [...]
 
 instance (Ord a) = Container (Abb a b) a b where
 [...]
 
 Note: The FlexibleInstances Language pragma is required by GHC 6.8.1 and
 6.8.2, but not by GHC 6.6.1 or hugs, I think that's a bug in 6.8.*

If it's a bug then it is probably in 6.6.1 too, it just gets hidden by the
fact that in 6.6.1 the -fglasgow-exts extensions cannot be activated
separately. If you enable one of them, you get them all.

Cheers
Ben

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


[Haskell-cafe] GHC + interactive input/output

2008-02-08 Thread Jonathan Cast

$ cat  foo.c
#include stdio.h

int
main()
{
  char s[1024];
  printf(gsi );
  gets(s);
  printf(%s\n, s);
  return 0;
}
$ make foo
cc gsi.c   -o gsi
$ ./foo
warning: this program uses gets(), which is unsafe.
gsi hello
hello
$ cat  foo.hs
main = do
  putStr gsi 
  s - getLine
  putStrLn s
$ ghc foo.hs -o foo
$ ./foo
hello
gsi hello

(This is on MacOS X).  It strikes me that GHC is being  
extraordinarily unhelpful here.  Is there anyone on the planet who  
ever actually wants this behavior?


jcc

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


Re: [Haskell-cafe] GHC + interactive input/output

2008-02-08 Thread Brandon S. Allbery KF8NH


On Feb 8, 2008, at 19:41 , Philip Weaver wrote:

Your gsi  is buffered because there's no newline at the end.  To  
flush the buffer and force it to be printed immediately, use  
'hFlush' from the System.IO library, or use 'hSetBuffering' from  
that same library: http://haskell.org/ghc/docs/latest/html/ 
libraries/base/System-IO.html


I believe you can observe the same behavior in C.


Most C stdio libraries in my experience have extra code in the  
functions that read stdin to flush stdout first, specifically because  
of lazy people who don't pay attention to buffering.


--
brandon s. allbery [solaris,freebsd,perl,pugs,haskell] [EMAIL PROTECTED]
system administrator [openafs,heimdal,too many hats] [EMAIL PROTECTED]
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] GHC + interactive input/output

2008-02-08 Thread Philip Weaver
Your gsi  is buffered because there's no newline at the end.  To flush
the buffer and force it to be printed immediately, use 'hFlush' from the
System.IO library, or use 'hSetBuffering' from that same library:
http://haskell.org/ghc/docs/latest/html/libraries/base/System-IO.html

I believe you can observe the same behavior in C.

- Phil


On Feb 8, 2008 4:14 PM, Jonathan Cast [EMAIL PROTECTED] wrote:

 $ cat  foo.c
 #include stdio.h

 int
 main()
 {
   char s[1024];
   printf(gsi );
   gets(s);
   printf(%s\n, s);
   return 0;
 }
 $ make foo
 cc gsi.c   -o gsi
 $ ./foo
 warning: this program uses gets(), which is unsafe.
 gsi hello
 hello
 $ cat  foo.hs
 main = do
   putStr gsi 
   s - getLine
   putStrLn s
 $ ghc foo.hs -o foo
 $ ./foo
 hello
 gsi hello

 (This is on MacOS X).  It strikes me that GHC is being
 extraordinarily unhelpful here.  Is there anyone on the planet who
 ever actually wants this behavior?

 jcc

 ___
 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] I love purity, but it's killing me.

2008-02-08 Thread Don Stewart
tomahawkins:
 On 2/8/08, Emil Axelsson [EMAIL PROTECTED] wrote:
  I know of a few of ways to express sharing in a pure language:
 
  1) Observable sharing, which, in general, is unsafe.
  2) Using Template Haskell
  3) Matthew Naylor has done some work on expressible sharing, which has
  4) Use a monad (but I'm sure this is what you're trying to avoid).
 
 Or...
 
 5) Forget embedding the DSL, and write a direct compiler.
 
 In addition to the sharing problem, another shortcoming of Haskell
 DSLs is they can not fully exploit the benefits of algebraic
 datatypes.  Specifically, pattern matching ADTs can only be used to
 control the compile-time configuration of the target, it can't be used
 to describe the target's behavior -- at least for DSLs that generate
 code that executes outside of Haskell's runtime.
 
 Writing a real compiler would solve both of these problems.  Is there
 any Haskell implementation that has a clean cut-point, from which I
 can start from a fully type-checked, type-annotated intermediate
 representation?

Taking the output of GHC's intermediate phase, after optimising
leaves you with type checked, optimised, 'Core' -- basically
lambda calculus with extras.

It's a good start if you then want to hand-compile that down.

Extract it with -fext-core

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


Re: [Haskell-cafe] GHC + interactive input/output

2008-02-08 Thread Jonathan Cast

On 8 Feb 2008, at 4:50 PM, Brandon S. Allbery KF8NH wrote:



On Feb 8, 2008, at 19:41 , Philip Weaver wrote:

Your gsi  is buffered because there's no newline at the end.   
To flush the buffer and force it to be printed immediately, use  
'hFlush' from the System.IO library, or use 'hSetBuffering' from  
that same library: http://haskell.org/ghc/docs/latest/html/ 
libraries/base/System-IO.html


I believe you can observe the same behavior in C.


Most C stdio libraries in my experience have extra code in the  
functions that read stdin to flush stdout first, specifically  
because of lazy people who don't pay attention to buffering.


Why can't GHC implement the same thing?

jcc

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


Re: [Haskell-cafe] Re: Implementing fixed-sized vectors (using datatype algebra?)

2008-02-08 Thread Bjorn Buckwalter
On Feb 6, 2008 8:47 PM, Alfonso Acosta [EMAIL PROTECTED] wrote:
 On Feb 7, 2008 2:30 AM, Bjorn Buckwalter [EMAIL PROTECTED] wrote:
  Ok. Is this what people want -- one big hold-all library with
  everything, as opposed to smaller more specialized packages? I guess I
  can see advantages (real or perceived) to both approaches.

 Apart from Dockins' typenats library there are no other user-friendly
 specific type-level libraries that know, so I cannot really tell if
 people would prefer a hold-all library or a couple of more granular
 specialized ones.

 Right now is not hold-all at all (it is still vaporware actually :)),
 so I think there's no reason to discuss that at this point. Let's see
 what people think.

Right, of course. I'll be taking a look at your no-longer-vaporware! ;)
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] Slightly Offtopic in Part

2008-02-08 Thread PR Stanley

Hi folks
The disjunction elimination rule:
I've been trying to make sense of it and I think I have had some 
success; however, it's far from adequate. I wonder, is there a way of 
demonstrating it in Haskell? A code frag with a jargon-free 
explanation would be mucho appreciated.

Cheers, Paul

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


Re: [Haskell-cafe] GHC + interactive input/output

2008-02-08 Thread Jonathan Cast

On 8 Feb 2008, at 5:29 PM, Philip Weaver wrote:

GHC certain *could* do this, but it's arguably not the right thing  
to do.  For performance, the operating system buffers writes until  
it is ready to write large chunks at a time.  If you do not want  
this behavior, change the buffering mode from its default.


To what?

BlockBuffering is worse, not better, and the docs *explicitly* say  
that switching to NoBuffering will break ^D (if it wasn't broken  
already...)  My specification for a working program is `one that  
works exactly like every other program on my machine'.  I don't see  
how to produce such a program with GHC.(1)


jcc

(1) Using readline might work (although I'm kind of sceptical given  
what's preceded it), but I haven't gotten it to link thus far...


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


Re: [Haskell-cafe] Slightly Offtopic in Part

2008-02-08 Thread Ryan Ingram
I'm assuming you mean the rule described in
http://en.wikibooks.org/wiki/Formal_Logic/Sentential_Logic/Inference_Rules

 type Disj a b = Either a b

 disj_elim :: Disj a b - (a - c) - (b - c) - c
 disj_elim (Left a) a2c b2c = a2c a
 disj_elim (Right b) a2c b2c = b2c b

If you know either a is true, or b is true
and you know from a, I can prove c,
and you know from b, I can prove c,
then you can prove c.

  -- ryan

On 2/8/08, PR Stanley [EMAIL PROTECTED] wrote:
 Hi folks
 The disjunction elimination rule:
 I've been trying to make sense of it and I think I have had some
 success; however, it's far from adequate. I wonder, is there a way of
 demonstrating it in Haskell? A code frag with a jargon-free
 explanation would be mucho appreciated.
 Cheers, 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] GHC + interactive input/output

2008-02-08 Thread Jonathan Cast

On 8 Feb 2008, at 6:34 PM, Ryan Ingram wrote:


import System.IO

myGetLine = hFlush stdout  getLine


That fixes this issue, certainly (although it's superfluous; my  
program really does contain only a single call to getLine)...


Nevertheless, it would be nice to at least have it in the standard  
library; it's much more useful than any of the input functions that  
already exist.


jcc


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


Re: [Haskell-cafe] Slightly Offtopic in Part

2008-02-08 Thread Dan Licata
Out of context (am I missing some earlier part of this thread?) I'm not
entirely sure what you mean.

Are you're talking about the disjunction elim rule in intuitionistic
natural deduction:

Gamma |- A + B   Gamma, A |- C   Gamma, B |- C
--
 Gamma |- C

If so, this is just 'case'.  If you annotate the rule with proof terms
(programs in the simply-typed lambda-calculus), you get the typing rule
for case:

Gamma |- e : A + B   
Gamma, x1 : A |- e1 : C   
Gamma, x2 : B |- e2 : C
--
Gamma |- case e of { Inl x1 - e1 ; Inr x2 - e2 } : C

I.e., when pattern matching on the following type

data Or a b = 
   Inl a
 | Inr b

(this type is isomorphic to Either in the Prelude)

you have two cases to consider, one where you have an 'a' and the other
where you have a 'b'.  

E.g., let's prove a simple theorem:

comm :: Or a b - Or b a
comm x = case x of 
   Inl x1 - Inr x1
   Inr x2 - Inl x2

Does that help?
-Dan

On Feb09, PR Stanley wrote:
 Hi folks
 The disjunction elimination rule:
 I've been trying to make sense of it and I think I have had some 
 success; however, it's far from adequate. I wonder, is there a way of 
 demonstrating it in Haskell? A code frag with a jargon-free 
 explanation would be mucho appreciated.
 Cheers, 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] Slightly Offtopic in Part

2008-02-08 Thread Stefan O'Rear
On Fri, Feb 08, 2008 at 06:47:51PM -0800, Ryan Ingram wrote:
 I'm assuming you mean the rule described in
 http://en.wikibooks.org/wiki/Formal_Logic/Sentential_Logic/Inference_Rules
 
  type Disj a b = Either a b
 
  disj_elim :: Disj a b - (a - c) - (b - c) - c
  disj_elim (Left a) a2c b2c = a2c a
  disj_elim (Right b) a2c b2c = b2c b
 
 If you know either a is true, or b is true
 and you know from a, I can prove c,
 and you know from b, I can prove c,
 then you can prove c.

aka:

import Data.Either

type Disj = Either
disj_elim = either

Stefan


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


Re: [Haskell-cafe] GHC + interactive input/output

2008-02-08 Thread Jonathan Cast

On 8 Feb 2008, at 6:50 PM, Jonathan Cast wrote:


On 8 Feb 2008, at 6:34 PM, Ryan Ingram wrote:


import System.IO

myGetLine = hFlush stdout  getLine


That fixes this issue, certainly (although it's superfluous; my  
program really does contain only a single call to getLine)...


Nevertheless, it would be nice to at least have it in the standard  
library; it's much more useful than any of the input functions that  
already exist.


Also, for some reason, this doesn't seem to be necessary inside an  
Emacs buffer...  Do we not care about performance in that case?


jcc

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


Re: [Haskell-cafe] GHC + interactive input/output

2008-02-08 Thread Ryan Ingram
import System.IO

myGetLine = hFlush stdout  getLine

  -- ryan

On 2/8/08, Jonathan Cast [EMAIL PROTECTED] wrote:
 On 8 Feb 2008, at 5:29 PM, Philip Weaver wrote:

  GHC certain *could* do this, but it's arguably not the right thing
  to do.  For performance, the operating system buffers writes until
  it is ready to write large chunks at a time.  If you do not want
  this behavior, change the buffering mode from its default.

 To what?

 BlockBuffering is worse, not better, and the docs *explicitly* say
 that switching to NoBuffering will break ^D (if it wasn't broken
 already...)  My specification for a working program is `one that
 works exactly like every other program on my machine'.  I don't see
 how to produce such a program with GHC.(1)

 jcc

 (1) Using readline might work (although I'm kind of sceptical given
 what's preceded it), but I haven't gotten it to link thus far...

 ___
 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] Slightly Offtopic in Part

2008-02-08 Thread Dan Weston

For more details, look for a function called orElim in the write-up

http://www.thenewsh.com/~newsham/formal/curryhoward/

Dan

Ryan Ingram wrote:

I'm assuming you mean the rule described in
http://en.wikibooks.org/wiki/Formal_Logic/Sentential_Logic/Inference_Rules


type Disj a b = Either a b



disj_elim :: Disj a b - (a - c) - (b - c) - c
disj_elim (Left a) a2c b2c = a2c a
disj_elim (Right b) a2c b2c = b2c b



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


Re: [Haskell-cafe] Slightly Offtopic in Part

2008-02-08 Thread Dan Weston
It should be emphasized that a type needs to be inhabited by (at least 
one) *total* function to prove a theorem. Otherwise, you could have the 
following partial function purporting to prove the phony theorem that A 
or B implies A:


phony :: Either a b - a
phony (Left a) = a

Dan

Dan Weston wrote:

For more details, look for a function called orElim in the write-up

http://www.thenewsh.com/~newsham/formal/curryhoward/

Dan

Ryan Ingram wrote:

I'm assuming you mean the rule described in
http://en.wikibooks.org/wiki/Formal_Logic/Sentential_Logic/Inference_Rules 




type Disj a b = Either a b



disj_elim :: Disj a b - (a - c) - (b - c) - c
disj_elim (Left a) a2c b2c = a2c a
disj_elim (Right b) a2c b2c = b2c b






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


[Haskell-cafe] ANN: Finance-Quote-Yahoo 0.5.0

2008-02-08 Thread brad clawsie
a new version of Finance-Quote-Yahoo has been uploaded to hackage that
breaks an api of the previous version for getting bulk historical
quote information.

specifically, notice this updated type signature:

getHistoricalQuote :: QuoteSymbol - Day - Day - QuoteFrequency -
IO (Maybe [HistoricalQuote])

the QuoteFrequency can be one of Daily, Weekly, Monthly or Dividend

old code using this function will break, which is why i am notifying the
list explicitly of this upload. since the versioning is still 0.* and
the library is listed as experimental, users should expect changes
until a 1.* version is released.

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