Re[2]: [Haskell-cafe] | vs. $ (was: request for code review)

2006-03-08 Thread Bulat Ziganshin
Hello Shannon,

Tuesday, March 7, 2006, 10:52:01 PM, you wrote:

SjB The function itself is a ParseContextTransformation.  It takes a
SjB context, transforms it, and returns it.  Most of the pipelines in the
SjB whole application are ParseContextTransformations, and the | (or $ or
SjB .) are ways of tying them together.  My questions concerning Monads
SjB are in this example are:

SjB 1. Monads apply a strategy to computation.  For instance, the list
SjB monad applies the strategy, Try it with each of my members.  What
SjB part of my code is the strategy?

SjB 2. Monads are containers that wrap a value.  For instance, the Maybe

12 is only possible variations, but they don't covers everything. in
GENERAL, monad is the way to write code as high-order functions that
then will be used in some special way. this allows to hide part of
computation details in the rules of this internal processing

what you need here, imho, is a state monad. your context will become a
state and monad should contain operations to read/write this state. to
be exact, you should use State monad here, which already contains
appropriate operations

in the State monad, each action has type:

type State a  =  StateType - (a, StateType)

i.e. each action is higher order function which transforms state
(having type StateType) and in addition can return value of type 'a'

are you read http://www.nomaware.com/monads/monad_tutorial.zip ?

it's comprehensive tutorial about monads

-- 
Best regards,
 Bulatmailto:[EMAIL PROTECTED]

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


Re: [Haskell-cafe] Annoucing alternative to Text.Regex

2006-03-08 Thread Bulat Ziganshin
Hello Chris,

Wednesday, March 8, 2006, 1:26:37 AM, you wrote:

CK It takes the string form of the regular expression and uses Parsec to 
create a

he-he, i written the same thing (but very simple) 2 years ago :)  i
planned to submit it to the Parsec developers as an example of
double-Parsec usage :)

i think that it is a great lib, but not sure that it should completely
replace current lib. old lib is more appropriate for packed string,
new lib work directly with Haskell strings

one more interesting thing - generation of faster and simpler parsers
for simple regexps. just as example, code from my own program, that
parse filename wildcards. it translates simple patterns directly to
the String-Bool functions and use Regex library for more complex
patterns

-- |Compiled regexpr representation  EXAMPLE
data RegExpr = RE_End -- 
 | RE_Anything-- *
 | RE_FromEnd RegExpr -- '*':bc
 | RE_AnyChar RegExpr -- '?':bc
 | RE_CharChar RegExpr-- 'a':bc
 | RE_FullRE  Regex   -- r[0-9][0-9]

is_wildcard s  =  s `contains_one_of` ?*[

translate_RE re = ^++ (replaceAll * .*
.replaceAll ? .
.replaceAll $ \\$
.replaceAll [[[ [^   
.replaceAll ^ \\^
.replaceAll [^ [[[   
.replaceAll + \\+
.replaceAll . \\.) re ++$

compile_RE s  =  case s of
   - RE_End
  *- RE_Anything
  '*':cs - if ('*' `elem` cs) || ('[' `elem` cs)
  then RE_FullRE  (mkRegex$ translate_RE$ s)
  else RE_FromEnd (compile_RE$ reverse$   s)
  '[':cs - RE_FullRE   (mkRegex$ translate_RE$ s)
  '?':cs - RE_AnyChar  (compile_RE cs)
  c  :cs - RE_Char   c (compile_RE cs)

match_RE re s  =  case re of
  RE_End- null s
  RE_Anything   - True
  RE_FullRE   r - isJust (matchRegex r s)
  RE_FromEnd  r - match_RE r (reverse s)
  RE_AnyChar  r - case s of
- False
 _:xs - match_RE r xs
  RE_Char   c r - case s of
- False
 x:xs - x==c  match_RE r xs

match re {-s-}  =  match_RE (compile_RE re) {-s-}

{-# NOINLINE translate_RE #-}



-- 
Best regards,
 Bulatmailto:[EMAIL PROTECTED]

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


[Haskell-cafe] RE: [Haskell] Re: Trying On Learn Haskell Web Server

2006-03-08 Thread Bayley, Alistair
[Moving to café]

 From: [EMAIL PROTECTED] 
 [mailto:[EMAIL PROTECTED] On Behalf Of Mattias Bengtsson
 
 
   I think that continuation-based web session state management, ala
   Smalltalk/Seaside, would be a very natural fit for a 
 Haskell framework -- all
   handled by a Web session monad, maybe.  (Or maybe I 
 just don't know what I'm
   talking about ;)
  
  This is by far the biggest drawback of HSP today. There is no
  high-level support for continuations (other than explicitly defined
  continuations at top level).
 
 I would really like to know exactly what this means. Are there any
 examples or papers on this?


I have a lot of links... which I'll feel free to spam you and the list with :-)

Here a list of continuation-based web-frameworks that I know about; there may 
be more:

Cocoon (Java + Javascript)  http://cocoon.apache.org/
Borges (Ruby)  http://borges.rubyforge.org/
Wee (Ruby)  http://www.ntecs.de/blog/Wee
WASH (Haskell)  http://www.informatik.uni-freiburg.de/~thiemann/haskell/WASH/
Seaside (Smalltalk)  http://www.seaside.st/
PLT Scheme (Scheme)  http://www.plt-scheme.org/  (can't find the actual library)
Siscweb (Scheme)  http://siscweb.sourceforge.net/
Uncommon Web (Common Lisp)  http://common-lisp.net/project/ucw/
Rife (Java)  http://rifers.org


One of the first people (but not the only, I think) to recognise that 
continuations were a good way of modelling web interations was Christian 
Queinnec:
http://www-spi.lip6.fr/~queinnec/PDF/www.pdf
http://www-spi.lip6.fr/~queinnec/Papers/webcont.ps.gz

Probably the best-known such framework is Seaside (ironic, as Smalltalk doesn't 
natively support continuations, AFAIK):
http://www.seaside.st/

Phil Wadler is also doing something along these lines in Links, I believe:
http://homepages.inf.ed.ac.uk/wadler/links/

Excellent summary of problems with REST and continuations (Dave Roberts):
http://www.findinglisp.com/blog/2004/11/web-application-design-rest-of-story.html

IBM article, mainly about Cocoon - a Java + Javascript framework:
http://www-128.ibm.com/developerworks/java/library/j-contin.html

More hype:
http://phirate.exorsus.net/wiki/doku.php?id=web_development_in_2005
http://phirate.exorsus.net/wiki/doku.php?id=further_discussion_of_continuations_and_sessions
http://phirate.exorsus.net/wiki/doku.php?id=sessions_and_state

Bill Clementson's postings (he's a Lisper):
http://bc.tech.coop/blog/041229.html


Alistair
*
Confidentiality Note: The information contained in this message,
and any attachments, may contain confidential and/or privileged
material. It is intended solely for the person(s) or entity to
which it is addressed. Any review, retransmission, dissemination,
or taking of any action in reliance upon this information by
persons or entities other than the intended recipient(s) is
prohibited. If you received this in error, please contact the
sender and delete the material from any computer.
*
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] library sort

2006-03-08 Thread John Hughes



Am Samstag, 4. März 2006 21:30 schrieb Neil Mitchell:
 


And a related question is: Which packages are searchable by Hoogle?
 


The best answer to that is some. I intentionally excluded OpenGL and
other graphics ones because they have a large interface and yet are
not used by most people using Haskell. [...]
   



Well, this a bold assumption IMHO, and I'm not particularly happy with that, 
as you can probably imagine. For my part, I would assume that Joe Programmer 
is much more likely to use some multimedia packages than TH or Data.Graph.* 
etc., but this is a bold assumption on *my* side...


...


Well, this a bold assumption IMHO, and I'm not particularly
happy with that, as you can probably imagine.
   



I would also imagine that Joe Programmer is more likely to use
wxHaskell or Gtk2Hs than those - however because those are outside the
standard tree they don't make it in. I don't think much of TH made it
in either (not becuase of deliberate exclusions, but because of
technical limitations in the tool).

 

When I surveyed Haskell users, I asked respondents to name the most 
important tools and libraries they use. (Caveat: respondents saw the 
list of tools and libraries already named, and could include these just 
by selecting them, so tools mentioned early in the survey were more 
likely to be named by subsequent respondents). Here are a few relevant 
entries, where the percentage is the proportion of respondents who named 
the tool:


29% Parsec
19% wxHaskell
16% QuickCheck
16% haddock
12% Monadic Parser Combinators
11% Gtk2Hs
9% hs-plugins
8% HaXml
7% Data.*
7% Monad foundation classes
6% Arrows
6% HOpenGL

The list includes all libraries named by more than 5% of respondents. 
Sure enough, wxHaskell and Gtk2Hs are more popular, but 6% naming 
HOpenGL as among the most important libraries is quite respectable.



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


[Haskell-cafe] Re: Haddock Problems

2006-03-08 Thread Christian Maeder

Daniel Fischer wrote:

Hi all,
I've just installed haddock-0.7, nice, but...
haddock -o h7doc -h -D h7doc/fusi.haddock --use-package=base Verwaltung.hs 

Teams.hs Stats.hs Match.hs Main.hs Liga.hs Item.hs Helpers.hs Datum.hs
Warning: Helpers: could not find link destinations for:
GHC.Base.Int GHC.Base.String GHC.Show.Show Data.Maybe.Maybe GHC.Base.Eq 
GHC.Base.Bool


and so on.
Same problem, if I use -i/usr/.../base.haddock instead of 


try --read-interface=/usr/.../base (and more such entries for other 
packages)


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


[Haskell-cafe] haskell-prime traffic

2006-03-08 Thread Ross Paterson
Just for fun, I've put up some statistics on haskell-prime traffic at

http://www.soi.city.ac.uk/~ross/haskell-prime-stats/

I'm not claiming it shows anything, except what a narrow base we have.

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


[Haskell-cafe] Re: Haddock Problems

2006-03-08 Thread Christian Maeder

Daniel Fischer wrote:

Hi all,
I've just installed haddock-0.7, nice, but...
haddock -o h7doc -h -D h7doc/fusi.haddock --use-package=base Verwaltung.hs 

Teams.hs Stats.hs Match.hs Main.hs Liga.hs Item.hs Helpers.hs Datum.hs
Warning: Helpers: could not find link destinations for:
GHC.Base.Int GHC.Base.String GHC.Show.Show Data.Maybe.Maybe GHC.Base.Eq 
GHC.Base.Bool


and so on.
Same problem, if I use -i/usr/.../base.haddock instead of 


try --read-interface=/usr/.../base (and more such entries for other
packages)

Sorry, that alone is not enough (and the same of what you've tried). 
I've also a magic -s path/%F on my haddock line.


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


[Haskell-cafe] MUA written in Haskell (was: Getting GHC to print Done when it's finished linking?)

2006-03-08 Thread Nils Anders Danielsson
On Tue, 07 Mar 2006, Brian Hulley [EMAIL PROTECTED] wrote:

(Moved from ghc-users.)

 Brian Hulley wrote:

 (time for a proper email client to be written in Haskell! ;-) )

I had the same thought yesterday, after an Emacs-Lisp session in which
I was trying to get Gnus to do exactly what I wanted it to...

Out of curiosity, how much work would it take to write an easily
configurable, decent MUA in Haskell? I don't know too much about MUAs,
but I have a feeling that we already have quite a few libraries that
are needed for the job: UIs (including HTML rendering...), plugins,
various protocols, encryption...

-- 
/NAD

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


Re: [Haskell-cafe] | vs. $ (was: request for code review)

2006-03-08 Thread Daniel Fischer
Am Dienstag, 7. März 2006 20:52 schrieb Shannon -jj Behrens:
 I did think of using a monad, but being relatively new to Haskell, I
 was confused about a few things.  Let's start by looking at one of my
 simpler functions:

 -- Keep pushing tokens until we hit an identifier.
 pushUntilIdentifier :: ParseContextTransformation
 pushUntilIdentifier ctx

   | currTokType ctx == Identifier = ctx
   | otherwise =

   let newStack = (currTok ctx) : (stack ctx) in
 (ctx {stack=newStack}) |
 getToken |
 pushUntilIdentifier

 The function itself is a ParseContextTransformation.  It takes a
 context, transforms it, and returns it.  Most of the pipelines in the
 whole application are ParseContextTransformations, and the | (or $ or
 .) are ways of tying them together.  My questions concerning Monads
 are in this example are:

 1. Monads apply a strategy to computation.  For instance, the list
 monad applies the strategy, Try it with each of my members.  What
 part of my code is the strategy?

 2. Monads are containers that wrap a value.  For instance, the Maybe
^^^
Some are, others embody computations that produce a value, yet others: ?

 monad can wrap any value, or it can wrap no value and just be Nothing.
  What part of my code is the thing being wrapped, and what part is
 extra data stored in the Monad itself?

 So I guess:

 3. Is the ParseContext the monad or the thing being wrapped?

 4. How do I divide the code between the functions on the right side of

 = and the functions in the monad itself?  The functions on the right

 side of = operate on the stuff inside the monad, and the functions
 in the monad itself operate on the stuff in the monad.

 5. How does the ParseContextTransformation relate?

 It is because I did not understand the answers to these questions that
 I thought maybe a monad might not be appropriate.  However, I surely
 could be wrong.  Afterall, ParseContext, ParseContextTransformation,
 and | are all *inspired* by what I knew about monads.

 Thanks for your help!

 -jj

I'd use a State-monad, say 

import Control.Monad.State

type CDParser a = State ParseContext a
 -- or perhaps StateT ParseContext m a, where m is an appropriate monad,
 -- I haven't thought much about it

then you'd have e.g.

pushUntilIdentifier :: CDParser ()
pushUntilIdentifier = do
tt - gets currTokType
case tt of
Identifier - return ()
_ - do
pushToken
getToken
pushUntilIdentifier

okay, that doesn't look really better, but if you'd done it monadically from 
the start, you'd probably chosen a different design (I think, I'd leave the 
current token out of the ParseContext and have that returned by the 
appropriate actions). Alternatively, you could use Parsec with Parsecontext 
as user state (removing the input from ParseContext) and take advantage of 
the many provided combinators in Parsec.
As another method, I've hacked up a translation by parsing a declaration and 
creating a customized Show-instance. It could be much improved, but for a 
quick hack, I can live with it.

-- | Translate C-declarations to english, well, sort of
module Translate where

import Text.ParserCombinators.ReadPrec
import qualified Text.ParserCombinators.ReadP as P
import Text.Read
import Data.Char (isAlpha, isAlphaNum)

-- lift some operators from ReadP to ReadPrec, indicates that I
-- should have originally worked with ReadP and lifted to
-- ReadPrec afterwards.
spaces = lift P.skipSpaces

string = lift . P.string

char = lift . P.char

many p = lift $ P.many $ readPrec_to_P p 0

-- | list of known types, struct, union and enum don't really
--   belong here, but since C is inherently sick, it doesn't matter
typeNames :: [String]
typeNames = [ void, char, signed, unsigned, short, int
, long, float, double, struct, union, enum]

-- | may this Char appear in a C-identifier?
isIdLetter :: Char - Bool
isIdLetter c = c == '_' || isAlphaNum c

-- | may this Char begin a C-identifier?
isIdStart :: Char - Bool
isIdStart c = c == '_' || isAlpha c

-- | the sort of types, we can handle
data CType
= Basic String -- ^ plain types like int, char...
| Const CType  -- ^ type with const
| Ptr   CType  -- ^ pointer to type
| Array [Maybe Int] CType -- ^ Array with dimensions

-- | type synonym to check whether a variable is volatile
type Volatile = Bool

-- | the declarations we can parse, due to C's horrible syntax,
--   we can't handle multiple variable declarations like
--
--  int *a, b[5], c;
--
--   but the original programme couldn't either.
data Decl
= VarDecl CType Volatile String
| FunDecl CType String [CType]

--
--  Show Instances  --
--

-- here 

[Haskell-cafe] Re: Haddock Problems

2006-03-08 Thread Christian Maeder

Daniel Fischer wrote:

Hi all,
I've just installed haddock-0.7, nice, but...
haddock -o h7doc -h -D h7doc/fusi.haddock --use-package=base Verwaltung.hs 

Teams.hs Stats.hs Match.hs Main.hs Liga.hs Item.hs Helpers.hs Datum.hs
Warning: Helpers: could not find link destinations for:
GHC.Base.Int GHC.Base.String GHC.Show.Show Data.Maybe.Maybe GHC.Base.Eq 
GHC.Base.Bool


and so on.
Same problem, if I use -i/usr/.../base.haddock instead of 


I hope the following is correct now:

--read-interface=/usr/../libraries/base,/usr/../libraries/base/base.haddock

(-s only supplies links to your own source code)

Cheers Christian

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


[Haskell-cafe] Lists of Lists

2006-03-08 Thread zell_ffhut

Just wondering if anyone can help me with a Haskell problem im having.

How would I get the value of, lets say, the 9th object in [4179355,
567412] ?

(in this case, that should return 6)

Any help/adivce would be great :)
--
View this message in context: 
http://www.nabble.com/Lists-of-Lists-t1245394.html#a3297506
Sent from the Haskell - Haskell-Cafe forum at Nabble.com.

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


[Haskell-cafe] Re: Haddock Problems

2006-03-08 Thread Daniel Fischer
Am Mittwoch, 8. März 2006 12:06 schrieben Sie:
 Daniel Fischer wrote:
  Hi all,
  I've just installed haddock-0.7, nice, but...
 
  haddock -o h7doc -h -D h7doc/fusi.haddock --use-package=base
  Verwaltung.hs
 
  Teams.hs Stats.hs Match.hs Main.hs Liga.hs Item.hs Helpers.hs Datum.hs
  Warning: Helpers: could not find link destinations for:
  GHC.Base.Int GHC.Base.String GHC.Show.Show Data.Maybe.Maybe
  GHC.Base.Eq GHC.Base.Bool
 
  and so on.
  Same problem, if I use -i/usr/.../base.haddock instead of

 I hope the following is correct now:

 --read-interface=/usr/../libraries/base,/usr/../libraries/base/base.haddock

I had that, first with -i/usr... then also with --read-interface=...,
no difference
haddock -h -o dock -D dock/fusi.haddock 
--read-interface=/usr/local/lib/ghc-6.4.1/libraries/base,/usr/local/lib/ghc-6.4.1/libraries/base/base.haddock
 
*.hs
Warning: Helpers: could not find link destinations for:
GHC.Base.Int GHC.Base.String GHC.Show.Show Data.Maybe.Maybe GHC.Base.Eq 
GHC.Base.Bool
...

 (-s only supplies links to your own source code)

 Cheers Christian

Any other ideas?

Thanks,
Daniel

-- 

In My Egotistical Opinion, most people's C programs should be
indented six feet downward and covered with dirt.
-- Blair P. Houghton

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


Re: [Haskell-cafe] Lists of Lists

2006-03-08 Thread Daniel Fischer
Am Mittwoch, 8. März 2006 10:51 schrieb zell_ffhut:
 Just wondering if anyone can help me with a Haskell problem im having.

 How would I get the value of, lets say, the 9th object in [4179355,
 567412] ?

 (in this case, that should return 6)

 Any help/adivce would be great :)
 --
 View this message in context:
 http://www.nabble.com/Lists-of-Lists-t1245394.html#a3297506 Sent from the
 Haskell - Haskell-Cafe forum at Nabble.com.

Use concat and (!!) ?

Cheers,
Daniel

-- 

In My Egotistical Opinion, most people's C programs should be
indented six feet downward and covered with dirt.
-- Blair P. Houghton

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


Re: [Haskell-cafe] Lists of Lists

2006-03-08 Thread Jens Fisseler
 How would I get the value of, lets say, the 9th object in [4179355,
 567412] ?
 
 (in this case, that should return 6)
 
 Any help/adivce would be great :)

Just concatenate the list elements and index the resulting list, but
note that list indices start from 0. Nevertheless I would say this is a
strange way to index such a list.

Regards,

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



[Haskell-cafe] Looking for an efficient tree in STM

2006-03-08 Thread Einar Karttunen
Hello

Does anyone have an efficient tree implemented in STM that
supports concurrent updates in an efficient fashion? This
seems suprisingly hard to implement - a normal binary
tree with links as TVar is very slow and does not scale
very well.

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


Re: [Haskell-cafe] Lists of Lists

2006-03-08 Thread Ketil Malde
zell_ffhut [EMAIL PROTECTED] writes:

 Just wondering if anyone can help me with a Haskell problem im having.

 How would I get the value of, lets say, the 9th object in [4179355,
 567412] ?

You mean the ninth character in the concatenation of the list of
strings?  Concatenate the strings, and select the ninth character?

Use 'concat' '!!', and probably '.' and '9' as well.

-k
-- 
If I haven't seen further, it is by standing in the footprints of giants

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


Re: [Haskell-cafe] library sort

2006-03-08 Thread Sven Panne
Am Dienstag, 7. März 2006 14:24 schrieb Neil Mitchell:
 I would also imagine that Joe Programmer is more likely to use
 wxHaskell or Gtk2Hs than those [...]

Just a (hopefully final) remark about this, because the above statement seems 
to imply something that is not completely true: 3 of the 4 packages I've 
mentioned, i.e. OpenGL (rendering) and OpenAL/ALUT (sound) do not compete in 
any way with the GUI packages mentioned above, they can be happily used with 
those. And regarding the 4th package (GLUT): It very much depends on which 
book you read first, lots of OpenGL books use GLUT as their GUI toolkit and 
do this for a very good reason (reproducibility, widespread availibility, 
ease of use for simple up to medium-sized programs etc.). For a larger 
application other GUI toolkits are probably a better choice, and all of the 
serious ones offer an OpenGL canvas to render on, anyway.

I just had to reply because lots of people seem to confuse GUI issues with 
rendering issues, which are two completely different beasts, and this might 
lead to various preconceptions.

 The data generation is now bundled with Haddock, and as far as I know,
 will be in the next release. [...]

That's good to hear. I really have to take a closer look at the current state 
of the former fptools projects, but my job and the switch to darcs got in the 
way...

Thanks for a really nice tool,
   S.
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Annoucing alternative to Text.Regex

2006-03-08 Thread Chris Kuklewicz
Bulat Ziganshin wrote:
 Hello Chris,
 
 Wednesday, March 8, 2006, 1:26:37 AM, you wrote:
 
 CK It takes the string form of the regular expression and uses Parsec to 
 create a
 
 he-he, i written the same thing (but very simple) 2 years ago :)  i
 planned to submit it to the Parsec developers as an example of
 double-Parsec usage :)

The proposed shootout version on the wiki (
http://haskell.org/hawiki/RegexDna#head-ac7a5b838757d66780247397221f3b4f1ace9051
) uses p_regexp :: CharParser () (CharParser st () - CharParser st ()) which is
even more bizarre at first glance.  But this is not what my full library uses.

 i think that it is a great lib, but not sure that it should completely
 replace current lib. old lib is more appropriate for packed string,
 new lib work directly with Haskell strings

Exactly.  If you have a packed ascii (or unicode?) string you should call c via
regex.h or pcre.h to do the matching.  But doing this with length 10^6 [Char]
via Text.Regex is next to impossible. Thus the niche for the [Char] version I
have created.

Another nice thing is that the Parsec versions of matchRegex / matchRegexAll /
subRegex / splitRegex are lazy, so you could substitute or split an infinite 
string.

Last night Igloo on the #haskell shared a HUnit test suite he used for his
personal version of basic and extended regular expression matching.  This
located two bugs and one specification error in my code (all now fixed).

After some more testing I will be looking for a place to post it.  Is there
somewhere on www.haskell.org that would work?

 one more interesting thing - generation of faster and simpler parsers
 for simple regexps. just as example, code from my own program, that
 parse filename wildcards. it translates simple patterns directly to
 the String-Bool functions and use Regex library for more complex
 patterns

Hmmm...Yes.  Another String-Pattern parser (probably in Parsec) could transform
filename wildcards.  But that would lose information on the simplicity.  I have
not created the infrastructure for such alternatives or meta-data (such as
anchored only at start of string or only uses greedy operators or does not
need back-references or can be reduced to a DFA).

 
 -- |Compiled regexpr representation  EXAMPLE
 data RegExpr = RE_End -- 
  | RE_Anything-- *
  | RE_FromEnd RegExpr -- '*':bc
  | RE_AnyChar RegExpr -- '?':bc
  | RE_CharChar RegExpr-- 'a':bc
  | RE_FullRE  Regex   -- r[0-9][0-9]
 

My parsed form of the string Regex is the Pattern data type.  It is not used to
actually do matching (though that would be possible), but to later compile a
Parsec parser.

data Pattern = PEmpty | PCarat | PDollar | PFail String
 | PGroup  PatternIndex Pattern
 | POr [Pattern]
 | PConcat [Pattern]
 | PQuest  Pattern-- ?
 | PPlus   Pattern-- +
 | PStar   Pattern-- *
 | PBound  Int (Maybe Int) Pattern  -- {3} or {3,5} or {3,}
-- PLazy indicates the pattern should try the shortest matches first
 | PLazy   Pattern-- non-greedy wrapper (?+*{} followed by ?)
-- PPossessive indicates the pattern can only fit the longest match
 | PPossessive Pattern -- possessive modifier (?+*{} followed by +)
 | PDot   -- Any character (newline?) at all
 | PAnyPatternSet -- Square bracketed things
 | PAnyNot PatternSet -- Inverted square bracketed things
 | PEscape Char   -- Backslashed Character
 | PChar   Char   -- Specific Character
-- After simplify adjacent PChar are merge'd into PString
 | PString String
   deriving (Eq,Show)

Where PatternSet is usually just a (Set Char) and Set of [:alpha:] character
classes.  It also holds parsed [.ch.] and [=x=] expressions, but these are not
really implemented in the matching.

PGroup is an empty or non-empty group () or (foo) with the back reference
index.  Also note that Pattern does not differentiate different types of escaped
characters (e.g. \a \* \4 are all PEscape patterns).

The meaning of PDot varies depending on the options.  Multiline expressions do
not match PDot with '\n' and to agree with Text.Regex '\NUL' characters are
disallowed in the string regex and not matched by PDot.  PCarat and PDollar
actions also depend on multiline, and case sensitivity affects the
character/string matching.

I ought to make another option to allow '\NUL' to be treated as a regular 
character.

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


Re: [Haskell-cafe] Looking for an efficient tree in STM

2006-03-08 Thread Tomasz Zielonka
On Wed, Mar 08, 2006 at 01:50:06PM +0200, Einar Karttunen wrote:
 Does anyone have an efficient tree implemented in STM that
 supports concurrent updates in an efficient fashion?

Interesting idea!

 This seems suprisingly hard to implement - a normal binary tree with
 links as TVar is very slow and does not scale very well.

By normal you mean unbalanced? Do you think it's slow because it's not
balanced, or because of STM?

Best regards
Tomasz

-- 
I am searching for programmers who are good at least in
(Haskell || ML)  (Linux || FreeBSD || math)
for work in Warsaw, Poland
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] Re: MUA written in Haskell, and MTA in Haskell help?

2006-03-08 Thread Shae Matijs Erisson
Nils Anders Danielsson [EMAIL PROTECTED] writes:

 I had the same thought yesterday, after an Emacs-Lisp session in which
 I was trying to get Gnus to do exactly what I wanted it to...

Yeah, same here. I use Gnus and it's nice, but occasionally I want to erase it
from the timestream.

 Out of curiosity, how much work would it take to write an easily
 configurable, decent MUA in Haskell? I don't know too much about MUAs,
 but I have a feeling that we already have quite a few libraries that
 are needed for the job: UIs (including HTML rendering...), plugins,
 various protocols, encryption...

It wouldn't be too hard. I'd suggest you start with Tuomo Valkonen's Riot[1]
and go for something like mutt.
I'm sure you could steal lots of useful code from Peter Simons' Postmaster[2].

Speaking of which, I've tried to use Postmaster for my own personal domain,
ScannedInAvian.com, but I've had various difficulties. Is anyone else using it
for their domain? I'd like to find anti-spam features that match those of
postfix, like greylisting, dns name checks, etc.

[1] http://modeemi.fi/~tuomov/riot/
[2] http://postmaster.cryp.to/
-- 
I've tried to teach people autodidactism,| ScannedInAvian.com
but it seems they always have to learn it for themselves.| Shae Matijs Erisson

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


Re[2]: [Haskell-cafe] Lists of Lists

2006-03-08 Thread Bulat Ziganshin
Hello Jens,

Wednesday, March 8, 2006, 2:31:36 PM, you wrote:

 How would I get the value of, lets say, the 9th object in [4179355,
 567412] ?
JF Just concatenate the list elements and index the resulting list, but

btw, due to the lazy evaluation time required to perform this
operation will be proportional to used index, not to the size of whole
catenated list


-- 
Best regards,
 Bulatmailto:[EMAIL PROTECTED]

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


Re: [Haskell-cafe] library sort

2006-03-08 Thread Ketil Malde
Neil Mitchell [EMAIL PROTECTED] writes:

 And a related question is: Which packages are searchable by Hoogle?

 The best answer to that is some. I intentionally excluded OpenGL and
 other graphics ones because they have a large interface and yet are
 not used by most people using Haskell.

I'm not sure I agree that is a good reason.  If there is a specificity
problem with Hoogle, that should be adressed in the interface e.g. by
providing more information about the search results, or letting the
user restrict his search (filtering out parts of the hierarchy from
the result list, for instance). 

-k
-- 
If I haven't seen further, it is by standing in the footprints of giants

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


Re: [Haskell-cafe] library sort

2006-03-08 Thread Neil Mitchell
 I'm not sure I agree that is a good reason.
I never claimed it was a good reason, merely that it was a reason :)

Hoogle 2 only allowed you to search the Haskell 98 libraries, which
obviously everyone wants to do. Hoogle 3 is still in beta - I
introduced searching more, but have not got round to letting the user
specify what to search.

My thinking with selecting which packages are defaults in Hoogle was
roughly guided by the question if a person is searching for this
package, would they know that they wanted that package?

For example, when searching for sort the user has no expectation of
where the sort will be. However when searching for something like a
newOpenGlContext the user knows they are looking for a very OpenGL
function. i.e. for one they are searching haskell - for the other
they really just want to search opengl.

Anyway, my current plan is:
* lots of smallish packages, and one big base package which is the
default search
* OpenGL, wxHaskell, Gtk2Hs, Darcs, GHC API, GHC (the code base), Yhc,
Parsec will all be options to search for. At some point in the future
I will send out an offer to everyone if they want their package
included.

See what functions users really do search for, if say 5% of users add
Parsec to their searches, consider including it in the defaults.

Maybe (depending on how efficient I can make Hoogle), it can give
google style hints - there were also 3 results in OpenGL, would you
like to add OpenGL to your search options.

Thanks

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


Re: [Haskell-cafe] library sort

2006-03-08 Thread Duncan Coutts
On Wed, 2006-03-08 at 11:25 +0100, John Hughes wrote:

 When I surveyed Haskell users, I asked respondents to name the most 
 important tools and libraries they use. (Caveat: respondents saw the 
 list of tools and libraries already named, and could include these just 
 by selecting them, so tools mentioned early in the survey were more 
 likely to be named by subsequent respondents). Here are a few relevant 
 entries, where the percentage is the proportion of respondents who named 
 the tool:
 
 29% Parsec
 19% wxHaskell
 16% QuickCheck
 16% haddock
 12% Monadic Parser Combinators
 11% Gtk2Hs
 9% hs-plugins
 8% HaXml
 7% Data.*
 7% Monad foundation classes
 6% Arrows
 6% HOpenGL
 
 The list includes all libraries named by more than 5% of respondents. 
 Sure enough, wxHaskell and Gtk2Hs are more popular, but 6% naming 
 HOpenGL as among the most important libraries is quite respectable.

As Sven said, HOpenGL is complementary to wxHaskell and Gtk2Hs as both
of these GUI toolkits can be used with HOpenGL to draw to an OpenGL
canvas widget.

Yes, there is some overlap with GLUT, but there are times when you'd
want to use GLUT rather than one of the bigger GUI toolkits.

wxWidets examples:
http://wxhaskell.sourceforge.net/samples.html
(at the bottom of the page)

Gtk2Hs example:
http://haskell.org/gtk2hs/archives/2005/11/11/more-opengl-goodness/


Duncan

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


Re: [Haskell-cafe] Lists of Lists

2006-03-08 Thread zell_ffhut

Thank you, It's working as planed now 

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

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

where x is the value to change to, i is the index of the value to change,
and [xs] is the list.

This however, dosen't work in Haskell. How would this be done in Haskell?
--
View this message in context: 
http://www.nabble.com/Lists-of-Lists-t1245394.html#a3301147
Sent from the Haskell - Haskell-Cafe forum at Nabble.com.

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


Re: [Haskell-cafe] library sort

2006-03-08 Thread Sven Panne
Am Mittwoch, 8. März 2006 15:11 schrieb Neil Mitchell:
 I never claimed it was a good reason, merely that it was a reason :) [...]

:-)

 Anyway, my current plan is:
 * lots of smallish packages, and one big base package which is the
 default search
 * OpenGL, wxHaskell, Gtk2Hs, Darcs, GHC API, GHC (the code base), Yhc,
 Parsec will all be options to search for. At some point in the future
 I will send out an offer to everyone if they want their package
 included. [...]

In the meantime it would be great if Hoogle could be made consistent with the 
documentation on http://haskell.org/ghc/docs/latest/html/libraries/ (this is 
the big base package IMHO). Currently the differences might be quite 
confusing for new people.

 Maybe (depending on how efficient I can make Hoogle), it can give
 google style hints - there were also 3 results in OpenGL, would you
 like to add OpenGL to your search options.

That would be a great feature IMHO.

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


Re: [Haskell-cafe] Lists of Lists

2006-03-08 Thread Thomas Davie


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



Thank you, It's working as planed now

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

somthing like -


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


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

and [xs] is the list.

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


Put simply it isn't.

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


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

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


Re: [Haskell-cafe] Lists of Lists

2006-03-08 Thread Jens Fisseler
  changeValue x i [xs] = [xs] !! i = x
 
 where x is the value to change to, i is the index of the value to change,
 and [xs] is the list.
 
 This however, dosen't work in Haskell. How would this be done in Haskell?

Think about what parts of the list you can reuse, how you can define
those parts and put them together.

You probably want to split the list at the index. 'splitAt' is the
function to use for this, as it will give you the resulting prefix and
suffix. The head of the suffix is the element you want to replace. So
you create a new list by appending the unaltered prefix, the new element
and the 'tail' of the suffix.

Regards,

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


Re: [Haskell-cafe] Lists of Lists

2006-03-08 Thread zell_ffhut

Stunning. That really helps 

Different thinking to what im used to :)
--
View this message in context: 
http://www.nabble.com/Lists-of-Lists-t1245394.html#a3301339
Sent from the Haskell - Haskell-Cafe forum at Nabble.com.

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


[Haskell-cafe] Re: Can't uninstall GHC or prepare SOE installation on OS X

2006-03-08 Thread Wolfgang Thaller

Xavier Elizalde wrote:

Hi. I sent this post to the haskell-cafe mailing list but haven't  
gotten any replies.


Ah well, I watch that list in digest mode only, easy to overlook things.

Basically, I can't get the Uninstall AppleScript for GHC 6.4.1to  
run properly because it encounters an error.


Oops. I *thought* I had tested that to death.
Anyway, for manual removal:

/usr/local/lib/ghc-6.4.1	(the big part; if disk space is all you're  
after, stop here)

In /usr/local/bin/:
ghc, ghc-6.4.1, ghc-pkg, ghc-pkg-6.4.1, ghci, ghci-6.4.1, ghcprof,  
hasktags, hp2ps, hsc2hs, runghc, runhaskell, stat2resid


in /Libraries/Receipts:
Some GHC-*.pkg file, I suspect now that it's called GHC-6.4.1.pkg

/Library/Frameworks/GMP.framework	(do not delete this unless you do  
not want to ever run any GHC-compiled program again until you re- 
install GHC).



I have the Haskell School of Expression book and want to try out  
the examples in the book that make use of X11 for graphics, and I  
don't know how to use GHC 6.4.1 for the SOE book examples. I  
thought it would be easiest to just uninstall it then install the  
SOE binaries for OS X.


The SOE binaries use hugs, and should therefore be completely  
independent of GHC, no uninstalling required.


But if GHC 6.4.1 works fine for the SOE book examples and is better  
than the SOE install, I'd like to use that, although I don't know  
how to get it to work with X11. Do you have any idea on what I  
should do?


Start your programs from an xterm.
If you want to use GHCi, set
export DYLD_LIBRARY_PATH=/usr/X11R6/lib/
before starting ghci in the xterm.



I have The Haskell School of Expression book and the
instructions for setting up and running the SOE software seem to have
a different configuration compared to GHC 6.4.1. Namely, it's meant
to use X11 and locations for files are different.


What files? I don't have the book, so all I can tell you is that GHC  
includes a library module by the name of Graphics.SOE.



Or does the GHC already
have GraphicsLIb as part of it? If so, shouldn't it launch an X11
Xterm terminal rather than the standard OS X Terminal?


Shouldn't it launch...? Are you referring to the AppleScript for  
launching GHCi?

If so, then no, for two reasons:
a) X11 is an optional install on Mac OS X, so many people don't have it.
b) The standard Terminal is a lot more convenient to use than an  
xterm, and most people don't need/want to use X11 for their Haskell  
programs.


So good luck with SOE, if there are any more problems, ask me.

Cheers,

Wolfgang

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


Re: [Haskell-cafe] Web application frameworks

2006-03-08 Thread Graham Klyne
Björn Bringert wrote:
 Graham Klyne wrote:
 [Switching to haskell-cafe]
 Niklas Broberg wrote:
 
 ...
 
 On 3/6/06, Graham Klyne [EMAIL PROTECTED] wrote:
 - Options to run the whole thing behind Apache to leverage its
 security and web
 space management capabilities

 Lemmih has implemented a HSP/FastCGI binding for Apache. I also know
 that work is being done on building a direct HSP/Apache binding. All
 work in progress though.

 Yes, I was aware of a fastCGI for Haskell.  Didn't Bjorn Bringert (also)
 implement one?  I tend to think of CGI programs as
 run-to-completion-then-exit,
 even when a fastCGI interface allows a persistent wrapper program to
 speed
 startup.  But I could easily be missing something here.
 
 Yes, I have written a FastCGI binding (darcs repo here:
 http://www.cs.chalmers.se/~bringert/darcs/haskell-fastcgi/). If I'm not
 mistaken, that's what Lemmih is using for his HSP/FastCGI binding.
 
 I have only used FastCGI the way you describe, as CGI without start-up
 penalty, though I can't see why you couldn't keep some state between
 requests to a FastCGI application. I believe that Ruby-on-Rails (which
 I've never used, so I'm not too sure) can use FastCGI.
 
 One problem with Apache and FastCGI is that the Apache FastCGI module
 doesn't seem to support concurrent requests to a single FastCGI process
 (even though the FastCGI protocol allows this). This means that Apache
 will have to run several instances of the Haskell-over-FastCGI app to
 serve concurrent requests, or be forced to serialize the requests.
 Having several instances of course means that you can't really keep
 stuff like session data in memory in the FastCGI process. If the Apache
 module supported concurrent requests we could spawn a new Haskell thread
 to serve each request, which ought to scale well.

Aha!  I think that homes in on what I was after when mentioning long-running
processes.  I think there are some separate but related issues to consider:

(a) can a single CGI invocation handle (respond to) a series of HTTP requests,
or is it strictly one http request for each CGI invocation?  Without this, you
may have to throw away session state after each request.

(b) is there a way to maintain state between CGI invocations?

(c) can multiple concurrent CGI/HTTP requests be handled?

Of these, I think (c) may be the least important, other than for performance
reasons (and maybe not even then), provided that there are ways to handle
upstream I/O asynchronously, and to encapsulate all the relevant session state
in a way that can be passed between invocations.  I guess it comes down to a
choice between an event-driven or multi-threaded processing model (and the
former seems to me to be a nicer fit with Haskell).

I think the minimum requirement is ((a) OR (b)) AND  ((c) OR (asynchronous I/O
completion))

#g

-- 
Graham Klyne
For email:
http://www.ninebynine.org/#Contact

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


[Haskell-cafe] Dropping trailing nulls from a list of list

2006-03-08 Thread Jeff . Harper

Today, I reviewed a function I wrote
a few months ago. The function, dropTrailNulls, takes a list of lists
and drops trailing null lists. For instance:

*Main dropTrailNulls [[1],[2,3],[],[]]
[[1],[2,3]]

My original implementation was terrible.
It was recursive, overly bulky, and difficult to understand. It
embarrasses me. I won't post it here.

Today, it occurred to me this would
do the trick:

dropTrailNulls list = reverse (dropWhile
null (reverse list))

The problem is 20 years of experience
writing efficient imperative programs says to me, You don't drop
things off the end of a structure by reversing the structure, dropping
stuff from the beginning, then reversing again. I suspect this
imperative bias prevented me from coming up with the simple solution when
I first wrote my function.

On the other hand, it is conceivable
to me that my new implementation may actually be relatively efficient since
Haskell uses lazy evaluation, and Haskell lists are constructed from the
tail to the beginning.

I'm sure there are many problems that
are encountered in Haskell where it is necessary to operate on the end
of a list. So, I'm wondering if the idiom, reverse, operate, then
reverse is something I should add to my toolbox. Or, is there a more
efficient idiom for addressing these problems?___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Dropping trailing nulls from a list of list

2006-03-08 Thread Neil Mitchell
 dropTrailNulls list = reverse (dropWhile null (reverse list))

Or more succinctly:

dropTrailNulls = reverse . dropWhile null . reverse

 Or, is there a more efficient idiom for addressing these problems?

The bad thing about this definition is that it is tail strict. Consider

[hello,everyone,... forever]

With your definition  you will get nothing back (since reverse is tail
strict). However, there is an alternative definition that will give
the first two elements back:

dropTrailNulls x = f 0 x
   where
  f n [] = []
  f n ([]:xs) = f (n+1) xs
  f n (x:xs) = replicate n [] ++ (x : f 0 xs)

-- note: untested, may not work

The reason is because it is significantly more lazy. It is also more
space efficient, and probably faster.

However, despite all this, I love the reverse . something . reverse
example, and I think its totally beautiful in terms of simplicity.

The general programming advice holds here as for everywhere else -
write beautifully, if performance demands, profile then write to
obtain speed.

Thanks

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


Re: [Haskell-cafe] Dropping trailing nulls from a list of list

2006-03-08 Thread Robert Dockins
On Mar 8, 2006, at 12:08 PM, [EMAIL PROTECTED] wrote:Today, I reviewed a function I wrote a few months ago.  The function, dropTrailNulls, takes a list of lists and drops trailing null lists.  For instance:  *Main dropTrailNulls [[1],[2,3],[],[]] [[1],[2,3]]  My original implementation was terrible.  It was recursive, overly bulky, and difficult to understand.  It embarrasses me.  I won't post it here.  Today, it occurred to me this would do the trick:  dropTrailNulls list = reverse (dropWhile null (reverse list))  The problem is 20 years of experience writing efficient imperative programs says to me, "You don't drop things off the end of a structure by reversing the structure, dropping stuff from the beginning, then reversing again."  I suspect this imperative bias prevented me from coming up with the simple solution when I first wrote my function.  On the other hand, it is conceivable to me that my new implementation may actually be relatively efficient since Haskell uses lazy evaluation, and Haskell lists are constructed from the tail to the beginning. Only if the list is spine strict (AND the compiler knows this AND it decides to strictify the call).  Lazy evaluation actually builds lists from the front, unfolding thunks as they are demanded.I'm sure there are many problems that are encountered in Haskell where it is necessary to operate on the end of a list.  So, I'm wondering if the idiom, reverse, operate, then reverse is something I should add to my toolbox.  Or, is there a more efficient idiom for addressing these problems?Use a data structure which allows efficient access to the end of a sequence.  (shameless plug)  Check out Edison, it has a couple that would serve; I hope to prepare an updated release pretty soon. (http://www.eecs.tufts.edu/~rdocki01/edison.html)As to lists in particular...While I suppose its _possible_ that (reverse . dropWhile p . reverse) will be fused into something more efficient, I don't think you can count on it (any core wizards care to contradict me?).  You might be able to do something more efficient with foldr.  Humm, lets see...dropTailNulls = snd . foldr f (True,[])f x (allNulls,y)  | null x  allNulls = (True, [])  | otherwise          = (False, x : y)That seems to work.  Dunno if it's any more efficient though; it is certainly less beautiful.Rob DockinsSpeak softly and drive a Sherman tank.Laugh hard; it's a long way to the bank.          -- TMBG ___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Lists of Lists

2006-03-08 Thread zell_ffhut

Im afraid im baffled again!

Im now trying to add a char to a string of strings (eg - [434233434
444929192 909313434]

Im sure i can use my previous function to help me achive this, but i can't
seem to get it workinging

 charToGrid :: Char - Position - Grid - Grid
 charToGrid c (row,col) g = concat g (changeValue c(row*9 + col)) 

Im not sure i should be using concat, as i have to return a grid as it was
given, just with the added char.
--
View this message in context: 
http://www.nabble.com/Lists-of-Lists-t1245394.html#a3305996
Sent from the Haskell - Haskell-Cafe forum at Nabble.com.

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


Re: [Haskell-cafe] Lists of Lists

2006-03-08 Thread Robert Dockins


On Mar 8, 2006, at 1:29 PM, zell_ffhut wrote:

Im afraid im baffled again!

Im now trying to add a char to a string of strings (eg - [434233434
444929192 909313434]

Im sure i can use my previous function to help me achive this, but  
i can't

seem to get it workinging


charToGrid :: Char - Position - Grid - Grid
charToGrid c (row,col) g = concat g (changeValue c(row*9 + col))


Im not sure i should be using concat, as i have to return a grid as  
it was

given, just with the added char.


As before, the idea is to create a new list with the changes you  
want, only now you have a list two levels deep.  So the first thing  
to do is to pick out the sublist (row) you want to change and  
create a new changed sublist (row), and then rebuild your grid.  Try  
this, it may get you started:


updateList :: (a - a) - Int - [a] - [a]
updateList f i l = begin ++ (f x : end)
  where (begin, x : end) = splitAt i l


BTW, lists aren't very good for these kinds of manipulations.  If you  
really need an indexable, mutable data structure, try one of  
Data.Array.*



Rob Dockins

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

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


Re: [Haskell-cafe] Dropping trailing nulls from a list of list

2006-03-08 Thread Udo Stenzel
[EMAIL PROTECTED] wrote:
 
 Today, I reviewed a function I wrote a few months ago.  The function,
 dropTrailNulls, takes a list of lists and drops trailing null lists.  For
 instance:
 
 *Main dropTrailNulls [[1],[2,3],[],[]]
 [[1],[2,3]]

dropTrailNulls = foldr dtn []
  where
dtn [] [] = []
dtn  x xs = x:xs

 
 dropTrailNulls list = reverse (dropWhile null (reverse list))

As the other responses said, this is needlessly strict.  Work on
deforesting reverse exists, but you can't count on it happenig.


 is there a more efficient idiom for addressing these problems?

Well, there's always the basic fold.  I'm not sure there's any lesson to
be learnt here other than fold is your friend.


Udo.
-- 
F:  Was ist ansteckend und kommutiert?
A:  Eine Abelsche Grippe.


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


Re: [Haskell-cafe] Lists of Lists

2006-03-08 Thread Udo Stenzel
zell_ffhut wrote:
 Imagine the strings are set out in a 9x9 grid type way, and i have to find
 the value of a set position given 2 gird values.
 
  getCharFromGrid (row,col) g = concat g !!(row * 9) + col

This isn't by chance evolving into the world's ugliest sudoku solver?
Are you sure, you don't want to use a FiniteMap?


Udo.
-- 
Slous' Contention:
If you do a job too well, you'll get stuck with it.


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


Re: [Haskell-cafe] Lists of Lists

2006-03-08 Thread zell_ffhut

Could you explain what the function does.. I can't seem to peice it together.
--
View this message in context: 
http://www.nabble.com/Lists-of-Lists-t1245394.html#a3307166
Sent from the Haskell - Haskell-Cafe forum at Nabble.com.

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


[Haskell-cafe] Re: MUA written in Haskell (was: Getting GHC to print Done when it's finished linking?)

2006-03-08 Thread Brian Hulley

Nils Anders Danielsson wrote:

On Tue, 07 Mar 2006, Brian Hulley [EMAIL PROTECTED] wrote:

(Moved from ghc-users.)


Brian Hulley wrote:



(time for a proper email client to be written in Haskell! ;-) )


I had the same thought yesterday, after an Emacs-Lisp session in which
I was trying to get Gnus to do exactly what I wanted it to...

Out of curiosity, how much work would it take to write an easily
configurable, decent MUA in Haskell? I don't know too much about MUAs,
but I have a feeling that we already have quite a few libraries that
are needed for the job: UIs (including HTML rendering...), plugins,
various protocols, encryption...


I'm afraid I don't know much about MUAs either.
I see there's some stuff in Network.* that may be useful...

Unfortunately I don't have time at the moment to try implementing one, but 
for what it's worth here are some thoughts I had on what an ideal email 
client, suitable for Haskell programmers, would be like:


1) Plain text based to avoid problems with viruses etc getting in via HTML. 
HTML emails received could just be displayed as plain text (including all 
markup)


2) What-you-see-is-exactly-what-will-be-sent for editing, so that when you 
press send you don't need to worry about the text being all mangled up by 
wrapping/replacement of characters etc


3) When you click reply or reply all, the original text should be 
indented with '' (at the moment OE requires QuoteFix to achieve this 
trivial but essential functionality)


4) An API could be exposed then the user could write scripts to put things 
into correct folders etc.
The API could provide info about what is currently waiting on the server, 
and the ability to download or delete without downloading (eg for big 
attachments that are suspected of being viruses)


5) Ideally the scripting language would be Haskell. There is already stuff 
in Language.Haskell.* for doing parsing but I can't find anything which 
would allow you to compile and load functions into a running program.


So I'd imagine that the email client would contain a plain text editor that 
wrapped text as it is edited (if wrapping is needed nowadays anyway?) with 
email addresses and URLs in the text clickable; a tree of folders and a 
folder contents window which could display the emails by date/subject/name/ 
or thread; and an API and way of loading scripts written in Haskell to do 
all the complicated automatic stuff - which would now be completely under 
the user's control.


Regards, Brian. 


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


Re: [Haskell-cafe] Dropping trailing nulls from a list of list

2006-03-08 Thread Bulat Ziganshin




Hello Jeff,

Wednesday, March 8, 2006, 8:08:57 PM, you wrote:







dropTrailNulls list = reverse (dropWhile null (reverse list))





dropTrailNulls [] = []
dropTrailNulls ([]:xs) = case dropTrailNulls xs of
 [] - []
 list - []:list
dropTrailNulls (x:xs) = x : dropTrailNulls xs

should work faster. but in most cases speed is just not critical and Haskell
allows to implement such parts of program faster and easier (and easier to understand)

--
Best regards,
Bulat  mailto:[EMAIL PROTECTED]



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


Re: [Haskell-cafe] Lists of Lists

2006-03-08 Thread Robert Dockins


On Mar 8, 2006, at 2:27 PM, zell_ffhut wrote:
Could you explain what the function does.. I can't seem to peice it  
together.


It takes three things 1) a function 2) an index and 3) a list.  It  
finds the nth element of the list, applies the function to it and  
then returns a new list containing the new element in the same  
position.  It dies with an error message if you index past the end of  
the list.


e.g.

updateList (\x - x + 10) 3 [0,1,2,3,4,5] == [0,1,2,13,4,5]


Rob Dockins

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


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


Re: [Haskell-cafe] Lists of Lists

2006-03-08 Thread zell_ffhut

I see, that seems to make sence.

Im still unsure of how to do that with the specification set to me

 charToGrid :: Char - Position - Grid - Grid
--
View this message in context: 
http://www.nabble.com/Lists-of-Lists-t1245394.html#a3308835
Sent from the Haskell - Haskell-Cafe forum at Nabble.com.

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


Re: [Haskell-cafe] | vs. $ (was: request for code review)

2006-03-08 Thread Shannon -jj Behrens
First of all, thank you all so much for taking the time to help me
with this exercise!  My hope is that once I'm able to understand it,
my understanding can come through in the article I write.

 Brian Hulley:
 In the pipe in the 'otherwise' branch, at the moment you have to
 assume that each of the transformations can successfully be done.
 What happens if getToken can't get a token because there are no more
 tokens left?  To solve this problem you could use a monad such as
 Maybe, to encapsulate the strategy keep going as long as no
 problems have been encountered so far eg:

I can see where you're going with the Maybe monad, and it does make
sense.  However, I see Maybe as a hammer for a nail I wasn't
really all that interested in nailing ;)  It's true that getToken
might fail.  Most of the program isn't prepared to handle errors
gracefully, but neither was the C version.  That's okay.  If
anything, handling it as an exception and printing out a generic
error message would be more than enough.

Aside from the better error handling, I fear the Maybe monad isn't
buying much.

 Bulat Ziganshin:
 what you need here, imho, is a state monad.

 Danil Fischer
 I'd use a State-monad, say

I suspect you guys are right.  I had always thought of states as
being isomorphic to integers (i.e. you can be in state 0, state 1,
... state n), not as contexts (you have this input, that output, and
this token stack), am I wrong?  I suspect I need to spend more time
trying to understand the state monad.  I must admit that I baulked
the last time I tried to squeeze it into my head.  I'll just need to
try again ;)

 but if you'd done it monadically from
 the start, you'd probably chosen a different design

I specifically chose not to have a radically different design
because I wanted to maintain the nature of the original C code.
Naturally, if I were to try to do this from scratch, I'd use a
powerful lexer and parser.  However, the beauty of this code (i.e.
the original C code) is that it works without *needing* to use or
understand such powerful tools.

 As another method, I've hacked up a translation by parsing a
 declaration and creating a customized Show-instance.

Yeah, I thought of that too, but decided against if for the reason
given above.

Think of camping--sometimes it's fun to rough it.  Sometimes it
can be fun to solve this problem without powerful tools.  Maybe I'm
just being silly ;)

 In My Egotistical Opinion, most people's C programs should be
 indented six feet downward and covered with dirt.

Yeah, yeah ;)

I'm mostly a Python guy, so you're preaching to the choir ;)

Thanks again, guys!!!
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Dropping trailing nulls from a list of list

2006-03-08 Thread Henning Thielemann


On Wed, 8 Mar 2006 [EMAIL PROTECTED] wrote:


Today, I reviewed a function I wrote a few months ago.  The function,
dropTrailNulls, takes a list of lists and drops trailing null lists.  For
instance:

*Main dropTrailNulls [[1],[2,3],[],[]]
[[1],[2,3]]


http://www.haskell.org/pipermail/libraries/2005-August/004217.html
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] Re: Library survey results

2006-03-08 Thread John Hughes

 29% Parsec
 19% wxHaskell
 16% QuickCheck
 16% haddock
 12% Monadic Parser Combinators
 11% Gtk2Hs
 9% hs-plugins
 8% HaXml
 7% Data.*
 7% Monad foundation classes
 6% Arrows
 6% HOpenGL

 The list includes all libraries named by more than 5% of respondents.
 Sure enough, wxHaskell and Gtk2Hs are more popular, but 6% naming
 HOpenGL as among the most important libraries is quite respectable.

 Well, I've never said that it is among the most important 
libraries, but

 OTOH I really much doubt that the way the survey was done delivers
 anything
 near reliable results. It heavily biases early entries, and I dare to
 speculate that the people taking part in the survey were probably not 
even

 near to a representative group, but a bunch of highly motivated,
 experienced
 non-Joe-Programmer kind of people who are actively participating on the
 mailing lists etc.

It wasn't as bad as you think--over 580 replies, with less than a 
quarter of

those from academics (there were actually more replies from people working
in industry than from academics!). So I'd dispute that the survey tells us
mostly about what the research community in particular wants. I'd guess the
survey was pretty representative of KEEN Haskell users. It's a bit unclear
who we mean by Joe Haskell-programmer anyway--I bet that, apart from
students of course, the number of Haskell programmers who are using the
language just because their boss tells them to can be counted on the
fingers of one hand! I'd claim Joe Haskell programmer probably IS keen,
highly motivated, experienced and active. In fact, the one group that is
obviously underrepresented badly in my survey is just students--I got
replies from just under 300, while another survey of teachers shows that at
least 5-10,000 were taught Haskell last year. But maybe tools like hoogle
SHOULD be aimed at the most active users?

You're right that libraries mentioned earlier in the survey received more
votes as a result, but since I have a record of all responses *in time
order* I can see the difference, for each library, between pre- and post-
first mention behaviour. HOpenGL was mentioned in the 7th response,
wxHaskell in the first, and Gtk2Hs in the 17th, so they were in the
previously mentioned category for almost the entire survey, and the 
effect

you're talking about was not significant for a comparison between those
three. Data.*, on the other hand, was first mentioned about half way 
through

the survey, which indicates that around 12% of respondents selected it as
among the most important libraries, when prompted to do so by seeing its
name. However, the proportion who name Data.* spontaneously is below 
2%--and

that conclusion is statistically significant at the 99% level. 580 replies
is enough to say statistically significant things (about the population the
survey sampled, anyway). I feel quite inspired--when I have a spare moment,
I'll analyse the results more carefully and see what one actually CAN say
with a degree of certainty, taking into account when each library was first
mentioned.

 Furthermore, some of the percentages above are extremely
 strange, e.g. how can people use huge GUI toolkits with 30% while staying
 largely away from something as fundamental as Data.*?

I don't find it so strange, really. Data.* implements lots of useful
standard datatypes, but you can import some of them in other ways (import
Maybe for example), and in many cases it's not too hard to roll your own.
OK, maybe with a worse result, but you're not *forced* to use Data.* -- so
if you're used to using something else, there's no 100% compelling 
reason to

change. Rolling your own wxHaskell or Gtk2Hs is prohibitively hard. So I'm
not at all surprised that GUI toolkits rated much higher--people's natural
conservatism gives them a big advantage, and even Haskell users can be
conservative sometimes!

Perhaps the most surprising thing here is that only 30% of keen Haskellers
think a GUI is important!

John


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


Re: [Haskell-cafe] Lists of Lists

2006-03-08 Thread zell_ffhut

Thanks for all the help i've recived through e-mails, but im still stuck on
this

Anyone want to save the day? :(
--
View this message in context: 
http://www.nabble.com/Lists-of-Lists-t1245394.html#a3311541
Sent from the Haskell - Haskell-Cafe forum at Nabble.com.

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


Re: [Haskell-cafe] haskell-prime traffic

2006-03-08 Thread John Meacham
On Wed, Mar 08, 2006 at 10:37:11AM +, Ross Paterson wrote:
 Just for fun, I've put up some statistics on haskell-prime traffic at
 
   http://www.soi.city.ac.uk/~ross/haskell-prime-stats/
 
 I'm not claiming it shows anything, except what a narrow base we have.

I had no idea I was so prolific. I must cut back on the language design
binges. obviously they arn't as healthy as the standard alcohol and food
ones. :)

John

-- 
John Meacham - ⑆repetae.net⑆john⑈
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] | vs. $ (was: request for code review)

2006-03-08 Thread Jared Updike
 I suspect you guys are right.  I had always thought of states as
 being isomorphic to integers (i.e. you can be in state 0, state 1,
 ... state n), not as contexts (you have this input, that output, and
 this token stack), am I wrong?

You're thinking of a state machine, I think, which is not quite what a
state monad would do here. (I have nightmares of writing a
state-machine parser in assembly like I did in an EE class once...
ouch).

  I suspect I need to spend more time
 trying to understand the state monad.  I must admit that I baulked
 the last time I tried to squeeze it into my head.  I'll just need to
 try again ;)

Here's the way I like to think about state in imperative
programs---it's hard because it's not something you can get far away
from enough to see, usually.

In imperative programs, the value of a variable 'a' at one point is
not always the value of the variable 'a' at another point later in the
code. In some sense, each statement that gets executed is passed the
entire state of the machine (the world) implicitly, and then when the
statement ends, it passes the state of the world on to the next
statement. If you want to access the value of the variable 'a', then
'a' gets looked up in the environment/state.
In C/C++/Java/C#/Python/Perl, etc. this is done for you automatically
and efficiently. It's just the way the machine works. But you don't
have the choice to change this or, as someone put it, overload the
semicolon.

In Haskell none of this variable-mutating, state-passing **can**
occur, so it gets created from scratch, and voila, we have the State
Monad. It makes it sound like a lot more work than it should be just
to do something that comes for free in most other languages, but in
these languages, you can't overload the semicolon! And if you could,
who knows what could go wrong at runtime (imagine Perl with semicolon
overloading... I bet some day they will do this just because they
can...). In Haskell, everything is watched over by the type system, so
the parts of your program that explicitly need to munge state are
isolated with the some type tag, e.g. ParseContext, while the rest of
your program is normal and pure and functional.

The problem with monads is not that they are advanced but that they
are so painfully and subtly abstract (I was going to say subtly
simple but maybe they aren't for most working non-Haskell
programmers...). (It just so happens that you **can** do amazing,
convenient, efficient, magic and otherwise advanced things with them,
especially with the libraries.) Another problem is that everyone has
different ways of explaining them or trying to define what they are (a
way of sequencing computation? or a type constructor? or a type
class?). Of course, they are all those things, which makes it even
more confusing. At a certain point, though, I think they just
subconciously click and boom, now you get it.

Anyway, if your goal is to get people to understand Haskell, then see
if you can use monads to simplify things. If your goal is to do a
straight translation of the C code, don't worry about monads.

My 2c,
  Jared.
--
http://www.updike.org/~jared/
reverse )-:
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] A syntax proposal: data replacements

2006-03-08 Thread ihope
I'd like to propose more syntactic sugar more Haskell. (A spoonful of
syntactic sugar makes the medicine go down...)

Put simply, this would provide a smallish bit of pattern matching, and
hopefully clarify some things. A simple example should pretty much
define the whole thing:

fromJust = {Just -- id; Nothing -- error Nothing}

This function takes a single value. If the constructor used to
construct it is Just, then the Just is replaced with id. Likewise, if
it's given Nothing, it will return (error Nothing). Another example:

consPair = {(,) -- (:)}

This takes a pair (x,y) and replaces the constructor (,) with (:),
yielding (x:y). Now, a final clarification:

foldr cons nil = {(:) -- cons; [] -- nil}

This will *not* work: only the top bit of list will be replaced this
way, as data replacements are not recursive.

One last example: the function {Left -- id; Right -- error} takes an
Either a String and either pulls out the a and returns that or uses
the String as an error message.
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Re: MUA written in Haskell, and MTA in Haskell help?

2006-03-08 Thread Donald Bruce Stewart
shae:
 Nils Anders Danielsson [EMAIL PROTECTED] writes:
 
  I had the same thought yesterday, after an Emacs-Lisp session in which
  I was trying to get Gnus to do exactly what I wanted it to...
 
 Yeah, same here. I use Gnus and it's nice, but occasionally I want to erase it
 from the timestream.
 
  Out of curiosity, how much work would it take to write an easily
  configurable, decent MUA in Haskell? I don't know too much about MUAs,
  but I have a feeling that we already have quite a few libraries that
  are needed for the job: UIs (including HTML rendering...), plugins,
  various protocols, encryption...
 
 It wouldn't be too hard. I'd suggest you start with Tuomo Valkonen's Riot[1]
 and go for something like mutt.
 I'm sure you could steal lots of useful code from Peter Simons' Postmaster[2].

Interestingly -- some may not know this -- I originally wrote hs-plugins
to provide Haskell configuration and extension to a planned mutt-like
MUA in Haskell :)

If I was actually going to write one now, I'd start with hmp3 for the
fast, portable curses ui and keystroke handling, and steal the mbox
parsing code from riot. You'd have something working in a day or two,
I'd reckon -- all the code is out there, it just needs to be assembled.

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


Re: [Haskell-cafe] Re: MUA written in Haskell (was: Getting GHC to print Done when it's finished linking?)

2006-03-08 Thread Donald Bruce Stewart
 5) Ideally the scripting language would be Haskell..

 ... I can't find anything which would allow you 
 to compile and load functions into a running program.

From haskell.org:
   hs-plugins
A library for compiling and loading plugins into a running Haskell 
program.

Have a look at:
Dynamic Applications From the Ground Up. Stewart and Chakravarty, 2005
Plugging Haskell In. Pang, Stewart, Seefried, and Chakravarty, 2004

:)

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


Re: [Haskell-cafe] A syntax proposal: data replacements

2006-03-08 Thread Cale Gibbard
On 08/03/06, ihope [EMAIL PROTECTED] wrote:
 I'd like to propose more syntactic sugar more Haskell. (A spoonful of
 syntactic sugar makes the medicine go down...)

 Put simply, this would provide a smallish bit of pattern matching, and
 hopefully clarify some things. A simple example should pretty much
 define the whole thing:

 fromJust = {Just -- id; Nothing -- error Nothing}

 This function takes a single value. If the constructor used to
 construct it is Just, then the Just is replaced with id. Likewise, if
 it's given Nothing, it will return (error Nothing). Another example:

 consPair = {(,) -- (:)}

 This takes a pair (x,y) and replaces the constructor (,) with (:),
 yielding (x:y). Now, a final clarification:

 foldr cons nil = {(:) -- cons; [] -- nil}

 This will *not* work: only the top bit of list will be replaced this
 way, as data replacements are not recursive.

If you're going to do this at all, why not make them recursive? I
suppose that what you want is somewhat the same as allowing partial
application of a constructor in pattern matching, so perhaps there is
a syntax which would reflect that. However, fromJust and consPair are
not awkward functions to write. It might be nice to have some
mechanism for generalised catamorphisms on algebraic datatypes though.

What you're describing is easy to get on any particular type you want.
(Not the exact syntax, but the effect.)

For example,
fromJust = maybe (error Nothing) id
consPair = uncurry (:)
using the catamorphisms for Maybe and (,) respectively.

It would be nice if there was an automatic way to construct functions
like 'maybe' and 'uncurry' and 'foldr' from the structure of the types
alone. You can do that, and many more things, in Generic Haskell.
There's also some provision for generics in GHC, but I'm not sure how
well maintained it is. The docs say that it is currently broken in
5.02 -- I seem to remember trying it more recently and having it work
on a few small tests, but I didn't do much more than play around, so I
don't know if it's horribly flawed or anything.

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


Re: [Haskell-cafe] Lists of Lists

2006-03-08 Thread zell_ffhut

Last attempt, as its due in a couple of hours

Here's what i have so far..

 charToGrid :: Char - Position - Grid - Grid
 charToGrid c [] (row,col) xs = xs
 charToGrid c (row,col) xs = (changeValue c (concat xs (row*9 + col)))

Using changeValue - 

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

Would really appritiate any help
--
View this message in context: 
http://www.nabble.com/Lists-of-Lists-t1245394.html#a3315187
Sent from the Haskell - Haskell-Cafe forum at Nabble.com.

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


Re: [Haskell-cafe] | vs. $ (was: request for code review)

2006-03-08 Thread Shannon -jj Behrens
On 3/8/06, Jared Updike [EMAIL PROTECTED] wrote:
  I suspect you guys are right.  I had always thought of states as
  being isomorphic to integers (i.e. you can be in state 0, state 1,
  ... state n), not as contexts (you have this input, that output, and
  this token stack), am I wrong?

 You're thinking of a state machine, I think, which is not quite what a
 state monad would do here. (I have nightmares of writing a
 state-machine parser in assembly like I did in an EE class once...
 ouch).

   I suspect I need to spend more time
  trying to understand the state monad.  I must admit that I baulked
  the last time I tried to squeeze it into my head.  I'll just need to
  try again ;)

 Here's the way I like to think about state in imperative
 programs---it's hard because it's not something you can get far away
 from enough to see, usually.

 In imperative programs, the value of a variable 'a' at one point is
 not always the value of the variable 'a' at another point later in the
 code. In some sense, each statement that gets executed is passed the
 entire state of the machine (the world) implicitly, and then when the
 statement ends, it passes the state of the world on to the next
 statement. If you want to access the value of the variable 'a', then
 'a' gets looked up in the environment/state.
 In C/C++/Java/C#/Python/Perl, etc. this is done for you automatically
 and efficiently. It's just the way the machine works. But you don't
 have the choice to change this or, as someone put it, overload the
 semicolon.

 In Haskell none of this variable-mutating, state-passing **can**
 occur, so it gets created from scratch, and voila, we have the State
 Monad. It makes it sound like a lot more work than it should be just
 to do something that comes for free in most other languages, but in
 these languages, you can't overload the semicolon! And if you could,
 who knows what could go wrong at runtime (imagine Perl with semicolon
 overloading... I bet some day they will do this just because they
 can...). In Haskell, everything is watched over by the type system, so
 the parts of your program that explicitly need to munge state are
 isolated with the some type tag, e.g. ParseContext, while the rest of
 your program is normal and pure and functional.

 The problem with monads is not that they are advanced but that they
 are so painfully and subtly abstract (I was going to say subtly
 simple but maybe they aren't for most working non-Haskell
 programmers...). (It just so happens that you **can** do amazing,
 convenient, efficient, magic and otherwise advanced things with them,
 especially with the libraries.) Another problem is that everyone has
 different ways of explaining them or trying to define what they are (a
 way of sequencing computation? or a type constructor? or a type
 class?). Of course, they are all those things, which makes it even
 more confusing. At a certain point, though, I think they just
 subconciously click and boom, now you get it.

 Anyway, if your goal is to get people to understand Haskell, then see
 if you can use monads to simplify things. If your goal is to do a
 straight translation of the C code, don't worry about monads.

Dude, that was a friggin' awesome email!  I'm trying to figure out how
I can just copy it wholesale into the article ;)  I've been struggling
with Haskell for long enough that my knowledge is now snowballing
downhill.  Everything you said made sense 100%.

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


Re: [Haskell-cafe] | vs. $ (was: request for code review)

2006-03-08 Thread Shannon -jj Behrens
On 3/8/06, Shannon -jj Behrens [EMAIL PROTECTED] wrote:
 On 3/8/06, Jared Updike [EMAIL PROTECTED] wrote:
   I suspect you guys are right.  I had always thought of states as
   being isomorphic to integers (i.e. you can be in state 0, state 1,
   ... state n), not as contexts (you have this input, that output, and
   this token stack), am I wrong?
 
  You're thinking of a state machine, I think, which is not quite what a
  state monad would do here. (I have nightmares of writing a
  state-machine parser in assembly like I did in an EE class once...
  ouch).
 
I suspect I need to spend more time
   trying to understand the state monad.  I must admit that I baulked
   the last time I tried to squeeze it into my head.  I'll just need to
   try again ;)
 
  Here's the way I like to think about state in imperative
  programs---it's hard because it's not something you can get far away
  from enough to see, usually.
 
  In imperative programs, the value of a variable 'a' at one point is
  not always the value of the variable 'a' at another point later in the
  code. In some sense, each statement that gets executed is passed the
  entire state of the machine (the world) implicitly, and then when the
  statement ends, it passes the state of the world on to the next
  statement. If you want to access the value of the variable 'a', then
  'a' gets looked up in the environment/state.
  In C/C++/Java/C#/Python/Perl, etc. this is done for you automatically
  and efficiently. It's just the way the machine works. But you don't
  have the choice to change this or, as someone put it, overload the
  semicolon.
 
  In Haskell none of this variable-mutating, state-passing **can**
  occur, so it gets created from scratch, and voila, we have the State
  Monad. It makes it sound like a lot more work than it should be just
  to do something that comes for free in most other languages, but in
  these languages, you can't overload the semicolon! And if you could,
  who knows what could go wrong at runtime (imagine Perl with semicolon
  overloading... I bet some day they will do this just because they
  can...). In Haskell, everything is watched over by the type system, so
  the parts of your program that explicitly need to munge state are
  isolated with the some type tag, e.g. ParseContext, while the rest of
  your program is normal and pure and functional.
 
  The problem with monads is not that they are advanced but that they
  are so painfully and subtly abstract (I was going to say subtly
  simple but maybe they aren't for most working non-Haskell
  programmers...). (It just so happens that you **can** do amazing,
  convenient, efficient, magic and otherwise advanced things with them,
  especially with the libraries.) Another problem is that everyone has
  different ways of explaining them or trying to define what they are (a
  way of sequencing computation? or a type constructor? or a type
  class?). Of course, they are all those things, which makes it even
  more confusing. At a certain point, though, I think they just
  subconciously click and boom, now you get it.
 
  Anyway, if your goal is to get people to understand Haskell, then see
  if you can use monads to simplify things. If your goal is to do a
  straight translation of the C code, don't worry about monads.

 Dude, that was a friggin' awesome email!  I'm trying to figure out how
 I can just copy it wholesale into the article ;)  I've been struggling
 with Haskell for long enough that my knowledge is now snowballing
 downhill.  Everything you said made sense 100%.

Yes, having read more, I can see clearly that the State monad was what
I was looking for.  Consider:

http://www.nomaware.com/monads/html/statemonad.html
A pure functional language cannot update values in place because it
violates referential transparency. A common idiom to simulate such
stateful computations is to thread a state parameter through a
sequence of functions...This approach works, but such code can be
error-prone, messy and difficult to maintain. The State monad hides
the threading of the state parameter inside the binding operation,
simultaneously making the code easier to write, easier to read and
easier to modify.
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe