[Haskell-cafe] Re: XML transformation difficulties

2006-07-14 Thread Greg Fitzgerald
Adding some code to go along with my last post:main = do   [tree] <- runX (readDocument [(a_validate, "0")] "
text.xml")   [fooDoc
] <- runX (constA tree >>> processChildren isFoo)   [expanded] <- runX (constA tree >>> processTopDown (expandNode fooDoc `when` hasName "bar"))
   [status]   <- runX (constA expanded >>> writeDocument [] "-" >>> getErrStatus)
   (putStrLn . show) status
where   expandNode :: (ArrowXml a) => XmlTree -> a XmlTree XmlTree   expandNode :: (ArrowXml a) => XmlTree -> a XmlTree XmlTree
   expandNode foos = this    -- what here???   isFoo = deep (hasName "foo")The issue is that in 'expandNode', I have an XmlTree (foos) and an arrow whose input is the node to be replaced (also an XmlTree), but I need a String and an arrow whose input is the XmlTree (foos):
expandNode' :: (ArrowXml a) => String -> a XmlTree XmlTreeexpandNode' name = processChildren (hasAttrValue "name" name)Somewhat related, if the output of an arrow is a string, can I get access to that string without using 'runX':
getAttrValue :: String -> a 
XmlTree StringAre Arrows the wrong tool for this job?Thanks,GregOn 7/14/06, Greg Fitzgerald <
[EMAIL PROTECTED]> wrote:> > I'm trying to think of a way to translate this input, to the output below:> > Input:> >>A
> >>   B>>>C
> >>   >   >> > > Output:> 
>>B>A>> > > That is, anywhere there is a 'bar', replace it with the contents of the 'foo' it references.  I'm having a difficult time representing this with HXT's Arrow API because the value of the 'ref' attribute is the output of an arrow, but I need it to be just a plain string so that I could use it as an input parameter to the 'hasAttrValue' function.  A similar problem, using 'processTopDown', once I traverse to a 'bar' node, I need to then traverse the root again to find the 'foo', but I'm in the context of the 'bar' node, not the root. 
> > My ears are open to solutions with HaXML or Scrap Your XML-plate, or anything else.> > Thanks,> > Greg> >   
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Comma in the front

2006-07-14 Thread Brian Hulley

Tim Docker wrote:

These layouts feel a bit artificial to me. I am quite partial to
python's
list syntax - a trailing comma is optional. meaning you can write

[
   a,
   b,
   c,
]

I'm surprised this approach isn't more widespread - Are there reasons
why
haskell syntax could not/should not be defined this way?


I think this would be confusing because it looks like a syntax error - the 
last element is missing. The advantage of just having comma as a separator 
is that it allows syntax errors to be detected, whereas making it optional 
would mean one less error is detected at compile time.


I'll take this opportunity to re-present my hyper-cool syntax proposal for 
lists ;-) :


   #[
   a
   b
   c

No need for commas or a closing ] because we could just use layout!

Regards, Brian.
--
Logic empowers us and Love gives us purpose.
Yet still phantoms restless for eras long past,
congealed in the present in unthought forms,
strive mightily unseen to destroy us.

http://www.metamilk.com 


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


Re: [Haskell-cafe] Type of a function?

2006-07-14 Thread Jason Dagit

On 7/14/06, Jenny678 <[EMAIL PROTECTED]> wrote:


Hallo

Can somebody tell me the type of  the following function?

func :: ?
func f x = (z,y)
  where (z,y) = f x


Let's try to reason about it.  Let's start with some approximation to
the type of 'func'.

It appears to take two parameters so we'll say,
func :: a -> b -> c

Now we look at the first parameter, f, and see that it can be applied
to x to get a tuple.
f :: b -> (d, e)

Now we can replace the the type variable 'a' with the signature for f.
func :: (b -> (d, e)) -> b -> c

But we also notice that the type (d, e) which is returned by f is also
returned by func.
func :: (b -> (d, e)) -> b -> (d, e)

So there you have it.  That's how you can reason about types. (and
hopefully I didn't make a clerical error...)

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


Re: [Haskell-cafe] Type of a function?

2006-07-14 Thread Jared Updike

(leave off the line with

func :: ???

and the compiler will figure it out for you, if possible---it works in
this case)

 Jared.

On 7/14/06, Jared Updike <[EMAIL PROTECTED]> wrote:

Did you try putting this in a file, say,   t.hsand running
   ghci  t.hs

then typing

   :type func

at the GHCi prompt? It should tell you the function type.

  Jared.

On 7/14/06, Jenny678 <[EMAIL PROTECTED]> wrote:
>
> Hallo
>
> Can somebody tell me the type of  the following function?
>
> func :: ?
> func f x = (z,y)
>   where (z,y) = f x
>
> Thanks
> --
> View this message in context: 
http://www.nabble.com/Type-of-a-function--tf1945843.html#a5335607
> Sent from the Haskell - Haskell-Cafe forum at Nabble.com.
>
> ___
> Haskell-Cafe mailing list
> Haskell-Cafe@haskell.org
> http://www.haskell.org/mailman/listinfo/haskell-cafe
>


--
http://www.updike.org/~jared/
reverse ")-:"


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


Re: [Haskell-cafe] Type of a function?

2006-07-14 Thread Jared Updike

Did you try putting this in a file, say,   t.hsand running
  ghci  t.hs

then typing

  :type func

at the GHCi prompt? It should tell you the function type.

 Jared.

On 7/14/06, Jenny678 <[EMAIL PROTECTED]> wrote:


Hallo

Can somebody tell me the type of  the following function?

func :: ?
func f x = (z,y)
  where (z,y) = f x

Thanks
--
View this message in context: 
http://www.nabble.com/Type-of-a-function--tf1945843.html#a5335607
Sent from the Haskell - Haskell-Cafe forum at Nabble.com.

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




--
http://www.updike.org/~jared/
reverse ")-:"
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] XML transformation difficulties

2006-07-14 Thread Greg Fitzgerald
I'm trying to think of a way to translate this input, to the output below:Input:   
  A
        B      
  C
                     Output:   
  B
  A   That is, anywhere there is a 'bar', replace it with the contents of the 'foo' it references.  I'm having a difficult time representing this with HXT's Arrow API because the value of the 'ref' attribute is the output of an arrow, but I need it to be just a plain string so that I could use it as an input parameter to the 'hasAttrValue' function.  A similar problem, using 'processTopDown', once I traverse to a 'bar' node, I need to then traverse the root again to find the 'foo', but I'm in the context of the 'bar' node, not the root.
My ears are open to solutions with HaXML or Scrap Your XML-plate, or anything else.Thanks,Greg
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] Type of a function?

2006-07-14 Thread Jenny678

Hallo

Can somebody tell me the type of  the following function?

func :: ?
func f x = (z,y)
  where (z,y) = f x

Thanks
-- 
View this message in context: 
http://www.nabble.com/Type-of-a-function--tf1945843.html#a5335607
Sent from the Haskell - Haskell-Cafe forum at Nabble.com.

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


[Haskell-cafe] Windows PowerShell "Monad"

2006-07-14 Thread Chad Scherrer

Yep, that's its codename.

Now, I'm not much of a Windows person. Is the name just a weird
coincidence, or does it have anything to do with monads as we know
them?

http://en.wikipedia.org/wiki/MSH_(shell)
--

Chad Scherrer

"Time flies like an arrow; fruit flies like a banana" -- Groucho Marx
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Computing lazy and strict list operations at the same time

2006-07-14 Thread Andrew Pimlott
On Mon, Jun 19, 2006 at 05:50:13PM +0100, Duncan Coutts wrote:
> On Mon, 2006-06-19 at 17:03 +0100, Jon Fairbairn wrote:
> > il [] = error "foo"
> > il [x] = ([], x)
> > il (x:xs) = cof x (il xs)
> > where cof x ~(a,b) = (x:a, b)
> > --  !
> 
> From a quick test, it looks like none of our suggested solutions
> actually work in constant space.
> 
> main = interact $ \s ->
>   case il s of
> (xs, x) -> let l = length xs
>in l `seq` show (l,x)

I was hoping to have enlightenment served to me, but since nobody has
explained this, I took a crack at it.  I still can't explain it, but I
got some data that maybe somebody else will understand.  My code:

initlast :: [a] -> ([a], a)
initlast [x]= ([], x)
initlast (x:xs) = let (init, last) = initlast xs
  in  (x:init, {-# SCC "last" #-} last)

lenshow n (_:xs) last = let n1 = n+1 in n1 `seq` lenshow n1 xs last
lenshow n [] last = show (n,last)

main = interact $ \s -> case initlast s of
  (xs, x) -> lenshow 0 xs x 

lenshow is just "show (length xs, x)", written out so I can tweak it
later.  This exhibits the runaway space usage with a large input that
Duncan described.  If you throw away "last" in lenshow and just "show
n", it runs in constant space.

It seems that the reference to "last" that I annotated as a cost center
is holding a chain of trivial thunks--trivial because "last" is just
being copied from the result of the recursive call to initlast.  I
thought maybe I could get rid of them by returning an unboxed tuple from
initlast, but this turned out to make no difference.

Profiling gave a couple hints.  Retainer set profiling (-hr) showed the
retainer set holding all the memory was

{}

I think this confirms that last holding a chain of thunks.  I'm still
surprised that ghc doesn't see that they're trivial.  It feels like it
should be an easy optimization.

Constructor and type profiling (-hd and -hy) both show the memory held
by stg_ap_1_upd_info.  I don't know what that means.

Most frustrating, I can't find any work around:  No matter how I tried
to write initlast, it had the same leak when consumed this way.  (NB:
functional implementations only need apply.)  Granted, I can't think of
any good reason to code in this style, but it's hard for me to accept
that it should be impossible.

Finally, here is a (silly) version that doesn't leak:

initlast :: [a] -> ([a], [a])
initlast [x]= ([], [x])
initlast (x:xs) = let (init, last) = initlast xs
  in  (x:init, undefined:last)

lenshow n (_:xs) (_:ls) = let n1 = n+1 in n1 `seq` lenshow n1 xs ls
lenshow n [] [last] = show (n,last)

This is the first case I recall in which adding more constructors makes
a space leak go away, because it gives me something to force (vis
"_:ls).  With the original implementation, there was no way to "partly
force" last, one thunk at a time.  Have others used this technique?

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


Re: [Haskell-cafe] The History of Haskell

2006-07-14 Thread Bulat Ziganshin
Hello Simon,

Friday, July 14, 2006, 7:21:26 PM, you wrote:

> The History of Haskell

how about naming it "Haskell: lazy programmer's language" ? :)



-- 
Best regards,
 Bulatmailto:[EMAIL PROTECTED]

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


Re: [Haskell-cafe] ldap-haskell questions

2006-07-14 Thread Donn Cave
On Thu, 13 Jul 2006, Ferenc Wagner wrote:
...
> Second, I find no trace of SSL/TLS routines.  Is that really
> left out, or do I overlook something?

OpenLDAP supports an option LDAP_OPT_X_TLS --

ldap_set_option Nothing LDAP_OPT_X_TLS LDAP_OPT_X_TLS_DEMAND
...
ldapconnection <- ldap_initialize url

I assume you will find something like that there (the above is
actually from my own LDAP interface, but since I haven't seen
any other response to this question ...)

Have no idea about static binaries, even what that means.  When 
I compile with ghc, I get reasonably static libraries inasmuch
as there aren't any GHC shared objects, but of course libc is
shared, as well as anything specified on the link command that
turns out to be a shared library.  If for example I have both
a libldap.so and libldap.a and I want to link to the latter (as
indeed I would), then it's up to me to say so on the link command,
libldap.a instead of -lldap.  Pardon me if that's obvious!

Donn Cave, [EMAIL PROTECTED]

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


[Haskell-cafe] can't WashNGo (abstract tables)

2006-07-14 Thread Ferenc Wagner
Hi,

trying to put WashNGo-2.9 to a nontrivial prototyping job
gave some very compelling results so far, but also got me
stumped on occasions.  I'd be grateful for some guidance on
the following points, concerning abstract tables mainly.

* selectionDisplay: looks like displayFun (fourth arg)
  mustn't fail for null arguments, as it's invoked with them
  after leaving the page it appears on.  An error or a
  feature?  Is it documented?

* trying to get around the "Strings only" restriction of
  AT's I threw in some show-read pairs, but got the
  impression that the channel is not Char-clean:
  Base64.encode . UTF8.encode helped.  What's the spec?

* should a click on an AT radio button result in submission
  of the form?  It does not, which is OK with me.  But the
  following code fails in a rather strange way:

> data Record = P String Person | R String Role | Unknown String deriving 
> (Read,Show)
>
> unAtSafe :: String -> Record
> unAtSafe = read . fst . UTF8.decode . Base64.decode
> 
> edit sg = case record of
>   P dn p-> editPerson dn p
>   R dn r-> editRole dn r
>   Unknown s -> standardQuery "No dice" $ CGI.div $ -- provokes error 
> in AbstractSelector.hs:115
>do p $ text s
>   goBack
> where record = unAtSafe $ head $ unAR $ value sg 
> 
> editPerson :: String -> Person -> CGI ()
> editPerson dn p =
> standardQuery "Edit person" $ CGI.div $
> do inputs <- personTable p
>actionPar "Modify" (createPerson dn) inputs

  In this case Person and Role contain String fields only.
  The abstract table contains Records, and the above
  function 'edit' dispatches on the type of the selected
  Record.  The first two cases work, the Unknown case trips
  on an 'error' in the WashNGo code as indicated.  It's in
  the valueSelectionGroup function, if selectionValue is
  Nothing.  How could I fix this?

* Lastly, how can I go back some queries?  goBack above is
  basically a 'submit0 (return ())' which continues the main
  'forever' loop.  But what if I need to go back in the
  middle of the current loop, as if the user pressed Back
  several times?
-- 
Thanks,
Feri.
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] The History of Haskell

2006-07-14 Thread Simon Peyton-Jones
Friends,

Phil Wadler, John Hughes, Paul Hudak and I have been writing a paper
about the

The History of Haskell

We've submitted an earlier draft to the History Of Programming Languages
conference (HOPL'07), and it's been accepted. We have to submit a
more-or-less final draft by 1 September.

This message is to invite you to read it, tell us what you think, and
help us improve it.  Here it is, along with a Wiki page for you to write
comments:

http://haskell.org/haskellwiki/History_of_Haskell

Enjoy!

Simon

PS: If you followed a link earlier today, and have a version dated Feb,
discard it.  The one you want is dated July 14th.
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] Re: Partial Tuple application

2006-07-14 Thread Christian Maeder
Henning Thielemann schrieb:
> I have seen $f(\cdot)$ instead of $f$ really often, as well as
> $f(\cdot-k)$ for \x -> f(x-k).

yes, but for first order functions only. Then parens can be seen as part
of the identifier (as I showed for tuples before).

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


Re: [Haskell-cafe] Re: Why is Day and Month bounded?

2006-07-14 Thread David Roundy
On Fri, Jul 14, 2006 at 02:28:20PM +0100, David House wrote:
> On 14/07/06, David Roundy <[EMAIL PROTECTED]> wrote:
> >Anyhow, just thought I'd mention that
> >this isn't useful only for "ordinary" cyclic objects like dates.
> 
> Correct. Which is why Chris Kuklewicz included instances for, e.g., Int :)

Ah, that's what I get for just skimming the thread!  :)

> I think this would be a great class to have in the standard libs. It
> would be even better if we could derive it.

I agree, it sounds very nice (although I've obviously not even looked
at the implementation).
-- 
David Roundy
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Re: Why is Day and Month bounded?

2006-07-14 Thread Chris Kuklewicz

David House wrote:

On 14/07/06, David Roundy <[EMAIL PROTECTED]> wrote:

Anyhow, just thought I'd mention that
this isn't useful only for "ordinary" cyclic objects like dates.


Correct. Which is why Chris Kuklewicz included instances for, e.g., Int :)


And the new version takes everything to Integer so there is never any internal 
overflow.



I think this would be a great class to have in the standard libs. It
would be even better if we could derive it.



All the existing instances are just three words:

instance Cyclic Foo

You only need more if you have something strange, or you want to avoid 
projecting to Integer.


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


Re: [Haskell-cafe] Re: Why is Day and Month bounded?

2006-07-14 Thread David House

On 14/07/06, Johan Holmquist <[EMAIL PROTECTED]> wrote:

> You mean  [Monday, Tuesday ... Sunday, Monday] ?

Actually not. No repetitions.


That seems like a very bad idea. '..' normally means 'inclusive',
breaking those semantics would be a very weird thing to do, and breaks
the principle of least surprise.

--
-David House, [EMAIL PROTECTED]
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Re: Why is Day and Month bounded?

2006-07-14 Thread David House

On 14/07/06, David Roundy <[EMAIL PROTECTED]> wrote:

Anyhow, just thought I'd mention that
this isn't useful only for "ordinary" cyclic objects like dates.


Correct. Which is why Chris Kuklewicz included instances for, e.g., Int :)

I think this would be a great class to have in the standard libs. It
would be even better if we could derive it.

--
-David House, [EMAIL PROTECTED]
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Re: Why is Day and Month bounded?

2006-07-14 Thread David Roundy
Interestingly, your Cyclic class idea may have practical purposes
beyond enumeration.  Integers modulo some number are also cyclical,
and can come in very handy.  In fact, raw unsigned ints are modulo
2^32 (or something like that), so they really ought (under one
interpretation) to be members of Cyclic rather than Bounded.  It would
certainly be more efficient, since you wouldn't need to do any
overflow checking, and the cpu implements the Cyclic operations, but
not the Bounded operations.  Anyhow, just thought I'd mention that
this isn't useful only for "ordinary" cyclic objects like dates.
-- 
David Roundy
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] Re: Building Data.Time on WinXP GHC6.4.1

2006-07-14 Thread Simon Marlow

Alistair Bayley wrote:

Has anyone built Ashley's Data.Time package on Windows? I ask because
timestuff.c fails to compile for me because it refers to fields
(tm_zone, tm_gmtoff) in struct tm which don't seem to exist on Windows
(at least, mingw).


Yes, I made it work on Windows recently.  The fixes should be in the darcs repo 
at http://darcs.haskell.org/packages/time, did you get it from there?


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


[Haskell-cafe] Re: Why is Day and Month bounded?

2006-07-14 Thread Johan Holmquist

> Would not "liftM2 (,) [0..] [Sunday .. Saturday]" do the trick?

You mean
  liftM2 (,) [0..] [January .. December] ?
(I chose Months in order to get a sensible example.)


Ah, yes. My mistake.


I assume that the Bounded class exists in order to stay independent from
the particular type. With minBound and maxBound you do not rely on whether
the counting starts on Sunday or Monday if you only want to do something
for all days.


Now I see. Sure, your code can be used for any bounded type while mine
is specific to Days (or Months).

Well, to achieve the same with cyclic enums I would need yet another
type class to get bounds which do not put any constraints on
exceptions for succ and pred. That would be rather stupid, I think.
Would be better with a dedicated cyclic enum class that do not have
the succ and pred constraints for bounded instances.


> Sure there are subtleties, like what should [Monday .. Monday] return,
either:
> [Monday] or
> [Monday, Tuesday ... Sunday]
> but to settle for one would be ok to me.

You mean  [Monday, Tuesday ... Sunday, Monday] ?


Actually not. No repetitions.


I also think that there must be a possibility to obtain an empty list.


That would be tricky. Not sure why an empty list must be obtained.

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


Re: [Haskell-cafe] Re: Why is Day and Month bounded?

2006-07-14 Thread Henning Thielemann

On Fri, 14 Jul 2006, Johan Holmquist wrote:

> from Henning Thielemann:
> > Since the days are cycling, what is more natural about your result
> > compared to my one?
> 
> I would prefer the one without any repetitions.
> 
> > I assume the Bounded instance exists in order to allow loops like
> >   liftM2 (,) [0..] [minBound .. (maxBound::System.Time.Month)]
> 
> Would not "liftM2 (,) [0..] [Sunday .. Saturday]" do the trick?

You mean
  liftM2 (,) [0..] [January .. December] ?
(I chose Months in order to get a sensible example.)

I assume that the Bounded class exists in order to stay independent from
the particular type. With minBound and maxBound you do not rely on whether
the counting starts on Sunday or Monday if you only want to do something
for all days.


> Sure there are subtleties, like what should [Monday .. Monday] return, either:
> [Monday] or
> [Monday, Tuesday ... Sunday]
> but to settle for one would be ok to me.

You mean  [Monday, Tuesday ... Sunday, Monday] ?

I also think that there must be a possibility to obtain an empty list.
Now I get it with
 [Monday .. Sunday]
but I assume that you prefer
 [Monday, Tuesday ... Sunday]
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] Re: Partial Tuple application

2006-07-14 Thread Henning Thielemann

On Fri, 14 Jul 2006, Christian Maeder wrote:

> Henning Thielemann schrieb:
> >> in haskell-prime list there was a proposal to use '?' for such things:
> >>
> >> (1,2,?)
> >>
> >> only problem is what it's hard to define exactly where the lambda
> >> should arise:
> 
> the placeholder '?' becomes part of a new implicit identifier (that
> exceeds Haskell's identifier syntax). If we have:
> 
> (,,) :: a -> b -> c -> (a, b, c)
> 
> we get a bunch of new identifiers:
> 
> (?,,) :: b -> c -> a -> (a, b, c)
> (,?,) :: a -> c -> b -> (a, b, c)
> (,,?) :: a -> b -> c -> (a, b, c)
> 
> And maybe also:
> (?,?,) :: c -> a -> b -> (a, b, c)
> 
> and so on. For infix ops this looks natural to me.

 I see. It would require that ? belongs to tuples exclusively and that it
will never be used elsewhere, say for lists like in [1,2,?]. Because then
the expression [(1,?)] becomes ambigous.
 Like with every kind of syntactic sugar, I fear that the next thing that
people request, are expressions like

(1,2,3+?)

for

\x -> (1,2,3+x)

> > Yes that's a really evil problem that I already encountered in
> > mathematics. Some mathematicians like to write f(·) or even f(·-k) which
> > exhibits exactly the ambiguity you mention. Such placeholders are a really
> > bad idea.
> 
> "f(?)" should not make sense in Haskell, since the parens do not belong
> to the identifier "f". (It's also not necessary: \ x -> f(x) = f)

Necessary or not, applied mathematicians don't care about redundancy. :-)  
I have seen $f(\cdot)$ instead of $f$ really often, as well as
$f(\cdot-k)$ for \x -> f(x-k).
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] Re: Why is Day and Month bounded?

2006-07-14 Thread Johan Holmquist

Yes, it would be possible to make ones own class and instantiate from
that. I was just thinking Day and Month should be cyclic per default.


from Henning Thielemann:

Since the days are cycling, what is more natural about your result
compared to my one?


I would prefer the one without any repetitions.


I assume the Bounded instance exists in order to allow loops like
  liftM2 (,) [0..] [minBound .. (maxBound::System.Time.Month)]


Would not "liftM2 (,) [0..] [Sunday .. Saturday]" do the trick?

Sure there are subtleties, like what should [Monday .. Monday] return, either:
[Monday] or
[Monday, Tuesday ... Sunday]
but to settle for one would be ok to me.

from Malcolm Wallace:

But how do you feel about the way it breaks some algebraic laws?
   fromEnum x < fromEnum (succ x)
   fromEnum x > fromEnum (pred x)


I would take the irresponsible and easy path and just accept it. As
you said, it is not stated that any such relations must hold.

Probably the cleanest approach is the one suggested by Chris Kuklewicz:
Make the cyclings explicit in their own class and escape all surprises
involved in sudden cyclic Enums.

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


[Haskell-cafe] Re: Partial Tuple application (Was: Comma in the front)

2006-07-14 Thread Christian Maeder
Henning Thielemann schrieb:
>> in haskell-prime list there was a proposal to use '?' for such things:
>>
>> (1,2,?)
>>
>> only problem is what it's hard to define exactly where the lambda
>> should arise:

the placeholder '?' becomes part of a new implicit identifier (that
exceeds Haskell's identifier syntax). If we have:

(,,) :: a -> b -> c -> (a, b, c)

we get a bunch of new identifiers:

(?,,) :: b -> c -> a -> (a, b, c)
(,?,) :: a -> c -> b -> (a, b, c)
(,,?) :: a -> b -> c -> (a, b, c)

And maybe also:
(?,?,) :: c -> a -> b -> (a, b, c)

and so on. For infix ops this looks natural to me.

>>
>> (1,2,\x->x)

I see no reason for this interpretation.

>> (\x -> (1,2,x))

That should exactly be the implicit definition of my above implicit
identifiers.

> Yes that's a really evil problem that I already encountered in
> mathematics. Some mathematicians like to write f(·) or even f(·-k) which
> exhibits exactly the ambiguity you mention. Such placeholders are a really
> bad idea.

"f(?)" should not make sense in Haskell, since the parens do not belong
to the identifier "f". (It's also not necessary: \ x -> f(x) = f)

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


Re: [Haskell-cafe] Re: Why is Day and Month bounded?

2006-07-14 Thread Chris Kuklewicz

Okay...final version attached.

This one fixes the toCycle bugs and changes from Int to Integer so overflow is 
no longer an issue.


The result of cycleFromThenTo fits what I would expect, but you are free to drop 
this or adapt it.


cycleFrom and cycleFromTo and cycleFromThen are easy, since there is no 
difference between ascending and descending.  Note that the returned list is 
never null.


cycleFromThenTo can be either ascending or descending depending on the first two 
arguments, and it considers the first occurrence of the third argument in that 
direction of the cycle starting from the initial argument:


*Cycle> cycleFromThenTo Monday Wednesday Tuesday
[Monday]

instead of


*Cycle> cycleFromThenTo Monday Wednesday Tuesday
[Monday,Wednesday,Friday,Sunday,Tuesday]


This agrees with things like [1,3 .. 2] returning [1] and [3,1 .. 2] returning 
[3].

{- By Chris Kuklewicz <[EMAIL PROTECTED]> 
   3 Clause BSD license, copyright 2006
-}
module Cycle (Cyclic(..)) where

import System.Time
import Data.Word
import Data.Int

default ()

class (Eq c,Enum c, Bounded c) => Cyclic c where
cyclePeriod :: c -> Integer
cyclePeriod _ = fromCycle (maxBound :: c) 
- fromCycle (minBound :: c) + 1

succCycle :: c -> c
succCycle c | c == maxBound = minBound
| otherwise = succ c

predCycle :: c-> c
predCycle c | c == minBound = maxBound
| otherwise = pred c

fromCycle :: c -> Integer
fromCycle = toInteger . fromEnum

toCycle :: Integer -> c
toCycle = toEnum 
  . fromInteger
  . (+ (fromCycle (minBound::c)))
  . (`mod` (cyclePeriod (undefined::c)))
  . (subtract (fromCycle (minBound::c)))

cycleFrom :: c -> [c]
cycleFrom x = map toCycle [fromCycle x ..]

cycleFromTo :: c -> c -> [c]
cycleFromTo x y = let xi = fromCycle x
  yi = fromCycle y
  zi = if xi > yi then yi + cyclePeriod (undefined::c)
  else yi
  in map toCycle [xi .. zi]

cycleFromThen :: c -> c -> [c]
cycleFromThen x y = let xi = fromCycle x
yi = fromCycle y
in map toCycle [xi, yi ..]

cycleFromThenTo :: c -> c -> c -> [c]
cycleFromThenTo x y z = let 
c = cyclePeriod (undefined::c)
xi = fromCycle x; yi = fromCycle y; zi = fromCycle z
zi' = if xi <= yi
then if xi <= zi 
   then zi
   else zi + c
else if zi <= xi
   then zi
   else zi - c
in map toCycle [xi, yi .. zi']

instance Cyclic ()
instance Cyclic Bool
instance Cyclic Ordering
instance Cyclic Int
instance Cyclic Char

instance Cyclic Day -- Imported from System.Time
instance Cyclic Month   -- Imported from System.Time

instance Cyclic Int8-- Imported from GHC.Int
instance Cyclic Int64   -- Imported from GHC.Int
instance Cyclic Int32   -- Imported from GHC.Int
instance Cyclic Int16   -- Imported from GHC.Int

instance Cyclic Word8   -- Imported from GHC.Word
instance Cyclic Word64  -- Imported from GHC.Word
instance Cyclic Word32  -- Imported from GHC.Word
instance Cyclic Word16  -- Imported from GHC.Word
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Re: Why is Day and Month bounded?

2006-07-14 Thread Chris Kuklewicz

Hmmm... I think I should have said:


toCycle :: Int -> c
toCycle = toEnum 
  . (+ (fromEnum (minBound::c))) 
  . (`mod` (cyclePeriod (undefined::c)))



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


Re: [Haskell-cafe] Re: Why is Day and Month bounded?

2006-07-14 Thread Chris Kuklewicz

Try this:


module Cycle (Cyclic(..)) where

import System.Time
import Data.Word
import Data.Int

class (Eq c,Enum c, Bounded c) => Cyclic c where
cyclePeriod :: c -> Int
cyclePeriod _ = fromEnum (maxBound :: c) - fromEnum (minBound :: c) + 1
succCycle :: c -> c
succCycle c | c == maxBound = minBound
| otherwise = succ c
predCycle :: c-> c
predCycle c | c == minBound = maxBound
| otherwise = pred c
fromCycle :: c -> Int
fromCycle = fromEnum
toCycle :: Int -> c
toCycle = toEnum . (`mod` (cyclePeriod (undefined::c)))
cycleFrom :: c -> [c]
cycleFrom x = map toCycle [fromCycle x ..]
cycleFromTo :: c -> c -> [c]
cycleFromTo x y = let xi = fromCycle x
  yi = fromCycle y
  zi = if xi > yi then yi + cyclePeriod (undefined::c)
  else yi
  in map toCycle [xi .. zi]
cycleFromThen :: c -> c -> [c]
cycleFromThen x y = let xi = fromCycle x
yi = fromCycle y
in map toCycle [xi, yi ..]
cycleFromThenTo :: c -> c -> c -> [c]
cycleFromThenTo x y z = let 
c = cyclePeriod (undefined::c)

xi = fromCycle x; yi = fromCycle y; zi = fromCycle z
zi' = if xi <= yi
then if yi <= zi 
   then zi

   else zi + c
else if zi <= yi
   then zi
   else zi - c
in map toCycle [xi, yi .. zi']

instance Cyclic Day
instance Cyclic Month
instance Cyclic Bool
instance Cyclic ()
instance Cyclic Ordering
instance Cyclic Int
instance Cyclic Char
instance Cyclic Int8-- Imported from GHC.Int
instance Cyclic Int64   -- Imported from GHC.Int
instance Cyclic Int32   -- Imported from GHC.Int
instance Cyclic Int16   -- Imported from GHC.Int
instance Cyclic Word8   -- Imported from GHC.Word
instance Cyclic Word64  -- Imported from GHC.Word
instance Cyclic Word32  -- Imported from GHC.Word
instance Cyclic Word16  -- Imported from GHC.Word


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


Re: [Haskell-cafe] Re: Why is Day and Month bounded?

2006-07-14 Thread Malcolm Wallace
"Johan Holmquist" <[EMAIL PROTECTED]> wrote:

> If Day (and Month) where NOT instances of Bounded, the following would
> be possible:
> 
> [Saturday .. Tuesday]
> => should return [Saturday, Sunday, Monday, Tuesday]
> => but returns []

This does seem like a reasonable argument to me.  Some enumerations are
semantically cyclic, rather than linear.

But how do you feel about the way it breaks some algebraic laws?
fromEnum x < fromEnum (succ x)
fromEnum x > fromEnum (pred x)
Of course, such laws are not explicitly stated anywhere in the
definition of the classes, so one would be foolish to rely on them in
any case.

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


[Haskell-cafe] Partial Tuple application (Was: Comma in the front)

2006-07-14 Thread Henning Thielemann

On Fri, 14 Jul 2006, Bulat Ziganshin wrote:

> Hello Tomasz,
> 
> Friday, July 14, 2006, 9:31:32 AM, you wrote:
> 
> >> There might be issues with tuples though, for example (1,2,) would be
> >> the (,) tuple and not the (,,) tuple, which is a bit weird.
> 
> > Besides, it might be a bit more natural if (1,2,) was a shorthand for
> (\x ->> (1,2,x))
> 
> in haskell-prime list there was a proposal to use '?' for such things:
> 
> (1,2,?)
> 
> only problem is what it's hard to define exactly where the lambda
> should arise:
> 
> (1,2,\x->x)
> (\x -> (1,2,x))

Yes that's a really evil problem that I already encountered in
mathematics. Some mathematicians like to write f(�) or even f(�-k) which
exhibits exactly the ambiguity you mention. Such placeholders are a really
bad idea.
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Re: Why is Day and Month bounded?

2006-07-14 Thread Henning Thielemann

On Fri, 14 Jul 2006, Johan Holmquist wrote:

> I'll answer my own post to elaborate:
> 
> If Day (and Month) where NOT instances of Bounded, the following would
> be possible:
> 
> [Monday .. Sunday]
> => should return [Monday, Tuesday ... Saturday, Sunday]
> => but returns []

Why not
  [Monday, Tuesday ... Saturday, Sunday, Monday, Tuesday ... Saturday, Sunday] ?

Since the days are cycling, what is more natural about your result
compared to my one?

I assume the Bounded instance exists in order to allow loops like
   liftM2 (,) [0..] [minBound .. (maxBound::System.Time.Month)]
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] Re: Why is Day and Month bounded?

2006-07-14 Thread Johan Holmquist

I'll answer my own post to elaborate:

If Day (and Month) where NOT instances of Bounded, the following would
be possible:

[Monday .. Sunday]
=> should return [Monday, Tuesday ... Saturday, Sunday]
=> but returns []

[Saturday .. Tuesday]
=> should return [Saturday, Sunday, Monday, Tuesday]
=> but returns []

succ Saturday
=> should return Sunday
=> but yields an exception

It would feel natural to be able to get the desired results above. The
Haskell98 report stipulates:

--->8---
For any type that is an instance of class Bounded as well as Enum, the
following should hold:
The calls succ maxBound and pred minBound should result in a runtime error.
--->8---

So, the standard library System.Time respects that and yields
exception for succ Saturday. But if Day was not an instance of Bounded
should it not be legal for succ Saturday to return Sunday?

Now I cannot see the advantage of letting Day (and Month) be instances
of Bounded. The only thing we get out of that is access to functions
maxBound and minBound, but those do not seem useful to me for either
Day or Month.


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


[Haskell-cafe] ANN: Takusen 0.5

2006-07-14 Thread Alistair Bayley

Oleg and I are pleased to announce the release of a new version of Takusen
(it's been a while; so long that we don't remember the last version number
we used).

The most significant code change is a new internal design (courtesy of Oleg)
which gives better separation of concerns like statement preparation,
binding, and result-set processing.

Also of note is a conversion to darcs, and hosting at haskell.org
(thanks to Simon Marlow):

 darcs get http://darcs.haskell.org/takusen

... which also has the nice property that the Haddock documentation is
browseable online:

 http://darcs.haskell.org/takusen/doc/html/index.html

A comprehensive description of API usage can be found in the documentation
for module Database.Enumerator:

 http://darcs.haskell.org/takusen/doc/html/Database-Enumerator.html

We hope that the use of darcs will encourage contributions...

Other changes:
 - support for multiple result sets returned from functions (PostgreSQL only).
   Oracle support for this is in the pipeline, which will allow
   use of nested cursors, and processing RefCursors returned as output
   parameters from procedure calls.

Future plans:
 - Cabalisation
 - use of Data.Time instead of System.Time
 - ODBC and MS Sql Server backends

For those of you unfamiliar with Takusen, here is our HCAR blurb:

Takusen is a library for accessing DBMS's. It is a low-level library like HSQL,
in the sense that it is used to issue SQL statements.
Takusen's "unique-selling-point" is a design for processing query results using
a left-fold enumerator. For queries the user creates an iteratee function,
which is fed rows one-at-a-time from the result-set.
We also support processing query results using a cursor interface,
if you require finer-grained control.
Currently we fully support Oracle, Sqlite, and PostgreSQL.


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


[Haskell-cafe] Building Data.Time on WinXP GHC6.4.1

2006-07-14 Thread Alistair Bayley

Has anyone built Ashley's Data.Time package on Windows? I ask because
timestuff.c fails to compile for me because it refers to fields
(tm_zone, tm_gmtoff) in struct tm which don't seem to exist on Windows
(at least, mingw).

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


Re[2]: [Haskell-cafe] Comma in the front

2006-07-14 Thread Bulat Ziganshin
Hello Tomasz,

Friday, July 14, 2006, 9:31:32 AM, you wrote:

>> There might be issues with tuples though, for example (1,2,) would be
>> the (,) tuple and not the (,,) tuple, which is a bit weird.

> Besides, it might be a bit more natural if (1,2,) was a shorthand for
(\x ->> (1,2,x))

in haskell-prime list there was a proposal to use '?' for such things:

(1,2,?)

only problem is what it's hard to define exactly where the lambda
should arise:

(1,2,\x->x)
(\x -> (1,2,x))

or even at some more outer level. aside of this, it would be very handy
addition to various existing partial application styles:

f a
`f` a
a `f`
(*2)
(2*)
(*)


-- 
Best regards,
 Bulatmailto:[EMAIL PROTECTED]

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