Re: [Haskell-cafe] Accumulating related XML nodes using HXT

2006-10-31 Thread Albert Lai
Daniel McAllansmith [EMAIL PROTECTED] writes:

 Hello.
 
 I have some html from which I want to extract records.  
 Each record is represented within a number of tr nodes, and all records 
 tr 
 nodes are contained by the same parent node.

This is very poorly written HTML.  The original structure of the data
is destroyed - the parse tree no longer reflects the data structure.
(If a record is to be displayed in several rows, there are proper
ways.)  It is syntactically incorrect: nested tr, and color in hr.
(Just ask http://validator.w3.org/ .)  I trust that you are parsing
this because you realize it is all wrong and you want to
programmatically convert it to proper markup.

Since the file is unstructured, I choose not to sweat over restoring
the structure in an HXT arrow.  The HXT arrow will return a flat list,
just as the file is a flat ensemble.  The list looks like:

[/prod17, Television,  (code: 17), A very nice telly.,
 /prod24, Cyclotron,  (code: 24), Mind your fillings.]

I then use a pure function to decompose this list four items at a time
to emit the desired records.  This is trivial outside HXT arrows.  I
use tuples, and every field is a string; you can easily change the
code to produce Prod's, turn  (code: 17) into the number 17, etc.

Here is a complete, validated HTML 4 file containing the table, just
so that my program below actually has valid input.

!DOCTYPE HTML PUBLIC -//W3C//DTD HTML 4.01//EN
http://www.w3.org/TR/html4/strict.dtd;
html
head
meta http-equiv=Content-Type content=text/html;charset=utf-8
titleProducts/title
/head
body

table
  tr
tdstrongProduct:/strong/td
tdstronga href=/prod17Television/a/strong (code: 17)/td
  /tr
  tr
tdstrongDescription:/strong/td
tdA very nice telly./td
  /tr

  tr
tdhr/td
  /tr

  tr
tdstrongProduct:/strong/td
tdstronga href=/prod24Cyclotron/a/strong (code: 24)/td
  /tr
  tr
tdstrongDescription:/strong/td
tdMind your fillings./td
  /tr

  tr
tdhr/td
  /tr
/table
/body
/html

Here is my program:

import Text.XML.HXT.Arrow

main =
do { unstructured - runX (p table.html)
   ; let structured = s unstructured
   ; print structured
   }

p filename =
readDocument [(a_parse_html,1)] filename 
deep (isElem  hasName table) 
getChildren  isElem  hasName tr 
getChildren  isElem  hasName td 
getChildren 
p1 + p2

p1 =
isElem  hasName strong 
getChildren  isElem  hasName a 
getAttrValue href + (getChildren  getText)

p2 =
getText

s (a:b:c:d: rest) = (a,b,c,d) : s rest
s _ = []
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


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

2006-10-12 Thread Albert Lai
Brian Hulley [EMAIL PROTECTED] writes:

 You'll never believe it but I've been struggling last night and all of
 today to try and think up a name for the following type and I'm still
 nowhere near a solution:
 
 data ??? = VarId | VarSym | ConId | ConSym

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


Re: [Haskell-cafe] Is Haskell a Keynesian language?

2006-10-12 Thread Albert Lai
Henning Thielemann [EMAIL PROTECTED] writes:

 Here is another approach of questionable classification of languages. :-)
 
  A lazy functional program is demand driven, an imperative program is
 supply driven.

  So is Haskell a Keynesian language and C++ a Say language?

Great, now we can talk about the Invisible Hand performing evaluations...

Alice: The Invisible Hand is holding up more memory than I thought.
My program is using O(n) space just to compute length!

Bob: You've violated Nash equilibrium!
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell] Evil code

2006-10-03 Thread Albert Lai
Thomas Davie [EMAIL PROTECTED] writes:

 The evil code and CPSness were actually intended to be completely
 separate entities.  I needed (and to a lesser extent now still need),
 examples that are (a) very higher order, and (b) evil and hard to
 understand the runtime behaviour of.

Generally code that produces and consumes lots of tuples, e.g., common
implementations of splitAt, span, mapAccumL (these are list
functions), the State monad (Control.Monad.State; you can strip out
the instance Monad thing and package the code as ordinary
functions).

Also Phil Wadler's Monads for Functional Programming
http://homepages.inf.ed.ac.uk/wadler/topics/monads.html#marktoberdorf
contains a monadic parser.  In section 5.11 improving laziness two
different ways of coding and their respective laziness effects are
shown.  This can be further exemplified by debugger traces, methinks.
___
Haskell mailing list
Haskell@haskell.org
http://www.haskell.org/mailman/listinfo/haskell


[Haskell-cafe] Re: Haskell web forum

2006-09-21 Thread Albert Lai
As requested, I continue here the thread on the proposal for a web forum.

You will soon enough find out what I think of web forums.  Let me
first show you what this mailing list looks like to me using software
of my choice:

!  [ 192: Mark Carroll] [Haskell-cafe] Card trick
!  [  37: Thomas Conway   ] Re: [Haskell-cafe] How can we detect and fix
E  [  19: Albert Lai  ] Re: [Haskell-cafe] Either e Monad
E  [  19: Deokhwan Kim]
   [  62: Bas van Dijk]
E  [  47: [EMAIL PROTECTED] [Haskell-cafe] Re: Optimization problem
   [  51: Ross Paterson   ]
E  [  42: Conor McBride   ]
   [  56: Robert Dockins  ]
   [  42: Conor McBride   ]
   [  61: [EMAIL PROTECTED] [Haskell-cafe] Re:  Optimization prob
   [  14: Ross Paterson   ]
   [ 154: Jan-Willem Maessen  ] Re: [Haskell-cafe] Traversing a graph in STM
   [  52: Josef Svenningsson  ]
   [  18: Bulat Ziganshin ] Re[2]: [Haskell-cafe] Traversing a graph 
   [  26: Sebastian Sylvan]
   [  22: Ashley Yakeley  ] [Haskell-cafe] Re: Wiki contact

An elaboration of the cool features I have always enjoyed is in order:

On browsing threads, both inter-thread jumps and intra-thread
navigation, the screenshot speaks for itself.  (If for any perverted
reason I want the messages listed chronologically rather than
well-organized, the software can do it too.)

The messages marked with E are messages I have just read.  With this
mark, they will not show up next time I browse this mailing list
again.  Take note that I can mark and unmark any subset of messages,
unlike certain people's linear-time idea that one single timestamp
distinguishes already read from new across the board.  (I have
always heard that non-linear thinking is superior to linear thinking.
I think I believe it for at least this application.)  (Is this an
example of what is meant when someone said that a web forum requires
less technical knowledge, i.e., programmers on a web forum will not
need to know about subsets?)  (Speaking of which, is the
thread-browsing part also an example, i.e., programmers on a web forum
will not need to know about trees and forests?)

Though the marked messages will not show up next time, they are not
thrown away yet.  They are kept on my disk for quite a while.  (I get
to set how many days they stay.)  The software offers several ways to
show them, but I think the most useful one is this.  Suppose I look at
apfelmus's message on Optimization problem (two are shown, I'm
referring to the first one), and wonder, gee, what is it replying
to?  To find out, I position myself to that message, then press a
button, then the software will show the desired parent message.  In
fact, the updated screen looks like this (I just include the thread in
question):

E  [  18: Ross Paterson   ] Re: [Haskell-cafe] Re: Optimization problem
E  [  47: [EMAIL PROTECTED]
   [  51: Ross Paterson   ]
E  [  42: Conor McBride   ]
   [  56: Robert Dockins  ]
   [  42: Conor McBride   ]
   [  61: [EMAIL PROTECTED] [Haskell-cafe] Re:  Optimizatio
   [  14: Ross Paterson   ]

So even if apfelmus's message quotes nothing from Ross's, I can still
find out, provided it is recently enough to be still on my disk.  Take
note that, on a linear-thinking web forum, there could be any number
of intervening messages in the same thread between Ross's and
apfelmus's, and even though it is true that Ross's is immortalized in
the database of the forum, the real question is how to fish for it.
(ObRant again about how web forums are friendly to programmers who
have no clue about trees.)

Here is a feature unrelated to threading, and in fact it is much more
fundamental and pervasive (since almost all email software, not just
mine, provides this), and in fact it has much to do with pervasive
computing too.  Here in Canada, in cafes one can get wireless Internet
access, but it has to be paid by the minutes.  So suppose I want to
visit haskell-cafe when I visit a Starbucks cafe, and there are 30
messages I want to read, and I can read them at the rate of half a
minute per message.  If haskell-cafe were on a web forum, I would end
up keeping my wireless connection for 15 minutes.  (Could I disconnect
and reconnect between messages?  First of all that's really a pain.
Secondly, let's say I do that, the billing is still such that I
connect for 2 seconds and I'm still charged for 1 minute.)  But since
haskell-cafe is on a mailing list, I can just connect for a few
seconds to download the messages, then disconnect and read offline;
I'm charged for at most 1 minute.

(Alternatively but equivalently, suppose I want to read haskell-cafe
while riding subway - underground trains.  Here in Toronto the subway
doesn't provide wireless Internet access yet, and probably won't for
another decade.  If haskell-cafe

Re: [Haskell-cafe] Either e Monad

2006-09-19 Thread Albert Lai
Deokhwan Kim [EMAIL PROTECTED] writes:

 Where is the Monad instance declaration of Either e?

It is in Control.Monad.Error as well.  Strange: the doc doesn't state it.
I found out in ghci using:

:module +Control.Monad.Error
:info Either

The relevant result is:

instance Error e = Monad (Either e)
-- Imported from Control.Monad.Error
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell] Haskell XML

2006-08-31 Thread Albert Lai
Till Mossakowski [EMAIL PROTECTED] writes:

 Could someone summarize the pros and cons of
 HXT versus HaXml versus HSX?

From my perspective (therefore perhaps important but hardly
comprehensive), HXT vs HaXml:

HXT provides arrows.  The con is you have to learn arrows.  The pro is
the arrows provided have the same capability as monads of state and IO.

Dually, HaXml does not provide arrows or equivalent.  The provided
functions of type Content - [Content] (Content is the node type)
are not very flexible or helpful if you want to thread a state through
a parse tree, e.g., a recent question in haskell-cafe on how to insert
random numbers as attribute values into a document using HaXml.

(I lied about the con of HXT.  You don't have to learn arrows if you
really resist --- monads of the same capability are provided too.)

I have no comment on HSX, and you already know the language vs library
contrast.
___
Haskell mailing list
Haskell@haskell.org
http://www.haskell.org/mailman/listinfo/haskell


Re: [Haskell-cafe] HaXml question

2006-08-31 Thread Albert Lai
Tim Newsham [EMAIL PROTECTED] writes:

 I thought this one would be easy but I'm starting to think its not.
 I am playing with HaXml and I want to transform an XML tree into
 another tree.  The transforms are simple enough, but the kicker
 is that I want them to be stateful.  In this example, the state
 is a random number generator.  So the transformation depends on
 the current node and the random number generator state.  I want
 to transform every node in the tree.

Indeed, the HaXml functions are pure, and in particular foldXml does
not thread a state through.

To introduce state, you provide your own state monad (fortunately
there is always Control.Monad.State).  To traverse the whole tree in
this monad, you write your own recursion and deconstruct the nodes
yourself (because foldXml is too specific to be re-usable).

Here is my example.  It replaces attribute values by random integers
between 0 and 99, so it is a similar task but slightly different from
yours.  Some names are inspired by yours, but I have simplified their
nature: The state I thread through is not a stream of generators, but
rather a stream of numbers; as long as this stream comes from
Random.randomRs, I'm good.


import Text.XML.HaXml
import Control.Monad.State
import Random

newtweak :: [Int] - CFilter
newtweak xs c = [evalState (reco c) xs]

reco :: Content - State [Int] Content
reco (CElem (Elem nm ats cs)) =
do { ats' - mapM newtweakAttr ats
   ; cs' - mapM reco cs
   ; return (CElem (Elem nm ats' cs'))
   }
reco c = return c

newtweakAttr (k,_) =
do { n - gets head
   ; modify tail
   ; return (k, AttValue[Left (show n)])
   }

main = do
gen - getStdGen
processXmlWith (newtweak (randomRs (0,99) gen))

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


Re: [Haskell-cafe] Why Not Haskell?

2006-08-08 Thread Albert Lai
Brian Hulley [EMAIL PROTECTED] writes:

 Also, the bottom line imho is that Haskell is a difficult language to
 understand, and this is compounded by the apparent cleverness of
 unreadable code like:
 
  c = (.) . (.)
 
 when a normal person would just write:
 
  c f g a b = f (g a b)

All mainstream languages are also difficult to understand, with
similarly clever, unreadable code.  Let's have a fun quiz!  Guess the
mainstream languages in question:

0. What language would allow

  4[hello world]

   when a normal person would just write

  hello world[4]

   I first saw this in Dr. Dobb's Journal a decade ago; the author
   said that someone actually used it in interviews!

1. What language, supporting a kind of both parametric polymorphism
   and subclass polymorphism, allows and actually features such a class
   declaration as

 class EnumT extends EnumT { ... }

2. What language allows you to test primality in constant runtime?
   That is, move all the work to compile time, using its polymorphism.

*   *   *

I have programmed and watched programming for more than two decades.
I have observed that the rise and fall of popularity is, of course,
driven by many factors: cultural, social, economical, religious,
political, propagandic, ... but superiority is never one of them.
(Library abundance is, I say, less of a cause and more of an effect.
You have some popularity and then you have more contributors;
conversely you lose popularity and then you lose authors.  Yes there
is some feeding back, but the bootstrapping is more significant.  Perl
has a large library, but that's because it has got an impressive
following.  And where did that following come from?  Mostly economic
(there was a demand, a niche) and religious (it's like natural
languages).)

Recall that some decent technology that once attained as much as 49%
market share could still decline and vanish in less than a decade.  I
am referring to Betamax video tapes.  It lost to VHS video tapes, of
lesser picture quality and 51% market share.  What did Betamax miss?
Apparently, nothing.  It seems that the only difference you can put
your finger at - and even this is elusive - is price.  VHS was
slightly cheaper, and apparently that did it.

If you were born after Betamax had vanished, I congratulate you, on
two counts.  First, you skipped the dark age during which there was no
Haskell, no Gofer, not even Scheme; there was Lisp but even then not
all functions were first-class.  Second, don't feel bad about missing
the video war, as you will soon see an even better one, this time
between Blu-Ray and HD-DVD.  Any bet?

I am trying to say this, with much foregoing digression: we could
equip Haskell with the perfect library, the perfect IDEs and tools,
the perfect tutorials and examples, the license that pleases
everyone... every nice thing mentioned in this thread, and it may
still not become popular.  Betamax had everything and 49% market share
(if Haskell had 49% mind share, we would be really thrilled, right?),
and it could still vanish.

How to make Haskell more popular?  How to make anything at all more
popular?  I am inclined to think it's a purely social question.
Nothing short of a rigorous social science can answer it.  All the nice
things mentioned in this thread, we should strive to build for our own
sake of course, but they don't answer the question.

I have long stopped asking that question.  Once again, I say we should
strive to build all the missing things mentioned.  What impact will
they make to the grand scheme of things, we don't know.  If there will
be none, don't be surprised; it's life.  One day we may have a
rigorous social science that can explain it.  Until then, I share with
you a line a Greek friend puts in his .plan file:

  Man plans and God laughs.

*   *   *

Answers to quiz:
0. http://c-faq.com/aryptr/joke.html
1. http://weblogs.java.net/blog/arnold/archive/2005/06/generics_consid_1.html
2. http://homepage.mac.com/sigfpe/Computing/peano.html
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Re: Haskell-Cafe Digest, Vol 33, Issue 9

2006-05-11 Thread Albert Lai
Alberto G. Corona  [EMAIL PROTECTED] writes:

 stmcache= newTVar 0

I will explain what this doesn't with an analogy.

import Data.IORef

notglobal = newIORef True

main = do a - notglobal
  b - notglobal
  writeIORef a False
  x - readIORef b
  print x

To better show what's going on, I also provide this for contrast:

import Data.IORef
import System.IO.Unsafe

global = unsafePerformIO (newIORef True)

main = do x - readIORef global
  print x
  writeIORef global False
  x - readIORef global
  print x
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Haskell vs OCaml

2005-12-29 Thread Albert Lai
I particularly like OCaml's provision of subtyping.  As a member of
the ML family, it's module system is also quite formidable.  Of course
the imperative constructs are also pretty convenient when you just
want to be quirky.  But I miss the monad do-notation.
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Function application like a Unix pipe

2005-11-21 Thread Albert Lai
I offer a simpler, more direct, and pre-existing correspondence
between a functional programming construct and unix pipes:

  http://www.vex.net/~trebla/weblog/pointfree.html

Scherrer, Chad [EMAIL PROTECTED] writes:

 I'm still trying to settle on a feel for good programming style in
 Haskell. One thing I've been making some use of lately is
 
 (\|) = flip ($)
 infixl 0 \|
 
 Then expressions like
 
 f4 $ f3 $ f2 $ f1 $ x
 
 become
 
 x  \|
 f1 \|
 f2 \|
 f3 \|
 f4
 
 I've seen something like this on haWiki using (#), but I prefer this
 notation because it looks like a Unix pipe, which is exactly how it's
 used. 

[...]

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


Re: [Haskell-cafe] Newbie question on Haskell type

2005-10-16 Thread Albert Lai
Huong Nguyen [EMAIL PROTECTED] writes:

 newtype Parser a = Parser(String - [(a, String)])

[...]

 parse :: Parser a - String - [(a, String)]
 parse p cs = p cs
 \end{code}

Try this instead:

parse (Parser p) cs = p cs

(You forgot to deconstruct! :) )
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] a new Monad

2005-09-17 Thread Albert Lai
Malcolm Wallace [EMAIL PROTECTED] writes:

 Microsoft has announced the following:
 
 Developers can also expect a new scripting language for management
 applications, called Monad.

If we embedded the Monad language, as a DSL, into Haskell using a
Haskell monad, would we get to call it the Monad monad? :)
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Best way to build strings?

2005-07-23 Thread Albert Lai
Andy Gimblett [EMAIL PROTECTED] writes:

 show (External p q) = ( ++ show p ++  []  ++ show q ++ )
 
 but to me the extensive use of ++ is not particularly readable.

[...]

 return (%s [] %s) % (self.p, self.q)
 
 which to me seems clearer, or at least easier to work out roughly what
 the string's going to look like.

I wish to toss out a new thought.  To that end let me blow up the example
to underline a scalability issue:

A. q ++   ++ a ++   ++ z ++  [ ++ m ++  -  ++ k ++  | ++ p ++ | 
   ++ g ++  -  ++ c ++ ]  ++ h ++   ++ b ++   ++ f ++   ++ i
B. printf %s %s %s [%s - %s |%s| %s - %s] %s %s %s %s q a z m k p g c h
   b f i

B looks clearer because without parsing you can see that the output will
contain a |blah| between two blah-blah's inside square brackets, etc.

A looks clearer because without counting you can see that p is the
thing that will go into |blah|, the first blah-blah will be m-k,
etc.

The best of both worlds may be something like the notation in the HOL
theorem prover:

``^q ^a ^z [^m - ^k |^p| ^g - ^c] ^h ^b ^f ^i``

Do you agree that this is much better?

Could someone implement something like this in GHC please? :)
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] Re: [Haskell] Going nuts

2005-04-20 Thread Albert Lai
Alexandre Weffort Thenorio [EMAIL PROTECTED] writes:

 outputLine keyno key orgFile = do
 part1 - getLeft keyno orgFile
 part2 - getRight keyno orgFile
 total - part1 ++ (strUpper key) ++ part2 ++ \n
 newHexFile - openFileEx newfile (BinaryMode WriteMode)
  hPutStrLn newHexFile (orgFile!!0 ++ \n ++ total ++ unlines (drop 2
 orgFile))

outputLine keyno key orgFile = do
let part1 = getLeft keyno orgFile
let part2 = getRight keyno orgFile
let total = part1 ++ (strUpper key) ++ part2 ++ \n
newHexFile - openFileEx newfile (BinaryMode WriteMode)
hPutStrLn newHexFile (orgFile!!0 ++ \n ++ total ++ unlines (drop 2 
orgFile))

let ... = instead of - because getLeft et al. aren't IO commands.

(Why type error rather than syntax error then? Because getLeft returns
a list, and list is a monad too. E.g.,

  do { part1 - getLeft keyno orgFile; return part1 }
= [ part1 | part1 - getLeft keyno orgFile ]

so part1 is inferred to be a Char.)

There will be another problem.  The type of orgFile is expected to be
String here, but the callsite gives it lines(hexFile) of type [String].

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


[Haskell-cafe] Re: [Haskell] Y in haskell?

2005-04-20 Thread Albert Lai
Bernard Pope [EMAIL PROTECTED] writes:

 I also meant to add that I think these solutions are not what Lloyd is
 after, because they rely on recursive equations, which I believe was
 avoided in Lloyd's SML code.

Those recursive equations are avoided in SML because SML is eager - y
f = f (y f) never terminates - and an SML programmer has to thunk by
hand; the obfuscation shows.  In Haskell there is no such need.
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: re-opening a closed stdin?

2002-11-22 Thread Albert Lai
Simon Marlow [EMAIL PROTECTED] writes:

 One reason, I think, is lazy I/O(*).  It's to stop you accidentally

[...]

 (*) kill it! die! die!

So you want
  main = readFile /dev/zero  return ()
to terminate violantly rather than terminate peacefully? :)

Seriously, I understand that the IO monad is the most intuitive and
robust when it is strict.  But sometimes it is also nice if one could
map a file to a lazy string.
___
Glasgow-haskell-users mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users



Re: Optimisation and unsafePerformIO

2002-10-29 Thread Albert Lai
David Sabel [EMAIL PROTECTED] writes:

 {-# NOINLINE b #-}
 
 b x  = if even x then unsafePerformIO getChar else bot
 
 bot = bot
 
 main = do
  putChar (b 4)
  putChar (b 6)

I am not a compiler implementer (or lawyer, for that matter :)
But I propose this guess.  First, both even 4 and even 6 get
constant-folded to True; so b 4 and b 6 both become unsafePerformIO
getChar.  Then there is a common subexpression elimination.
___
Glasgow-haskell-users mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users



Re: Docs missing?

2002-07-24 Thread Albert Lai

The doc RPM package for Red Hat 7.3 suffers the same problem as the
SuSE one.  Could someone please give a hand-holding guide so that we
can fix it ourselves?  Please?  Please?
___
Glasgow-haskell-users mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users



Double your monad in 30 days

2002-03-05 Thread Albert Lai

Ashley Yakeley [EMAIL PROTECTED] writes:

 Prelude 0 * 2
 0

We can generalize this.

import Monad

double_your_monad_in_30_days :: (MonadPlus M) = M a
double_your_monad_in_30_days = mzero `mplus` mzero

___
Glasgow-haskell-users mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users



Re: Congrats to Mandrake

2002-02-20 Thread Albert Lai

[EMAIL PROTECTED] (Ketil Z. Malde) writes:

 I'm not sure what the point would be, if they are in the
 distributions anyway?  Isn't it better to install them by apt-get or
 up2date or whatever?  (In fact, I had almost thought manually
 downloading packages a thing of the past, but then the IT department
 insisted on Red Hat)

If I, a developer, wrote a program, and some distributions included it
(while others didn't), I would want to acknowledge and thank them in
public.

If I, a potential customer choosing among Linux distributions, liked
to use a program, and I saw on the program home page that so-and-so
distributions included the program, I would arrange my preference
accordingly.

If I, an absent-minded user, heard about some great program from my
friends, and saw on the program home page which distributions included
it, I might realize Gosh, *my* distribution CD already has it! and
save some download and install effort.  Remember, I am absent-minded,
so I wouldn't know what's on my CD unless someone stick it on my
face. :)

I probably don't need hyperlinks; I just need to know if my
distribution includes it or not.
___
Glasgow-haskell-users mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users



Re: i368-pc-os2-emx port

2002-02-20 Thread Albert Lai

Simon Marlow [EMAIL PROTECTED] writes:

 On the other hand, you'd need something like mingw for OS/2 - does
 such a beast exist?

The substring emx refers to an OS/2 version of gcc and libraries
that make OS/2 look really like Unix from the programmer's point of
view.  (It probably even pre-dates cygwin.)  I have two encouraging
stories to tell.  First, for a school assignment, I wrote an OpenGL
program on emx, then ported it to school's Solaris+Mesa ten minutes
before the deadline --- where porting meant removing #include
os2.h.  Second, I wrote a program that used tcpip sockets on Unix,
then merely recompiled it on emx to use it on OS/2 as well.

___
Glasgow-haskell-users mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users



Re: Instances of IArray

2002-02-15 Thread Albert Lai

I had looked into the source code of IArray a bit.  Like you have
found, (!) is not a class method.  In fact, none of the claimed class
methods in the doc is a class method, and no class method of IArray is
documented.  Instead, IArray class methods seem to pertain to
implementation details (I mean, unsafeAt!), and user operations
such as (!) are constrained polymorphic functions, e.g.,

(!) :: (IArray a e, Ix ix) = a ix e - ix - e

From the user's point of view, there is little difference between a
class method and a class-constrained polymorphic function when the
provided instances are abstract types.  So the documentation is
telling a white lie.  Of course, you see the difference when you
roll your own IArray instance.

I think the white lie is a balance between exposition simplicity
and implementation tuning.

___
Glasgow-haskell-users mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users



Re: State Transformer

2002-01-11 Thread Albert Lai

  testfunc = do
 r - newSTRef ('x',0)
 foo r
 bar r
 (c,n) - readSTRef r
 return n

Jorge Adriano [EMAIL PROTECTED] writes:

 Yeap, I could do it like this myself :)
 The whole problem is with passing the 'r' as a parameter, which is precisly 
 what I'm trying to avoid.

I agree with you.  My work-around is then to define foo and bar locally
to testfunc, in the scope of r:

testfunc = do
   r - newSTRef ('x',0)
   let foo = do
 (c,n) - readSTRef r
 writeSTRef r ('a', n+1)
   bar = do
 (c,n) - readSTRef r
 writeSTRef r (c,n+2)
   foo
   bar
   (c,n) - readSTRef r
   return n

But if this looks like unsatisfactory (it does to me, too), perhaps
you have to go back to DIY monads.

DIY monads are good when: you fix the state variables, you don't want
to mention them in subprogram parameters.

The ST monad is good when: you create more state variables on the fly,
you use mutable arrays, you don't want to write your own monad and
put/get commands.


___
Glasgow-haskell-users mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users



Re: State Transformer

2002-01-11 Thread Albert Lai

Theodore Norvell [EMAIL PROTECTED] writes:

 Jorge's question raised a question in my mind.  The IOExts
 module has many of the same features as the ST module, why
 are there two ways to do the same thing?  Is the ST module
 only there for legacy purposes?

My user view is that I appreciate the presence of both.

When I write a pure function that can be implemented efficiently in
imperative programming, I want the ST monad to support mutable
variables.  E.g., to implement f n returns a list of all primes
between 2 and n, I want to use a mutable array and hide it.

When I write an I/O-bound routine that can be implemented conveniently
with state variables, I want the IO monad to support mutable
variables.

Now my grief is that I cannot write a subprogram with state variables
and have it reused in ST and IO.  Fortunately I can write a subprogram
with mutable arrays and have it reused in ST and IO, so I can write
sort a given array; but I cannot write increment a given integer
variable.

Of course, you can tell me to use mutable arrays of length 1 to
simulate mutable variables.  Fine!

___
Glasgow-haskell-users mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users



Re: ghc image size

2001-12-17 Thread Albert Lai

Mike Gunter [EMAIL PROTECTED] writes:

 Why is executable size a barrier?  1.64 megabytes (that's the size of
 the executable I built with GHC most recently) of disk space costs less
 than half a cent.

I don't like this argument.  Can I go to a computer store, pay a cent,
and get a hard disk with space 1.64 megabytes or more?  Until then, I
can't believe that 1.64 megabytes of disk space costs less than half a
cent.

When a compiler does not perform as good as other compilers (e.g., in
terms of generated code size), it is important to ask: Why does it
happen? Is there anything we can do to improve it?  Being critical is
the first step towards progress.  (Of course these questions should be
asked in a constructive rather than whining way.)  Why would anyone
optimize code for time --- a second of electricity and labour cost
less than a cent...


___
Glasgow-haskell-users mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users



Re: Working character by character in Haskell

2001-10-18 Thread Albert Lai

Andre W B Furtado [EMAIL PROTECTED] writes:

[...]

 For example, suppose function doSomeStuffWith returns its own parameter.
 Using a 1.5MB file in this case, the Haskell program ends in almost 5
 seconds, while the C program ends in less than 0.5 seconds... Is my Haskell
 program too bad implemented? (I'm using GHC 4.08-1 under a Windows 98
 platform.)

I indeed think that your Haskell program is inefficient and is not a
translation of your C program.  It reverses a huge string, which takes
not only execution time but also garbage collection time and memory,
which entails even more time for OS overhead and swapping out other
things in the physical memory.

(Many programmers complain my linear-time algorithm takes just 1
second on a 100M list, so why is it taking 5 seconds on a 200M list?
They forget that because of issues such as cache locality and virtual
memory, their computers do not scale.)

I am wondering that if doSomeStuffWith is pure-functional, why are you
writing and using copyFile instead of just using map?  I mean:

main :: IO ()
main = do
 bmFile - openFileEx in.txt (BinaryMode ReadMode)
 bmString - hGetContents bmFile
 writeFile out.txt (map doSomestuffWith bmString)
 hClose bmFile

Because both hGetContents and map are lazy and use O(1) memory, this
program behaves exactly as your C program plus occasional garbage
collections that don't hurt too much.  In partcular, the OS will see
no difference (although the cache does).

___
Glasgow-haskell-users mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users



Re: Student Programming Projects

2001-09-20 Thread Albert Lai

Consider goal-directed theorem prover (or proof checker).  Two existing
samples are in Lawrence Paulson's ML for the Working Programmer, and
yours truly's http://www.cs.utoronto.ca/~trebla/fp/prover/index.html

The advantage of mine is it illustrates monads.  The advantage of Paulson's
is it doesn't scare people with monads :) and it includes a substitution
library (yet another monad, but shhh) for use in first-order logic.

___
Glasgow-haskell-users mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users



Re: [ghc5] getDirectoryContents: trouble on Linux/NFS

2001-04-18 Thread Albert Lai

Volker Stolz [EMAIL PROTECTED] writes:

 ghc[i] was built from source. The Solaris binary provided on the GHC-
 download page works fine. I'll investigate FreeBSD as soon as I get home.
 Feel free to ask for more details regarding machine setup/compilation.

I guess a standard question would be: when you built from source, did you
build twice (once from 4.08.x and then once from 5.00 itself)?  Hmm wait a
second, getDirectoryContents fails, so there is no way you can build for
the second time. :)

___
Glasgow-haskell-bugs mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/glasgow-haskell-bugs



ghc/rts/parallel/HLComms.c

2001-02-16 Thread Albert Lai

I try to build ghc 4.08.2 with parallelism turned on, i.e., GhcLibsWays=mp.
At ghc/rts/parallel/HLComms.c line 550:

  GarbageCollect(GetRoots);

it barfs because the new GarbageCollect() function expects a boolean
parameter after the first parameter.  (See ghc/rts/Storage.h for example.)

Is this why I should use gum 4.06 instead? :)

I would really like to have just one installation of ghc for every
way I use it, not one for sequential execution and one for parallel
execution.  One installation is already faring at 90MB; having two
such beasts on a shared disk at school is not nice...

___
Glasgow-haskell-bugs mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/glasgow-haskell-bugs



Re: ghc/rts/parallel/HLComms.c

2001-02-16 Thread Albert Lai

Albert Lai [EMAIL PROTECTED] writes:

 I try to build ghc 4.08.2 with parallelism turned on, i.e., GhcLibsWays=mp.
 At ghc/rts/parallel/HLComms.c line 550:
 
   GarbageCollect(GetRoots);
 
 it barfs because the new GarbageCollect() function expects a boolean
 parameter after the first parameter.  (See ghc/rts/Storage.h for example.)

For now, I will just steal the code from gum 4.06 and replace this
(and all other occurences in HLComms.c) by

  GarbageCollect(GetRoots, rtsFalse);

and hope it works.

___
Glasgow-haskell-bugs mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/glasgow-haskell-bugs



Confused about enabling parallel ghc

2001-02-14 Thread Albert Lai

I installed ghc 4.08.2 binaries for sparc solaris (and those for intel
linux, too), then tried compiling a sample program (the fibonacci one
in the user guide) with ghc -parallel.  The compiler complained:

Could not find interface file for `Prelude'
in the directories ./*.hi
   /u/trebla/lib/ghc-4.08.2/imports/lang/*.mp_hi
   /u/trebla/lib/ghc-4.08.2/imports/concurrent/*.mp_hi
   /u/trebla/lib/ghc-4.08.2/imports/lang/*.mp_hi
   /u/trebla/lib/ghc-4.08.2/imports/concurrent/*.mp_hi
   /u/trebla/lib/ghc-4.08.2/imports/std/*.mp_hi

(and similarly for Parallel.)

Does it mean I must build ghc myself from source?

The user guide promises a lot of binary bundles such as par.  Ever
since 4.0x, the ghc download page ceases to mention them.  Where
are they?

___
Glasgow-haskell-users mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users