[Haskell-cafe] Re: Haskell performance (again)!

2006-10-10 Thread Jón Fairbairn
Brian Hulley [EMAIL PROTECTED] writes:

 Lennart Augustsson wrote:
  I think your first try looks good.
 [snip]
  ...
  addPoly1 p1@(p1h@(Nom p1c p1d):p1t) p2@(p2h@(Nom p2c p2d):p2t)
 | p1d == p2d = Nom (p1c + p2c) p1d : addPoly1 p1t p2t
 | p1d  p2d = p1h : addPoly1 p1t p2
 | p1d  p2d = p2h : addPoly1 p1 p2t
  ...
 
 The last comparison is redundant (this was in the original
 version too) because p1d  p2d is implied (certainly for
 this case where p1d, p2d::Int) by the fall through from not
 satisfying == and  so how about:
 
 addPoly1 p1@(p1h@(Nom p1c p1d):p1t) p2@(p2h@(Nom p2c p2d):p2t)
 | p1d == p2d = Nom (p1c + p2c) p1d : addPoly1 p1t p2t
 | p1d  p2d = p1h : addPoly1 p1t p2
 | otherwise = p2h : addPoly1 p1 p2t

Surely all but one of the comparisons is unnecessary? If you
use `compare` instead of (==) and friends, won't one do (I'm
assuming that the compiler can convert cases on LT, EQ and
GT into something sensible -- after all, wasn't that the
purpose of compare?)?

-- 
Jón Fairbairn [EMAIL PROTECTED]
http://www.chaos.org.uk/~jf/Stuff-I-dont-want.html  (updated 2006-09-13)

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


[Haskell-cafe] Profiling CAFs (re-post)

2006-10-10 Thread Matthias Fischmann


Hi again,

I posted a bunch of questions on profiling here a few days back, but
couldn't tickle anybody to post a reply.  Since I am not tired any
more today, but still can't understand the documentation, or the
output of the profiler, here it goes again:

  What qualifies as constant applicable form, and why is it not
  labelled in a more informative way?

  Why are there functions that inherit all of their (considerable)
  time and space consumption from elsewhere, but nothing in the
  list would allow for such a rich inheritage?

As I said, I am happy to set up a wiki page if I learn anything that
helps me improve the utility of profiling (the profiler and the
rudimentary documentation are of great value as is).  And i am happy
to take pointers and go read articles if you tell me they help in the
everyday work with ghc profiling.

thanks / cheers,
matthias


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


[Haskell-cafe] beginner's problem about lists

2006-10-10 Thread falseep
Hi all,I'm trying to  implement a function that returns the shorter  one oftwo given lists,something likeshorter :: [a] - [a] - [a]suchthat shorter [1..10] [1..5]  returns [1..5],and it's okay for shorter [1..5] [2..6] to return either.
Simple, right?However,   it becomes difficult when   dealing with infinite lists, for example,shorter [1..5] (shorter [2..] [3..])Could this evaluate to [1..5]? I haven'tfounda  proper implementation.
Again it's ok for shorter [2..] [3..] to return  whatever that can solve theabove problem correctly.An infinite listcould work, I guess, but I don't know how.Thanks for any help.
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] beginner's problem about lists

2006-10-10 Thread Neil Mitchell

Hi,

The trick is not call length, since length demands the whole of a
list, and won't terminate on an infinite list. You will want to
recurse down the lists.

Is this a homework problem? It's best to declare if it is, and show
what you've managed to do so far.

Thanks

Neil

On 10/10/06, [EMAIL PROTECTED] [EMAIL PROTECTED] wrote:

Hi all,

I'm trying to implement a function that returns the shorter one of two given
lists,
something like
shorter :: [a] - [a] - [a]
such that shorter [1..10] [1..5] returns [1..5],
and it's okay for shorter [1..5] [2..6] to return either.

Simple, right?

However, it becomes difficult when dealing with infinite lists, for example,
shorter [1..5] (shorter [2..] [3..])
Could this evaluate to [1..5]? I haven't found a proper implementation.

Again it's ok for shorter [2..] [3..] to return whatever that can solve the
above problem correctly.
An infinite list could work, I guess, but I don't know how.

Thanks for any help.


___
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] a monad for secret information

2006-10-10 Thread Seth Gordon
Cale Gibbard wrote:
 Why not just:
 
 secret :: a - Classification String a
 secret = Classification xyzzy
 
 The password string isn't part of the type, it doesn't even
 necessarily exist at compile time. You might have just got confused
 between type and data constructors for a moment.
 

But now I want to be able to process the secret monadically:

mySecret =
  secret Jimmy Hoffa is buried under the 50-yd line in the Meadowlands

do secretData - mySecret
   return (length secretData)

How do I define return so that it will put the password back, and how
do I define (=) so that the password won't be accessible within the
do-block?
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] a monad for secret information

2006-10-10 Thread Neil Mitchell

Hi,

I'm not sure what you are after, but:

data Secret a = Secret {password :: String, value :: a}

classify :: String - a - Secret a
classify = Secret

declassify :: String - Secret a - Maybe a
declassify guess (Secret pw v) | guess == pw = Just v
| otherwise = Nothing

Put that in a module, do not export the Secret data type, and you're
good to go. I'm unsure what a Monad is giving you

Thanks

Neil


On 10/10/06, Seth Gordon [EMAIL PROTECTED] wrote:

Cale Gibbard wrote:
 Why not just:

 secret :: a - Classification String a
 secret = Classification xyzzy

 The password string isn't part of the type, it doesn't even
 necessarily exist at compile time. You might have just got confused
 between type and data constructors for a moment.


But now I want to be able to process the secret monadically:

mySecret =
  secret Jimmy Hoffa is buried under the 50-yd line in the Meadowlands

do secretData - mySecret
   return (length secretData)

How do I define return so that it will put the password back, and how
do I define (=) so that the password won't be accessible within the
do-block?
___
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] beginner's problem about lists

2006-10-10 Thread Matthias Fischmann
On Tue, Oct 10, 2006 at 08:10:44PM +0800, [EMAIL PROTECTED] wrote:
 To: haskell-cafe@haskell.org
 From: [EMAIL PROTECTED]
 Date: Tue, 10 Oct 2006 20:10:44 +0800
 Subject: [Haskell-cafe] beginner's problem about lists
 
 Hi all,
 
 I'm trying to implement a function that returns the shorter one of two given
 lists,
 something like
 shorter :: [a] - [a] - [a]
 such that shorter [1..10] [1..5] returns [1..5],
 and it's okay for shorter [1..5] [2..6] to return either.
 
 Simple, right?
 
 However, it becomes difficult when dealing with infinite lists, for example,
 shorter [1..5] (shorter [2..] [3..])
 Could this evaluate to [1..5]? I haven't found a proper implementation.
 
 Again it's ok for shorter [2..] [3..] to return whatever that can solve
 the above problem correctly.
 An infinite list could work, I guess, but I don't know how.

a function that takes two lists and decides whether one of them is
finite or not , without being given further information on the lists,
does not exist.

you could add a third argument 'inifinity :: Int' that sets the minium
length of all lists that are considered infinite.  this is where your
function could stop looking for an end in either of the two
parameters:

-- untested
shorter infinity = reverse . f infinity [] []
f 0 ar al _ _ = ar
f _ ar al [] _ = ar
f _ ar al _ [] = al
f (i+1) ar al (x:xs) (y:ys) = f i (x:ar) (y:al) xs ys

or you could specify your function to be callable with at most one
infinite list.

i guess that's all you can do?


matthias


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


Re: [Haskell-cafe] beginner's problem about lists

2006-10-10 Thread Lennart Augustsson


On Oct 10, 2006, at 08:49 , Matthias Fischmann wrote:


On Tue, Oct 10, 2006 at 08:10:44PM +0800, [EMAIL PROTECTED] wrote:

To: haskell-cafe@haskell.org
From: [EMAIL PROTECTED]
Date: Tue, 10 Oct 2006 20:10:44 +0800
Subject: [Haskell-cafe] beginner's problem about lists

Hi all,

I'm trying to implement a function that returns the shorter one of  
two given

lists,
something like
shorter :: [a] - [a] - [a]
such that shorter [1..10] [1..5] returns [1..5],
and it's okay for shorter [1..5] [2..6] to return either.

Simple, right?

However, it becomes difficult when dealing with infinite lists,  
for example,

shorter [1..5] (shorter [2..] [3..])
Could this evaluate to [1..5]? I haven't found a proper  
implementation.


Again it's ok for shorter [2..] [3..] to return whatever that can  
solve

the above problem correctly.
An infinite list could work, I guess, but I don't know how.


a function that takes two lists and decides whether one of them is
finite or not , without being given further information on the lists,
does not exist.


A function that takes two lists and decides if one is finite does  
indeed exist.  But if both are infinite you'll get partial  
information out.


The example
  shorter [1..5] (shorter [2..] [3..])
is a little tricky, but certainly doable.

-- Lennart

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


Re: [Haskell-cafe] Profiling CAFs (re-post)

2006-10-10 Thread Ian Lynagh
On Tue, Oct 10, 2006 at 01:31:58PM +0200, Matthias Fischmann wrote:
 
   What qualifies as constant applicable form, and why is it not
   labelled in a more informative way?

CAFs are, AIUI, things that are just values (i.e. things that don't take
an argument) that have been floated up to the top level.

Compiling with -caf-all might give you more useful information.
If that doesn't help then you might find it helpful to look at heap
profiles rather than just the normal profiler output.

   Why are there functions that inherit all of their (considerable)
   time and space consumption from elsewhere, but nothing in the
   list would allow for such a rich inheritage?

I didn't understand that. If it's possible to give a small example then
that might help?


Thanks
Ian

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


Re: [Haskell-cafe] beginner's problem about lists

2006-10-10 Thread Henning Thielemann

On Tue, 10 Oct 2006 [EMAIL PROTECTED] wrote:

 Hi all,
 
 I'm trying to implement a function that returns the shorter one of two given
 lists,
 something like
 shorter :: [a] - [a] - [a]
 such that shorter [1..10] [1..5] returns [1..5],
 and it's okay for shorter [1..5] [2..6] to return either.
 
 Simple, right?
 
 However, it becomes difficult when dealing with infinite lists, for example,
 shorter [1..5] (shorter [2..] [3..])
 Could this evaluate to [1..5]? I haven't found a proper implementation.
 
 Again it's ok for shorter [2..] [3..] to return whatever that can solve
 the above problem correctly.
 An infinite list could work, I guess, but I don't know how.

With PeanoNumbers,
   http://darcs.haskell.org/htam/src/Number/PeanoNumber.hs
 I would first attach a lazy length information to each list before any
call to 'shorter', then I would remove this information after the last
call to 'shorter'.

Untested code follows:

attachLength :: [a] - (PeanoNumber.T, [a])
attachLength xs = (genericLength xs, xs)

detachLength :: (PeanoNumber.T, [a]) - [a]
detachLength = snd 

shorter :: (PeanoNumber.T, [a]) - (PeanoNumber.T, [a]) - (PeanoNumber.T, [a])
shorter (xl,xs) (yl,ys) = (min xl yl, if xl  yl then xs else ys)


detachLength
   (shorter (attachLength [1..5])
   (shorter (attachLength [2..]) 
(attachLength [3..])))


This will work with if one of the lists is finite. If all lists are
infinite, this solution fails. You can simulate the peano numbers also 
with [()].
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] beginner's problem about lists

2006-10-10 Thread Colin DeVilbiss

On 10/10/06, [EMAIL PROTECTED] [EMAIL PROTECTED] wrote:


I'm trying to implement a function that returns the shorter one of two given
lists,
something like
shorter :: [a] - [a] - [a]



However, it becomes difficult when dealing with infinite lists, for example,
shorter [1..5] (shorter [2..] [3..])
Could this evaluate to [1..5]? I haven't found a proper implementation.


If you can figure out a solution that works for both shorter [1..5]
[2..] and shorter [2..] [1..5], the essence of that solution will
work to define a shortest [[1..5],[2..],[3..]] (leaving shorter a b
= shortest [a, b]).

As shown elsewhere in the thread, there is at least one solution with
slightly different type signatures that works much like you want;
something like:

unFoo (shorter' (foo a) (shorter' (foo b) (foo c)))

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


Re: [Haskell-cafe] beginner's problem about lists

2006-10-10 Thread falseep
Thanks for your reply. I tried afew ways butnoneworked.One islike: shorter as bs =  f id id as bs wheref ca cb [] _ =ca[]  f ca cb _ [] = cb []f ca cb (a:as) (b:bs) = f (ca.(a:)) (cb.(b:)) as bs
However this will result in a non-terminating loop for shorter [1..] [2..],sincethefirsttwopatternsoffshall nevermatch.Another way, I could guarantee that the evaluation  ofshorter [1..5] (shorter [1..] [2..])
terminate butI lose the information to   figure out whichlistwasthe shortestone.Using zips:shorter = zipWith (\ab- undefined) -- this   returns the length,butnotthecontentoftheshorter list
(\ab-undefined) could be replaced with something that encode the contents ofthe two lists, but  it makes no difference since I won't know which one is the answer.The difficulty is that I cannot   have these both:
A. ifonelistisfinite,figureouttheshorterone B. if both are infinite, returning an infinite list could workBTW, there   IS an way to implement this functionality for a finite list of (possibly infinite) lists:
shortest = measureWith [] wheremeasureWith ruler as = f matcheswhere ruler' = undefined : rulermatches = filter p asp a = length (zip ruler' a) == length (zip ruler a)
f [] = measureWith ruler' asf matches = matcheswhich somehow makes it unnecessary to   find the function shorter,but the original simple problem is interesting itself.
Thanks.On 10/10/06, Neil Mitchell [EMAIL PROTECTED] wrote:
Hi,The trick is not call length, since length demands the whole of alist, and won't terminate on an infinite list. You will want torecurse down the lists.Is this a homework problem? It's best to declare if it is, and show
what you've managed to do so far.ThanksNeil
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] beginner's problem about lists

2006-10-10 Thread Neil Mitchell

Hi


However this will result in a non-terminating loop for shorter [1..] [2..],
since the first two patterns of f shall never match.


The specification of your problem makes this a guarantee. How do you
know that a list is finite? You find the [] at the end. How do you
know a list is infinite? You spend an infinite amount of time and
never find the []. Hence you can't tell if you have two big lists, or
two infinite lists.

Thanks

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


[Haskell-cafe] A type in search of a name...

2006-10-10 Thread Brian Hulley

Hi,
You'll never believe it but I've been struggling last night and all of today 
to try and think up a name for the following type and I'm still nowhere near 
a solution:


   data ??? = VarId | VarSym | ConId | ConSym

this is part of a type to describe Haskell lexemes:

   data Token = TName !??? !ByteString.T | ...

Here are some of my attempts to fill in ??? and my reasons for rejecting 
them:


1) VarConIdSym - the problem is that it's too long and the first letter is 
'v' which could be confused with the letter 'V' in VarId or VarSym


2) Name - the problem is that this suggests the string itself rather than 
the VarId/VarSym/ConId/ConSym'ness of the token


3) NameType - I'm trying to avoid using the words Type Kind etc because 
I'll probably want to use these later for other things and in any case 
NameType suggests the type of a lexical name ie Token itself


4) Space - this can be confused with something to represent whitespace or 
the namespaces introduced by modules


5) Just using data Token = TVarId !BS.T | TVarSym !BS.T | ... -- explodes 
into too many different cases when you add tokens for qualified names and 
all their variations (since I'm also representing incomplete tokens like 
Foo. and Foo.where (as a prefix of Foo.whereas etc since it can't 
stand by itself because where is a reserved word))


6) Using Bool as in data Token = TName !Bool !Bool !BS.T -- problem is that 
then I won't get any help from the typechecker if I accidentally confuse the 
order of Bools when matching etc. I could use the record syntax but then 
code can become very clunky to look at and it would still allow the Bools to 
get confused when they are passed about


Any ideas? I must say that trying to think up names for things is absolutely 
the most difficult task in programming imho. The problem is that once fixed 
down, a name gets used all over the place and becomes totally entrenched in 
the code and affects how one thinks about the code thereby influencing its 
whole future development in a very deep and pervasive way (think suffixes/ 
prefixes/ relationships with other concepts etc).


I would also be satisfied with just good names for the following types:

   data ???1 = Var | Con
   data ???2 = Id | Sym
   data ???3 = Op | Plain

(I just combined ???1 and ???2 in ??? to try and save some space in the 
representation but ideally they would be separate types if only there were a 
way to tell the compiler to represent each by 1 bit in a word at the machine 
level like C's struct {VarCon vc : 1; IdSym is : 1;})


Any suggestions welcome,
Thanks, 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] casting

2006-10-10 Thread Bulat Ziganshin
Hello Thomas,

Monday, October 9, 2006, 3:47:05 PM, you wrote:

 constraints on its type. Rather than being just any type that is an
 instance of A, I want to do a runtime check and do something different

it's a sort of problem that bites me many times when i start to wrote
Streams library :)  although you said that you discovered the
dictionaries mechanism, i propose you to read
http://haskell.org/haskellwiki/OOP_vs_type_classes page where you can
find something that you don't yet know

-- 
Best regards,
 Bulatmailto:[EMAIL PROTECTED]

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


Re: Re: [Haskell-cafe] beginner's problem about lists

2006-10-10 Thread Nicolas Frisby

I suppose using indicative types (dependent style) is out of the
question? I presume i) that would over-simplify the problem and ii)
we're tied to the [-] type.

It deserves mention no less.


data Fin
data Inf



data List l a = Cons a (List l a) | Nil



shorter :: List Inf a - List Inf a - List Inf a
shorter :: List Fin a - List Inf a - List Fin a
shorter :: List Inf a - List Fin a - List Fin a
shorter :: List Fin a - List Fin a - List Fin a


where the result of the last typecase is the shorter one. shorter
would probably be defined in a type-class.

The normal un-typechecked code disclaimer applies.

Nick

On 10/10/06, Neil Mitchell [EMAIL PROTECTED] wrote:

Hi

 However this will result in a non-terminating loop for shorter [1..] [2..],
 since the first two patterns of f shall never match.

The specification of your problem makes this a guarantee. How do you
know that a list is finite? You find the [] at the end. How do you
know a list is infinite? You spend an infinite amount of time and
never find the []. Hence you can't tell if you have two big lists, or
two infinite lists.

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] Profiling CAFs (re-post)

2006-10-10 Thread Matthias Fischmann

On Tue, Oct 10, 2006 at 01:59:23PM +0100, Ian Lynagh wrote:
 To: Matthias Fischmann [EMAIL PROTECTED]
 Cc: haskell-cafe@haskell.org
 From: Ian Lynagh [EMAIL PROTECTED]
 Date: Tue, 10 Oct 2006 13:59:23 +0100
 Subject: Re: [Haskell-cafe] Profiling CAFs (re-post)
 
 On Tue, Oct 10, 2006 at 01:31:58PM +0200, Matthias Fischmann wrote:
  
What qualifies as constant applicable form, and why is it not
labelled in a more informative way?
 
 CAFs are, AIUI, things that are just values (i.e. things that don't take
 an argument) that have been floated up to the top level.

Ok, this is consistent with the documentation.  However, it doesn't
explain why we would need to treat them differently.  In particular, I
don't understand why I wouldn't want to know their (module-global)
names.

 Compiling with -caf-all might give you more useful information.

Oops.  I thought i had that in my Makefile, but appearently i was
wrong...  If I add it, this is what happens:

==
module Main where

x = f [1..5] (f [2..] [3..])

f xs ys = l
where
l = [ if s then x else y | (x, y) - zip xs ys ]
s = g xs ys
g [] _ = True
g _ [] = False
g (x:xs) (y:ys) = g xs ys

main = print (show x)
==

$ ghc -prof -caf-all Main.hs -o Main  # (ghc 6.4)
/tmp/ghc22775.hc:1475: error: redefinition of `Mainmain_CAF_cc_ccs'
/tmp/ghc22775.hc:1470: error: `Mainmain_CAF_cc_ccs' previously defined here
/tmp/ghc22775.hc:1490: error: redefinition of `Mainsat_CAF_cc_ccs'
/tmp/ghc22775.hc:1480: error: `Mainsat_CAF_cc_ccs' previously defined here
/tmp/ghc22775.hc:1495: error: redefinition of `Mainsat_CAF_cc_ccs'
/tmp/ghc22775.hc:1490: error: `Mainsat_CAF_cc_ccs' previously defined here

$ ghc -prof -auto-all -caf-all Main.hs -o Main
/tmp/ghc22771.hc:1517: error: redefinition of `Mainmain_CAF_cc_ccs'
/tmp/ghc22771.hc:1512: error: `Mainmain_CAF_cc_ccs' previously defined here

 If that doesn't help then you might find it helpful to look at heap
 profiles rather than just the normal profiler output.

Section 5.4, prof.hp, yes.  Probably should have thought of that
myself.  Will do.

Why are there functions that inherit all of their (considerable)
time and space consumption from elsewhere, but nothing in the
list would allow for such a rich inheritage?
 
 I didn't understand that. If it's possible to give a small example then
 that might help?

Small is harder in this case than with type errors.  But I'll try as
soon as I know what's wrong with the above.


thanks,
matthias


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


Re: [Haskell-cafe] [off-topic / administrative] List Reply-to

2006-10-10 Thread Misha Aizatulin
Matthias Fischmann wrote:
 Some lists have the Reply-To: set to the list address.  I think you
 can even configure the From: to be haskell-cafe instead of the poster,
 making the poster merely identifiable by the Sender: field.
 
 Do you have strong opinions on this subject?  

  Here is an argument against Reply-To munging. I'd say I agree with it:

http://www.unicom.com/pw/reply-to-harmful.html

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


Re: [Haskell-cafe] a monad for secret information

2006-10-10 Thread Seth Gordon
 data Secret a = Secret {password :: String, value :: a}
 
 classify :: String - a - Secret a
 classify = Secret
 
 declassify :: String - Secret a - Maybe a
 declassify guess (Secret pw v) | guess == pw = Just v
 | otherwise = Nothing
 
 Put that in a module, do not export the Secret data type, and you're
 good to go. I'm unsure what a Monad is giving you

I was just curious if I could do that within a monad.

If the answer to my question is no, you can't, then I'll pick up the
shattered pieces of my life and move on.  :-)
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] a monad for secret information

2006-10-10 Thread Robert Dockins


On Oct 10, 2006, at 12:04 PM, Seth Gordon wrote:


data Secret a = Secret {password :: String, value :: a}

classify :: String - a - Secret a
classify = Secret

declassify :: String - Secret a - Maybe a
declassify guess (Secret pw v) | guess == pw = Just v
| otherwise = Nothing

Put that in a module, do not export the Secret data type, and you're
good to go. I'm unsure what a Monad is giving you


I was just curious if I could do that within a monad.

If the answer to my question is no, you can't, then I'll pick up the
shattered pieces of my life and move on.  :-)



I think you can.  Your original monad is just a little too  
simplistic.  Try something like this (untested):



import Control.Monad.State

type Password = String
type Secret s a = State (Password - Maybe s) a

classify :: Password - s - Secret s ()
classify pw s = put (\x - if x == pw then Just s else Nothing)

declassify :: Password - Secret s (Maybe s)
declassify pw = get = \f - return (f pw)

runSecret :: Secret s a - a
runSecret m = runState m (const Nothing)


Note how this relies on opaque functions to hide the secret.  This  
wouldn't work if Haskell had intensional observation of functions,  
although you could still use a newtype in that case.



Slightly related: I've sometimes wondered about a monadic API for  
cryptographic primitives.  With compiler support you could do nifty  
things like make sure to use non-swappable memory for encryption keys  
and use fancy special purpose hardware for cryptographic primitives,  
if available.  The API would give a nice way to ensure proper  
information hiding policy.  Has anything like this been done or studied?




Rob Dockins

Speak softly and drive a Sherman tank.
Laugh hard; it's a long way to the bank.
  -- TMBG



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


Re: [Haskell-cafe] a monad for secret information

2006-10-10 Thread David Roundy
On Mon, Oct 09, 2006 at 11:06:35PM -0400, Seth Gordon wrote:
 I finally (think I) understand monads well enough to make one up:
[...]
 The not-so-nice thing is that the literal text of the password is baked
 into the data definition.  I'd like to have a more general version of
 Secret that allows someone to pass the password in when constructing a
 secret, and preserves that password when return is used, but doesn't
 let the second argument of (=) see the password.  Something like this:...

 data Classification pw a = Classification pw a
 declassify (Classification pw a) pw' = case pw' of
  pw - Just a
  _  - Nothing
 
 type Secret = Classification xyzzy

Try

module Secret (Secret, classify, declassify)
where

data Secret a = Secret String a

classify :: String - a - Secret a
classify pw x = Secret pw x

declassify :: Secret a - String - Maybe a
declassify (Secret pw x) pw' | pw' == pw = Just x
declassify (Secret _ _) _ = Nothing

instance Monad Secret where
return = classify 
(Secret pw x) = f = case f x of
  Secret _ y - Secret pw y

Now return itself doesn't assign a password, but you can classify something
manually, and then perform computations on that data in a safe manner.
It's just as safe as your code, because the constructor of secret is hidden
which hides the password just as well as the data.

Of course, this is run-time checking, and you'd be safer with a phantom
type-level password which is statically verified, which is also doable, but
not so easily.  It wouldn't be very hard either, though.  It also wouldn't
be Haskell 98.

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


[Haskell-cafe] Re: Is Haskell a 5GL?

2006-10-10 Thread Henning Thielemann

On Thu, 5 Oct 2006, Ch. A. Herrmann wrote:

 Henning Thielemann wrote:
 
  ...
  
  The notation
[f x | x - xs]
  describes operations on list elements, and looks like the imperative
   forall x in xs do f x,
  whereas
   map f xs
  is a list transformation. The second one is more abstract, isn't it?
   
 for that simple example yes, but what's about list comprehensions like:
 
 sequence of parsers:
 (p + q) r = [ ((x,y), r2) | (x, r1) - p r, (y, r2) - q r1 ]

More abstract:

p + q = runStateT (liftM2 (,) (StateT p) (StateT q))

If you give the parsers the StateT type, then it is even

+ = liftM2 (,)


 or triples:
 [ (x,y,z) | x-[1..n], let x2=x*x, y-[1..x], let y2=y*y, let z=isq (x2,y2), 
 x2+y2==z*z ]

This is rather a 1:1 translation of an imperative program, a bit shorter,
ok, but it will certainly not impress an imperative programmer. I find it
more important that the generation of pairs, where the first element is
smaller than the second one, can be nicely separated from the Pythagoras
check, due to laziness.
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] Multiple stages in Template Haskell

2006-10-10 Thread Lyle Kopnicky

Hi folks,

I noticed that in Template Haskell, you can only have one level of 
splicing or quasi-quoting. E.g., you can't write:


   $(zipN ($(sel 2 3) (zip level,3,( ['a'..'Z'] [1..] (words now 
is the time)


Because you can't have a splice inside a splice. But wouldn't it be 
handy to use all these macros when defining other macros?


This would be like stages in MetaML, which have no such limitation. But 
all the stages but the last one would be evaluated at compile time. The 
compiler would look for the deepest level of nested splices and evaluate 
it first.


On the other hand, I can understand why you wouldn't include splices and 
quasi-quotes in the Language.Haskell.TH.Syntax - programmers could write 
functions that dynamically created arbitrarily (even infinitely) nested 
splices - so it would be undecidable where to start.


I'm wondering if there's some reason this restriction is imposed. Is it 
particularly difficult to implement, or are there more theoretical 
problems? Does that mean I'm volunteering? ;)


- Lyle

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


Re: [Haskell-cafe] Profiling CAFs (re-post)

2006-10-10 Thread Jason Dagit

On 10/10/06, Ian Lynagh [EMAIL PROTECTED] wrote:

On Tue, Oct 10, 2006 at 01:31:58PM +0200, Matthias Fischmann wrote:

   What qualifies as constant applicable form, and why is it not
   labelled in a more informative way?

CAFs are, AIUI, things that are just values (i.e. things that don't take
an argument) that have been floated up to the top level.


Actually, I don't know if this is a ghc bug but I was profiling last
week and a majority of the time/allocation was done in a CAF in a
module which didn't  seem to be doing much work.  Turned out in my
case that the module in question imported a function from another
package which was doing a tremendous amount of work.  It wasn't until
I used -caf-all that I could see the real culprit.  So, I guess a CAF
can also be a function in a library you're using.  And I say function
here because the work horse definetly was not a CAF.  It was hPutXml
from HaXml.

The lesson for me was that -caf-all is handy to know about.

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


[Haskell-cafe] Re: a monad for secret information

2006-10-10 Thread Arie Peterson

David Roundy wrote:
 Try

module Secret (Secret, classify, declassify)
where

data Secret a = Secret String a

classify :: String - a - Secret a
classify pw x = Secret pw x

declassify :: Secret a - String - Maybe a
declassify (Secret pw x) pw' | pw' == pw = Just x
declassify (Secret _ _) _ = Nothing

instance Monad Secret where
return = classify 
(Secret pw x) = f = case f x of
  Secret _ y - Secret pw y

 Now return itself doesn't assign a password, but you can classify
 something
 manually, and then perform computations on that data in a safe manner.
 It's just as safe as your code, because the constructor of secret is
 hidden
 which hides the password just as well as the data.

What should 'q = r' mean, when 'q' and 'r x' are secrets with different
passwords? In the code above, the result is a secret with the same
password as 'q'. This allows you to declassify any secret without knowing
its password:

  break :: Secret a - a
  break q = fromJust $ declassify (classify bloep ()  q) bloep

.

-- 

Mr. Pelican Shit may be Willy.

  ^
 /e\
 ---


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


Re: [Haskell-cafe] Trying to understand HList / hMapOut

2006-10-10 Thread Bulat Ziganshin
Hello oleg,

Saturday, October 7, 2006, 11:25:07 AM, you wrote:

 Well, `foo' is a polymorphic function -- which is not, strictly
 speaking, a first-class object in Haskell.

btw, GHC 6.6 supports impredicative polymorphism described in User
Guide 7.4.9. is this makes polymorphic functions first-class citizens?


-- 
Best regards,
 Bulatmailto:[EMAIL PROTECTED]

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


[Haskell-cafe] Re: [off-topic / administrative] List Reply-to

2006-10-10 Thread Aaron Denney
On 2006-10-10, Misha Aizatulin [EMAIL PROTECTED] wrote:
 Matthias Fischmann wrote:
 Some lists have the Reply-To: set to the list address.  I think you
 can even configure the From: to be haskell-cafe instead of the poster,
 making the poster merely identifiable by the Sender: field.
 
 Do you have strong opinions on this subject?  

   Here is an argument against Reply-To munging. I'd say I agree with it:

 http://www.unicom.com/pw/reply-to-harmful.html

Agreed.  There is a semi-standard header List-Reply-To: that some MUAs
will use...

-- 
Aaron Denney
--

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


Re: Re: [Haskell-cafe] beginner's problem about lists

2006-10-10 Thread ihope

On 10/10/06, Nicolas Frisby [EMAIL PROTECTED] wrote:

 data Fin
 data Inf

 data List l a = Cons a (List l a) | Nil


It's possible to make both infinite list and finite list datatypes:

data Inf a = InfCons a (Inf a)
data Fin a = FinCons a !(Fin a) | FinNil

At least, I think the Fin type there has to be finite...
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Re: Haskell performance (again)!

2006-10-10 Thread Lennart Augustsson


On Oct 10, 2006, at 14:58 , Jón Fairbairn wrote:


Bulat Ziganshin [EMAIL PROTECTED] writes:


Hello Jon,

Tuesday, October 10, 2006, 1:18:52 PM, you wrote:


Surely all but one of the comparisons is unnecessary? If you
use `compare` instead of (==) and friends, won't one do (I'm
assuming that the compiler can convert cases on LT, EQ and
GT into something sensible -- after all, wasn't that the
purpose of compare?)?


it will too smart for GHC. actual code is:

compareInt# :: Int# - Int# - Ordering
compareInt# x# y#
| x# #  y# = LT
| x# ==# y# = EQ
| otherwise = GT


But once that's been inlined and through whatever code
generator, what then? If it doesn't get turned into one test
on the data and conditional jumps on sign bits, something
isn't doing a thorough job...


Assuming your machine architecture supports something like condition  
codes.  On, e.g., the MIPS you would need to test for  and ==  
separately.


-- Lennart

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


Re: [Haskell-cafe] Re: a monad for secret information

2006-10-10 Thread Seth Gordon

David Roundy wrote:

Try


module Secret (Secret, classify, declassify)
where

data Secret a = Secret String a

classify :: String - a - Secret a
classify pw x = Secret pw x

declassify :: Secret a - String - Maybe a
declassify (Secret pw x) pw' | pw' == pw = Just x
declassify (Secret _ _) _ = Nothing

instance Monad Secret where
   return = classify 
   (Secret pw x) = f = case f x of
 Secret _ y - Secret pw y


That's just the sort of thing I was looking for.  Thanks!

Arie Peterson wrote:

What should 'q = r' mean, when 'q' and 'r x' are secrets with different
passwords? In the code above, the result is a secret with the same
password as 'q'. This allows you to declassify any secret without knowing
its password:


Yeah, but I think that's easy to fix: make classify and declassify take 
a set of strings rather than a single string, and then make = return a 
secret containing the union of passwords on both sides.


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


Re: [Haskell-cafe] a monad for secret information

2006-10-10 Thread Felipe Almeida Lessa
2006/10/10, David Roundy [EMAIL PROTECTED]:
declassify :: Secret a - String - Maybe adeclassify (Secret pw x) pw' | pw' == pw = Just xdeclassify (Secret _ _) _ = NothingWhy does this works? Yet Another Haskell Tutorial teaches that pattern matching occurs at one stage and guard processing at other, and that there's no back (page 94).
-- Felipe.
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] GHC Core still supported?

2006-10-10 Thread Jim Apple

In http://www.haskell.org/ghc/dist/current/docs/users_guide/ext-core.html
, I see two notes that I can't verify:

1. I don't see any CORE pragma on
http://www.haskell.org/ghc/dist/current/docs/users_guide/pragmas.html

2.  Using GHC 6.5.20060920, I compile

module Core where
data Foo = Bar

with -fext-core to get

%module main:Core
 %data main:Core.Foo =
   {Bar};

I then compile the resulting hcr file with no flags to get

no location info:
   1: Parse error
:
 %data main:Core.Foo =
   {Bar};

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


Re: [Haskell-cafe] Profiling CAFs (re-post)

2006-10-10 Thread Ian Lynagh
On Tue, Oct 10, 2006 at 05:21:52PM +0200, Matthias Fischmann wrote:
 
  Compiling with -caf-all might give you more useful information.
 
 Oops.  I thought i had that in my Makefile, but appearently i was
 wrong...  If I add it, this is what happens:
 
 $ ghc -prof -caf-all Main.hs -o Main  # (ghc 6.4)
 /tmp/ghc22775.hc:1475: error: redefinition of `Mainmain_CAF_cc_ccs'
 /tmp/ghc22775.hc:1470: error: `Mainmain_CAF_cc_ccs' previously defined here

Hmm, filed as http://hackage.haskell.org/trac/ghc/ticket/931


Thanks
Ian

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


[Haskell-cafe] Re: Trying to understand HList / hSequence now [why it works]

2006-10-10 Thread oleg

Matthias Fischmann wrote:
 instance (Monad m, HSequence m HNil HNil) = HSequence m HNil HNil 
 where hSequence _ = return HNil

 how can i use the goal of the declaration as one of the conditions
 without causing some sort of black hole in the type inference
 algorithm?

Very easily: the instance head is implicitly the part of its own
context (so that a method can be recursive). A simple way to see that
is the following deliberately erroneous class:

 class C a where mc :: a - Bool
 instance Eq a = C a where mc x = x  x

The error message says

Could not deduce (Ord a) from the context (C a, Eq a)
  arising from use of `' at /tmp/f2.hs:30:36

It is revealing to observe the context that the typechecker thinks is
available: it is (C a, Eq a). Eq a is there because we explicitly
wrote it in the instance declaration. C a is there just by default. We
could just as well written

 instance (Ord a, C a) = C a where mc x = x  x

Incidentally, the hSequence can be written as follows

 import TypeCastGeneric2
 data ConsM

 instance (TypeCast (m1 l) (m l), Monad m) 
 = Apply ConsM (m a, m1 l) (m (HCons a l)) where
 apply _ (me,ml) = liftM2 HCons me (typeCast ml)

 hSequence l = hFoldr (undefined::ConsM) (return HNil) l

 hlist = HCons (Just 1) (HCons (Just 'c') HNil)
 hlist2 = HCons ([1]) (HCons (['c']) HNil)
 testHSequence = hSequence hlist
 testHSequence2 = hSequence hlist2

*Foo :t testHSequence
testHSequence :: Maybe (HCons Integer (HCons Char HNil))
*Foo testHSequence
Just (HCons 1 (HCons 'c' HNil))
*Foo testHSequence2
[HCons 1 (HCons 'c' HNil)]

The typechecker will complain if we try to mix different monads within
the same HList, and then sequence it.

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


[Haskell-cafe] Re: Haskell performance (again)!

2006-10-10 Thread Stefan Monnier
 Assuming your machine architecture supports something like condition  codes.
 On, e.g., the MIPS you would need to test for  and ==  separately.

And even if your machine supports condition codes, you'll need one test plus
two conditional jumps.  Not much better than MIPS's 2 independent tests plus
2 conditional jumps.


Stefan

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