Re: [Haskell-cafe] Why were unfailable patterns removed and fail added to Monad?

2012-01-26 Thread Scott Turner

On 2012-01-24 05:32, Michael Snoyman wrote:

On Fri, Jan 20, 2012 at 6:52 AM, Michael Snoymanmich...@snoyman.com  wrote:

provide an extra warning flag (turned on by -Wall) that will

 warn when you match on a failable pattern.


I've filed a feature request for this warning:
http://hackage.haskell.org/trac/ghc/ticket/5813


Thanks!  I wish the compiler could tell the difference between monads 
that handle failure nicely (e.g. List) and those that throw a runtime 
error (e.g. IO).


Something's wrong -- I'm feeling nostalgic for MonadZero.

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


Re: [Haskell-cafe] Why were unfailable patterns removed and fail added to Monad?

2012-01-20 Thread Scott Turner

On 2012-01-19 23:52, Michael Snoyman wrote:

maybe I should file a feature request: provide an extra warning
flag (turned on by -Wall) that will warn when you match on a failable
pattern.


I fully agree if it's IO, so that a failed pattern match leads to an 
exception.  The nice implementations of fail in the List and Maybe 
monads are a different story.


Ideally one would want to be able to turn on a warning whenever IO is 
used in a way which could generate a pattern match exception.  This 
would call for a type distinction, as you said, reinstate the MonadZero 
constraint.


Here's an idea that might address SPJ's killer.
  b) if you add an extra constructor to a single-constructor
 type then pattern matches on the original constructor
 suddenly become failable

Another binding operator might be introduced so that the code would show 
the intention either to have a failable or non-failable pattern match.

 do (x,y) - pair   failable, requires MonadZero
 do (x,y) =- pair  requires non-failable pattern
supports Monads that should not fail

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


Re: [Haskell-cafe] On the purity of Haskell

2011-12-30 Thread Scott Turner
On 2011-12-30 14:32, Steve Horne wrote:
 A possible way to implement a Haskell program would be...
 
  1. Apply rewrite rules to evaluate everything possible without
 executing primitive IO actions.
  2. Wait until you need to run the program.
  3. Continue applying rewrite rules to evaluate everything possible, but
 this time executing primitive IO actions (and substituting run-time
 inputs into the model) as and when necessary so that the rewriting
 can eliminate them.

This is inadequate, because it is does not specify when the program's
various IO actions are executed, or even which of them are executed. Try
print first `seq` print second
or
let x = print x in print value
Also, evaluate everything possible is strangely hard to match up with
the concepts involved in Haskell's non-strict evaluation.

An accurate description of how an IO expression is executed would be:

Evaluate the expression. There are three possible results.
1. If it is a 'return' operation, the result is the operand.
2. If it is a bind (=) operation,
   a. Execute the left operand, obtaining a result expression.
   b. The right operand is a function. Apply it to the returned
  expression, obtaining an IO expression.
   c. Execute the IO expression.
3. If it is a primitive, execute it, obtaining an expression.

A Haskell program is an IO expression, and is executed as above. Notice
that when a program is executed, its IO actions are not performed as a
result of being evaluated. Rather, they are evaluated (down to values)
in order to be performed. Every evaluation in the above procedure is
pure, with no IO effects.

The concept of AST is no more helpful in explaining IO than it is in
explaining
foldr (*) 1 [1..5]
IMO it's no help at all.

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


Re: [Haskell-cafe] On the purity of Haskell

2011-12-29 Thread Scott Turner
On 2011-12-29 15:23, Gregg Reynolds wrote:
 On Dec 29, 2011, at 1:21 PM, Heinrich Apfelmus wrote:
 
 Why would  IO Int  be something special or mysterious?
 
 I'm pretty sure IO is non-deterministic, non-computable, etc.  In other words 
 not the same as computation.
 
 It's an ordinary value like everything else; it's on the same footing as 
 [Char], Maybe Int, Int - String, Bool, and so on. I see no difference 
 between the list  [1,2,3] :: [Int]  and the action  pick a random number 
 between 1 and 6 :: IO Int  .
 
 We'll have to agree to disagree - I see a fundamental difference.

You're misunderstanding the location of disagreement. We all know very
well how IO Int is special.

The example pick a random number between 1 and 6 was unfortunate. I hope
fmap read getLine :: IO Int
serves better.  The Haskell community says this expression indicates a
value.  To be clear,
fmap read getline
has the same value wherever it is written in a program or however many
times it is called, or however many different Int values it produces.
This definition of 'value' is at the heart of how we understand Haskell
to be referentially transparent and pure.

You can disagree, but if you hold that this expression does not have a
value until at execution time it produces an Int, then your
unconventional terminology will lead to confusion.

So what is the benefit of using Haskell?  Isn't
fmap read getline
just as problematic as the C function
gets()
regardless of whether you call it pure?  In Haskell, the type of
fmap read getline
prevents it from being used in arbitrary parts of the program, so the
programmer or compiler can use the type to know whether a function is
performing I/O or other effects.

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


Re: [Haskell-cafe] On the purity of Haskell

2011-12-29 Thread Scott Turner
On 2011-12-29 19:44, Steve Horne wrote:
 [Interaction with its environment] is as much an aspect of what
 Haskell defines as the functional core.
 
 Switching mental models doesn't change the logic
But it does. Other languages do not support the distinction between pure
functions and I/O effects. In those languages a function call is what
triggers I/O.

Haskell uses a different set of types for I/O. It does not use functions
for this. The distinction between pure functions and impure code,
supported by the language, is a valuable logical tool.

You refer to the fact that as part of executing the Haskell program, it
is translated into an AST that does not make that distinction. The
effect getAnIntFromTheUser is translated into a function. The type of
the function says nothing about whether the function has an effect. In
that sense Haskell is impure, but so what? That doesn't take away the
power of Haskell's distinction between pure functions and impure types,
for reasoning about Haskell code.

 Either way, at run-time, Haskell is impure.
No big deal. Who would want to use a language that you would call
pure? Haskell has referential transparency. In Haskell, you have
assurance that any function without IO in its type is as pure as the
lambda calculus.

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


Re: [Haskell-cafe] If you'd design a Haskell-like language, what would you do different?

2011-12-23 Thread Scott Turner
On 2011-12-23 13:46, Conor McBride wrote:

 The plan is to make a clearer distinction between being and doing by
 splitting types clearly into an effect part and a value part, in a sort
 of a Levy-style call-by-push-value way. The notation

 [list of effects]value type

 is a computation type whose inhabitants might *do* some of the
 effects in
 order to produce a value which *is* of the given value type.
 
 The list of effects is arbitrary, and localizable, by means of defining
 handlers.
 So it's not a single monad.
 
 It's probably still disappointing.

On the contrary!

 Haskell doesn't draw a clear line in types between the effect part
 and the value part, or support easy fluidity of shifting roles
 between the two. Rather we have two modes: (1) the
 implicit partiality mode, where the value part is the whole of
 the type and the notation is applicative;
 (2) the explicit side-effect mode, where the type is an
 effect operator applied to the value type and the notation
 is imperative.

I was drawn to call-by-push-value a few years ago while attempting to
create a language which would support both call-by-value and
call-by-name.  I haven't had the skill to express what I have felt to be
the shortcoming of Haskell, but I believe you've put your finger right
on it.

 it's an attempt to re-rationalise techniques that emerged
 from Haskell programming.
Exactly.

Haskell has grown a wealth of features/libraries/techniques for
combining monads, yet the fundamental monad, evaluation, has a separate
place in the language.

-- Scott Turner

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


Re: [Haskell-cafe] Is it possible to represent such polymorphism?

2011-10-02 Thread Scott Turner
On 2011-10-02 14:15, Du Xi wrote:
 I guess this is what I want, thank you all. Although I still wonder why
 something so simple in C++ is actually more verbose and requires less
 known features in Haskell...What was the design intent to disallow
 simple overloading?

Simple overloading is known as ad-hoc polymorphism, while Haskell's
type system is based on parametric polymorphism.  As Wikipedia says,
Parametric polymorphism is a way to make a language more expressive,
while still maintaining full static type-safety.

For example, functional programming gets a lot of power out of passing
functions as arguments. Compare what this gives you in C++ versus
Haskell.  In C++ an overloaded function has multiple types, and when a
function appears as an argument one of those types is selected.  In
Haskell, a polymorphic function can be passed as an argument, and it
still can be used polymorphically within the function that receives it.

When each name in the program has just one type, as in Haskell, type
inference can be much more effective. Type declarations are not
required. Most of the type declarations in my own Haskell code are there
either for documentation, or to ensure that the compiler will catch type
errors within a function definition.

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


Re: [Haskell-cafe] What is a simple pattern binding?

2011-06-25 Thread Scott Turner
On 2011-06-25 10:52, David Mazieres wrote:
 Further confusing things, GHC accepts the following:
 
   g1 x y z = if xy then show x ++ show z else g2 y x
 
   g2 :: (Show a, Ord a) = a - a - String
   g2 | False = \p q - g1 q p ()
  | otherwise = \p q - g1 q p 'a'
where x = True
 
 
 and infers type:
 
   g1 :: (Show a, Show a1, Ord a1) = a1 - a1 - a - [Char]
 
 According to 4.4.3.2, g2 definitely does not have a simple pattern
 binding, as its binding is not of the form p = e where p is a pattern.
 Yet by section 4.5.5, if g2 were not considered a simple pattern
 binding, the constrained type variables in the binding group
 containing g1 and g2 (in particular the inferred type (Show a = a) of
 z in g1) would not be allowed to be generalized.

It appears to me that GHC is justified. According to 4.5.1 and 4.5.2, g1
by itself constitutes a declaration group. It is considered by itself
and is generalized prior to combining it with g2.

I agree that the report is confusing in its use of simple pattern binding.

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


Re: [Haskell-cafe] Robert Harper on monads and laziness

2011-05-02 Thread Scott Turner
On 2011-05-02 03:54, Ketil Malde wrote:
   There is a particular reason why monads had to arise in Haskell,
though, which is to defeat the scourge of laziness.
 
 I wonder if there are any other rationale for a statement like that?

He spends one paragraph dismissing the usefulness of referential
transparency

   You cannot easily convert between functional and monadic
style without a radical restructuring of code.  ... you
are deprived of the useful concept of a benign effect

I imagine that he considered how he prefers ML the way it is, without
base libraries thoroughly rewritten to support purity. If purity and RT
aren't the reason why Haskell uses monads, what's left?  Laziness does
have disadvantages.

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


Re: [Haskell-cafe] Asynchronous Arrows need Type Specialization - Help!

2011-04-01 Thread Scott Turner
On 2011-03-21 01:18, David Barbour wrote:
 I was giving Control.Arrow a try for a reactive programming system.
 The arrows are agents that communicate by sending and returning
 time-varying state. Different agents may live in different 'vats'
 (event-driven threads) to roughly model distributed computing. For the
 most part, the state varies asynchronously - i.e. a file updates at a
 different rate than the mouse position. Anyhow, I ran into a problem:
 The (***) and () operations, as specified in Control.Arrow, are
 inherently synchronization points.

Hughes's remark in his original paper may be relevant:
In a deep sense, then, the Either type behaves more like a product than
the pair type does, when we work with stream processors.  And indeed, a
channel carrying a sum type corresponds much more closely to a pair of
channels than does a channel carrying pairs.

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


Re: [Haskell-cafe] Byte Histogram

2011-02-15 Thread Scott Turner
On 2011-02-11 02:06, wren ng thornton wrote:
 And it is clear
 that pointed and unpointed versions are different types[1]. 
...
 [1] Though conversion between them is easy. From unpointed to pointed is
 just a forgetful functor; from pointed to unpointed is the monad of
 evaluation.

I'm unskilled with categories.  For the monad of evaluation, don't the
category's objects need to be strict types?

There was an old thread in which Luke Palmer looked at an implementation
of (=) that uses seq to evaluate the left operand. He showed that it's
not a monad.

It would be nice to use a language with rich monads like Haskell, but
with an evaluation monad that fits together with a variety of monad
transformers.  I think this requires strict types. Adding them to
Haskell may not be achievable.

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


Re: [Haskell-cafe] How to generalize executing a series of commands, based on a list?

2010-11-18 Thread Scott Turner
On 2010-11-17 21:03, Peter Schmitz wrote:
 I am wondering how to generalize this to do likewise for a
 series of commands, where the varying args (filenames, in this
 case) are in a list ('inOutLeafs').

The 'sequence' function is handy for combining a series of actions, such
as [system cmd1, system cmd2, ...].

 I will also want to accumulate some results; probably just a
 failure count at this time.

'sequence' hangs on to the results. That may be what you need. For
control over accumulating results the good stuff is in Data.Foldable.

 Any advice or pointers to examples would be much appreciated.
 
 Thanks in advance,
 -- Peter
 
 
 run :: ... - IO (Int)-- will return a fail count
 run
-- some args to this function here...
= do
   -- ... set up: inputLeafs, outputLeafs, etc.

   -- zip two lists of filenames:
   let inOutLeafs = zip inputLeafs outputLeafs

   -- the first pair for the first command:
   let (inFile1,outFile1) = head inOutLeafs

   -- build 1st command using 1st pair of filenames:
   let cmd1 = ...

   exitCode - system cmd1
   case (exitCode) of
  ExitSuccess - do
 putStrLn $ -- OK.
 return 0
  ExitFailure failCnt - do
 putStrLn $ -- Failed:  ++ show failCnt
 return 1
 ___
 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: how to user mergeIO

2010-03-14 Thread Scott Turner
The essence of mergeIO is to merge the _lists_ that are produced by 
independent threads.  As far as Haskell is concerned, the elements in the list 
are another matter, as is the evaluation of those elements.

So the merge functions force the evaluation of their arguments to a certain 
extent. It's up to the program to determine how much more is done in the 
thread.  Your program can be modified to have the effect you wish by defining 
the two lists so that evaluating each list forces the evaluation of its 
element.

[res0, res1] - mergeIO [sum0] [sum1]
---
sum0s = sum0 `seq` [sum0]
sum1s = sum1 `seq` [sum1]
[res0, res1] - mergeIO sum0s sum1s


On Sunday 14 March 2010 19:26:02 Brock Peabody wrote:
 OK, I think I figured it out. If I understand correctly, I was just
 computing the input lists in parallel. The actual values were computed in
 the main thread lazily, later. This seems unintuitive to me. Shouldn't the
 merge functions force the evaluation of their arguments? Surely one
  wouldn't be calling them if they wanted to compute the results lazily.
 
 On Sun, Mar 14, 2010 at 6:25 PM, Brock Peabody 
brock.peab...@gmail.comwrote:
  Hi,
  I've been trying to use Control.Concurrent.mergeIO to parallelize
  computation, and can't make it work.  In the sample program below, I
  expect the function 'parallelTest' to be almost twice as fast as
  'sequentialTest', and to compute its results in two threads, as implied
  by the documentation for mergeIO.  This is not what happens.  If I link
  my program with the option '-threaded', the running process does have
  three threads.  If I run with the option +RTS -N2, the process will
  have 5 threads.  In no case does the process appear to be using more than
  one CPU, and in fact it is slower with the threading options turned on.
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] How can i set the seed random number generator ?

2009-12-22 Thread Scott Turner
On Monday 21 December 2009 20:37:30 zaxis wrote:
 In erlang, first i use the following function to set the seed:
 new_seed() -
 {_,_,X} = erlang:now(),
 {H,M,S} = time(),
 H1 = H * X rem 32767,
 M1 = M * X rem 32767,
 S1 = S * X rem 32767,
 put(random_seed, {H1,M1,S1}).
 
 then use random:uniform/1 to get the random number.
 
 In haskell, i just use the following function to get the random number. It
 seems i donot need to set the seed of random number generator manually?
 
 rollDice ::  Int - IO Int
 rollDice n = randomRIO(1,n)

That's correct.   randomRIO uses the global random number generator which is 
automatically initialized with a different seed each time your program starts 
up.
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Monadic Floating Point [was: Linking and unsafePerformIO]

2008-10-16 Thread Scott Turner
On 2008 October 16 Thursday, Duncan Coutts wrote:
 On Thu, 2008-10-16 at 01:24 +0200, Ariel J. Birnbaum wrote:
  Floating point operations, at least by IEEE754, depend on environmental
  settings like the current rounding mode. They may modify state, like the
  sticky bits that indicate an exception occurred.

 It is an interesting question: can IEEE floating point be done purely
 while preserving the essential features.

The trouble is that the best numerical algorithms have been written using the 
imperative-style IEEE operations for more than 20 years.  If Haskell had a 
floating point monad, then those algorithms could be coded in Haskell. But 
that doesn't seem like an interesting and fruitful approach. Haskell can 
access those algorithms using FFI. 

The test of making IEEE floating point accessible in pure Haskell code is 
whether it stirs any interest in the numerical analysis community.
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] please help me to find errors from my first app

2008-08-09 Thread Scott Turner
On 2008 August 08 Friday, Changying Li wrote:
 I want to write a reverse proxy like perlbal to practive haskell. Now I
 just write a very simple script to forward any request to
 www.google.com.

 but it dosn't work. I run command ' runhaskell Proxy.hs'  and 'wget
 http://localhost:8080/'. but wget just wait forever and runhaskkell can
 get request. when I break wget, the 'runhaskell' can print response
 returned from www.google.com.

The problem is with
   request - hGetContents hRequest
which blocks until wget closes the connection.  Using lazy bytestrings just 
defers the problem slightly. Your processRequest blocks when the 'request' 
string is used.

For some insight into how this can be avoided, see hGetBufNonBlocking.  I'm 
not familiar enough with the Haskell libraries to point you to the ideal 
solution.
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Higher order types via the Curry-Howard correspondence

2007-05-15 Thread Scott Turner
On 2007 May 13 Sunday 14:52, Benja Fallenstein wrote:
 2007/5/12, Derek Elkins [EMAIL PROTECTED]:
  In Haskell codata and data coincide, but if you want consistency, that
  cannot be the case.

 For fun and to see what you have to avoid, here's the proof of Curry's
 paradox, using weird infinite data types. 

I've had some fun with it, but need to be led by the nose to know what to 
avoid. Which line or lines of the below Haskell code go beyond what can be 
done in a language with just data? And which line or lines violate what can 
be done with codata?

 We'll construct an 
 expression that inhabits any type a. (Of course, you could just write
 (let x=x in x). If you want consistency, you have to outlaw that one,
 too. :-))

 I'll follow the proof on Wikipedia:
 http://en.wikipedia.org/wiki/Curry's_paradox

 data Curry a = Curry { unCurry :: Curry a - a }

 id :: Curry a - Curry a

 f :: Curry a - (Curry a - a)
 f = unCurry . id

 g :: Curry a - a
 g x = f x x

 c :: Curry a
 c = Curry g

 paradox :: a
 paradox = g c
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] IO is not a monad

2007-01-25 Thread Scott Turner
On 2007 January 23 Tuesday 17:33, Yitzchak Gale wrote:
 1. Find a way to model strictness/laziness properties of Haskell functions 
in a category in a way that is reasonably rich.
 2. Map monads in that category to Haskell, and see what we get.
 3. Compare that to the traditional concept of a monad in Haskell.

 Is this possible? Any more ideas how to proceed?

Paul B. Levy's studies of call-by-push-value model strictness/laziness using 
a category theoretic approach.

He considers evaluation as an effect, such that if you brought it into Haskell 
you would expect evaluation to take the form of a monad transformer.

There would be difficulty, though, in the same areas which have been discussed 
in this thread, because his morphisms are functions on something distinct 
from Haskell values. The corresponding monads could return data in WHNF and 
thunks of functions, but not functions themselves.
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Re: iterative algorithms: how to do it in Haskell?

2006-08-21 Thread Scott Turner
On 2006 August 21 Monday 04:42, Gene A wrote:
 but can you have
 a list of type [Num] ?? I thought that it had to be the base types of
 Int, Integer, Float, Double  etc..  No?

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


Re: [Haskell-cafe] Newbie: Haskell Sine Oddities

2006-04-29 Thread Scott Turner

Aditya Siram wrote:
 Prelude sin pi
 1.22460635382238e-16  --WRONG!

Neil Mitchell wrote:
 Floating point numbers are not exact, the value of pi is not exact
 either, and I guess that between them they are giving you errors.

Yes. Actually, this particular inexactness is entirely due to the value of pi. The calculation of sin pi is being performed using the Double data type, which cannot represent pi exactly. Since Double uses binary fractions, doing
   Hugs.Base pi
   3.14159265358979
shows a decimal approximation to the binary approximation.  To investigate the representation  of pi, subtract from it a number which _can_ be represented easily and exactly as a binary fraction, as follows:
   Hugs.Base pi-3.140625
   0.000967653589793116
This shows that pi is represented using an approximation that is close to
   3.141592653589793116
This value, the computer's pi, differs from true pi by
   0.000122...
so the sin function is working perfectly.

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


Re: [Haskell-cafe] request for code review

2006-03-05 Thread Scott Turner
On 2006 March 05 Sunday 05:43, Shannon -jj Behrens wrote:
 classifyString s        = Token (whichType s) s
   where whichType volatile = Qualifier
         whichType void     = Type
         whichType char     = Type
         whichType signed   = Type
         whichType unsigned = Type
         whichType short    = Type
         whichType int      = Type
         whichType long     = Type
         whichType float    = Type
         whichType double   = Type
         whichType struct   = Type
         whichType union    = Type
         whichType enum     = Type
         whichType _          = Identifier

whichType doesn't need to be a function.

classifyString s= Token whichType s
  where whichType = case s of
volatile - Qualifier
void - Type
char - Type
signed   - Type
unsigned - Type
short- Type
int  - Type
long - Type
float- Type
double   - Type
struct   - Type
union- Type
enum - Type
_  - Identifier
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Network parsing and parsec

2005-09-17 Thread Scott Turner
On 2005 September 15 Thursday 12:09, John Goerzen wrote:
 However, the difficulty I come up time and again is: parsec normally
 expects to parse as much as possible at once.

 With networking, you must be careful not to attempt to read more data
 than the server hands back, or else you'll block.

 I've had some success with hGetContents on a socket and feeding it into
 extremely carefully-crafted parsers, but that is error-prone and ugly.

 Here's the problem.  With a protocol such as IMAP, there is no way to
 know until a server response is being parsed, how many lines (or bytes)
 of data to read.  Ideally, I would be able to slrup in more data as I
 go, but that doesn't seem to be very practical in Parsec either.

Assuming I've understood the gist of Koen Claessen's Parallel Parsing 
Processes, its implementation of the Parsec interface returns all possible 
parses, in the order of how much input they consume. Also, no more input is 
consumed than necessary.  For the purpose of parsing network input, that's 
superior to the usual order in which parse alternatives are considered. The 
Parsec interface supports lookahead, which implies examining beyond what is 
consumed. That could be error-prone, but I expect lookahead is considerably 
easier to manage than Parsec's order of considering alternatives.
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] IO platform for testing

2005-07-16 Thread Scott Turner
On 2005 July 16 Saturday 11:19, yin wrote:
 I need some testing 'main' function:

 ./bundle01 cmd arg1 arg2 ...

Your code is close to working. Most likely the detail which gave you trouble 
is the syntax for mod. It should be
b01_mod a b = a `mod` b
Infix operator names in Haskell all use backquotes.

There are some other, minor problems -- for indexing you need ss!!0, the name 
m01_mod, and you may need an 'import' to make getArgs visible.
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Space questions about intern and sets

2005-06-02 Thread Scott Turner
On 2005 June 02 Thursday 04:38, Gracjan Polak wrote:
  iorefset :: Ord a = IORef(Map.Map a a)
  iorefset = unsafePerformIO $ do
   newIORef $ Map.empty

 I could have as many dictionaries as there are types. The problem is I
 get one dictionary for each object which defeats the idea.

To avoid unsafe operations and get control over the dictionaries that are 
created, I would put the desired dictionaries into a state monad.  The type 
of 'intern' becomes
Ord a = a - DictionaryState a
All the code that uses 'intern' would need some modification to deal more 
directly with the dictionary state. It may be more complex, but it's also 
more solid.
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Text search

2005-05-17 Thread Scott Turner
On 2005 May 17 Tuesday 11:44, Donn Cave wrote:
  You can get efficiency, the desired data, and deal with infinite strings.
 reversed_inits = scanl (flip (:)) 
 find (isPrefixOf (reverse needle)) (reversed_inits haystack)

With get efficiency, I was comparing this program which is linear time and 
constant space in the amount of the haystack searched, to an earlier 
suggestion which was quadratic time and linear space.

 Is it practical to process a serious volume of data as [Char]?

As for your question, GHC _can_ handle a serious volume of [Char]. I don't 
know how competitive the efficiency is.
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Text search

2005-05-16 Thread Scott Turner
On 2005 May 16 Monday 08:00, Gracjan Polak wrote:
 Ketil Malde wrote:
   While the result isn't exactly the same, I suspect
   using isPrefixOf and tails would be more efficient.

 I need the data before and including my needle.

When the haystack gets large, the beautiful
   find (isSuffixOf needle) (inits haystack)
is quite inefficient where it uses isSuffixOf searching longer and longer 
strings.

You can get efficiency, the desired data, and deal with infinite strings by 
using a function that is like 'inits' but which returns the initial strings 
reversed.

   reversed_inits = scanl (flip (:)) 
   find (isPrefixOf (reverse needle)) (reversed_inits haystack)
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Trying to implement this code

2005-04-18 Thread Scott Turner
On 2005 April 18 Monday 16:57, Dmitry Vyal wrote:
 Am not sure about the relevance of this approach as i have very little
 experience with Haskell and FP. So it would be great if someone offers
 better solution.
It's a valid approach.  Rather than declare an Updateable class, I'd just have 
the update function be a parameter of ins_in_tree.  Also, the key and value 
types can be independent parameters of BinTree.

 Why doesnt translator automatically deduce constraints in type of
 ins_in_tree and flat_tree functions so i need to explicitly define them?
It deduces not just the constraints, but the entire type. You don't have to 
state the types of ins_in_tree or flat_tree at all.   The following types are 
distinct
(Ord a, Updateable a) = BinTree a - a - BinTree a
BinTree a - a - BinTree a
because the latter type has no constraints, and names having the latter type 
can be used in more contexts than the former.  If
foo :: BinTree a - a - BinTree a
meant that foo might or might not have constraints, then there would be no way 
to tell the translator that foo has no constraints.

 ---
 data (Ord a, Updateable a) = BinTree a =
  Leaf | Node (BinTree a) a (BinTree a)

 class Updateable a where
  update :: a - a

 data Word_stat = Word_stat String Int deriving Show

 instance Eq (Word_stat) where
  (==) (Word_stat s1 _) (Word_stat s2 _) = s1 == s2

 instance Ord (Word_stat) where
  (Word_stat s1 _)  (Word_stat s2 _) = s1s2

 instance Updateable (Word_stat) where
  update (Word_stat s i) = Word_stat s (i+1)
 -- inserts new element in the tree or updates existing one
 ins_in_tree :: (Ord a, Updateable a) = BinTree a - a - BinTree a
 ins_in_tree Leaf el = Node Leaf el Leaf
 ins_in_tree (Node left cur right) el

  | el  cur = Node (ins_in_tree left el) cur right
  | el == cur = Node left (update cur) right
  | otherwise = Node left cur (ins_in_tree right el)

 -- loads list of strings in the tree
 ins_list :: [String] - BinTree Word_stat
 ins_list lst = foldl ins_in_tree  Leaf (map wrap lst)
  where wrap :: String - Word_stat
 wrap s = Word_stat s 1
 --traverses the tree
 flat_tree :: (Ord a, Updateable a) = BinTree a - [a]
 flat_tree Leaf = []
 flat_tree (Node left el right) =
  (flat_tree left) ++ [el] ++ (flat_tree right)

 -- function you probably need
 summary :: [String] - [Word_stat]
 summary lst  = flat_tree $ ins_list lst
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: UTF-8 BOM, really!? (was: [Haskell-cafe] Re: File path programme)

2005-01-31 Thread Scott Turner
On 2005 January 31 Monday 04:56, Graham Klyne wrote:
 How can it make sense to have a BOM in UTF-8?  UTF-8 is a sequence of
 octets (bytes);  what ordering is there here that can sensibly be varied?

Correct. There is no order to be varied.

A BOM came to be permitted because it uses the identical code as NBSP 
(non-breaking space). Earlier versions of Unicode permit NBSP just about 
anywhere in the character sequence.  Unicode 4 deprecates this use of NBSP.

If I read it correctly, Unicode 4 says that a BOM at the beginning of a UTF-8 
encoded stream is not to be taken as part of the text. The BOM has no effect. 
The rationale for this is that some applications put out a BOM at the 
beginning of the output regardless of the encoding.  Other occurrences of 
NBSP in a UTF-8 encoded stream are significant.
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Haskell Pangolins

2004-12-29 Thread Scott Turner
On 2004 December 29 Wednesday 19:13, Dominic Fox wrote:
 any obvious respects in which this program
 could be simplified, clarified or made more idiomatic.

isYes = `elem` [y, yes, Y, YES]

withArticle fullString@(x:xs) =
 (if x `elem` aeiou then an  else a ) ++ fullString
withArticle [] =  -- in case of empty input
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] code example

2004-12-19 Thread Scott Turner
On 2004 December 19 Sunday 17:31, armin langhofer wrote:
 this is the use:
 
 Prelude :l e:\haskell\burstall.hs
 Main fix square 0.01
 0.01

 it seems that i dont have a clue how it works. maybe some of you could
 explain it to me that i can pass the exam tomorrow,

Do you know what fix square would do with other argument values?  If not, it 
would be worth your while to look at a whole lot more arguments because the 
results could be illuminating.  Also, try replacing square with some other 
functions like id or (\x - x - 1) respectively.

Consider the value of the expression
abs(f x -x) = 0.01
if the function parameter f is square.  What values of x would produce a 
True or a False result?  You'll find a close relationship between this 
question and the result of evaluating fix square 
___
Haskell-Cafe mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Random obeservations from my playing with Haskell

2004-12-05 Thread Scott Turner
On 2004 December 05 Sunday 18:19, Rolf Wilms wrote:
 [Newbie warning on] Here's a few random obeservations from my playing with
 Haskell:
You've got into Haskell with unusual rapidity. Most of your observations are 
fairly aimed.

 Recently found a memoization modulue in Hugs, but no docs. 
 There's a reference to the Haskell '97 Report, but I didn't find it online. 
http://www.cse.ogi.edu/~jl/ACM/Haskell.html
http://www.cse.ogi.edu/~byron/memo/dispose.ps

 7. There's a lot of discussion w.r.t state, at least on this list. Is
 threading state through many functions respectivley polluting many
 functions with monads the solution?
If a function is pure, there's never any need to involve it with a monad.  
Monads don't cause pollution. They serve to indicate what functions have 
side effects, while the choice of monad tells what kinds of side effects may 
occur. 

Haskell people enjoy pure functions, but are not shy of side effects, which 
are recognized as an essential feature of every program. Functions that 
return monadic values provide an excellent way to organize side effects.
___
Haskell-Cafe mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Haskell IO and exceptions

2004-12-04 Thread Scott Turner
On 2004 December 02 Thursday 09:35, Mark Carroll wrote:
 I like Control.Monad.Error but often my stuff is threaded through
 the IO monad so, AFAICT from the functional dependency stuff, that means
 my errors have to be IOErrors. Is that right? And, then, I want control
 over what's actually reported to the user, but if I make a userError than
 the consequent message (where the details are presumably
 platform-dependent) is wrapped up in extra text that I didn't want
 appearing. Can I use Control.Monad.Error for IO monad stuff such that I
 can control what string will appear when my error handler tries to show
 my exception?

Yes. Although Control.Monad.Error forces your error type to be in the Error 
class, that puts no constraints on what you save in the errors. If you thread 
your errors with the IO Monad then you would be using the monad:
   ErrorT YourErrorType IO
When you invoke runErrorT (within the plain IO monad) it returns an Either 
result which delivers your error type and it can be reported however you 
wish.

Note that there is no integration between the error tracking of ErrorT, and IO 
error handling.  If your code currently calls userError, it would have to be 
modified.
___
Haskell-Cafe mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] maybe IO doesn't suck, but my code does...

2004-12-03 Thread Scott Turner
On 2004 December 03 Friday 05:33, Frédéric Gobry wrote:
 important memory usage problems (in fact, at each attempt, I

 Alternatively, if I took the wrong direction, please refocus my search
http://haskell.org/hawiki/ForcingEagerEvaluation and especially follow the 
link and look at Strict datatypes, seq, ($!), DeepSeq and Strategies.
___
Haskell-Cafe mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Mutable data design question

2004-12-03 Thread Scott Turner
On 2004 December 03 Friday 15:16, GoldPython wrote:
 until I joined this email list a couple weeks ago, I had never met another
 human being that knew what functional programming was

My experience has been different in Massachusetts.  At my first job after my 
Comp Sci degree, developing compilers for a now-defunct minicomputer 
manufacturer, another developer stated that his favorite programming language 
was the pure subset of Lisp.  These days when I go on site to interview for a 
job as a C++ programmer, usually at least one of the developers with whom I 
talk recognizes Haskell on my résumé and knows something of functional 
programming.

 I've never even heard the topic mentioned

Granted, the average programmer can get along on just the information that 
comes out of the OOP/UML/IDE industry. But the people who brought templates 
to C++ and generics to Java made no secret of their knowledge of functional 
programming, and cited these capabilities as they existed in SML and/or 
Haskell.
___
Haskell-Cafe mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Re: Pure Haskell Printf

2004-11-16 Thread Scott Turner
On 2004 November 16 Tuesday 06:42, Jérémy Bobbio wrote:
 There is a probleme with ShowS though: it is not internationalizable at
 all.  Strings like printf's or with any kind of variable substitution is
 required for proper internationalization / localization.
Printf is not adequate for internationalization either, because word (and thus 
parameter) ordering may vary among languages.  Note that MissingH.Printf 
addresses this with a feature which supports keys in format items, e.g. 
%(item1)s.
___
Haskell-Cafe mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Re: Processing of large files

2004-11-03 Thread Scott Turner
On 2004 November 03 Wednesday 09:51, Alexander Kogan wrote:
 merge' a x = (addToFM (+) $! a) x 1
 is not strict.
 Can I do something to make FiniteMap strict?
 Or the only way is to make my own StrictFiniteMap?

You can replace
addToFM_C (+) a x 1
with
let a' = addToFM_C (+) a x 1 in 
lookupFM a' x `seq` a'
or you can generalize that into your own strict version of addToFM_C.  It's a 
little ugly, but probably gets the job done.
___
Haskell-Cafe mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Re: Processing of large files

2004-11-01 Thread Scott Turner
On 2004 November 01 Monday 16:48, Alexander N. Kogan wrote:
 Sorry, I don't understand. I thought the problem is in laziness - 
You're correct. The problem is laziness rather than I/O.
 my list 
 of tuples becomes (qqq, 1+1+1+.) etc and my program reads whole file
 before it starts processing. Am I right or not? If I'm right, how can I
 inform compiler that  my list of tuples should be strict?

The program does not read the whole file before processing the list. You might 
expect that it would given that most Haskell I/O take place in exactly the 
sequence specified.  But readFile is different and sets things up to read the 
file on demand, analogous to lazy evaluation.

The list of tuples _does_ need to be strict. Beyond that, as Ketil Malde said, 
you should not use foldl -- instead, foldl' is the best version to use when 
you are recalculating the result every time a new list item is processed.

To deal with the list of tuples, you can use 'seq' to ensure that its parts 
are evaluated.

For example, change 
 (a,b+1):xs
to
 let b' = b+1 in b' `seq` ((a,b'):xs)
'seq' means evaluate the first operand (to weak head normal form) prior to 
delivering the second operand as a result.  Similarly the expression 
merge xs x
needs to be evaluated explicitly.


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


Re: [Haskell-cafe] strictness and the simple continued fraction

2004-10-11 Thread Scott Turner
On 2004 October 09 Saturday 15:33, William Lee Irwin III wrote:
 So, I discovered that simple continued fractions are supposed to be
 spiffy lazy lists and thought I'd bang out some continued fraction code.
 But then I discovered ContFrac.hs and couldn't really better it. Of
 course, I went about trying to actually do things relying on their
 laziness, and discovered they weren't as lazy as I hoped they'd be.

I tried using continued fractions in a spiffy lazy list implementation a 
while ago. Never got them working as well as expected. 

Evenutally I realized that calculating with lazy lists is not as smooth as you 
might expect. For example, the square root of 2 has a simple representation 
as a lazy continued fraction, but if you multiply the square root of 2 by 
itself, your result lazy list will never get anywhere.  The calculation will 
keep trying to determine whether or not the result is less than 2, this being 
necessary to find the first number in the representation. But every finite 
prefix of the square root of 2 leaves uncertainty both below and above, so 
the determination will never be made.

Your problems may have some other basis, but I hope this helps.
___
Haskell-Cafe mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] A Typing Dilemma

2004-10-08 Thread Scott Turner
On 2004 October 08 Friday 09:57, John Goerzen wrote:
 defaultHandler :: LogHandler b = IO (a - IORef b)
 defaultHandler = do
  h - (streamHandler stdout WARNING)
  r - newIORef h
  return (\x - r)

 The idea is to create a new IORef to something in the LogHandler class
 and return a function that returns it.  The thing returned by that call
 to streamHandler is in the LogHandler class.  Specifically, its
 declaration looks like this:

 instance LogHandler (GenericHandler a) where

defaultHandler returns its result for _some_ LogHandler type, while the type 
declaration
 defaultHandler :: LogHandler b = IO (a - IORef b)
has an implicit universal interpretation of b.  To satisfy this type 
declaration, defaultHandler would have to be able to return a handler for 
_any_ LogHandler type, depending on the context in which defaultHandler is 
called.

The Haskell type for defaultHandler uses an existential type, and would look 
like this:

data SomeLogHandler = forall a . (LogHandler a) = SomeLogHandler a
defaultHandler :: IO (a - IORef SomeLogHandler)
defaultHandler = do
 h - (streamHandler stdout WARNING)
 r - newIORef (SomeLogHandler h)
 return (\x - r)

Then you would use it as
 f - defaultHandler
SomeLogHandler h - readIORef (r 0)
... use the LogHandler h ...

By the way, when you say return a function that returns it, I suspect you 
are thinking of how this would work in C or Java, where to accomplish 
anything you need to call a function or invoke a method.  If the function 
parameter of type 'a' serves no useful purpose, then the above can be 
simplified to 

data SomeLogHandler = forall a . (LogHandler a) = SomeLogHandler a
defaultHandler :: IO (IORef SomeLogHandler)
defaultHandler = do
 h - (streamHandler stdout WARNING)
 r - newIORef (SomeLogHandler h)
 return r

Then you would use it as
 f - defaultHandler
SomeLogHandler h - readIORef r
... use the LogHandler h ...
___
Haskell-Cafe mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] monad question

2004-09-19 Thread Scott Turner
On 2004 September 19 Sunday 13:40, Andrew Harris wrote:
 handleSeeRecord :: [SeeObjInfo_type] - RobotState - IO (RobotState, ())
 handleSeeRecord seeobjlist p = do flaglist - return (morphToList
 flagFinder seeobjlist)
                                  balllist - return (morphToList
 ballFinder seeobjlist)
                                  friendlist - return (morphToList
 friendFinder seeobjlist)
                                  foelist - return (morphToList
 foeFinder seeobjlist)
                                  Robot e - return (assign_flags
 (flagSpread flaglist))
                                  Robot f - return (assign_ball balllist)
                                  Robot g - return (assign_friends
 friendlist) Robot h - return (assign_foes foelist) (r', ()) - e p
                                  (r'', ()) - f r'
                                  (r''', ()) - g r''
                                  h r'''

What you're looking for is something like
handleSeeRecord :: [SeeObjInfo_type] - Robot ()
handleSeeRecord seeobjlist = do 
 let flaglist = morphToList flagFinder seeobjlist
 let balllist = morphToList ballFinder seeobjlist
 let friendlist = morphToList friendFinder seeobjlist
 let foelist = morphToList foeFinder seeobjlist
 assign_flags (flagSpread flaglist)
 assign_ball balllist
 assign_friends friendlist
 assign_foes foelist
This uses the 'do' notation with the Robot monad, whose operations are closer 
to what the code is doing than the IO monad. Also, replacing 'return' with 
'let' removes the unnecessary reference to the monad.
___
Haskell-Cafe mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Re: Writing binary files?

2004-09-16 Thread Scott Turner
On 2004 September 16 Thursday 06:19, Simon Marlow wrote:
 Argv and the environment - I don't know.  Windows CreateProcess() allows
 these to be UTF-16 strings, but I don't know what encoding/decoding
 happens between CreateProcess() and what the target process sees in its
 argv[] (can't be bothered to dig through MSDN right now). 

In Windows, CommandLineToArgvW provides a way to obtain a Unicode set of argv 
and argc values from a Unicode command-line string. Visual C++ supports 
defining a wmain function which is like main except it receives a Unicode 
argv. I looked for details of how the args are converted for an ordinary C 
'main' function, but didn't turn up much else while digging through MSDN. 
Windows distinguishes between the system code page and the C runtime locale 
(which is initially ASCII).

So Windows would work best if getArgs returns a String, while on Unix it would 
avoid encoding problems if it returns [Byte].
___
Haskell-Cafe mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Type Theory? Relations

2004-07-26 Thread Scott Turner
On 2004 July 26 Monday 13:46, [EMAIL PROTECTED] wrote:
 According to Enderton, one of the ways to define an ordered pair (a,b)
 is {{a},{a,b}}.  A relation is defined as a set of ordered-pairs.  A
 map, of course, is a single-valued relation.

The motivation for defining ordered pairs that way is more mathematical than 
type-theoretic.   It arises from having sets as a starting point, and needing 
to define ordered pairs, relations, and functions.

 Given all that, suppose I have a FiniteMap Int String in Haskell.
 This is, according to the definitions above, a Set (Int,String).   

You have run into a problem expressing your meaning, because (Int, String) 
indicates a specific type in Haskell which is _not_ a Set.  

 An 
 element of that has type (Int,String), which contains {Int,String}.  But
 that can't exist because a Set contains only elements of one type.

The ordered pair 1,one would be represented as {{1},{1,one}}. Now, 
{1,one} can't exist in Haskell as you say, but it can be represented using 
the Either type constructor. 

Either enables a value to be chosen from two otherwise incompatible types. 
Either Int String is a type which can have values that are Ints or Strings, 
but the value must specify which using the Left or Right constructor.
Left 5 and Right five 
are both values of the type Either Int String.
Left five
would be invalid.

Instead of {1,one), in Haskell you would have {Left 1, Right one} 
of type Set (Either Int String). The ordered pair would be
   {Left {1}, Right {Left 1, Right one}}
of type
  Set (Either Int (Either Int String))
and the finite map would be
  Set (Set (Either Int (Either Int String)))

Few people would be able to tolerate writing a program using this type. :-)
___
Haskell-Cafe mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Of types and constructors; a question of programming style

2004-07-06 Thread Scott Turner
On 2004 July 06 Tuesday 05:35, Graham Klyne wrote:
 When I'm designing datatypes for a Haskell program, I sometimes seem to end
 up with a slightly incoherent mixture of algebraic types and
 constructors. 

 example 

 data Event = Document DocURI Element
 | Element Name BaseURI Language Children Attributes LiIndex
 | Subject EndElement
 | Attribute Name AttributeVal
 | Text TextVal

At first I was going to say that I would _never_ feel the need to turn a set 
of constructors into a set of types. But looking again at your example 
constructors I grasp what you mean by incoherent.  In such cases, what may 
help is to consider why such disparate entities would be grouped together.  

It is not uncommon that the reason is that they all are processed by one or a 
few functions. Then you can consider making those functions into a class.  
Whether this is desirable depends on whether splitting up the implementation 
of the original functions, reorganized by type, makes the program more 
modular.
___
Haskell-Cafe mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Join and it's relation to = and return

2004-06-07 Thread Scott Turner
On 2004 June 07 Monday 15:19, Ron de Bruijn wrote:
 newtype S a = State - (a,State) -- functor T to map
 objects
 mapS::(a- b) - (S a - S b)  -- functor T to map
 morphisms
 unitS :: a - S a  --\eta
 joinS::S(S a)- S a -- \mu

 This is a complete monad using a direct mapping from
 Category Theory. I really like it, because it's
 mathematically grounded. But I don't know how to map
 this to Haskell monads using the standard bind and
 return, as I explain below.

Wadler's The Essence of Functional Programming goes into monads to the point 
of relating map, unit, and join to bind and return.
http://homepages.inf.ed.ac.uk/wadler/topics/monads.html
___
Haskell-Cafe mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: Precision of `Double's in Hugs

2002-01-12 Thread Scott Turner

On Saturday 12 January 2002 17:35, you wrote:
 (I'm just a new convertee to the ways of Functional Programming, so
 please go easy on me! ^_^;;)

Welcome. Hope you find it as fun and useful as I.

 Why is it that `Double's in Hugs only seem to have the same
 precision as a `Float'? I've some code here that only iterates a few
 hundred times, and the amount of accuracy lost is getting a bit
 ridiculous ...

As the Hugs manual says in 9.1,
The Double type is implemented as a single precision float (this isn't 
forbidden by the standard but it is unusual).

But if you build Hugs yourself, there's a line in options.h
/* Define if you want to use double precision floating point arithmetic*/
#define USE_DOUBLE_PRECISION 0
From a bit of browsing the code, it appears that setting USE_DOUBLE_PRECISION 
will increase the precision of both Float and Double types.

 BTW: From the description at http://haskell.cs.yale.edu/communities/
 , I seem to get the impression that [EMAIL PROTECTED] should only
 be used for announcements, yet the archive shows quite a bit of
 general discussion going on. Should I have posted this to the
 aforementioned list as well / instead?

Haskell-cafe is fine for your question. For a description of the way the 
mailing lists are split, I'd recommend 
http://www.haskell.org/mailinglist.html.

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



RE: stack overflow

2001-02-26 Thread Scott Turner

At 01:26 2001-02-26 -0800, Simon Peyton-Jones wrote:
And so on.  So we build up a giant chain of thunks.
Finally we evaluate the giant chain, and that builds up
a giant stack.
 ...
If GHC were to inline foldl more vigorously, this would [not] happen.

I'd hate to have my programs rely on implementation-dependent optimizations.

BTW, I've wondered why the Prelude provides foldl, which commonly leads to
this trap, and does not provide the strict variant foldl', which is useful
enough that it's defined internal to the Hugs prelude.  Simple prejudice
against strictness?

--
Scott Turner
[EMAIL PROTECTED]   http://www.billygoat.org/pkturner

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



Re: [newbie] Lazy = ?!

2001-02-17 Thread Scott Turner

Andrew Cooke wrote:
2.  Why does the following break finite lists?  Wouldn't they just
become lazy lists that evaluate to finite lists once map or length or
whatever is applied?

 Now, if this were changed to 
 ~(x:xs) = f = f x ++ (xs = f)
 (a lazy pattern match) then your listList2 would work, but finite
 lists would stop working.

They wouldn't just become lazy lists.  A "lazy" pattern match isn't about
removing unnecessary strictness.  It removes strictness that's necessary
for the program to function normally.  A normal pattern match involves
selecting among various patterns to find the one which matches; so it
evaluates the expression far enough to match patterns.  In the case of
 (x:xs)
it must evaluate the list sufficiently to know that it is not an empty
list.  A lazy pattern match gives up the ability to select which pattern
matches.  For the sake of less evaluation, it opens up the possibility of a
runtime error, when a reference to a named variable won't have anything to
bind to.

The list monad is most often used with complete finite lists, not just
their initial portions.  The lazy pattern match shown above breaks this
because as it operates on the list, it assumes that the list is non-empty,
which is not the case when the end of the list is reached.  A runtime error
is inevitable. 

--
Scott Turner
[EMAIL PROTECTED]   http://www.billygoat.org/pkturner

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