
module Main where
import Data.List
-- quicksort of any list
qsort [] = []
qsort (x:xs) = qsort(filter(

leledumbo wrote:
module Main where
import Data.List
-- quicksort of any list qsort [] = [] qsort (x:xs) = qsort(filter(
=x) xs) -- optimized quicksort, uses middle element as pivot qsortOpt [] = [] qsortOpt x = qsortOpt less ++ [pivot] ++ qsortOpt greater where pivot = x !! ((length x) `div` 2) less = filter (
=pivot) (delete pivot x) main = do putStr "Enter a list: " l <- readLn print (qsortOpt l) -- end of code
Why do I get
ERROR "qsort.hs":17 - Unresolved top-level overloading *** Binding : main *** Outstanding context : (Read b, Show b, Ord b)
The compiler doesn't know what kind of list you are trying to read, sort, and print. Try something like: (l::[Int]) <- readLn in the penultimate line. -- Dr. Janis Voigtlaender http://wwwtcs.inf.tu-dresden.de/~voigt/ mailto:voigt@tcs.inf.tu-dresden.de

On Wed, Oct 15, 2008 at 5:44 PM, leledumbo
module Main where
import Data.List
-- quicksort of any list qsort [] = [] qsort (x:xs) = qsort(filter(
=x) xs) -- optimized quicksort, uses middle element as pivot qsortOpt [] = [] qsortOpt x = qsortOpt less ++ [pivot] ++ qsortOpt greater where pivot = x !! ((length x) `div` 2) less = filter (
=pivot) (delete pivot x) main = do putStr "Enter a list: " l <- readLn print (qsortOpt l) -- end of code
I'm curious as to why taking the pivot from the middle is an 'optimized' version. For this to be true you must be making some assumptions about the contents of the list.

Google "median order statistic". E.g. this is an interesting (and colorful) discussion: http://ocw.mit.edu/NR/rdonlyres/Electrical-Engineering-and-Computer-Science/... Toby Hutton wrote:
On Wed, Oct 15, 2008 at 5:44 PM, leledumbo
wrote: module Main where
import Data.List
-- quicksort of any list qsort [] = [] qsort (x:xs) = qsort(filter(
=x) xs) -- optimized quicksort, uses middle element as pivot qsortOpt [] = [] qsortOpt x = qsortOpt less ++ [pivot] ++ qsortOpt greater where pivot = x !! ((length x) `div` 2) less = filter (
=pivot) (delete pivot x) main = do putStr "Enter a list: " l <- readLn print (qsortOpt l) -- end of code
I'm curious as to why taking the pivot from the middle is an 'optimized' version. For this to be true you must be making some assumptions about the contents of the list. _______________________________________________ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe

On Thu, Oct 16, 2008 at 9:01 AM, Dan Weston
Google "median order statistic".
E.g. this is an interesting (and colorful) discussion:
http://ocw.mit.edu/NR/rdonlyres/Electrical-Engineering-and-Computer-Science/...
Hrmm, maths and statistics definitely aren't a strong area for me, but doesn't that PDF say on the second page that choosing i = 0 or i = n or i = median is equally naive? The rest of the document describes other interesting methods for getting the pivot. I couldn't follow the Wikipedia page on order statistics though. Still, with no assumptions as to the contents of a list whatsoever, when choosing 1 element to be the pivot, intuitively it makes no difference which one you choose. (Then again, I find statistical analysis rarely is intuitive.)

The compiler doesn't know what kind of list you are trying to read, sort, and print.
So, the type must be specific? Then why it's possible to call the sorting function with any list?
I'm curious as to why taking the pivot from the middle is an 'optimized' version.
Consider if it's used in a GUI program which calls the function when a button is pressed. Often, users clicks the button more than once. If the pivot is the first (or last) element, the second (and further) click will cause worst case scenario to happen. OTOH, if the pivot is the middle element, best case scenario will happen. -- View this message in context: http://www.nabble.com/List-as-input-tp19987726p20007078.html Sent from the Haskell - Haskell-Cafe mailing list archive at Nabble.com.

On 2008 Oct 16, at 0:53, leledumbo wrote:
The compiler doesn't know what kind of list you are trying to read, sort, and print.
So, the type must be specific? Then why it's possible to call the sorting function with any list?
A function may have a polymorphic type; this allows its actual type to be set by context. A *program* must have fully determined types, which includes polymorphic functions whose calls provide enough context to determine the actual type at the call site. If there isn't enough information to set a concrete type at the call, type inference fails. This is what you get with strong typing. -- brandon s. allbery [solaris,freebsd,perl,pugs,haskell] allbery@kf8nh.com system administrator [openafs,heimdal,too many hats] allbery@ece.cmu.edu electrical and computer engineering, carnegie mellon university KF8NH

On Wed, Oct 15, 2008 at 9:53 PM, leledumbo
The compiler doesn't know what kind of list you are trying to read, sort, and print.
So, the type must be specific? Then why it's possible to call the sorting function with any list?
It isn't. The type of data in the list must be able to be compared. See the type signature for Data.List.sort Data.List.sort :: (Ord a) => [a] -> [a] So "any" list may be sorted if the items in the list are of Ord.
I'm curious as to why taking the pivot from the middle is an 'optimized' version.
Consider if it's used in a GUI program which calls the function when a button is pressed. Often, users clicks the button more than once. If the pivot is the first (or last) element, the second (and further) click will cause worst case scenario to happen. OTOH, if the pivot is the middle element, best case scenario will happen.
-- View this message in context: http://www.nabble.com/List-as-input-tp19987726p20007078.html Sent from the Haskell - Haskell-Cafe mailing list archive at Nabble.com.
_______________________________________________ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe

... If there isn't enough information to set a concrete type at the call, type inference fails. This is what you get with strong typing.
In my case, where does type inference fail? Strong typing is good, but quite confusing when combined with polymorphism.
It isn't. The type of data in the list must be able to be compared.
Oops, sorry. What I mean by "any" is exactly as what you said: "anything than can be compared". Can you tell me an example of list whose elements can't be compared (don't include user defined types, please) ? -- View this message in context: http://www.nabble.com/List-as-input-tp19987726p20026066.html Sent from the Haskell - Haskell-Cafe mailing list archive at Nabble.com.

On Thu, Oct 16, 2008 at 7:22 PM, leledumbo
... If there isn't enough information to set a concrete type at the call, type inference fails. This is what you get with strong typing.
In my case, where does type inference fail? Strong typing is good, but quite confusing when combined with polymorphism.
It isn't. The type of data in the list must be able to be compared.
Oops, sorry. What I mean by "any" is exactly as what you said: "anything than can be compared". Can you tell me an example of list whose elements can't be compared (don't include user defined types, please) ?
How about a list of functions from int to int? Jason

How about a list of functions from int to int?
Hmm... it does make sense. -- View this message in context: http://www.nabble.com/List-as-input-tp19987726p20026222.html Sent from the Haskell - Haskell-Cafe mailing list archive at Nabble.com.

On 2008 Oct 16, at 22:22, leledumbo wrote:
... If there isn't enough information to set a concrete type at the call, type inference fails. This is what you get with strong typing.
In my case, where does type inference fail? Strong typing is good, but quite confusing when combined with polymorphism.
Consider the types of "show" and "read": show :: Show a => a -> String -- you could use any variable names but read :: Read b => String -> b -- I'm doing it this way to make a point and therefore the type of (read . show) is (read . show) :: (Show a, Read b) => a -> b -- a cannot be unified with b! It has no clue that (read . show) are effectively inverses, nor can it; you can't describe that with Show and Read. It would be possible to combine the Show and Read classes into a single class which allowed this to work. What you lose is flexibility: it is possible to define Show for types which cannot be read. Consider, for example, functions: the Typeable class can be used to show a function in terms of its types (as long as it isn't polymorphic), but that's useless to read back in. And outputting a function such that it could be read back in would require either disassembler+assembler or a virtual machine runtime like the JVM or .NET/Mono. -- brandon s. allbery [solaris,freebsd,perl,pugs,haskell] allbery@kf8nh.com system administrator [openafs,heimdal,too many hats] allbery@ece.cmu.edu electrical and computer engineering, carnegie mellon university KF8NH

So, what's the solution? This one: (l::[Ord]) <- readLn doesn't work (because Ord isn't a type constructor). It doesn't even comply to Haskell 98 standard. I want to be able to read any list of ordered elements. -- View this message in context: http://www.nabble.com/List-as-input-tp19987726p20033244.html Sent from the Haskell - Haskell-Cafe mailing list archive at Nabble.com.

On Fri, Oct 17, 2008 at 7:21 AM, leledumbo
So, what's the solution? This one:
(l::[Ord]) <- readLn
doesn't work (because Ord isn't a type constructor). It doesn't even comply to Haskell 98 standard. I want to be able to read any list of ordered elements.
What you're after is not possible that easily. What you want to do is to read a bunch of elements, and based on what you read in, determine their type. This is contrary to static typing. A number of ways are possible, but they all involve some sort of enumeration of all the possible types to read in. Way #1: make a data type which represents any of the types of things you can accept, and define Ordering on it. data Thing = ThingInt Int | ThingString String | ThingList [Thing] | ... deriving Ord And then define a parser to get from a string to a Thing (pretty easy using ReadP or Parsec or something). Note that this would accept a heterogeneous list like 1, "foo", 2, [3,"bar",4], and it would sort it as 1, 2, "foo", [3,"bar",4], because of the way Ord deriving works (all Ints are less than all Strings are less than all Lists ...). You can customize this by not using "deriving", and instead manually declaring the instance. Way #2: use the parser from way #1 to parse the first one and determine what kind of thing you're reading, and then read a bunch of those. sortThings :: (Read a) => IO [a] main = do first <- getLine case first of ThingInt _ -> print =<< (sortThings :: IO [Int]) ThingString _ -> print =<< (sortThings :: IO [String]) ... There are some other more clever ways. But you will not be able to get Haskell to make the choice for you. In particular, there are some ambiguous choices, for example is read "42" an Int, an Integer, a Double ? So you need to write an algorithm which resolves the ambiguities. Luke

On Fri, Oct 17, 2008 at 2:21 PM, leledumbo
So, what's the solution? This one:
(l::[Ord]) <- readLn
doesn't work (because Ord isn't a type constructor). It doesn't even comply to Haskell 98 standard. I want to be able to read any list of ordered elements.
I hope to be enlightened, but I'm pretty sure this is not possible. Your readLn has to present a list of some specific type which can be inferred at compile time. Which type is it? String? Int? Something else? Also, neither Show nor Read relate to Ord, so you cannot ever be sure that all Readable/Showable types are Ordered, or that all Ordered types can be Read/Shown. D

I can't think of a language that lets you do this; that is, allow you to input a list of any type as text. Some languages effectively encode the types in the parsing, for example in LISP, you know that 'foo is a symbol. It has a very limited set of data types and new types are described entirely in terms of those simple types, which makes parsing simple. But lets say you have
data Color = Red | Green | Blue deriving (Read,Show,Eq,Ord)
Now you suddenly expect "readLn" to detect the word "Green" and
interpret it differently from "1.0", restricting the type at runtime?
Do you realize how difficult this is?
What if Green is also used in a type in another module?
You need to specify the type to read, or provide a parser that works
for every type you care about.
-- ryan
On Fri, Oct 17, 2008 at 2:21 PM, leledumbo
So, what's the solution? This one:
(l::[Ord]) <- readLn
doesn't work (because Ord isn't a type constructor). It doesn't even comply to Haskell 98 standard. I want to be able to read any list of ordered elements. -- View this message in context: http://www.nabble.com/List-as-input-tp19987726p20033244.html Sent from the Haskell - Haskell-Cafe mailing list archive at Nabble.com.
_______________________________________________ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe

On Fri, Oct 17, 2008 at 6:21 AM, leledumbo
So, what's the solution? This one:
(l::[Ord]) <- readLn
doesn't work (because Ord isn't a type constructor). It doesn't even comply to Haskell 98 standard. I want to be able to read any list of ordered elements.
The problem is one of decoding data from a data source. This is usually handled with parsers. Neither static nor dynamic typing could really save you here, unless the file is written out in a format that could be automatically parsed by the input. (like S-expressions perhaps for a lisp read call...) If it was as easy as your code would like it to be, people wouldn't have bothered with things like XDR, XML, ASN.1 (BER) etc. They'd just send binary data everywhere. How can you tell a 32bit value from four 8 bit bytes for instance? You must parse I think.
-- View this message in context: http://www.nabble.com/List-as-input-tp19987726p20033244.html Sent from the Haskell - Haskell-Cafe mailing list archive at Nabble.com.
_______________________________________________ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe
participants (10)
-
Brandon S. Allbery KF8NH
-
Dan Weston
-
David Leimbach
-
Dougal Stanton
-
Janis Voigtlaender
-
Jason Dagit
-
leledumbo
-
Luke Palmer
-
Ryan Ingram
-
Toby Hutton