Re: [Haskell-cafe] New slogan for haskell.org

2007-11-26 Thread Thomas Davie


On 26 Nov 2007, at 15:50, Henning Thielemann wrote:



On Mon, 26 Nov 2007, Thomas Davie wrote:


On 26 Nov 2007, at 15:15, Henning Thielemann wrote:



On Thu, 4 Oct 2007, Don Stewart wrote:


The Haskell website has the rather strange motivational text:

  Haskell is a general purpose, purely functional programming
language
  featuring static typing, higher order functions, polymorphism,
type
  classes, and monadic effects. Haskell compilers are freely
available
  for almost any computer.


To continue an old thread: What about turning the strange words like
'monadic effects' into links to glossary articles?

Btw. where is 'lazy' ?


I believe the point of this discussion was that anyone reading the
Haskell webpage will currently get about as far as featuring static
typing, and go this is all very nice, but what exactly does this
language do for me?  Why should I use it?.  Take for example what  
the

python website says:


I didn't want to repeat the discussion. I think the discussion ended  
with:
Anything more helpful would be too long for the title line at  
haskell.org,
and a more detailed explanation (but not a generic advertisement  
like that

from Python) should be reachable easily. Now my idea was, that making
links to glossary articles leaves the slogan as short as it is, and  
allows

people to find out quickly about the words they still don't know. An
explanation why Haskell's features are useful for programmers is still
required.


But the point is that this section of the site is the bit that's meant  
to be an advertisement -- we're trying to encourage people to read  
more, and quite frankly, making it a fist full of links would make at  
least me think Well bugger this if I have to read 10 pages before I  
even have a clue what it is.


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


Re: [Haskell-cafe] St. Petersburg Game

2007-11-27 Thread Thomas Davie

main =  do  let b = 0
let c = randomRIO (1,2)
until (c == 1)  increment b
return b

This is intended to print the number of consecutive heads (i.e., 2)  
before

the first tail, but I get the following error:

ERROR StPetersburg.hs:8 - Type error in application
*** Expression : until (c == 1) increment b
*** Term   : c == 1
*** Type   : Bool
*** Does not match : Int - Bool

I don't really see what's going on, so any help will be more than  
welcome.

I hope this is a suitable question for the Haskell Café list.


I'm not familiar with the problem, so I won't comment on how I would  
implement it.  However what you appear to be doing is trying to write  
something in an imperative style.


If you want to generate random coin tosses and count how many are  
heads, I suggest you write a function that returns an infinite list of  
coin toss results.  Something like


tosses :: IO ([Int])
tosses = do ts - tosses
return (randomRIO (1,2):ts)

Then your main function merely needs to count them:

main = do ts - tosses
  return $ countHeads ts

countHeads = if (head fg == 1) then 0 else length fg where fg = head $  
group ts


Your immediate error is caused by a misunderstanding of how until works.

Until essentially is a restricted while loop implemented with  
recursion.  It takes three things:

1) A condition for stopping looping
2) A thing to do in the loop
3) A value to start with.

Because there's no mutable state, a while loop can't alter the program  
state, so we must do something else instead.  What we do is we have a  
function for computing whether we're done looping or not, and we pass  
a value into it. ___

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


Re: [Haskell-cafe] New slogan for haskell.org

2007-11-27 Thread Thomas Davie

On 27 Nov 2007, at 14:44, David Menendez wrote:


On Nov 26, 2007 1:44 PM, Thomas Davie [EMAIL PROTECTED] wrote:

But the point is that this section of the site is the bit that's meant
to be an advertisement -- we're trying to encourage people to read
more,

Are we? I thought Haskell.org was intended to describe what Haskell  
*is*. There are plenty of articles and blog posts and wiki pages out  
there that advocate Haskell. I don't see why the main web page needs  
to be polluted with marketing.


Because someone's first contact with Haskell is likely to be someone  
saying I use this really cool language called Haskell, or a lecturer  
teaching it to them.  In either case, if a tiny amount of interest is  
sparked, their likely second contact is likely to be haskell.org  
(through guessing or googling).  Quite frankly, there's nothing going  
to put me off a language more than a paragraph full of unknown buzz  
words that I have to look up on the front page.


There's plenty of places on Haskell.org where we can describe what  
haskell *is*, but the front page should be used for grabbing peoples  
attention and telling them why it's useful.


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


Re: [Haskell-cafe] New slogan for haskell.org

2007-11-28 Thread Thomas Davie


On 28 Nov 2007, at 13:41, Ian Lynagh wrote:


On Wed, Nov 28, 2007 at 09:27:39AM +0100, Thomas Schilling wrote:


Sorry, but are you talking of *one* homepage?  This can all go into  
own

wiki pages that are aimed at certain audiences, but this really can't
all fit on the front page.


I'm reminded of http://www.shiregames.com/shiregames/

We could do something similar, with a column for
   When you hear programming, if you immediately think of C or perl,
   then please read the following:
and maybe
   ML or lisp
for the other column.

I don't know if it's a good idea or not, just something to think  
about.


That's an excellent idea as far as I'm concerned.  We get the  
advertising pitch to the uninitiated, and the old hands keep their  
navigation routes to the important documentation.


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


Re: [Haskell-cafe] What is the role of $!?

2007-11-28 Thread Thomas Davie


On 29 Nov 2007, at 06:32, PR Stanley wrote:


Hi
Thanks for the response.

	JCC: In most languages, if you have some expression E, and when the  
computer attempts to evaluate E it goes in to an infinite loop, then  
when the computer attempts to evaluate the expression f(E), it also
goes into an infinite loop, regardless of what f is.  That's the  
definition of a strict language.


PRS: Does that mean that a strict language is also imperative?


Nope, not at all.  Just a strict language has slightly fewer programs  
it can evaluate correctly, as more will loop infinitely.



Either e or f(e) could result in an infinite loop.

	JCC: In Haskell, this isn't the case ---we can write functions f  
such that the computation f(E)  terminates,
even when E does not.  (:) is one such function, as are some  
functions built from it, such as (++); xn ++ ys terminates whenever  
xn does, even if ys is an infinite loop.  This is what makes it easy
and convenient to build infinite loops in Haskell; in most strict  
languages, if you said

let fibs = 0 : 1 : zipWith (+) fibs (tail fibs)
the language would insist on evaluating fibs before it actually  
assigned anything to the memory cell for fibs, giving rise to an  
infinite loop.  (For this reason, most strict languages make such  
definitions compile-time errors).


Unfortunately, non-strictness turns out to be a pain in the ass to  
implement, since it means when the code generator sees an  
expression, it can't just generate code to evaluate it --- it has to  
hide the code somewhere else, and then substitute a pointer to that  
code for the value of the expression.


	PRS: Is there a kind of strictness applied when the compiler/ 
interpreter sorts the various sub-expressions into little memory  
compartments indexed with pointers for later evaluation? To put it  
another way, does lazy evaluation begin with the outer-most  
expression, the most abstract, and determine what sshould go where  
in relation to the subsequent inner expressions?  For example:


takeWhile (20) [0..9] ++ [10..]

The compiler determiens at the outset that the result of takeWhile  
is a list followed by the calculation of the length of that list  
based on the predicate (20), and then calls ++ which is for all  
intents and purposes on its own an infinite loop. Is this what  
happens?


Not really.  For lazy evaluation the compiler doesn't decide the  
order statically -- it merely gives the program rules to follow for  
what the next expression to be evaluated should be.  Lets look at a  
slightly simpler example:


takeWhile ( 2) (map (+1) [0..])

We will always attempt to evaluate the outermost left most  
expression.  We do this by matching against the rules given in the  
program, to make this clearer, here are the rules for takeWhile and map:


takeWhile _ []=  []
takeWhile p (x:xs) | p x  =  x : takeWhile p xs
  | otherwise =  []

map _ [] = []
map f (x:xs) = f x : map f xs

   takeWhile ( 2) (map (+1) [0..])
   -- We start by evaluating the leftmost outermost expression.  We  
attempt to match on the first rule of takeWhile, and discover that we  
can't because we don't know whether the result of (map (+1) [0..]) is  
the empty list or not.  Therefore we demand the evaluation of (map +1)  
[0..])

- takeWhile ( 2) ((+1) 0 : map (+1) [1..])
   -- We now know that we don't have the empty list, so we must use  
the second rule of takeWhile.  We must evaluate the guard first though:

- (2) ((+1) 0) |
   -- To do this, we must evaluate ((+1) 0)
- (2) 1 |
   -- This evaluates to True, so we may insert the right hand side --  
note that x remains evaluated

- True | 1 : takeWhile (2) (map (+1) [1..])
   -- We can drop the guard now, but lets carry on.  We have already  
evaluated the outermost expression, so lets evaluate the next in.   
Again pattern matching on takeWhile demands the evaluation of map:

- 1 : takeWhile (2) ((+1) 1 : map (+1) [2..])
   -- We again, can pattern match on takeWhile, and must evaluate the  
guard again:

- 1 : ((2) ((+1) 1) |)
   -- Again, we must evaluate the result of the addition
- 1 : ((2) 2 |)
   -- This time we get False, so we must evaluate the next guard
- 1 : (otherwise |)
   -- otherwise is a synonym for True, so we use this right hand side.
- 1 : (True | [])
   -- and we can get rid of the guard, and prettify the result,  
giving us:

- [1]

Note that we followed a set of rules that gave us non-strict  
semantics.  The set of rules is called lazy evaluation.  We may come  
up with several other sets of rules that give us different evaluation  
orders, but still non-strict semantics (e.g. Optimistic Evaluation).


This is a very simple example, that's to say, I am aware that the  
compiler may be faced with a much more complex job of applying lazy  
evaluation. Nevertheless, I wonder if there are a set of fundamental  
rules to which the compiler must always adhere in lazy 

Re: [Haskell-cafe] Re: Trees

2007-12-03 Thread Thomas Davie
One could alway store a node's depth at each node -- then you must  
search for u and v, creating a list of what nodes you found at each  
depth, and finally, simply compare the lists -- O(n) in the depth of u  
and v.


Bob

On 3 Dec 2007, at 08:40, apfelmus wrote:


Adrian Neumann wrote:

 data Tree a = Leaf a | Node a [Tree a]
But now the assignments require more than a simple top-down  
traversal. For example: given a tree t and two nodes u,v, find the  
first common ancestor.


Well, this problem doesn't make much sense in Haskell. How do you  
specify the subtrees u and v in the first place?



Regards,
apfelmus

___
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] OOP'er with (hopefully) trivial questions.....

2007-12-17 Thread Thomas Davie


On 17 Dec 2007, at 10:46, Nicholls, Mark wrote:


I can obviously at a later date add a new class Triangle, and not  
have to touch any of the above code….


Yes, and you can indeed do a similar thing in Haskell.  The natural  
thing to do here would be to define a type Shape...


data Shape = Circle Int
| Rectangle Int Int
| Square Int

area :: Shape - Int -- Note, this is an interesting type if you want  
the area of circles

area (Circle r) = pi * r^2
area (Rectangle h w) = h * w
area (Square l) = area (Rectangle l l)

If however, you *really* want to keep your shapes as being seperate  
types, then you'll want to invoke the class system (note, not the same  
as OO classes).


class Shape a where
  area :: a - Int

newtype Circle = C Int

instance Shape Circle where
  area (C r) = pi * r^2

newtype Rectangle = R Int Int

instance Shape Rectangle where
  area (R h w) = h * w

newtype Square = Sq Int

instance Shape Square where
  area (Sq l) = l * l

-- Now we can do something with our shapes
doubleArea :: Shape a = a - Int
doubleArea s = (area s) * 2

Hope that helps

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


Re: [Haskell-cafe] OOP'er with (hopefully) trivial questions.....

2007-12-17 Thread Thomas Davie


On 17 Dec 2007, at 11:14, Nicholls, Mark wrote:


OK I'll have to digest this and mess about a bitbut can I make an
observation at this point

If I define Shape like

data Shape = Circle Int
| Rectangle Int Int
| Square Int

Isn't this now closed...i.e. the statement is effectively defining
that shape is this and only ever thisi.e. can I in another module
add new types of Shape? (sorry about all the quotation marks, but  
it's

a minefield of potential confusions over types, classes etc).


That's correct, another module could not add constructors to this  
type.  The idea here is that you tell it all of the possible ways to  
construct Shape, and can then write functions to deal with it elsewhere.



My other observation is...are the things on the right hand side of the
the ='s sign not types?
Correct, they're constructors.  So you could never for example write a  
function that accepts only Rectangles (unless you start getting into  
odd type extensions)


The lower version makes more sense to me...I'll have to give it a  
go


Both versions make sense.  They differ only in how heavy weight they  
are.  Defining a type allows you to do pattern matching on the  
constructors, and is a much better way of defining anything you know  
the structure of in the first place.  Using the class system on the  
other hand, gives you more flexibility, but at the cost of a lot of  
readability.  The class system is designed to be able to describe  
things that aren't explicitly the same type, but exhibit similar  
properties.  For example the Eq class describes all things that are  
equatable, it defines the (==) and (/=) operators.  Your Shape class  
describes all types in which it's sane to compute an area.



A P.S. would be...I tend to write code rather than mess about in the
GHCi shell.is there a way in code to output the type of a
value..i.e. the :t operation?


Take a look at the Typable class.  Although, pretty much any code that  
you can compile can be loaded into ghci without modification, and  
that's by far the easier way of finding the types of things.


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


Re: [Haskell-cafe] OOP'er with (hopefully) trivial questions.....

2007-12-17 Thread Thomas Davie


On 17 Dec 2007, at 12:22, Nicholls, Mark wrote:


Ok...

Thanks I need to revisit data and newtype to work out what the
difference is I think.


Beware in doing so -- type, and newtype are not the same either.  type  
creates a type synonim.  That is, if I were to declare


type Jam = Int

then Jam and Int from that point on become completely interchangable,  
the only thing this does is make things readable.  For example, a  
parser might be described as a function that takes a list of tokens,  
and outputs a parse tree, and a list of unparsed tokens:


type Parser = [Token] - (ParseTree, [Token])

if I write some parser combinators, I can now give them clear types like

| :: Parser - Parser - Parser

I could however still write this, and it would have *exactly* the same  
meaning.


| :: ([Token] - (ParseTree, [Token])) - ([Token] - (ParseTree,  
[Token])) - [Token] - (ParseTree, [Token])


newtype on the other hand introduces a new type to the type system.   
Because of this, the type system has to be able to tell when you're  
using your new type, so a tag gets attached.


newtype Ham = Ham Int

This creates a type that contains only an integer, but is different  
from Int (and Jam) in the type system's eyes.  Thus, I cannot for  
example write


(Ham 5) + (Ham 6)

Because Ham is not Int and thus (+) does not work (or actually, more  
specifically, Ham is not a member of the class Num, the numeric types,  
and therefore (+) doesn't work).  This can of course be fixed thus:


newtype Ham = Ham Int deriving Num

Hope that helps

Tom Davie

p.s. Sorry for the slip with the newtype Rectangle.
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] [newbie question] Memoization automatic in Haskell?

2008-01-12 Thread Thomas Davie


On 12 Jan 2008, at 23:16, Hugh Perkins wrote:


On Jan 12, 2008 10:54 PM, Henning Thielemann
[EMAIL PROTECTED] wrote:


On Sat, 12 Jan 2008, Hugh Perkins wrote:


I guess that Haskell's referential transparence means the answers to
the isPerfectSquare will be cached, ie automatically memoized? (not
sure if is correct term?)


http://www.haskell.org/haskellwiki/Memoization



Interesting... but I dont understand... I thought that referential
transparence meant that once the answer to a function has been
calculated once, it will always be the same, and that the interpreter
can, and will, cache this answer?

So, if I call f( 20 ) once, for some, arbitrary, f, it will have to go
away and calculate f(20), but if I call it multiple times, it will
just return the value it already calculated?


No,
  Memorisation has it's costs too... Suppose you wanted to computer  
map f [1..100]?  Each time f was called, your program  
would look up a table of on average 50 results for f.   
That doesn't sound very efficient if f is a simple function. Now  
suppose you're running a program for several hours -- imagine how  
large your table would become, and how slow your lookup would be.


What you can do however, is introduced constants.  Constants are  
evaluated once and only once, so using them, you can tell the compiler  
exactly what should be memorized.


Bob


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


Re: [Haskell-cafe] Hackape package lackage

2010-03-22 Thread Thomas Davie
I'd love to see that map normalised by the population of the country – would be 
interesting to see where Haskell is popular.

Bob

On 22 Mar 2010, at 16:22, Don Stewart wrote:

 We're watching *massive* traffic right now due to HP release.
 It's not down, just very very busy.
 
 For fun, here's a map of who's downloading Haskell:
 
http://imgur.com/flwPF.png
 
 74 countries in 12 hours, and counting.
 
 - Don
 
 dougal:
 Hackage seems to be down again.
 
 $ cabal update
 Downloading package list from server
 'http://hackage.haskell.org/packages/archive'
 ^Ccabal: interrupted
 
 $ ping -c3 hackage.haskell.org
 PING abbot.galois.com (69.30.63.204) 56(84) bytes of data.
 
 --- abbot.galois.com ping statistics ---
 3 packets transmitted, 0 received, 100% packet loss, time 2012ms
 ___
 Haskell-Cafe mailing list
 Haskell-Cafe@haskell.org
 http://www.haskell.org/mailman/listinfo/haskell-cafe
 ___
 Haskell-Cafe mailing list
 Haskell-Cafe@haskell.org
 http://www.haskell.org/mailman/listinfo/haskell-cafe

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


Re: [Haskell-cafe] [OT?] Haskell-inspired functions for BASH

2010-04-01 Thread Thomas Davie
Unfortunately though, h4sh seems to be broken, for one, there's no fps package 
(apparently required), and hsplugins won't build with 6.12.1.

Bob

On 1 Apr 2010, at 15:41, Jeremy Shaw wrote:

 How about:
 
 http://www.cse.unsw.edu.au/~dons/h4sh.html
 
 It brings a lot of familiar Haskell functions to the command-line. And *is* 
 actually written in Haskell ;)
 
 - jeremy
 
 On Wed, Mar 31, 2010 at 6:05 PM, Patrick LeBoutillier 
 patrick.leboutill...@gmail.com wrote:
 Hi all,
 
 I've been studying Haskell for about a year now, and I've really come
 to like it. In my daily work I write a lot of BASH shell scripts and I
 thought I'd try add some of the haskell features and constructs to
 BASH to make my scripting life a bit easier. So I've been working on a
 small BASH function library that implements some basic functional
 programming building blocks.
 
 Note: There is no actual Haskell code involved here.
 
 I put up the full manpage here:
 http://hpaste.org/fastcgi/hpaste.fcgi/view?id=24564
 Source is here: http://svn.solucorp.qc.ca/repos/solucorp/bashkell/trunk/trunk/
 
 All this is very prototypical, but here is an example of some of the
 stuff I've got so far (map, filter, foldr):
 
 $ ls data
 1.txt  2.txt
 
 # basic map, argument goes on the command line
 $ ls -d data/* | map basename
 1.txt
 2.txt
 
 # map with lambda expression
 $ ls -d data/* | map '\f - basename $f .txt'
 1
 2
 
 # simple filter, also works with lambda
 $ ls -d data/* | map basename | filter 'test 1.txt ='
 1.txt
 
 # sum
 $ ls -d data/* | map '\f - basename $f .txt' | foldr '\x acc - echo
 $(($x + $acc))' 0
 3
 
 Basically I'm looking for a bit of feedback/info:
 - Does anyone know if there are already similar projets out there?
 - Does anyone find this interesting?
 - Any other comment/suggestion/feedback
 - Where's a good place to promote such a project?
 
 
 Thanks a lot,
 
 Patrick LeBoutillier
 
 
 --
 =
 Patrick LeBoutillier
 Rosemère, Québec, Canada
 ___
 Haskell-Cafe mailing list
 Haskell-Cafe@haskell.org
 http://www.haskell.org/mailman/listinfo/haskell-cafe
 
 ___
 Haskell-Cafe mailing list
 Haskell-Cafe@haskell.org
 http://www.haskell.org/mailman/listinfo/haskell-cafe

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


Re: [Haskell-cafe] Re: Haskellers hate GUIs!!

2010-04-02 Thread Thomas Davie

On 2 Apr 2010, at 21:01, Brandon S. Allbery KF8NH wrote:

 On Apr 2, 2010, at 15:21 , Thomas Schilling wrote:
 On 2 April 2010 20:15, Brandon S. Allbery KF8NH allb...@ece.cmu.edu wrote:
 On Apr 2, 2010, at 10:41 , David Leimbach wrote:
 Having said that, are there any plans to make it really easy to get gtk2hs
 working on Mac OS X?
 
 It's in MacPorts.
 
 But that's the variant using X11, no?  There now is a Gtk+ framework,
 
 BTW, native Cocoa support is now part of the standard Gtk+ distribution.

Unfortunately, it still doesn't behave anything like a Cocoa 
application.___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Re: Haskell.org re-design

2010-04-07 Thread Thomas Davie

On 7 Apr 2010, at 02:53, Ben Millwood wrote:

 On Wed, Apr 7, 2010 at 2:22 AM, Thomas Schilling
 nomin...@googlemail.com wrote:
 I have
 set a maximum width on purpose so that it doesn't degrade too badly on
 big screens.
 
 I've never really trusted this argument - it's not required that the
 browser window occupy the entire screen, so why not let the user
 choose how wide they want their text?

Unfortunately, because the majority operating system has such bad window 
management that all users do make their windows take up the entire screen.

:(

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


Re: [Haskell-cafe] Re: instance Eq (a - b)

2010-04-14 Thread Thomas Davie
Your instances of Finite are not quite right:

bottom :: a
bottom = doSomethingToLoopInfinitely.

instance Finite () where
 allValues = [(), bottom]

instance Finite Nothing where
 allValues = [bottom]

Though at a guess an allValuesExculdingBottom function is also useful, perhaps 
the class should be

class Finite a where
 allValuesExcludingBottom :: [a]

allValues :: Finite a = [a]
allValues = (bottom:) . allValuesExcludingBottom

Bob

On 14 Apr 2010, at 08:01, Ashley Yakeley wrote:

 Joe Fredette wrote:
 this is bounded, enumerable, but infinite.
 
 The question is whether there are types like this. If so, we would need a new 
 class:
 
 class Finite a where
   allValues :: [a]
 
 instance (Finite a,Eq b) = Eq (a - b) where
p == q = fmap p allValues == fmap q allValues
 
 instance (Finite a,Eq a) = Traversable (a - b) where
sequenceA afb = fmap lookup
  (sequenceA (fmap (\a - fmap (b - (a,b)) (afb a)) allValues))
 where
  lookup :: [(a,b)] - a - b
  lookup (a,b):_ a' | a == a' = b
  lookup _:r a' = lookup r a'
  lookup [] _ = undefined
 
 instance Finite () where
   allValues = [()]
 
 data Nothing
 
 instance Finite Nothing where
   allValues = []
 
 -- 
 Ashley Yakeley
 ___
 Haskell-Cafe mailing list
 Haskell-Cafe@haskell.org
 http://www.haskell.org/mailman/listinfo/haskell-cafe

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


Re: [Haskell-cafe] Re: instance Eq (a - b)

2010-04-14 Thread Thomas Davie

On 14 Apr 2010, at 08:29, Ashley Yakeley wrote:

 On Wed, 2010-04-14 at 08:13 +0100, Thomas Davie wrote:
 Your instances of Finite are not quite right:
 
 bottom :: a
 bottom = doSomethingToLoopInfinitely.
 
 instance Finite () where
 allValues = [(), bottom]
 
 Bottom is not a value, it's failure to evaluate to a value.
 
 But if one did start considering bottom to be a value, one would have to
 distinguish different ones. For instance, (error ABC) vs. (error
 PQR). Obviously this is not finite.

Certainly bottom is a value, and it's a value in *all* Haskell types.  Of note, 
bottom is very important to this question – two functions are not equal unless 
their behaviour when handed bottom is equal.

We also don't need to distinguish different bottoms, there is only one bottom 
value, the runtime has different side effects when it occurs at different times 
though.

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


Re: [Haskell-cafe] Re: instance Eq (a - b)

2010-04-14 Thread Thomas Davie

On 14 Apr 2010, at 09:01, Jonas Almström Duregård wrote:

 But if one did start considering bottom to be a value, one would have to
 distinguish different ones. For instance, (error ABC) vs. (error
 PQR). Obviously this is not finite.
 
 Nor is it computable, since it must distinguish terminating programs
 from nonterminating ones (i.e. the halting problem).
 
 On a side note, since instance (Finite a, Finite b) = Finite (a -
 b) should be possible, one can even compare some higher order
 functions with this approach ;).

f,g :: Bool - Int
f x = 6
g x = 6

We can in Haskell compute that these two functions are equal, without solving 
the halting problem.

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


Re: [Haskell-cafe] Re: instance Eq (a - b)

2010-04-14 Thread Thomas Davie

On 14 Apr 2010, at 09:08, Jonas Almström Duregård wrote:

 f,g :: Bool - Int
 f x = 6
 g x = 6
 
 We can in Haskell compute that these two functions are equal, without 
 solving the halting problem.
 
 Of course, this is the nature of generally undecidable problems. They
 are decidable in some cases, but not in general.

Well yes, but we already knew that this was true of function equality – we 
can't tell in general.

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


Re: [Haskell-cafe] Re: instance Eq (a - b)

2010-04-14 Thread Thomas Davie

On 14 Apr 2010, at 09:12, Jonas Almström Duregård wrote:

 f,g :: Bool - Int
 f x = 6
 g x = 6
 
 We can in Haskell compute that these two functions are equal, without 
 solving the halting problem.
 
 what about these?
 f,g :: Bool - Int
 f x = 6
 g x = x `seq` 6

As pointed out on #haskell by roconnor, we apparently don't care, this is a 
shame...  We only care that x == y = f x == g y, and x == y can't tell if _|_ 
== _|_.

It's a shame that we can't use this to tell if two functions are equally lazy 
(something I would consider part of the semantics of the function).

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


[Haskell-cafe] Re: instance Eq (a - b)

2010-04-14 Thread Thomas Davie

On 14 Apr 2010, at 09:17, Ashley Yakeley wrote:

 Thomas Davie wrote:
 Certainly bottom is a value, and it's a value in *all* Haskell types.
 
 This is a matter of interpretation. If you consider bottom to be a value, 
 then all the laws fail. For instance, (==) is supposed to be reflexive, but 
 undefined == undefined is not True for almost any type.
 
 For this reason I recommend fast and loose reasoning:
 http://www.cs.nott.ac.uk/~nad/publications/danielsson-et-al-popl2006.html

It might be nice to have a definition of whether we consider bottom to be a 
value in Haskell then, because the definition of second and fmap on tuples are 
different because of this consideration:

fmap f (x,y) = (x,f y)
second f ~(x,y) = (x,f y)

Because we consider that the Functor laws must hold for all values in the type 
(including bottom).

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


[Haskell-cafe] Re: instance Eq (a - b)

2010-04-14 Thread Thomas Davie

On 14 Apr 2010, at 09:25, Ashley Yakeley wrote:

 Thomas Davie wrote:
 Because we consider that the Functor laws must hold for all values in the 
 type (including bottom).
 
 This is not so for IO, which is an instance of Functor. fmap id undefined 
 is not bottom.

It isn't?

fPrelude fmap id (undefined :: IO ())
*** Exception: Prelude.undefined

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


[Haskell-cafe] Re: instance Eq (a - b)

2010-04-14 Thread Thomas Davie

On 14 Apr 2010, at 09:31, Ashley Yakeley wrote:

 On Wed, 2010-04-14 at 09:29 +0100, Thomas Davie wrote:
 It isn't?
 
 fPrelude fmap id (undefined :: IO ())
 *** Exception: Prelude.undefined
 
 ghci is helpfully running the IO action for you. Try this:
 
 seq (fmap id (undefined :: IO ())) not bottom

Ah, rubbish...

I guess this further reinforces my point though – we have a mixture of places 
where we consider _|_ when considering laws, and places where we don't consider 
_|_.  This surely needs better defined somewhere.

For reference, the fmap on tuples which ignores the bottom case for the sake of 
the laws is useful :(.

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


Re: [Haskell-cafe] Re: instance Eq (a - b)

2010-04-14 Thread Thomas Davie

On 14 Apr 2010, at 09:35, Jonas Almström Duregård wrote:

 what about these?
 f,g :: Bool - Int
 f x = 6
 g x = x `seq` 6
 
 As pointed out on #haskell by roconnor, we apparently don't care, this is a
 shame...  We only care that x == y = f x == g y, and x == y can't tell if
 _|_ == _|_.
 
 So the facts that
 (1) f == g
 (2) f undefined = 6
 (3) g undefined = undefined
 is not a problem?

Yeh :(

Shame, isn't it.

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


[Haskell-cafe] Re: instance Eq (a - b)

2010-04-14 Thread Thomas Davie

On 14 Apr 2010, at 09:39, Ashley Yakeley wrote:

 Thomas Davie wrote:
 I guess this further reinforces my point though – we have a mixture of 
 places where we consider _|_ when considering laws, and places where we 
 don't consider _|_.  This surely needs better defined somewhere.
 
 It's easy: don't consider bottom as a value, and the laws work fine.

If it were this easy, then why is our instance of Functor on tuples gimped?

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


Re: [Haskell-cafe] help with Haskell programming

2010-04-18 Thread Thomas Davie
I'm not certain exactly what you mean, but I *think* you mean:

func :: (a - Bool) - (a - Bool)
func = (not .)

Bob

On 18 Apr 2010, at 16:35, Mujtaba Boori wrote:

 Hello I am kinda newbie in Haskell you can help help me with some programming
 
 I am trying to make function like for example 
 
 func :: (a - Bool) - (a - Bool)
 
 this function make calculation  and return bool . I want to be able to make 
 bool True when It is False and False when it is True while returning the a. 
 
 Thank you 
 
 -- 
 Mujtaba Ali Alboori
 ___
 Haskell-Cafe mailing list
 Haskell-Cafe@haskell.org
 http://www.haskell.org/mailman/listinfo/haskell-cafe

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


Re: [Haskell-cafe] Re: help with Haskell programming

2010-04-18 Thread Thomas Davie
To do this, you need not just fmap (composition), but also ap, or the combined 
form, liftA2:

func = liftA2 (||)

Bob

On 18 Apr 2010, at 18:21, Keith Sheppard wrote:

 Using composition can be tricky with more than one arg. I just want to
 be sure you're not really looking for something like:
 
 func :: (a - Bool) - (b - Bool) - (a - b - Bool)
 
 keeping with your given type I think you're looking for something like:
 
 func f1 f2 x = (f1 x) || (f2 x)
 
 I'm sure there is a nice way to do this with function composition but
 I still find composition less intuitive than explicit args in cases
 like this.
 
 On Sun, Apr 18, 2010 at 1:00 PM, Mujtaba Boori mujtaba.bo...@gmail.com 
 wrote:
 Thanks for helping me but I have another problem (sorry for asking) . I
 tried to figure it out .
 how about if I want to compare two kind with () (||)  for
 func :: (a - Bool) - (a - Bool) - (a - Bool)
 
 I tried some thing like
 func = ((||) .)
 This is the annoying part about Haskell . I can not understand composition .
 
 On Sun, Apr 18, 2010 at 4:35 PM, Mujtaba Boori mujtaba.bo...@gmail.com
 wrote:
 
 Hello I am kinda newbie in Haskell you can help help me with some
 programming
 I am trying to make function like for example
 func :: (a - Bool) - (a - Bool)
 this function make calculation  and return bool . I want to be able to
 make bool True when It is False and False when it is True while returning
 the a.
 Thank you
 --
 Mujtaba Ali Alboori
 
 
 
 --
 Mujtaba Ali Alboori
 
 ___
 Haskell-Cafe mailing list
 Haskell-Cafe@haskell.org
 http://www.haskell.org/mailman/listinfo/haskell-cafe
 
 
 
 
 
 -- 
 keithsheppard.name
 ___
 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] Why Either = Left | Right instead of something like Result = Success | Failure

2010-05-27 Thread Thomas Davie

On 27 May 2010, at 15:25, Ionut G. Stan wrote:

 Hi,
 
 I was just wondering if there's any particular reason for which the two 
 constructors of the Either data type are named Left and Right. I'm thinking 
 that something like Success | Failure or Right | Wrong would have been a 
 little better.

The reason I guess is that Success/Failure and Right/Wrong are a lot less 
general than Left/Right.  One can use Either for types with two possible valid 
types contained within, it doesn't only have to be used for types where one is 
for correct results and the other for erroneous.

Of course, there's nothing stopping you implementing your own type :)

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


Re: [Haskell-cafe] Proposal: Sum type branches as extended types (as Type!Constructor)

2010-06-03 Thread Thomas Davie

On 3 Jun 2010, at 16:14, Gabriel Riba wrote:

 Extending sum types with data constructors would spare runtime errors or
 exception control, 
 
 when applying functions to inappropriate branches, as in the example ...
 
   data List a = Nil | Cons a (List a)  -- List!Nil and List!Cons 
-- as extended types
 
 
 * Actual system, with runtime errors (as in GHC Data.List head) or 
 exception throwing
 
   hd :: List a - a
   hd (Cons x _) - x
   hd Nil - error error: hd: empty list -- error or exception throwing
 
 
 * Proposed system extending types with constructors as Type!Constructor:
 
 User must do pattern matching before applying the constructor-specific 
 type function.
 
 In ''var @ (Constructor _ _)'' the compiler should append the constructor
 to the type as a pair (Type, Constructor) as an extended type for ''var'' 
 
 No need for runtime errors or exception control
 
   hd :: List!Cons a - a
 
   hd (Cons x _) = x
 
 using it:
 
   headOf :: List a - Maybe a
 
   headOf list = case list of
 
li @ (Cons _ _) - Just hd li  -- extTypeOf li == ( 'List', 'Cons')
  -- should pass typechecker for List!Cons
 
li @ Nil  - Just hd li -- compiler error !! 
-- extTypeOf ('List','Nil') don't match
 
_ - Just hd list   -- compiler error !! 
-- extTypeOf ('List',Nothing) don't match
 
 
 Maybe we could take out importance on the number of _ wildcards (constructor
 arity) with a syntax like.
 li @ (Cons ...)
 li @ (Nil ...)

This looks fairly similar to total functional programming, though putting the 
onus on the caller to make sure it meets preconditions, rather than the callee 
to make sure it's the right type.

In total functional programming we would say

head :: List a - Maybe a
head (Cons x _) = Just x
head Nil = Nothing

We'd then allow the caller to deal with the maybe any way it likes (commonly 
with fmap, or with the maybe function).

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


Re: [Haskell-cafe] Physical equality

2010-06-28 Thread Thomas Davie

On 28 Jun 2010, at 09:38, José Romildo Malaquias wrote:

 Is there in Haskell a non monadic function of type a - a - Bool which
 test for physical equality of two values? It would return True if only
 if both values are the same object in memory.
 
 For instance:
 
  value1 = good
  value2 = good
 
  eq value1 value2 = False
 
  value1 = good
  value2 = value1
 
  eq value1 value2 = True

This simply isn't possible without manually tagging values yourself (or with a 
library), it would violate referential transparency.

Remember, a function, called twice with semantically identical arguments must 
always return the same value, that isn't true of eq.

Even if this weren't an issue, you're relying heavily on the runtime's 
behaviour here.  There's nothing to stop the runtime, in the first example, 
observing that the two values are identical, and making them both take up the 
same memory – they are after all immutable, so that's totally safe.  There's 
similarly nothing to stop the runtime, in the second example, arbitrarily 
copying the the string (although it's probably not a great idea for efficiency).

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


Re: [Haskell-cafe] How easy is it to hire Haskell programmers

2010-07-03 Thread Thomas Davie

On 3 Jul 2010, at 03:39, Don Stewart wrote:

 ivan.miljenovic:
 Hmm, interesting. Applicative and Traversable are two classes I've never  
 used and don't really understand the purpose of. I have no idea what  
 hsc2hs is. I keep hearing finger trees mentioned, but only in connection  
 to papers that I can't access. So I guess that means that I don't count  
 as a knowledgable Haskell programmer. :-(
 
 RWH is free and online, and covers many useful things. There's no
 excuse :-)
 
 Knowing about something /= knowing how to use it.  I own and have read
 RWH, but I've never had to use hsc2hs, or Applicative, etc.
 
 
 Writing libraries that bind to C is a great way to have to use a lot of
 hsc2hs (or c2hs), so clearly you need to contribute more libraries :-)

Alternatively, they're already busy contributing lots of purely functional 
libraries, instead of doing (still valuable) work getting C cludges working.

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


Re: [Haskell-cafe] Are you a Haskell expert? [How easy is it to hire Haskell programmers]

2010-07-03 Thread Thomas Davie

On 3 Jul 2010, at 11:04, Brandon S Allbery KF8NH wrote:

 -BEGIN PGP SIGNED MESSAGE-
 Hash: SHA1
 
 On 7/3/10 05:57 , Andrew Coppin wrote:
 Agreed. So let me rephrase: Why should _every_ Haskell library involve C? ;-)
 
 Who says they do, or should?

Dons rather implied it... The suggestion is that someone who hasn't used hsc2hs 
is an inexperienced Haskeller... I'd bet though that there are many *extremely* 
experienced haskellers who have never once in their life written a C binding.

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


Re: [Haskell-cafe] lists of arbitrary depth

2010-07-13 Thread Thomas Davie

On 13 Jul 2010, at 10:11, Shlomi Vaknin wrote:

 Thank you all for replying!
 
 I am really beginning my baby steps in this fascinating language, and was 
 just wondering if it was possible to naturally scan lists with arbitrary 
 lists (aka trees :) ).

Trees aren't lists, Trees are trees...  Here's how you create one*

data Tree a = Leaf
 | Branch a [Tree a]

This roughly says, a tree can be made up of two possible things... First, it 
could be a leaf, and secondly, it could be a branch with an element at it, and 
a list of subtrees.

Some example trees using this data type:

1) Leaf
2) Branch 5 []
3) Branch 5 [Leaf]
4) Branch 5 [Branch 10 [], Branch 20 [], Leaf, Branch 50 [Branch 10 [], Leaf]]

When you have really strong typing, you also have very well specified types.  
You don't just use a list as if it were a tree, you declare what a tree is.

Bob

* In this case an arbitrarily branching tree, we could ofc declare different 
forms of tree here.___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Re: Can we come out of a monad?

2010-08-01 Thread Thomas Davie

On 1 Aug 2010, at 11:43, Ertugrul Soeylemez wrote:

 Ivan Lazar Miljenovic ivan.miljeno...@gmail.com wrote:
 
 No, a pure function is one without any side effects.
 
 There are no functions with side effects in Haskell, unless you use
 hacks like unsafePerformIO.  Every Haskell function is perfectly
 referentially transparent, i.e. pure.

This is why we badly need a new term, say, io-pure.  That means, neither has 
side effects, nor produces an action that when run by the runtime has side 
effects.

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


Re: [Haskell-cafe] Re: Exercise in point free-style

2006-09-01 Thread Thomas Davie

Shorter, although perhaps less insightful.

Bob

On 2 Sep 2006, at 01:36, Lennart Augustsson wrote:

An easy way to solve this is to ask lambdabot.  Log on to the  
Haskell IRC channel:

lennart: @pl  \ f l - l ++ map f l
lambdabot: ap (++) . map

Notice how it's much shorter than the Hughes' solution. :)

-- Lennart

On Sep 1, 2006, at 13:11 , John Hughes wrote:


From: Julien Oster [EMAIL PROTECTED]
Subject: [Haskell-cafe] Exercise in point free-style

I was just doing Exercise 7.1 of Hal Daumé's very good Yet Another
Haskell Tutorial. It consists of 5 short functions which are to be
converted into point-free style (if possible).

It's insightful and after some thinking I've been able to come up  
with

solutions that make me understand things better.

But I'm having problems with one of the functions:

func3 f l = l ++ map f l

Looks pretty clear and simple. However, I can't come up with a  
solution.
Is it even possible to remove one of the variables, f or l? If  
so, how?


Thanks,
Julien


Oh, YES!!

Two ways to remove l:

func3a f = uncurry ((.map f).(++)) . pair
func3b f = uncurry (flip (++).map f) . pair

And just to make sure they're right:

propab new f l =
 func3 f l == new f l
 where types = f :: Int-Int

quickCheck (propab func3a)
quickCheck (propab func3b)

If you don't mind swapping the arguments, then

propc f l =
 func3 f l == func3c l f
 where types = f :: Int-Int

func3c l = (l++) . (`map` l)

With the arguments swapped, you can even remove both!

propd f l =
 func3 f l == func3d l f
 where types = f :: Int - Int

func3d = uncurry ((.(flip map)) . (.) . (++)) . pair

MUCH clearer!

The trick is to observe that l is duplicated, so you need to use a  
combinator that duplicates something. The only one available here  
is pair, which you then have to combine with uncurry.


It would be nicer to have

(f  g) x = (f x,g x)

available. ( is one of the arrow combinators). Then you could  
remove l by


func3e f = uncurry (++) . (id  map f)

which is sort of readable, and remove both by

func3f = (uncurry (++).) . (id ) . map

John


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


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


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


Re: [Haskell-cafe] smallest double eps

2006-09-30 Thread Thomas Davie


On 30 Sep 2006, at 17:19, Brian Hulley wrote:


Lennart Augustsson wrote:

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


1 + 0 /= 0

0 is smaller than 4.5e15

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


But then 0 isn't positive.

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


Re: [Haskell-cafe] Composing functions with runST

2007-01-03 Thread Thomas Davie


It's true that this is the typical way of learning Haskell, but I for
one think it's a bad way of learning Haskell.
Very few real world programs get by without the impure stuff, so if
you give the newbie the impression that it isn't there (by postponing
it) there's a chance he'll run into a situation where he needs it
before it's been even mentioned (queue newbie going bah, academic
language and switching to C++).
On the contrary, I think it's an excellent way of learning Haskell.   
I'm writing a lot of useful Haskell code with only one IO action  
(interact).  I don't think I could reasonably construct an  
introductory problem that couldn't be solved with it, and I haven't  
yet found an application for which I've needed more.  I think it's  
destructive to teach people we have a wonderful new paradigm of  
programming that solves all sorts of problems, but all we're going to  
use it for is doing what we did with C++ anyway.


That's just my 2¢ -- I like Haskell specifically because I don't have  
to do things in order and I don't have to do things in an imperative  
style, I would love for more people to be taught about this wonderful  
thing.


Bob


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


Re: [Haskell-cafe] Win32 help please

2007-02-04 Thread Thomas Davie


On 4 Feb 2007, at 17:59, Stefan O'Rear wrote:


On Sun, Feb 04, 2007 at 10:42:23PM +1100, John Ky wrote:

# hsc2hs mywin32.hsc
# ghc -fffi mywin32.hs
C:/system/ghc/ghc-6.6/libHSrts.a(Main.o):Main.c:(.text+0x1b):  
undefined

reference to `__stginit_ZCMain'
C:/system/ghc/ghc-6.6/libHSrts.a(Main.o):Main.c:(.text+0x3f):  
undefined

reference to `ZCMain_main_closure'
collect2: ld returned 1 exit status

What am I missing?


A function named main.


s/function/constant/

In a module called Main.

Bob

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


Re: [Haskell-cafe] Haskell and GUI

2008-01-14 Thread Thomas Davie
There's also the HOC (Haskell Objective-C bridge), which lets you use  
Apple's Cocoa APIs.


Bob

On 14 Jan 2008, at 22:09, Torsten Otto wrote:

Seeing my woes with FranTk - what else is out there that people use  
if a (simple) GUI is desired for a Haskell app? Just a few textboxes  
and a button or two would do me.


Thanks in advance!

Regards,
Torsten
___
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] Doubting Haskell

2008-02-22 Thread Thomas Davie
A quick note here.  This is a *really* excellent tutorial on a variety  
of subjects.  It shows how monad operators can be used responsibly (to  
clarify code, not obfuscate it), it shows how chosing a good data  
structure and a good algorithm can work wonders for your code, and on  
a simplistic level, it shows how to build a database in Haskell.


Would it be possible to clean this up and put it in the wiki somewhere?

Thanks

Bob

On 20 Feb 2008, at 09:58, Cale Gibbard wrote:


(I'm copying the list on this, since my reply contains a tutorial
which might be of use to other beginners.)

On 19/02/2008, Alan Carter [EMAIL PROTECTED] wrote:

Hi Cale,

On Feb 19, 2008 3:48 PM, Cale Gibbard [EMAIL PROTECTED] wrote:

Just checking up, since you haven't replied on the list. Was my
information useful? Did I miss any questions you might have had? If
you'd like, I posted some examples of using catch here:


Thanks for your enquiry! My experiment continues. I did put a  
progress

report on the list - your examples together with a similar long an
short pair got me over the file opening problem, and taught me some
things about active whitespace :-) I couldn't get withFile working
(says out of scope, maybe 'cos I'm ghc 6.6 on my Mac)


Make sure to put:

import System.IO

at the top of your source file, if you haven't been. This should
import everything documented here:
http://www.haskell.org/ghc/docs/latest/html/libraries/base/System-IO.html

but it turned out the line I was looking for (collapsed from the  
examples)

was:

 text - readFile data.txt `catch` \_ - return 

This ensures the program never loses control, crashing or becoming
unpredictable by attempting to use an invalid resource, by yielding  
an

empty String if for any reason the file read fails. Then an empty
String makes it very quickly through parsing. I guess that's quite
functiony :-)

Amazing how easy once I knew how. Even stranger that I couldn't  
find a

bread and butter example of it.

Then I was going very quickly for a while. My file is dumped from a
WordPress MySql table. Well formed lines have 4 tab separated fields
(I'm using pipes for tabs here):

line id | record id | property | value

Line IDs are unique and don't matter. All lines with the same record
ID give a value to a property in the same record, similar to this:

1|1|name|arthur
2|1|quest|seek holy grail
3|1|colour|blue
4|2|name|robin
5|2|quest|run away
6|2|colour|yellow

Organizing that was a joy. It took minutes:


let cutUp = tail (filter (\fields - (length fields) == 4)
 (map (\x - split x '\t')  
(lines text)))


This should almost certainly be a function of text:

cutUp text = tail (filter (\fields - (length fields) == 4)
(map (\x - split x '\t') (lines  
text)))



I found a split on someone's blog (looking for a library tokenizer),
but I can understand it just fine. I even get to chuck out ill-formed
lines and remove the very first (which contains MySql column names)  
on

the way through!


Sadly, there's no general library function for doing this. We have
words and lines (and words would work here, if your fields never have
spaces), but nobody's bothered to put anything more general for simple
splitting into the base libraries (though I'm sure there's plenty on
hackage -- MissingH has a Data.String.Utils module which contains
split and a bunch of others, for example). However, for anything more
complicated, there are also libraries like Parsec, which are generally
really effective, so I highly recommend looking at that at some point.


I then made a record to put things in, and wrote some lines to play
with it (these are the real property names):

data Entry = Entry
 { occupation:: String
 , iEnjoyMyJob   :: Int
 , myJobIsWellDefined:: Int
 , myCoworkersAreCooperative :: Int
 , myWorkplaceIsStressful:: Int
 , myJobIsStressful  :: Int
 , moraleIsGoodWhereIWork:: Int
 , iGetFrustratedAtWork  :: Int
 }
...
 let e = Entry{occupation = , iEnjoyMyJob = 0}
 let f = e {occupation = alan}
 let g = f {iEnjoyMyJob = 47}
 putStrLn ((occupation g) ++   ++ (show (iEnjoyMyJob g)))

Then I ran into another quagmire. I think I have to use Data.Map to
build a collection of records keyed by record id, and fill them in by
working through the list of 4 item lists called cutUp. As with the
file opening problem I can find a few examples that convert a list of
tuples to a Data.Map, one to one. I found a very complex example that
convinced me a map from Int to a record is possible, but gave me no
understanding of how to do it. I spent a while trying to use foldl
before I decided it can't be appropriate (I need to pass more  
values).

So I tried a couple of recursive functions, something like:

type Entries = M.Map Int Entry
...
 let entries = loadEntries cutUp
...
loadEntries :: [[String]] - Entries
loadEntries [] = M.empty Entries
loadEntries [x : xs] = loadEntry 

Re: [Haskell-cafe] Re: ANN: haskell-src-exts 0.3.2

2008-03-17 Thread Thomas Davie


On 17 Mar 2008, at 23:41, Niklas Broberg wrote:


Could this be used to add support for refactoring of source files
containing language extensions?

Because if I'm correct, the current most popular refactoring  
solution (I

forgot the name) for Haskell does not support extensions.


I supppose you're talking about HaRe, that Thomas Schilling linked to.
I have no idea how that system is built so I can't answer your
question. But in principle I don't see why not. :-)


I believe that the limitation is that they use Programatica's parser  
to get an AST to run their refactorings on.  I think they've looked  
several times at using ghc's apis to do this, but hit various  
problems.  I think that the main problem is that no other parser  
preserves things like code layout and commenting, which is of course  
pretty critical to refactoring programs in a sane kind of way.


Thanks

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


Re: [Haskell-cafe] monadic debugging

2008-04-15 Thread Thomas Davie


On 16 Apr 2008, at 00:04, Bulat Ziganshin wrote:

Hello Vasili,

Wednesday, April 16, 2008, 2:53:32 AM, you wrote:


I have an Linux executable of my Haskell library and test
case. I see there are several debuggers, e.g. Buddha, Hat, etc.
Which debugger is currently preferred for monadic (imperative)  
code? Thanks.


i use print mainly :)  btw, there is also built-in ghci debugger, i
suspect that it's closest one to the usual debuggers and most useful
one for imperative code (but i never tried anything, so don't trust  
me :)


Having worked lots on Hat, and studied all (I hope or I've got a hole  
in my research) of the debuggers out there, I'd have to say that  
debugging monadic code is still very much an unsolved problem.   
Putting print statements in is probably your best option.


You may want to try hat-delta, or buddha's functional mapping mode --  
both of them should be capable of reducing sequences of monadic  
operations to a single operation and a function map.


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


Re: [Haskell-cafe] Fw: I have a problem

2008-04-24 Thread Thomas Davie
First, I'd refer you to this list's rules on homework, and what people  
will or won't answer.


Secondly to that though, rather than provide a solution, I'll give you  
an idea that may lead to you coming up with a solution.  First, try  
and write a function that can test if your first list is at the start  
of the second list:


 startlist [2,3] [2,3,4,5]
True
 startlist [2,3] [1,2,3,4]
False

Then use this function to write your sublist function.

Hope that helps

Tom Davie

On 24 Apr 2008, at 10:29, cetin tozkoparan wrote:

I have a problem which i can't solve. Is there any one who has an  
idea?
Two lists is sent as parameter to a function. If second list  
contains first list, return true, else return false. This  
comparision must be in order of first list. You can look at examples.



function type as follows:

sublist:: [a] - [a] - Bool


examples:


For instance [2,4,5] list is sub list of [3,7,2,4,5,9] list but not  
of [3,7,4,2,5,9] list.



sublist [2,8] [1,5,6,2,4,7,8,2]
False

sublist [1,2,3] [0,1,2,3,4,5,6]
True
sublist [5,4] [1,4,5,7,8,3,5,4]
True
sublist [1,2,4,3,4,5,7,8,9,5] [8,2,3,1,2,4,3,4,5,7,8,9,5,1,6,2]
True




Be a better friend, newshound, and know-it-all with Yahoo! Mobile.  
Try it now.___

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] unapplying function definitions?

2008-05-04 Thread Thomas Davie


On 4 May 2008, at 17:33, PR Stanley wrote:


Hi
What on earth is unapplying function definitions?
The following is taken from chapter 13 of the Hutton book:
...when reasoning about programs, function definitions can be both  
applied from left to right and unapplied from right to left.


Well, because of referential transparency, we can say that the left  
hand side of a function is exactly equal to the right hand side.   
Thus, we can instead of applying functions, and making progress  
towards a normal form, unapply them and get further away from a normal  
form... for example:


5 = head [5,6,7,8,9] = head ([5,6] ++ [7] ++ [8,9]) = head (([] ++ [5]  
++ [6]) ++ [7] ++ [8,9]) ...


There are of course an infinite number of ways of doing this, so it's  
usually only interesting, if we have some reason for applying a  
specific expansion.


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


Re: [Haskell-cafe] IO Help

2008-05-08 Thread Thomas Davie


On 8 May 2008, at 16:31, Mark Wallsgrove wrote:


Was there? I have been google'ing that problem for ages..

Just one more thing. I have to make a menu system where the user  
chooses what functionality they want. Because you cannot change a  
value once it is set I have used recursion so that when something  
changes it then calls the menu back up. I feel this is way to memory  
consuming. Is there another way?


While this method feels like it should consume lots of memory, it in  
fact doesn't.  Remember that you're dealing with a graph machine, and  
that no stack is maintained of all the calls you've made.  The garbage  
collector will simply follow you through the menu system clearing up  
the memory behind you.


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


Re: [Haskell-cafe] inserting values in a binary tree

2008-05-09 Thread Thomas Davie

On 10 May 2008, at 00:35, PR Stanley wrote:


Hi
data Ord a = Tree a = Nil | Node (Tree a) a (Tree a)
How would one go about inserting a value in a binary search tree of  
the above description?


All you need to do is consider what the trees should look like in the  
two cases:


If I try and insert an item into a completely empty tree, what do I  
end up with?  I'll give you a hint, it has one Node, and 2 Nils.
If I have a Node, do I need to insert into the left tree, or the right  
tree?


Take it from there

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


Re: [Haskell-cafe] Type Coercion

2008-05-28 Thread Thomas Davie


On 28 May 2008, at 09:34, PR Stanley wrote:


Hi
(16 :: Float) is a perfectly legitimate statement although I'm  
surprised that it's allowed in a type strong language such as  
Haskell. It's a bit like casting in good old C. What's going on here?


It's not a coercion -- it happens at compile time.

In a coercion, 16 starts off it's runtime life as an integer, gets a  
couple of things done to it, and then is coerced into a floating point  
number.  What's happening here is you are telling the compiler I  
would like the number 16, but a floating point version of it please.   
That instance of 16 always will have type Float.


Slightly more detail:  numeric literals like this normally have the  
type Int, but get pre-processed by the compiler.  Whenever you write  
16, the compiler writes (fromInteger 16).  This has the effect that  
instead of having the type Int, your literal has the type Num a = a.   
You adding the type signature constrains it to being a Float again.


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


Re: [Haskell-cafe] modelling C in Haskell ..

2008-05-30 Thread Thomas Davie

Yes, you must write them seperately as something like

data A = A Int B
data B = B1 Int
   | B2 Int Int

one of the many wonders of Haskell -- it encourages you to split up  
your code into nice small chunks.


Bob

On 30 May 2008, at 08:46, Galchin, Vasili wrote:


Hello,

 I don't want to write kludgy Haskell code!

typedef struct blah
{
   int val1;

   union {

   int  val2;

   struct {

 int val3;

 int val4;
   }
   }
}C_type;

question: in Haskell, can I embed definition of the union inside  
of the C typedef, i.e. recursion definition? Or must I have a  
separate definition for the union which I instantiate inside the  
Haskell typedef, i.e. Haskell data?


Kind regards, Vasili
___
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] automatically deriving Map and Filter on datatypes etc.

2008-06-05 Thread Thomas Davie
Even deriving an instance of Functor seems rather implausable, what  
should it do for


data Wierd a b = Nil | A a (Wierd a b) | B b (Wierd a b)

Should fmap's function argument operate on 'a's, 'b's, or both?

Bob

On 5 Jun 2008, at 10:28, Miguel Mitrofanov wrote:

Well, it's certainly not possible for filter, at least, not  
without additional hints to the compiler. For example, consider this  
type:


data Weird a = A | B a (Weird a) (Weird a)

filter p A = A
filter p (B x w1 w2) | p x = B x (filter p w1) (filter p w2)
| otherwise = ?

On 5 Jun 2008, at 12:03, Cetin Sert wrote:


Hi ^_^,

Let's say we have the following data type and functions:
data Tab a =  (:↺:)

  | a :↓:   Tab a
  | Tab a :↙↘: (Tab a,Tab a)
  deriving (Eq, Show, Read)

map f (:↺:)  = (:↺:)
map f (a :↓: t)  = f a :↓: map f t
map f (h :↙↘: (l,r)) = map f h :↙↘: (map f l, map f r)


filter p (:↺:)  = (:↺:)
filter p (a :↓: t)  | p a   = filter p t
   | otherwise = a :↓: filter p t
filter p (h :↙↘: (l,r)) = filter p h :↙↘: (filter p l,  
filter p r)


is it possible to automatically derive map and filter?
data Tab a =  (:↺:)
  | a :↓:   Tab a
  | Tab a :↙↘: (Tab a,Tab a)
  deriving (Eq, Show, Read, Map, Filter)

If not, do you think it might be nice to have something like this  
in the future?


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


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


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


Re: [Haskell-cafe] ANN: Topkata

2008-06-14 Thread Thomas Davie

On 14 Jun 2008, at 12:45, Christoph Bauer wrote:


Hi All,

Topkata is a simple OpenGL Game written in Haskell. It's not very
advanced. Goal so far is to guide a ball trough an labyrinth to the
opposite corner.  The web page shows an screenshot. It's only tested
under Linux.

http://home.arcor.de/chr_bauer/topkata.html

FeedbackPatches are welcome. BTW, I had a lot of support in #haskell!


Looks awesome, and I completely agree with Niel -- hackage it up!

In the mean time -- who knows enough to make ghc target ARM, and get  
this to link against the iPhone libraries?  This would be quite a coup  
if it could be made to run there!


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


Re: [Haskell-cafe] ANN: Topkata

2008-06-15 Thread Thomas Davie


On 15 Jun 2008, at 07:41, Deborah Goldsmith wrote:


On Jun 14, 2008, at 1:06 PM, Don Stewart wrote:

tom.davie:

In the mean time -- who knows enough to make ghc target ARM, and get
this to link against the iPhone libraries?  This would be quite a  
coup

if it could be made to run there!


I'd be interested. We should start a wiki page for Haskell on the
iphone..


It's an interesting idea, but I think it would need to be a cross- 
compiler. Does ghc support cross-compilation?


The most obvious place to start I guess would be using -fvia-C and the  
C cross compiler that apple supply.  I'll certainly be looking into  
this as soon as I get an iPhone (which unfortunately I need to wait  
for  3G one in Belgium).


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


Re: [Haskell-cafe] Re: How to do this in FP way?

2008-06-16 Thread Thomas Davie


One half of all Haskell coders will tell you that mutable state  
isn't a

good starting point to learn Haskell, the other half will tell you the
same because they want to be cool kids, too.


And the one left over will point out that he asked how to do this the  
FP way, not the imperative way?


If it was me btw, I'd take a stab at the problem being that each time  
we do something a time gets updated and we want to know how much time  
has passed since we last did something.


I'd approach this by generating a lazy list of times at which we  
started doing something, and then generating a lazy list of time  
differences.


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


Re: [Haskell-cafe] Re: How to do this in FP way?

2008-06-16 Thread Thomas Davie


On 16 Jun 2008, at 18:28, Achim Schneider wrote:


Thomas Davie [EMAIL PROTECTED] wrote:



One half of all Haskell coders will tell you that mutable state
isn't a
good starting point to learn Haskell, the other half will tell you
the same because they want to be cool kids, too.


And the one left over will point out that he asked how to do this
the FP way, not the imperative way?


There's no difference, as you can't do time-accounting non-strict and
still expect it to give meaningful results: I'm merely trying to be
helpful. None of the other solutions allow for the IO Monad.


Firstly, I'd phrase that differently -- the IO Monad doesn't allow for  
the other solutions -- the other solutions are the truly functional  
ones.  Secondly, I'm curious as to why you think that the two are  
incompatible, are you saying that for any meaningful kind of  
computation we need to resort to IORefs?  I'd strongly contest that  
idea.


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


Re: [Haskell-cafe] Re: How to do this in FP way?

2008-06-16 Thread Thomas Davie


On 16 Jun 2008, at 19:24, Achim Schneider wrote:


Thomas Davie [EMAIL PROTECTED] wrote:



On 16 Jun 2008, at 18:28, Achim Schneider wrote:


Thomas Davie [EMAIL PROTECTED] wrote:



One half of all Haskell coders will tell you that mutable state
isn't a
good starting point to learn Haskell, the other half will tell you
the same because they want to be cool kids, too.


And the one left over will point out that he asked how to do this
the FP way, not the imperative way?


There's no difference, as you can't do time-accounting non-strict
and still expect it to give meaningful results: I'm merely trying
to be helpful. None of the other solutions allow for the IO Monad.


Firstly, I'd phrase that differently -- the IO Monad doesn't allow
for the other solutions -- the other solutions are the truly
functional ones.  Secondly, I'm curious as to why you think that the
two are incompatible, are you saying that for any meaningful kind of
computation we need to resort to IORefs?  I'd strongly contest that
idea.


We have to resort to IO actions to get the time, and to IORefs because
we need to chain up different calls to getCurrentTime using the IO
Monad. The rest of the program can work with whatever you like best.


And in what way is this incompatible with either FRP as pierre  
suggested, or with generating an infinite list of times at which we  
call the function, and scanning it to find the differences?


Bob

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


Re: [Haskell-cafe] Qualified import syntax badly designed (?)

2008-07-09 Thread Thomas Davie


I think a better design for namespacing might be:

import Data.Map as M implicit (Map)
import Data.Map as M explicit (lookup)


Why 'implicit' and 'explicit'? Do you mean something like 'include'  
and 'exclude'?


To me at least, implicit and explicit make more sense.  I don't want  
to exclude importing lookup, I want to make it so I have to explicitly  
tag lookup as being M.lookup.  Similarly, I don't want to include Map  
(as opposed to all the other things I'm getting from Data.Map), I just  
want to make it so that when I say Map, I implicitly mean M.Map.


Personally I'd extend this syntax (something Neil may have had in  
mind), so that


import Data.Map as M (lookup, union) implicit (Map)
gives me M.lookup, M.union and Map

while
import Data.Map as M hiding (union) explicit (lookup)
gives me everything in Data.Map with no qualification except for union  
and lookup, plus it gives me M.lookup.


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


Re: [Haskell-cafe] Data.Derive problems

2008-07-10 Thread Thomas Davie


On 10 Jul 2008, at 21:25, Ron Alford wrote:

On Thu, Jul 10, 2008 at 3:18 PM, Neil Mitchell  
[EMAIL PROTECTED] wrote:

Hi Ron,


I'm using GHC 6.8.3 with $ cabal --version
cabal-install version 0.5.1
using version 1.4.0.1 of the Cabal library

I installed Data.Derive from hackage, only to be unable to find the
'derive' binary!


Did you do the runhaskell Setup configure  runhaskell Setup build  


runhaskell Setup install?


I used 'sudo cabal install derive'.  I did find the binary - in my
user's .cabal/bin directory!  Odd that it should default to that when
run as root.

I don't have the darcs version working yet, though.


I've found that cabal install doesn't actually install anything on my  
system either, despite going through all the motions.  I just download  
the tarballs of hackage and config/build/install them myself, and I  
then end up with all the relevant bits installed.


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


Re: [Haskell-cafe] a newbie's question

2005-04-21 Thread Thomas Davie
On Apr 21, 2005, at 3:47 PM, SCOTT J. wrote:
Hi,
I'm beginning to study Haskell, For the following
a = [1,2,3]
b = there
do x - a
  y - b
 return (x , y)
Winhugs cannot run it. Gives
 Syntax error in input (unexpected backslash (
lambda))
Your problem is that you're using monads to grab the contents of a  
and b, while a and b are not monadic... You probably if you're only  
just setting out don't want to pay attention to any of the do  
notation or monadic code.  To get the result it looks like you want,  
all you need to do is this:
(a, b)
you can then define this as a new constant:
c = (a, b)

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


Re: [Haskell-cafe] Specify array or list size?

2005-05-07 Thread Thomas Davie
No, it introduces a variable of type array of 50 ints, which can be
converted to pointer to int.
It matters when you make a pointer of such arrays, an array of such
arrays, or sizeof such array. In C++ the size can be matched by
template parameter, and you can have separate overloadings for
separate array sizes.
I'm not familiar with your C++ example (not being familiar with C++),  
but I think that it's a bit of a stretch of the imagination to say  
that C introduces a variable of type array of 50 ints, the fact  
that this is now an array of 50 integers is never checked at any  
point in the compilation or run, and I'm not sure it can be even if  
KR had wanted to.  If I'm thinking straight then *any* array  
definition merely gets re-written to a memory allocation of the  
relevant amount of ram, and beyond this point it is forever of type  
pointer to array content type.

As an example:
int bobsArray[5];
bobsArray[6] = 23;
is not badly typed  it is merely a badly broken program.
Bob
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Specify array or list size?

2005-05-07 Thread Thomas Davie
On May 7, 2005, at 8:07 PM, Marcin 'Qrczak' Kowalczyk wrote:
Thomas Davie [EMAIL PROTECTED] writes:

I'm not familiar with your C++ example (not being familiar with C++),
but I think that it's a bit of a stretch of the imagination to say
that C introduces a variable of type array of 50 ints, the fact
that this is now an array of 50 integers is never checked at any
point in the compilation or run, and I'm not sure it can be even if
KR had wanted to.
The size is taken into account when such array type is an element of
another array, and by sizeof.
int (*p)[50]; /* p may legally point only to arrays of 50 ints each */
++p; /* p is assumed to point into an array, and is moved by one
element, i.e. by 50 ints */
I'm not sure what you're trying to prove by saying that... There is  
still no type information that says that the contents of p are an  
array of 50 elements... I can still attempt to access element 51 and  
get a runtime memory error.  The type of p is still int**, not  
pointer to array of 50 ints

As an example:
int bobsArray[5];
bobsArray[6] = 23;
is not badly typed - it is merely a badly broken program.
Because the array size is not taken into account by indexing. But it's
a part of the type. These issues are independent, for example in C#
both are the opposite.
I don't think it is part of the type... Does the compiler ever know  
any more about the type of bobsArray other than it's a pointer to an  
integer?  I think that the above code can be directly translated to:

int *bobsArray;
bobsArray = (int *)malloc(5 * sizeof(int));
bobsArray[6] = 23
Which stores exactly the same about on type information.
Bob
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Compiling with NHC98

2005-05-07 Thread Thomas Davie
Incidentally, if you aren't already familiar with make or some other
build system, I strongly recommend looking into one. Even for a  
project
with only two files, having a build system keep track of compilation
dependencies makes things a lot less tedious.
In random addition to this... hmake will automatically keep track of  
Haskell dependencies, and will also allow you to easily compile your  
code to work with the hat (hmake -hat) tracing suite.

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


[Haskell-cafe] Type system extension

2005-05-15 Thread Thomas Davie
Hi,
  I'd just been writing some code and an interesting idea for an  
extension to Haskell's type system sprang into my head.  I have no  
idea if people have played with it, but it looked vaguely useful to  
me, so I thought I'd see what everyone else thought.

Supposing you have these types:
type Export = String
data SCode = SModule String [Export] | SUnknown
It would be useful to specify a function as so:
doSomethingToAModule :: SCode(SModule) - SomeRandomOtherType
which would specify, not only that the first argument was of type  
SCode, but more specifically, that it used the SModule constructor.   
This would then allow you to safely only write a case for the SModule  
constructor, and not worry about a runtime error when pattern  
matching failed on an SUnknown (as this would be checked at compile  
time).

I hope this makes sense
What does anyone think of the idea, and is there an obvious flaw in  
the plan?

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


Re: [Haskell-cafe] Type system extension

2005-05-15 Thread Thomas Davie
On May 16, 2005, at 12:46 AM, Neil Mitchell wrote:
Hi,
Yes, sounds like a good idea. I'm not sure the right approach is to
make the user give this information though - the code will very likely
be something like
doSomethingToAModule (SModule a b) = f a b
from which you can derive the type SCode(SModule) very easily. As the
expressions get more complex, you will want more substantial
annotations - i.e. SCode(SModule(_,[])|SUnknown) for something which
either exports nothing, or is unknown. At this point getting the
programmer to type in essentially the same information twice is likely
to become annoying.
I'm not certain I agree with you.  Where I do agree is that the types  
are liable to get very complex fairly quickly, and this may well be  
the flaw in the plan, however, I think Haskell benefits greatly from  
asking the programmer to provide the same information twice in  
slightly different forms.

The type system after all is essentially a method of providing a  
sanity check -- does the code actually match up with what the  
programmer specified as a type.

My current work on my PhD is all related to checking that a Haskell
program cannot raise a pattern match error, and it is accomplished in
a similar sort of method to what you are suggesting, and achieves
similar goals. This work is still ongoing, but a first order checker
exists for a subset of Haskell already - so progress is being made.
I haven't thought about this for more than half a day when the idea  
popped into my head, so obviously you've dealt with it a bit more,  
but I wonder if this is only half the problem.  By the sounds of it  
you are doing type inferencing from the program (as you explained  
above), which allows for a certain level of checks.  However, type  
errors are not only thrown when the type inference system can't  
generate types to fit the program, but also when the programmer has  
specified types that are different to that the inference worked out.

Thanks for a very interesting reply
Tom Davie
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] Type extensions

2005-06-01 Thread Thomas Davie

Hi,
  I was wondering if I hat missed something and it was possible to  
do this within the Haskell type system or not...


Essentially I would like some sort of inderritance property for  
Haskell types, I often find myself wanting to for example extend a  
tree with black/white colouring, or later extend the tree with some  
sort of ID, etc.


So I would eno up with three data types

data MyTree = Branch MyTree MyTree | Leaf

type BwTag = Bool
data MyBwTree = Branch BwTag MyBwTree MyBwTree | Node BwTag

data MyBwTaggedTree = Branch BwTag Int MyBwTaggedTree MyBwTaggedTree  
| Node BwTag Int


and several functions to move from one to another.  (Or define the  
most complex and not always use all the attrdbutes). What I would  
prefer is to be able to spocify something like:


data MyTree = Branch MyTree MyTree | Leaf

type BwTag = Bool
data MyBwTree extends MyTree with BwTag=True

data MyBwTaggedTree extends MyBwTree with Int=0

Specifying that myBwTree is the same as MyTree but with an extra  
argument on each node, and to generate functions to translate between  
them that fill in True as a default value for the extra tag.


Is this possible?

Thanks

Tom Davie

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


Re: [Haskell-cafe] Type extensions

2005-06-01 Thread Thomas Davie


On 1 Jun 2005, at 15:54, Henning Thielemann wrote:



On Wed, 1 Jun 2005, Thomas Davie wrote:



Hi,
   I was wondering if I hat missed something and it was possible to
do this within the Haskell type system or not...

Essentially I would like some sort of inderritance property for
Haskell types, I often find myself wanting to for example extend a
tree with black/white colouring, or later extend the tree with some
sort of ID, etc.

So I would eno up with three data types

data MyTree = Branch MyTree MyTree | Leaf

type BwTag = Bool
data MyBwTree = Branch BwTag MyBwTree MyBwTree | Node BwTag



What about

data MyTree a = Branch a (MyTree a) (MyTree a) | Node a

and the types
 MyTree ()
 MyTree Bool
 MyTree (Bool, Int)
 ?
That's exactly what I would normally do, but my data type is in a  
library and is not parameterised.


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


Re: [Haskell-cafe] Monadic vs pure style (was: pros and cons of sta tic typing and side effects)

2005-08-30 Thread Thomas Davie
On Aug 30, 2005, at 12:13 PM, Bayley, Alistair wrote:From: Duncan Coutts [mailto:[EMAIL PROTECTED]] This is often a misconception, that just because you find you need to'do' something in the middle of your algorithm, that you need to convert it wholly to monadic style. Yes. However, Wadler makes a convincing (at least to me) case that themonadic style is easier to extend. The code changes for the monadic styleappear to be more localised.Something else I noticed about my non-monadic code was the way I wasthreading state through functions. I was tempted to introduce a State monadto make this easier to manage, but then I decided to try mutable arraysinstead, so that experiment was not attempted. So it might well have beenbetter in monadic style anyway, even with immutable arrays.I'm conscious that for most (?) monads, monadic code can be invoked fromnon-monadic code. I'm only aware of the IO monad as a one-way trap. Sochanging code from pure to monadic doesn't necessarily involve program-widechanges, unless the monad you're introducing happens to be IO. In my arrayexample, I introduced STArrays, but the main interface remained pure(non-monadic), which was my goal.I was also wondering what the disadvantages of monadic style are? Are therecompiler optimisations which are not possible with monadic code?Both the advantage and the disadvantage is that you break lazy evaluation.  90% of the time lazyness is your friend and monadifying your code can break some nice features, but there is an occasional 10% of the time when it's useful to break lazyness.On a side note, whenever I find myself tempted to pass state around, I consider whether using CPS is better... It provides some method of ordering code, but doesn't break lazyness.Just 2¢ from a relative newbie.Bob___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Functional vs Imperative

2005-09-13 Thread Thomas Davie


On 13 Sep 2005, at 14:45, Dhaemon wrote:



Hello,
I'm quite interested in haskell, but there is something I don't  
understand(intuitively). I've been crawling the web for an answer,  
but nothing talks to me...

So I was hoping I could find some help here:
How is evaluating an expression different from performing action?
I'm puzzled... Doesn't it amount to the same thing? Maybe I have a  
wrong definition of evaluating(determine the value of an  
expression)?

Examples would be appreciated.
Also, just for kicks, may I had this: I read the code of some  
haskell-made  programs and was astonished. Yes! It was clean and  
all, but there were dos everywhere... Why use a function language  
if you use it as an imperative one?(i.e. most of the apps in http:// 
haskell.org/practice.html)




The difference is all about referential transparency -- in short, a  
function given the same inputs will always give the same result.   
This is not the same as in imperative languages, where functions/ 
methods/actions can have 'side-effects' that change the behavior of  
the rest of the program.


Take this example:

C program:
#define square(x) ((x) * (x))
#define inc(x) ((x)++)

int myFunc (int *x)
{
return square(inc(*x));
}

the C preprocessor will re-write the return line to:
return x)++)) * (((x)++)));

this will be performed in sequence, so, x will be incremented  
(changing the value of x), and that result will be multiplied by x  
incremented again.


so if we run myFunc(y), where y is 5, what we get is 5 incremented  
to 6, and them multiplied by 6 incremented to 7.  So the result of  
the function is 42 (when you might reasonably expect 36), and y is  
incremented by 2, when you might reasonably expect it to be  
incremented by 1.


Haskell program:

square x = x * x
inc = (+1)
myFunc = square . inc

and we now call myFunc 5, we get this evaluation:

myFunc 5 is reduced to (square . inc) 5
(square . inc) 5 is reduced to square (inc 5)
square (inc 5) is reduced to square ((+1) 5)
square ((+1) 5) is reduced to square 6
square 6 is reduced to 6 * 6
6 * 6 is reduced to 36

If you want to study these reductions on a few more examples, you  
might want to download the Hat tracer, and use hat-anim to display  
reductions step by step.


Bob

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


Re: [Haskell-cafe] Functional vs Imperative

2005-09-13 Thread Thomas Davie


On 13 Sep 2005, at 16:22, David Roundy wrote:


On Tue, Sep 13, 2005 at 01:45:52PM +, Dhaemon wrote:

Also, just for kicks, may I had this: I read the code of some  
haskell-made
programs and was astonished. Yes! It was clean and all, but there  
were dos
everywhere... Why use a function language if you use it as an  
imperative

one?(i.e. most of the apps in http://haskell.org/practice.html)



Monadic code isn't synonymous with imperative code, and do only  
indicates
that you're looking at monadic code.  The Maybe monad is an example  
of a
very useful, very non-imperative monad that can be used to cleanly  
write

functional code.

On the other hand, IO is always monadic, so perhaps you're looking  
at IO
code.  But I'd assert that even monadic IO code isn't quite the  
same as
true imperative code.  I'd probably say that the difference has  
to do
with whether you create modifiable variables.  When you start  
doing that,

whether you're in the ST monad or the IO monad, I think you're writing
imperative-style code.  But I think that that sort of usage is  
actually

pretty uncommon.


I would tend to argue that even in those monads you aren't really  
writing imperative style code -- you still can't have side effects.   
The point of the monad is that it preserves referential transparency  
while doing something ordered.


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


Re: [Haskell-cafe] newbe question

2005-09-27 Thread Thomas Davie

The reason is that you can define =- as on operator

so for example, in this (obfuscated) code:

(=-) x y = x * y

sq y = y =- y

Thus, in your code, you had an operator on the LHS of the definition,  
and the interpreter baulked at it.


Bob

On 27 Sep 2005, at 10:34, [EMAIL PROTECTED] wrote:



Hi
i can not load program test1 into hugs, but test2 works.
Am i missing some special syntax?

greetings,
Philip

-- test1 --

foo :: Maybe Int - Int
foo Nothing =-1
foo (Just a)= a

-- test2 --

foo :: Maybe Int - Int
foo Nothing = -1
--   ^
--   +-- note an extra space
foo (Just a)= a
___
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] newbe question

2005-09-27 Thread Thomas Davie


On 27 Sep 2005, at 16:53, [EMAIL PROTECTED] wrote:



On 27 Sep, Wolfgang Jeltsch wrote:




Hello,

obviously, Hugs thinks that =- is a special operator.  In Haskell  
you have the
ability to define your own operators, so it would be possible to  
define an
operator =-.  I would suggest that you always put spaces around  
the = in

declarations.

Best wishes,
Wolfgang





Hello,
thank you for fast reply.
Ok, but what is the semantic of '=-' ? If it's an operator, it should
have some impact (right term?).



The semantics are whatever you define them to be:

(=-) x y = doSomeFunkyStuff x y

Note that this also introduces problems with comments, a common  
mistake people make is to not put a space after the -- comment  
symbol, so they may end up with:


--| something

The compiler then interprets --| as an operator.

Bob

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


Re: [Haskell-cafe] how to break foldl' ?

2005-09-30 Thread Thomas Davie


On 30 Sep 2005, at 11:33, gary ng wrote:



Hi,

say if I want to sum a list of numbers but only until
it hits a max limit.

Currently, I control it through the function and
basically do nothing when the max is hit. However, if
the list is very long, would this mean the same
function would be called for the rest of the list
which can be a waste of cycle ? In an imperative
language, I just break/return in the middle of the
loop.



No - lazy evaluation guarantees that if a reduct is never needed, it  
is never reduced.  So as your function never needs the latter values  
in the list, it is never evaluated.


Bob

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


Re: [Haskell-cafe] how to break foldl' ?

2005-09-30 Thread Thomas Davie
Again, it depends how takeWhile is implemented -- if it's not tail  
recursive, the compiler will usually manage to run such functions in  
constant space.


Bob

On 30 Sep 2005, at 16:02, gary ng wrote:


Once again, many thanks to all who taught me about
this small little problem. Don't even know there is
init/last and thought there is only head/tail.

But just for my curiosity, would the takeWhile still
store the intermediate result till my result is
reached ? If so, and my list is really very long(and I
need to go to 1/2 of its length), I would still use a
lot more memory than imperative method or even the
foldl one(where in both case, I just take one element)
?

--- Henning Thielemann [EMAIL PROTECTED]
wrote:



No problem:
  last (takeWhile (maxX) (scanl (+) 0 xs))
Convinced?

The first sum which exceeds the limit could be
computed with
  head (dropWhile (=maxX) (scanl (+) 0 xs))








__
Yahoo! Mail - PC Magazine Editors' Choice 2005
http://mail.yahoo.com
___
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] file i/o

2006-01-03 Thread Thomas Davie
The other thing to mention, is that if you have the ability to change  
file formats, it may be better to make just a slight adjustment... If  
you make it look exactly like the haskell data structure you want:


[(Foo, [1,2,3,4,5,6,7])
,(Bar, [7,6,5,4,3,2,1])
,...]

Then your parser becomes even simpler:

parseFile :: FilePath - IO [(String,[Int])]
parseFile = do src - readFile x
   return $ read src

On Jan 3, 2006, at 11:33 AM, Neil Mitchell wrote:


Hi Robert,

The first thing to mention is that Haskell uses linked-lists, not
arrays as the standard list type structure, so [1,2] is actually a
linked list.

The next thing to note is that Haskell is *lazy*. It won't do work
that it doens't have to. This means that you can return a linked list
with all the lines in the file, but they won't actually be read til
they are required. i.e. Haskell cleverly worries about all the
getting a next line as required stuff, without you even noticing -
it will read it line by line.

A simple function that does some of what you want is:

parseFile :: FilePath - IO [(String, [Int])]
parseFile x = do src - readFile x
 return (map parseLine (lines src))



parseLine :: String - (String, [Int])
parseLine = for you to write :)


The other point is that Haskell linked lists have to have every
element of the same type, so you can't have [test,1] as a linked
list, what you actually want is a tuple, written (test,1) - a tuple
is of fixed length and all elements can be of different type.

Hope that helps,

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] Re: Can I use Haskell for web programming

2006-01-21 Thread Thomas Davie


On Jan 21, 2006, at 8:34 PM, Maurício wrote:

  They both look cool. Do you think I'll be able to find someone to  
host professional sites using those libraries?


  [],
  Maurício


Try http://contextshift.co.uk/vps.html ... or I guess any other  
virtual server hosts, but they're cheep and good.


Bob


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


Re: [Haskell-cafe] Lists of Lists

2006-03-08 Thread Thomas Davie


On 8 Mar 2006, at 14:21, zell_ffhut wrote:



Thank you, It's working as planed now

Trying to do a function now that changes the value of an element of  
the
list. In programming languages i've used in the past, this would be  
done

somthing like -


changeValue x i [xs] = [xs] !! i = x


where x is the value to change to, i is the index of the value to  
change,

and [xs] is the list.

This however, dosen't work in Haskell. How would this be done in  
Haskell?


Put simply it isn't.

One of the percepts of a functional language is that variables are  
bound, not set - once a variable has a value it has that value  
forever.  What you want to do is return a new list, that looks like  
the old one, but has one value changed


changeValue x 0 (y:ys) = (x:ys)
changeValue x n (y:ys) = y:(changeValue x (n-1) ys)

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


Re: [Haskell-cafe] Porting GHC to OSX86?

2006-03-22 Thread Thomas Davie


On Mar 21, 2006, at 8:09 PM, Deling Ren wrote:


Hi there,

Has anyone made any attempt to port GHC to Mac OS X on x86?  
Wolfgang Thaller’s binary package runs over Rosetta but slow (not  
surprising). It can not be used to compile a native version either  
(I got some errors related to machine registers).


I tried to do a bootstrap but can't find the .HC files mentioned  
in the manual. They don't seem to be on the download page of GHC.  
Any ideas?


Why not use darwin ports to build it?

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


Re: [Haskell-cafe] Re: Editors for Haskell

2006-05-25 Thread Thomas Davie


On May 25, 2006, at 6:14 PM, Jeremy O'Donoghue wrote:


Hi Walt,


I'm using Haskell (GHC and Hugs) on several different platforms.
Windows, OS X and Linux systems.


Assuming that you want your students to be able to use any of the
above platforms, the only options I know of which work well on all of
the platforms are Emacsen, Vim, hIDE, Eclipse and JEdit.


I'd like to have an IDE that works well for medium to large size
projects. I know of Eclipse and hIDE.
Vim works fine but I'd like more. hiDE seems to be in process.


When working on Macs I've found SubEthaEdit to be by far the best  
Haskell editor, emailing the guy tends to have quite good results in  
terms of getting it free if you say you're involved in education.


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


Re: [Haskell-cafe] Re: Can we come out of a monad?

2010-08-11 Thread Thomas Davie

On 11 Aug 2010, at 12:39, Ertugrul Soeylemez wrote:

 Martijn van Steenbergen mart...@van.steenbergen.nl wrote:
 
 On 8/2/10 7:09, Ertugrul Soeylemez wrote:
 Given the definition of a Haskell function, Haskell is a pure
 language.  The notion of a function in other languages is not:
 
   int randomNumber();
 
 The result of this function is an integer.  You can't replace the
 function call by its result without changing the meaning of the
 program.
 
 I'm not sure this is fair. It's perfectly okay to replace a call
 randomNumber() by that method's *body* (1), which is what you argue
 is okay in Haskell.
 
 This is not the same.  In Haskell you can replace the function call by
 its /result/, not its body.  You can always do that.  But the result of
 an IO-based random number generator is an IO computation, not a value.
 It's not source code either, and it's not a function body.  It's a
 computation, something abstract without a particular representation.

It's still rather papering over the cracks to call this pure though.  The IO 
based computation itself still has a result that you *can't* replace the IO 
based computation with.  The fact that it's evaluated by the runtime and not 
strictly in haskell may give us a warm fuzzy feeling inside, but it still means 
we have to watch out for a lot of things we don't normally have to in a very 
pure[1] computation.

Bob

[1] Bob's arbitrary definition 1 – very pure computations are ones which can be 
replaced with their result without changing the behavior of the program *even* 
if said result is computed in the runtime and not by the Haskel 
program.___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Re: Can we come out of a monad?

2010-08-11 Thread Thomas Davie

On 11 Aug 2010, at 14:17, Ertugrul Soeylemez wrote:
 
 There is a fundamental difference between an IO computation's result and
 a Haskell function's result.  The IO computation is simply a value, not
 a function.

That's a rather odd distinction to make – a function is simply a value in a 
functional programming language.  You're simply wrapping up we're talking 
about haskell functions when we talk about referential transparency, not about 
IO actions in a way that maintains the warm fuzzy feeling.

Bob

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


Re: [Haskell-cafe] On to applicative

2010-08-26 Thread Thomas Davie

On 26 Aug 2010, at 08:01, michael rice wrote:

 Hmm... it was my understanding that the example was showing how to *avoid* 
 having to create a  lot of functions that do the same thing but have 
 different numbers of arguments.
 
 From the Wiki page:
 
 Anytime you feel the need to define different higher order functions to 
 accommodate for function-arguments with a different number of arguments, 
 think about how defining a proper instance of Applicative can make your life 
 easier.
 
 Not so?
 
 
Very much so – instead of defining liftA2, liftA3 etc like this, just use pure 
to get things into the applicative, and write * instead of ' ' to apply 
applicatives and you're done.

Don't write
liftA3 sumsq (Just 3) (Just 4) (Just 5)

Write
(pure sumsq) * (pure 3) * (pure 4) * (pure 5)

or you can get rid of that first pure with a quick fmap:
sumsq $ (pure 3) * (pure 4) * (pure 5)

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


Re: [Haskell-cafe] Re: Do expression definition

2010-09-13 Thread Thomas Davie

On 13 Sep 2010, at 10:28, Gleb Alexeyev wrote:

 On 09/13/2010 12:23 PM, Michael Lazarev wrote:
 2010/9/13 Henning Thielemannlemm...@henning-thielemann.de:
 It means that variables bound by let, may be instantiated to different types
 later.
 
 Can you give an example, please?
 
 testOk = let f = id in (f 42, f True)
 
 --testNotOk :: Monad m = m (Int, Bool)
 --testNotOk = do f - return id
 --   return (f 42, f True)
 
 Try uncommenting the 'testNotOk' definition.

There's no later here at all.

Two seperate definitions in a Haskell program act as if they have always been 
defined, are defined, and always will be defined, they are not dealt with in 
sequence (except for pattern matching but that doesn't apply here).

Instead, what's going on here is scoping.  The f in testOk is a different f to 
the one in testNotOkay, distinguished by their scope.

Finally, this is not how you use a let in a do expression, here's how you 
should do it:

testOk2 :: Monad m = m (Int, Bool)
testOk2 = do let f = id
 return (f 42, f True)


Thanks

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


Re: [Haskell-cafe] Generating arbitrary functions with QuickCheck?

2010-09-15 Thread Thomas Davie

On 15 Sep 2010, at 16:29, Matias Eyzaguirre wrote:

 Hi,
 I'v been reading a small paper/lesson on writing parser combinators in 
 Haskell, and it seems more or less straightforward. In this case a parser is 
 defined thusly:
 type Parser a = String - Maybe (a, String)
 And then it goes on to list some simple parsers, and then starts going on 
 about combinators.
 I was wondering how one would write quickcheck properties for the items 
 presented in the paper, and the answer seemed fairly straightforward for the 
 actual parsers. But how on earth would you write a test for a combinator? 
 Presumable one would need to make the type an instance of Arbitrary.
 I see two problems:
 Firstly, as far as i can tell, one cannot declare a type synonym to be an 
 instance of a type class, thus how would you make it an instance of Arbitrary?

The standard solution here is to create a newtype, and generate them instead.

 Secondly, (and more importantly, or at least more interesting) I can see how 
 one would make a generator for simple compound data types, but how on earth 
 do you make a generator produce functions?

With some difficulty, but it can be done.  You could for example, select at 
random, a combinator or axiomatic parser, on selecting a combinator, generate a 
pair of parsers to hand to it with a slightly lower chance of generating a 
combinator and stick them together.

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


Re: [Haskell-cafe] ANNOUNCE: tls, native TLS/SSL protocolimplementation

2010-10-11 Thread Thomas Davie
 
 While I agree with the potential benefits, I also worry that you will
 end up making something that is far less well tested in practice. For
 widely used and fairly low-level libraries like gnutls, openssl and
 zlib, I'm just skeptical that the benefits outweigh the risks and costs.
 
 Anyway, it's just a feeling. Please do prove me wrong :-)

This certainly isn't a proof by a long shot, but my feeling on at least 
low-level libraries is exactly the reverse of this.

C libraries are usually designed to be extremely stateful (this certainly 
includes openssl), and because of that any Haskell wrapper for them ends up 
being heavily IO based.  The result of this is that any code that incorporates 
it ends up being trapped in an IO mess to do essentially pure (yes, I know the 
arguments about IO being pure, you know what I mean) things.  It's precisely 
these libraries that we need not just implemented in a native way, but 
designed in a pure, beautiful, simple way for Haskell.

While I can see your point about potentially introducing new security holes, 
and producing much less trusted code, I feel having tidy, pure libraries that 
we can all integrate into our Haskell is a benefit that far outweighs this.  
Especially when we have nice things like the type system, which can be used to 
alleviate many of the security worries.

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


Re: [Haskell-cafe] Serialization of (a - b) and IO a

2010-11-11 Thread Thomas Davie

On 11 Nov 2010, at 08:36, Luke Palmer wrote:

 On Thu, Nov 11, 2010 at 12:53 AM, Jesse Schalken
 jesseschal...@gmail.com wrote:
 I have had a look at hs-plugins, but it is unclear how to derive a simple
 pair of functions `(a - b) - ByteString` and `ByteString - Either
 ParseError (a - b)`, for example, from the functionality it provides, if it
 is possible at all. I guess such a thing requires thorough digging into the
 depths of GHC, (or maybe even LLVM if
 an architecture independent representation is sought, but I don't know
 enough to say.). Perhaps this is more a question for those interested and
 knowledgable in Haskell compilation (and, to some extent, decompilation).
 If not Haskell, are there any languages which provide a simple serialization
 and deserialization of functions?
 
 As far as I know, GHC has no support for this.  There are issues with
 the idea that will come out pretty fast, such as:
 
(1) Those cannot be pure functions, because it differentiate
 denotationally equal functions.  So it would have to be at least (a -
 b) - IO ByteString.

I don't think I agree, I didn't see a rule f == g = serialise f == serialise g 
anywhere.

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


Re: [Haskell-cafe] Why is Haskell flagging this?

2010-12-18 Thread Thomas Davie

On 17 Dec 2010, at 21:44, Christopher Done wrote:

 On 17 December 2010 18:04, michael rice nowg...@yahoo.com wrote:
 ===
 
 f :: [Int] - IO [Int]
 f lst = do return lst
 
 main = do let lst = f [1,2,3,4,5]
   fmap (+1) lst
  
 The problem is that you are applying fmap to a type IO a.
 
 fmap (+1) (return [1,2,3])
 
 But to achieve the behaviour you expect, you need another fmap:
 
 fmap (fmap (+1)) (return [1,2,3])

Which can be more neatly written with Conal's semantic editor cominators as

(fmap . fmap) (+1) (return [1,2,3])

Of course, I question why the list is put in the IO monad at all here... surely 
this would be much better

return $ fmap (+1) [1,2,3]

Finally, that has the wrong type for main... perhaps you meant to print it out?

main :: IO ()
main = print $ fmap (+1) [1,2,3]

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


Re: [Haskell-cafe] GHC optimizations and unsafePerformIO - Was: Data.Typeable TypeRep Ord instance.

2011-01-01 Thread Thomas Davie

On 1 Jan 2011, at 12:38, Andreas Baldeau wrote:

 Thinking about this there might be one problem:
 
 Without having looked further into this I think perfomance might not
 be as expected. Using unsafePerformIO affects ghc's optimzations,
 doesn't it?
 
 So I wonder if it's a good idea (from a performance point of view) to
 use this.
 
 2010/12/30 Andreas Baldeau andr...@baldeau.net:
 instance Ord TypeRep where
compare t1 t2 =
compare
(unsafePerformIO (typeRepKey t1))
(unsafePerformIO (typeRepKey t2))
 
 typeRepKey :: TypeRep - IO Int
 typeRepKey (TypeRep (Key i) _ _) = return i
 
 So the question is, if ghc could transform this to simply compare the
 keys throwing away unsafePerformIO and return.

Wouldn't a much better plan simply be to take typeRepKey out of the IO monad?

Bob

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


Re: [Haskell-cafe] ANNOUNCE: Utrecht Haskell Compiler (UHC) -- first release

2009-04-18 Thread Thomas Davie


On 18 Apr 2009, at 22:44, Antoine Latter wrote:


On Sat, Apr 18, 2009 at 9:03 AM,  a...@cs.uu.nl wrote:

   Utrecht Haskell Compiler -- first release, version 1.0.0
   


The UHC team is happy to announce the first public release of the
Utrecht Haskell Compiler (UHC). UHC supports almost all Haskell98
features plus many experimental extensions. The compiler runs on  
MacOSX,

Windows (cygwin), and various Unix flavors.

Features:

 * Multiple backends, including a bytecode interpreter backend and a
   GRIN based, full program analysing backend, both via C.

 * Experimental language extensions, some of which have not been
   implemented before.

 * Implementation via attribute grammars and other high-level tools.

 * Ease of experimentation with language variants, thanks to an
   aspect-oriented internal organisation.


Getting started  Download
--

UHC is available for download as source distribution via the UHC home
page:

   http://www.cs.uu.nl/wiki/UHC

Here you will also find instructions to get started.


Status of the implementation


Like any university project UHC is very much work in progress. We  
feel

that it is mature and stable enough to offer to the public, but much
work still needs to be done; hence we welcome contributions by  
others.


UHC grew out of our Haskell compiler project (called Essential  
Haskell
Compiler, or EHC) over the past 5 years. UHC internally is  
organised as

a combination of separate aspects, which makes UHC very suitable to
experiment with; it is relatively easy to build compilers for
sublanguages, or to generate related tools such as documentation
generators, all from the same code base. Extensions to the language  
can

be described separately, and be switched on or of as need arises.


Warning
---

Although we think  that the compiler is stable enough to compile
subtantial Haskell programs, we do not recommend yet to use it for  
any

serious development work in Haskell. We ourselves use the GHC as a
development platform! We think however that it provides a great  
platform

for experimenting with language implementations, language extensions,
etc.


Mailing lists
-

For UHC users and developers respectively:

   http://mail.cs.uu.nl/mailman/listinfo/uhc-users
   http://mail.cs.uu.nl/mailman/listinfo/uhc-developers


Bug reporting
-

Please report bugs at:

   http://code.google.com/p/uhc/issues/list


The UHC Team


--
Atze Dijkstra, Department of Information and Computing Sciences. /|\
Utrecht University, PO Box 80089, 3508 TB Utrecht, Netherlands. / | \
Tel.: +31-30-2534118/1454 | WWW  : http://www.cs.uu.nl/ 
~atze . /--|  \
Fax : +31-30-2513971  | Email: a...@cs.uu.nl  /   | 
___\


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



After running ./configure on my Intel Mac (running OS 10.5.6 with
GHC 6.10), I try to run make uhc and get the following:




$ make uhc
src/ruler2/files.mk:34: build/ruler2/files-ag-d-dep.mk: No such file
or directory
src/ruler2/files.mk:35: build/ruler2/files-ag-s-dep.mk: No such file
or directory
mkdir -p build/shuffle ; \
	 --module=CDoc -dr  -Psrc/shuffle/ -o build/shuffle/CDoc.hs src/ 
shuffle/CDoc.ag

/bin/sh: --module=CDoc: command not found
make: Failed to remake makefile `build/ruler2/files-ag-s-dep.mk'.
make: Failed to remake makefile `build/ruler2/files-ag-d-dep.mk'.
make EHC_VARIANT=`echo install/101/bin/ehc | sed -n -e
's+install/\([0-9_]*\)/bin/ehc.*+\1+p'` ehc-variant
src/ruler2/files.mk:34: build/ruler2/files-ag-d-dep.mk: No such file
or directory
src/ruler2/files.mk:35: build/ruler2/files-ag-s-dep.mk: No such file
or directory
mkdir -p build/shuffle ; \
	 --module=CDoc -dr  -Psrc/shuffle/ -o build/shuffle/CDoc.hs src/ 
shuffle/CDoc.ag

/bin/sh: --module=CDoc: command not found
make[1]: Failed to remake makefile `build/ruler2/files-ag-s-dep.mk'.
make[1]: Failed to remake makefile `build/ruler2/files-ag-d-dep.mk'.
make EHC_VARIANT_RULER_SEL=((101=HS)).(expr.base patexpr.base
tyexpr.base decl.base).(e.int e.char e.var e.con e.str p.str) \
  ehc-variant-dflt
src/ruler2/files.mk:34: build/ruler2/files-ag-d-dep.mk: No such file
or directory
src/ruler2/files.mk:35: build/ruler2/files-ag-s-dep.mk: No such file
or directory
mkdir -p build/shuffle ; \
	 --module=CDoc -dr  -Psrc/shuffle/ -o build/shuffle/CDoc.hs src/ 
shuffle/CDoc.ag

/bin/sh: --module=CDoc: command not found
make[2]: Failed to remake makefile `build/ruler2/files-ag-s-dep.mk'.
make[2]: Failed to remake makefile `build/ruler2/files-ag-d-dep.mk'.
make[1]: *** [ehc-variant] Error 2
make: *** [install/101/bin/ehc] Error 2


This is fairly bewildering.  Am I the only one seeing errors like  
this?


This looks like the same error I got – see bug report 1 in the bug  

Re: [Haskell-cafe] ANNOUNCE: Utrecht Haskell Compiler (UHC) -- first release

2009-04-18 Thread Thomas Davie


On 19 Apr 2009, at 00:31, Antoine Latter wrote:

On Sat, Apr 18, 2009 at 4:38 PM, Thomas Davie tom.da...@gmail.com  
wrote:


This looks like the same error I got – see bug report 1 in the bug  
database
– the configure script reports that you have uuagc even if you  
don't – cabal

install it, reconfigure, and you should be on your way.

Second thing to watch for – it depends on fgl, but this isn't  
caught by the

configure script.



Apparently a user install of uuagc and fgl isn't good enough.  Fun  
to know.


I've found user installs don't work at all on OS X, various people in  
#haskell were rather surprised to discover this, so apparently it's  
not the default behavior on other platforms.


It really rather makes cabal install rather odd – because it doesn't  
actually install anything you can use without providing extra options!


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


Re: [Haskell-cafe] ANNOUNCE: Utrecht Haskell Compiler (UHC) -- first release

2009-04-19 Thread Thomas Davie


On 19 Apr 2009, at 09:52, Duncan Coutts wrote:


On Sun, 2009-04-19 at 00:41 +0200, Thomas Davie wrote:


Apparently a user install of uuagc and fgl isn't good enough.  Fun
to know.


I've found user installs don't work at all on OS X, various people in
#haskell were rather surprised to discover this, so apparently it's
not the default behavior on other platforms.


Currently, user installs are the default on all platforms except
Windows.

It really rather makes cabal install rather odd – because it  
doesn't
actually install anything you can use without providing extra  
options!


It should work fine, you'll need to give more details.


This has been the result, at least every time I've installed ghc:

$ cabal install xyz
$ runhaskell Setup.hs configure -- where abc depends on xyz
Configuring abc-0.0...
Setup.lhs: At least the following dependencies are missing:
xyz -any
$ sudo cabal install --global xyz
$ runhaskell Setup.hs configure
Configuring abc-0.0...
$ runhaskell Setup.hs build
...

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


Re: [Haskell-cafe] ANNOUNCE: Utrecht Haskell Compiler (UHC) -- first release

2009-04-19 Thread Thomas Davie


On 19 Apr 2009, at 11:10, Duncan Coutts wrote:


On Sun, 2009-04-19 at 10:02 +0200, Thomas Davie wrote:


It really rather makes cabal install rather odd – because it
doesn't actually install anything you can use without providing  
extra

options!


It should work fine, you'll need to give more details.


This has been the result, at least every time I've installed ghc:

$ cabal install xyz


So this does a per-user install.


$ runhaskell Setup.hs configure -- where abc depends on xyz


This does a global install. Global packages cannot depend on user
packages. You have two choices:

$ cabal configure

because the cabal program does --user installs by default
or use

$ runhaskell Setup.hs configure --user

which explicitly does a --user install.

The reason for this confusion is because the original runghc Setup
interface started with global installs and we can't easily change that
default. On the other hand, per-user installs are much more convenient
so that's the sensible default for the 'cabal' command line program.


I don't understand what makes user installs more convenient.   
Certainly, my preference would be for global all the time – I expect  
something that says it's going to install something to install it  
onto my computer, like any other installation program does.  What is  
it that makes user installs more convenient in this situation?


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


Re: [Haskell-cafe] ANNOUNCE: Utrecht Haskell Compiler (UHC) -- first release

2009-04-19 Thread Thomas Davie


I don't understand what makes user installs more convenient.   
Certainly,
my preference would be for global all the time – I expect something  
that
says it's going to install something to install it onto my  
computer,

like any other installation program does.  What is it that makes user
installs more convenient in this situation?


You don't need 'sudo' access for user installs. This means that 'cabal
install' works out of the box on every system, without needing
admin/root privs (esp. important for students).


But students will be used to needing to configure this – in every  
other installation system out there they need to tell it to install in  
their user directory.  Personally – I find it more convenient to have  
the install program do what it says it does! Install it!


This would save confusion about old tools that do things globally, and  
not confuse students, because they're all already used to giving extra  
flags to make install not install things system wide.


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


Re: [Haskell-cafe] Optimizing unamb by determining the state of a thunk?

2009-04-20 Thread Thomas Davie


On 20 Apr 2009, at 09:41, Peter Verswyvelen wrote:

I was wandering if it would be possible to optimize unamb by  
checking if a value is already evaluated to head normal form.


So

f `unamb` g

would then be extremely fast if either f or g is already evaluated  
to head normal form.


Maybe using some vacuum tricks?

This function would need to be in IO since it is of course not  
referentially transparent.


Really?  Is it any less referentially transparent than unamb already  
is - i.e. it's referentially transparent, as long as the two values  
really are equal.


Although threads are lightweight in Haskell, forking/waiting/killing  
surely must have more overhead than just checking the thunk of an  
expression?


Of course one could also make unamb a primitive :-)


That would be a lovely solution for me.

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


Re: [Haskell-cafe] Optimizing unamb by determining the state of a thunk?

2009-04-20 Thread Thomas Davie


On 20 Apr 2009, at 10:57, Peter Verswyvelen wrote:

On Mon, Apr 20, 2009 at 10:23 AM, Thomas Davie tom.da...@gmail.com  
wrote:
Really?  Is it any less referentially transparent than unamb already  
is - i.e. it's referentially transparent, as long as the two values  
really are equal.


I think it is. Suppose we call the function hnf :: a - Bool. hnf  
might return a different result for the same argument, since the  
evaluation of the argument might be happening on a different thread,  
so the result of hnf depends on the time when it is evaluated.  Or  
am I missing something here?


Sure, so hnf would give us a non-determined result, but I don't think  
that makes unamb any less referentially transparent – the same value  
is always returned, and always reduced at least to hnf.


Bob

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


[Haskell-cafe] Cabal's default install location

2009-04-21 Thread Thomas Davie
There seems to be an assumption amongst the community that a user's  
home directory is the most useful place for cabal to install to by  
default.  A few people have challenged that.  I wanted to find out  
which one most people do actually prefer, so please go and vote on  
this poll.


http://noordering.wordpress.com/2009/04/21/cabals-default-install-location/

It's no more than a straw poll, I don't know how protected it is  
against ballot stuffing, but I'm pretty confident that Haskellers are  
trustworthy enough not to play with it that way.


I'll tell you all the result next week.

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


Re: [Haskell-cafe] Being impure within a 'pure' function

2009-04-22 Thread Thomas Davie


On 22 Apr 2009, at 10:38, Daniel K. wrote:


Hello,

imagine the following situation: You want to implement e.g.  
Dijkstra's algorithm to find a shortest path between nodes u and v  
in a graph. This algorithm relies heavily on mutating arrays, so the  
type signature would look something like


getDistance :: Graph - Node - Node - IO Int

Not mutating the underlying arrays would probably result in poor  
performance. BUT: For a constant graph, the distance between two  
nodes stays the same all the time, so in fact getDistance should be  
a pure function!
So here is my question: Is there a way to write functions in Haskell  
that do some IO internally, but that are guaranteed to be side- 
effect free? Of course one would have to make sure that the array  
that is mutated inside getDistance must not be accessible from  
outside the function.


Is that possible? If not, wouldn't that be desirable? If not, why not?


Either, as Eugene suggested, use the ST monad, as is possible in this  
case (and much better than the solution I'm proposing), or if you  
*really* can't get out of using IO, use unsafePerformIO.  You will  
though have to provide several guarantees yourself that the type  
system would normally provide for you (hence the unsafe part - it  
should really be verifyItsSafeYourselfPerformIO).


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


[Haskell-cafe] Re: Cabal's default install location

2009-04-23 Thread Thomas Davie
[Moved from the UHC thread – lets stop treading on those guys toes,  
they did something very very shiny]


On 23 Apr 2009, at 07:02, Richard O'Keefe wrote:





It's irrelevant, because I _do_ have root access to my machine,


How nice to be you.
Since the argument is entirely about people who _don't_,
your point it?


His point is that that kind of person is not the only kind of person,  
so to base an argument on what they want is as weak as basing an  
argument on what he wants.



It is clear that the only sensible default is no default.


That sounds pretty sensible to me too – much like darcs asks what your  
email address is the first time you work on a repository, cabal should  
probably ask the first time you run it do you prefer global or user  
installs?



I think the right question is how many people prefer user installs
over system installs, wrt. their hackage packages?.


No, because the costs are asymmetric.


I think this is a case of not seeing the costs to the other users  
because you're firmly entrenched in your camp.  I would have said  
originally that the costs are asymmetric too – but that it's a much  
greater cost for the people who expect all installers to do global  
installs.  So I think that the question asked there is a very valid one.


However, I do like the solution of not giving any default.

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


Re: [Haskell-cafe] Re: Cabal's default install location

2009-04-23 Thread Thomas Davie
The results in the poll seem to have stabilised now, so I'll tell you  
what happened...


For user installs: 103
For global installs: 52
Others: 9

Interesting Ideas:

 • Claus made the suggestion that there be no default, instead that  
cabal asks you which you prefer the first time you run, or directs you  
to the configuration file.
 • Many users made the suggestion that cabal should install globally  
when running as root, and for a user when running as a user, possibly  
also displaying a prominent message about what's going on.


Conclusions:
--
Most people do indeed want user installs, but a very much not  
insignificant population want global installs.  Perhaps one of these  
other suggestions is the way forward?


Bob

p.s. I personally very much like Claus' 
idea.___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: Is 78 characters still a good option? Was: [Haskell-cafe] breaking too long lines

2009-04-23 Thread Thomas Davie


On 23 Apr 2009, at 10:02, Matthijs Kooijman wrote:


 Some material I've read on typography -- can't find the
 reference now -- suggests ~65 is the best number of characters
 per line. The advice was, if your page is larger than that,
 you should make columns.
That fits my observations. In particular, I noticed that your emails  
were
particularly comfortable to read, which might also be partly be  
caused by the
extra indent at the start of your lines, which also seems  
comfortable. Not

sure how applicabable all this is to code, though :-)


I think the non-applicable to code observation is very likely true –  
we'd like to be able to write nice descriptive variable names.  In  
doing this, we probably want them to be more than the 1 or 2  
characters that Haskellers traditionally use, maybe of the order of  
5-10.


Given this, it would seem a shame to only be able to fit 6-13  
litterals on a line, that sounds like we'll quickly be having to wrap  
lines with deffinititions of any significance on them.


My personal preference with Haskell is to ignore the 78 character  
limit, but only when layout otherwise becomes horrible otherwise.


Haskell is a very horizontal language, and to limit our horizontal  
space seems pretty weird.


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


Re: Is 78 characters still a good option? Was: [Haskell-cafe] breaking too long lines

2009-04-25 Thread Thomas Davie


On 25 Apr 2009, at 10:51, Daniel Fischer wrote:


Am Samstag 25 April 2009 08:48:16 schrieb Thomas Davie:

On 24 Apr 2009, at 14:37, Loup Vaillant wrote:

2009/4/23 Miguel Mitrofanov miguelim...@yandex.ru:

On 23 Apr 2009, at 12:17, Thomas Davie wrote:

Haskell is a very horizontal language, and to limit our horizontal
space
seems pretty weird.


+1. I sometimes use lines up to 200 characters long, when I feel
they would
be more readable.


200 sounds awfully long. Do you have any example?


Sure...

arrow :: forall (~) b c d e. ( Arrow (~), Show (d ~ e), Show (c ~
d), Show (b ~ c), Show b, Show c, Show d, Show e, Arbitrary (d ~  
e),

Arbitrary (c ~ d), Arbitrary (b ~ c), Arbitrary b, Arbitrary c,
Arbitrary d, Arbitrary e, EqProp (b ~ e), EqProp (b ~ d), EqProp
((b,d) ~ c), EqProp ((b,d) ~ (c,d)), EqProp ((b,e) ~ (d,e)),  
EqProp

((b,d) ~ (c,e)), EqProp b, EqProp c, EqProp d, EqProp e) = b ~
(c,d,e) - TestBatch


.


In all seriousness though, that one got broken, but I do find that I
occasionally have lines around 100 characters that just look silly if
I break them, this is a good example:

filterNonRoots (GCase e bs) = filter ((/= e) ^()^
(not . (`elem` bs)))


Not that I'd deny that it can sometimes be more readable to have  
longer lines*, but in

this example, would

 filterNonRoots (GCase e bs)
 = filter ((/= e) ^()^ (not . (`elem` bs)))

be any less readable in your opinion?


Yes – this particular line is mixed in with several other pattern  
matches, each of which has a similar form, laying it out on one line  
lets you see the similarities and differences, laying it out on two  
lines creates visual noise.


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


Re: Is 78 characters still a good option? Was: [Haskell-cafe] breaking too long lines

2009-04-25 Thread Thomas Davie


On 25 Apr 2009, at 21:09, Jason Dusek wrote:


 There will always be some people who prefer longer lines. The
 real issue is, how do we deal with the fundamental
 disagreement here? It's not like we can have both. Also those
 people who like long lines -- will they all agree to a long
 line length?


Is there a fundamental disagreement here?

There are those who are driven by an archaic standard from the width  
of the terminal screen, and there are those who are driven by the  
aesthetics of their code.  As always, opinions on aesthetics differ  
slightly, but overall, everyone seems to mostly agree that we should  
try to keep lines short where possible, but lengthen then when needed.


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


Re: [Haskell-cafe] applicative challenge

2009-05-05 Thread Thomas Davie


On 4 May 2009, at 23:15, Thomas Hartman wrote:


{-# LANGUAGE NoMonomorphismRestriction #-}
import Data.List
import Control.Monad
import Control.Applicative

-- Can the function below be tweaked to quit on blank input,
provisioned in the applicative style?
-- which function(s) needs to be rewritten to make it so?
-- Can you tell/guess which function(s) is the problem just by looking
at the code below?
-- If so, can you explain what the strategy for doing so is?
notQuiteRight = takeWhile (not . blank) $ ( sequence . repeat $  
echo )


echo = do
 l - getLine
 putStrLn l
 return l


-- this seems to work... is there a way to make it work Applicatively,
with lifted takeWhile?
seemsToWork = sequenceWhile_ (not . blank) (repeat echo)

sequenceWhile_ p [] = return ()
sequenceWhile_ p (mx:mxs) = do
 x - mx
 if p x
   then do sequenceWhile_ p mxs
   else return ()


Conor's already give you a comprehensive explanation of why  
Applicative can't be used to do this, but that doesn't mean you can't  
use applicative style!


How about...

echo = unlines . takeWhile (not . blank) . lines

seemsToWork = interact echo

Bob

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


Re: [Haskell-cafe] How to understand the fmap here ?

2009-05-05 Thread Thomas Davie


On 5 May 2009, at 11:27, z_axis wrote:


The following code snippets is from xmonad:
-- Given a window, find the screen it is located on, and compute
-- the geometry of that window wrt. that screen.
floatLocation :: Window - X (ScreenId, W.RationalRect)
--...
rr - snd `fmap` floatLocation w

Prelude :i fmap
class Functor f where fmap :: (a - b) - f a - f b

It seems it is different from the definition of fmap ?
sincerely!


As the type signature of fmap explains, it transforms a function.   
Specifically, it starts with a function (a - b), and it transforms it  
to accept an 'a' inside a functor instead of just an a, and return a  
'b' inside the same functor instead of just a b.  In other words, fmap  
applies functions inside containers.


We can see from floatLocation that it returns a pair inside a  
container - specifically, an X container.  Fmap takes snd, and  
transforms it to work on values inside the X.


So, snd has type (a,b) - b, thus fmap snd has type f (a,b) - f b.   
In this case, the type it's being applied to is X (ScreenId,  
W.RationalRect), so f unifies with X, a with ScreenID and b with  
W.RationalRect.  Making snd `fmap` floatLocation w hav the type X  
W.RationalRect.


Finally, the bind into rr there takes it out of the X monad all  
together, getting you a W.RationalRect.


You may want to read this article which explains some of Haskell's  
abstraciton mechanisms:


http://noordering.wordpress.com/2009/03/31/how-you-shouldnt-use-monad/

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


  1   2   3   >