[Haskell-cafe] ANNOUNCE: grammar-combinators 0.1 (initial release): A parsing library of context-free grammar combinators

2010-09-08 Thread Dominique Devriese
The grammar-combinators library is a parsing library employing a novel
grammar representation with explicit recursion. The library features
much of the power of a parser generator like Happy or ANTLR, but with
the library approach and most of the benefits of a parser combinator
library. Grammars and grammar algorithms are defined in a
functional style. The library currently has the following features:

* Grammar specified completely in Haskell using an elegant syntax
* Grammar algorithms implemented in a functional style (no fresh
 identifiers), with elegant and meaningful types.
* Multi-backend: use the same grammar with a Packrat, Parsec or
 UUParse parser
* Grammar transformations: use left-recursive grammars directly thanks
 to a powerful grammar transformation library, featuring the
 left-corner left-recursion removal transform, a uniform version of
 the classic Paull left-recursion removal, and various smaller
 transformations (dead-branch removal, dead non-terminal removal,
 consecutive epsilon combination, selective unfolding etc.).
* Grammar utility functions: printing of grammars, FIRST-set
 calculation, reachability analysis of non-terminals, etc.
* Compile-time transformations (using Template Haskell), given a
 suitable definition of the grammar. This is currently limited to a
 certain set of transformations.

The library is currently not intended for mainstream use. Its API is
relatively stable, but performance needs to be looked at further.

We are submitting a paper about the ideas behind this library to PADL
2011. A draft is linked on the project's website.

More information:

* Project website: http://projects.haskell.org/grammar-combinators/
* Tutorial: http://projects.haskell.org/grammar-combinators/tutorial.html
* Hackage: http://hackage.haskell.org/package/grammar-combinators

All comments welcome!

Dominique

PS. The documentation on hackage currently doesn't build because of
(seemingly) a Hackage dependency problem during the build [1].
Compiling and generating the documentation locally should work fine. A
version of the docs is available on the project's webpage as a
temporary replacement [2].

Footnotes:
[1]  http://www.haskell.org/pipermail/libraries/2010-September/014168.html
[2]  http://projects.haskell.org/grammar-combinators/docs/index.html
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] ANNOUNCE: game-probability-1.1

2010-09-08 Thread Neil Brown

Hi,

I've just released version 1.1 of my game-probability library.  It's 
intended to be an easy way to investigate the probability of various 
dice rolls and card draws (the latter is the new addition for the 1.1 
release), using a Haskell library/EDSL.  It has various examples in the 
documentation, plus a few blog posts on its design (all links below).


Hackage: http://hackage.haskell.org/package/game-probability
Docs (while waiting for Hackage to generate): 
http://twistedsquare.com/game-probability-1.1/

Blog posts:
http://chplib.wordpress.com/2010/08/13/nice-dice-in-haskell/
http://chplib.wordpress.com/2010/08/23/sharp-cards-in-haskell-drawing-cards/
http://chplib.wordpress.com/2010/09/08/sharp-cards-in-haskell-the-odds/

As a quick taster, below are some examples of using the library.

Showing the probabilities of a dice roll prints out a bar chart -- here 
is the sum of two six-sided dice:



 show (2 * d6)

2 : #
3 : ##
4 : ###
5 : 
6 : #
7 : ##
8 : #
9 : 
10: ###
11: ##
12: #

Querying probabilities of the outcomes of dice rolls:


 chancePred (= 16) (3*d6)

5 % 108

The chance of drawing different numbers of Copper cards in a starting 
hand of 5 drawn from 7 Copper and 3 Estate (this is from the card game 
Dominion):



 chanceMap (makeCards $ replicate 7 Copper ++ replicate 3 Estate) (drawCount (== 
Copper) 5)

fromList [(2,1 % 12),(3,5 % 12),(4,5 % 12),(5,1 % 12)]


Thanks,

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


[Haskell-cafe] Re: ANNOUNCE: grammar-combinators 0.1 (initial release): A parsing library of context-free grammar combinators

2010-09-08 Thread Dominique Devriese
Some snippets from the Tutorial [1] to give an idea of the
grammar-combinator library's approach, its functional style and its
additional power (e.g. the transformations used):

Defining a simple expresssions grammar:
  grammarArith :: ExtendedContextFreeGrammar ArithDomain Char
  grammarArith Line =
LineF $ ref Expr * endOfInput
  grammarArith Expr =
SubtractionF $  ref Expr * token '-'  ref Term
||| SumF $  ref Expr * token '+'  ref Term
||| SingleTermF $   ref Term
  grammarArith Term =
SingleFactorF $ ref Factor
||| QuotientF $ ref Term * token '/'  ref Factor
||| ProductF $  ref Term * token '*'  ref Factor
  grammarArith Factor =
NumberF $   many1Ref Digit
||| ParenthesizedF $*   token '('  ref Expr * token ')'
  grammarArith Digit =
DigitF $tokenRange ['0' .. '9']

A semantic processor:
  data family ArithValue ix
  newtype instance ArithValue Line   = ArithValueL Int deriving (Show)
  newtype instance ArithValue Expr   = ArithValueE Int deriving (Show)
  newtype instance ArithValue Term   = ArithValueT Int deriving (Show)
  newtype instance ArithValue Factor = ArithValueF Int deriving (Show)
  newtype instance ArithValue Digit  = ArithValueD Char deriving (Show)

  calcArith :: Processor ArithDomain ArithValue
  calcArith Line   (LineF (ArithValueE e))= ArithValueL e
  calcArith Expr   (SumF (ArithValueE e) (ArithValueT t)) =
ArithValueE $ e + t
  calcArith Expr   (SingleTermF (ArithValueT t))  = ArithValueE t
  calcArith Term   (ProductF (ArithValueT e) (ArithValueF t)) =
ArithValueT $ e * t
  calcArith Term   (SingleFactorF (ArithValueF t))= ArithValueT t
  calcArith Factor (ParenthesizedF (ArithValueE e))   = ArithValueF e
  calcArith Factor (NumberF ds)   =
ArithValueF $ read $ map unArithValueD ds
  calcArith Digit  (DigitF c) = ArithValueD c

  unArithValueD :: ArithValue Digit - Char
  unArithValueD (ArithValueD c) = c

Transforming the grammar:
  calcGrammarArith :: ProcessingExtendedContextFreeGrammar ArithDomain
Char ArithValue
  calcGrammarArith = applyProcessorE grammarArith calcArith
  calcGrammarArithTP :: ProcessingExtendedContextFreeGrammar (UPDomain
ArithDomain) Char (UPValue ArithValue)
  calcGrammarArithTP = transformUniformPaullE calcGrammarArith
  calcGrammarArithTPF :: ProcessingExtendedContextFreeGrammar
(UPDomain ArithDomain) Char (UPValue ArithValue)
  calcGrammarArithTPF = filterDiesE (unfoldDeadE calcGrammarArithTP)
  calcGrammarArithTPFF :: ProcessingContextFreeGrammar
(FoldLoopsDomain (UPDomain ArithDomain)) Char (FoldLoopsValue (UPValue
ArithValue))
  calcGrammarArithTPFF = foldAndProcessLoops calcGrammarArithTPF

Parsing:
  *Main parsePackrat calcGrammarArithTPFF (FLBase (UPBase Line)) 123
  Parsed FLBV {unFLBV = UPBV {unUPBV = ArithValueL 123}} _
  *Main parsePackrat calcGrammarArithTPFF (FLBase (UPBase Line)) 123+
  NoParse
  *Main parsePackrat calcGrammarArithTPFF (FLBase (UPBase Line)) 123+12
  Parsed FLBV {unFLBV = UPBV {unUPBV = ArithValueL 135}} _
  *Main parseParsec calcGrammarArithTPFF (FLBase (UPBase Line))  123+12
  Right (FLBV {unFLBV = UPBV {unUPBV = ArithValueL 135}})
  *Main parseUU calcGrammarArithTPFF (FLBase (UPBase Line)) 123+12
  FLBV {unFLBV = UPBV {unUPBV = ArithValueL 135}}

Dominique

Footnotes:
[1]  http://projects.haskell.org/grammar-combinators/tutorial.html
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] Did anyone manage to build glade hackage-package on Windows

2010-09-08 Thread Daniel Kahlenberg
Hi list again,

if there is anyone who managed to build the glade package on the Windows
platform, could you please tell me the installer package for glade you used,
possibly the version and download source too? Installing gtk2hs now seems
made really simply by the guys providing it and I installed and tested it
successfully on a Windows machine. Where I'm stucking is the glade/libglade
thing. I took the version from
http://ftp.gnome.org/pub/GNOME/binaries/win32/libglade/2.6/ for a start and
installed some http://ftp.gnome.org/pub/GNOME/binaries/win32/dependencies/too,
but when running the cabal-configure step it halts with the oh so
familiar:

* Missing C libraries: glade-2.0, gtk-win32-2.0, xml2, gdk-win32-2.0,
atk-1.0,
gio-2.0, gdk_pixbuf-2.0, pangowin32-1.0, gdi32, pangocairo-1.0, pango-1.0,
cairo, gobject-2.0, gmodule-2.0, glib-2.0, intl

This is my user ghc-pkg cache list:
...APPDATA...\ghc\i386-mingw32-6.12.3\package.conf.d:
SDL-0.6.2
base64-bytestring-0.1.0.0
cairo-0.11.1
gio-0.11.1
glib-0.11.2
gtk-0.11.2
pango-0.11.2
random-1.0.0.2

And my pkg-config output:
cmd pkg-config --cflags --libs gtk+-2.0 libglade-2.0
-mms-bitfields -IH:/takeoffgw/i686-pc-mingw32/sys-root/mingw/include/libxml2
-IH
:/takeoffgw/usr/local/include/gtk-2.0
-IH:/takeoffgw/usr/local/lib/gtk-2.0/inclu
de -IH:/takeoffgw/usr/local/include/atk-1.0
-IH:/takeoffgw/usr/local/include/cai
ro -IH:/takeoffgw/usr/local/include/pango-1.0
-IH:/takeoffgw/usr/local/include/g
lib-2.0 -IH:/takeoffgw/usr/local/lib/glib-2.0/include
-IH:/takeoffgw/usr/local/i
nclude/freetype2 -IH:/takeoffgw/usr/local/include
-IH:/takeoffgw/usr/local/inclu
de/libpng14 -IH:/takeoffgw/usr/local/include/libglade-2.0
-LH:/takeoffgw/i686-p
c-mingw32/sys-root/mingw/lib -LH:/takeoffgw/usr/local/lib -lglade-2.0
-lgtk-win3
2-2.0 -lxml2 -lgdk-win32-2.0 -latk-1.0 -lgio-2.0 -lgdk_pixbuf-2.0
-lpangowin32-1
.0 -lgdi32 -lpangocairo-1.0 -lpango-1.0 -lcairo -lgobject-2.0 -lgmodule-2.0
-lgt
hread-2.0 -lglib-2.0 -lintl
ExitSuccess
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] Re: Crypto-API is stabilizing

2010-09-08 Thread Heinrich Apfelmus

Thomas DuBuisson wrote:

Sorry, the example was all messed up, even if it did communicate what
I wanted its just so broken I must fix.

Slightly contrived example:

   buildAgreementMessage :: (Monad m, CryptoRandomGen g,
ASymetricCipher k) = g - k - m (B.ByteString, (k,k), g)
   buildAgreementMessages g k = do
   ((p,q),g') - eitherToFail (buildKeyPair g)
   let pBS = encode p
   msg = runPut $ do
   putByteString agreementHeader
   putWord16be (B.length pBS)
   putByteString pBS
   return $ (sign msg k, (p,q), g')

Again, this is simply trying to re-enforce the fact that buildKeyPair
(formerly 'generateKeyPair') does have a place.


Granted.

However, the key feature of your example is that a new key is derived 
from an old key, i.e. the function used is


type BuildKeyPair g k = CryptoRandomGen g = g - ((k,k),g)

buildKeyPair' :: k - BuildKeyPair g k

Thanks to the additional argument, this can be added to the  Key  record

data Key = Key { cipher :: BuildKeyPair g k , ... }

In other words, the  Key  can also store a method to generate new keys 
with the same cipher algorithm.



All examples that use  buildKeyPair  and type classes can be 
reformulated in terms of  Key  with this additional field. That's 
because  buildKeyPair  actually expects a type argument; the  cipher 
filed merely shifts that argument to the value level.



Regards,
Heinrich Apfelmus

--
http://apfelmus.nfshost.com

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


Re: [Haskell-cafe] ANNOUNCE: text 0.8.0.0, fast Unicode text support

2010-09-08 Thread Daniel Fischer
On Wednesday 08 September 2010 06:44:32, Bryan O'Sullivan wrote:
 I have a Replace.hs benchmark in the main text repo, just to be sure
 we're talking about the same thing.

Grabbed the darcs repo, compiled with the darcs version and also with the 
installed text package, both exhibit the same behaviour - what I reported 
before.

 Factoring out the time spent on I/O,
 with GHC HEAD, my replace code takes twice the space and time of that in
 the stringsearch package.

That's very good. Twice the space is a given for mostly ASCII text, twice 
the time is okay, I think.
My timings are quite different, but that's probably because 6.12.3's 
inliner doesn't give the full fusion benefit, so it'll improve 
automatically with the next GHC release.

 Given that the space involved is just 121KB
 maximum residency while processing a 124MB file, I'm not concerned about
 it.

I wouldn't either.

 And the time required isn't a bad place to start from, I think.

 By the way, as this implies, I can't reproduce your space behaviour at
 all.


That's surprising.
Have you made sure to replace a pattern which does not occur in the text?
Can you reproduce the behaviour with a) Data.List.intersperse instead of 
the lazier version now used, b) ghc-6.12.* instead of HEAD?

Anyway, I would've thought that with

split pat src
| null pat= emptyError split
| isSingleton pat = splitBy (== head pat) src
| otherwise   = go 0 (indices pat src) src
  where
go  _ [] cs = [cs]
go !i (x:xs) cs = let h :*: t = splitAtWord (x-i) cs
  in  h : go (x+l) xs (dropWords l t)
l = foldlChunks (\a (T.Text _ _ b) - a + fromIntegral b) 0 pat

you can't start returning chunks before it's known whether the list of 
indices is empty, so split would have O(index of pattern) space behaviour.

If HEAD manages to make the chunks available before they are complete 
(before it's known how long they will be), it's even awesomer than I'd have 
dared to hope.
Okay, so I'll have to try HEAD.

  I can now say more. Looking at Data.Text.Lazy.replace,
 
  replace s d = intercalate d . split s
 
  , I also got a space leak with that for BS.Lazy's intercalate and
 
  stringsearch's split.

 How did you observe the space leak? Looking at -hT charted with hp2ps
 shows me nothing, and the program executes in constant space regardless
 of input size.

top and +RTS -s. I've attached the -hT graph of a run on a 74.3MB file with 
a pattern that does not occur. It shows exactly the behaviour I expected 
from the code of split, pretty constant growth of the heap until about 
twice the file size is reached, then fast and pretty constant shrinking as 
the text is output. The graphs are much more interesting if you do 
replacements of patterns without large gaps between occurrences.



nbenchText.ps
Description: PostScript document
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] Re: ANNOUNCE: grammar-combinators 0.1 (initial release): A parsing library of context-free grammar combinators

2010-09-08 Thread Johannes Waldmann

 .. grammar-combinator library's approach ..

am I reading this correctly: in the traditional combinator approach,
a grammer (a parser) is a Haskell value,
while in your approach, the grammar is a Haskell (GAD)type?

then you'll get more static guarantees (e.g., context-freeness)
but you need extra (type-level, or even syntax-level) machinery
to handle grammars. Convince me that it's worth it ...

I guess the proper solution (TM) is to blur the distiction
between types and values by switching to dependent types altogether...

J.W.


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


[Haskell-cafe] Unwrapping newtypes

2010-09-08 Thread Kevin Jardine
I have a generic object that I want to wrap in various newtypes to
better facilitate type checking.

For example,

newtype Blog = Blog Obj
newtype Comment = Comment Obj
newtype User = User Obj

Unlike Obj itself, whose internal structure is hidden in a library
module, the newtype wrappings are purely to facilitate type checking.
It is no secret that each is just a wrapper around Obj.

It is obvious how to construct the various wrapper objects. It is not
so obvious how to extract the Obj they contain in a reasonably generic
way however. What I want is a getObj function that works on all of
them.

Of course this could work if someone using the library wrote an
instance for each wrapper object:

instance GetObject Blog where
getObj (Blog obj) = obj

but this is a pain in the neck to write for each newtype.

I discovered that Foldable defines a handy toList function that
extracts content from generic Foldable structures.

So that I could write:

toObj :: Foldable thing = thing Obj - Obj
toObj w = head $ toList w

Slightly kludgy but it works.

Even better, recent versions of GHC will allow you to automatically
derive Foldable.

Unfortunately,

newtype Blog = Blog Obj deriving Foldable

returns a kind error.

What does work is:

newtype BlogF a = Blog a deriving Foldable
type Blog = BlogF Obj

After having spent close to a day on this, I am a bit baffled that
such a seemingly trivial problem seems so hard to do.

I am wondering if I am missing something really, really obvious.

Any suggestions? Or is there perhaps a more Haskelly way to place type
constraints on a more generic type?

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


Re: [Haskell-cafe] Unwrapping newtypes

2010-09-08 Thread Tony Morris
I think you might want -XGeneralizedNewtypeDeriving

http://haskell.org/ghc/docs/6.12.2/html/users_guide/deriving.html#id659906

On 08/09/10 22:01, Kevin Jardine wrote:
 I have a generic object that I want to wrap in various newtypes to
 better facilitate type checking.

 For example,

 newtype Blog = Blog Obj
 newtype Comment = Comment Obj
 newtype User = User Obj

 Unlike Obj itself, whose internal structure is hidden in a library
 module, the newtype wrappings are purely to facilitate type checking.
 It is no secret that each is just a wrapper around Obj.

 It is obvious how to construct the various wrapper objects. It is not
 so obvious how to extract the Obj they contain in a reasonably generic
 way however. What I want is a getObj function that works on all of
 them.

 Of course this could work if someone using the library wrote an
 instance for each wrapper object:

 instance GetObject Blog where
 getObj (Blog obj) = obj

 but this is a pain in the neck to write for each newtype.

 I discovered that Foldable defines a handy toList function that
 extracts content from generic Foldable structures.

 So that I could write:

 toObj :: Foldable thing = thing Obj - Obj
 toObj w = head $ toList w

 Slightly kludgy but it works.

 Even better, recent versions of GHC will allow you to automatically
 derive Foldable.

 Unfortunately,

 newtype Blog = Blog Obj deriving Foldable

 returns a kind error.

 What does work is:

 newtype BlogF a = Blog a deriving Foldable
 type Blog = BlogF Obj

 After having spent close to a day on this, I am a bit baffled that
 such a seemingly trivial problem seems so hard to do.

 I am wondering if I am missing something really, really obvious.

 Any suggestions? Or is there perhaps a more Haskelly way to place type
 constraints on a more generic type?

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

   

-- 
Tony Morris
http://tmorris.net/


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


[Haskell-cafe] Re: Unwrapping newtypes

2010-09-08 Thread Kevin Jardine
Hi Tony,

I stared at that specific section for at least half an hour earlier
today but could not figure out how it applied in my specific case. The
only examples I have see are for deriving Num. Do you have any more
detail on how I could use that extension?

Kevin

On Sep 8, 2:05 pm, Tony Morris tonymor...@gmail.com wrote:
 I think you might want -XGeneralizedNewtypeDeriving

 http://haskell.org/ghc/docs/6.12.2/html/users_guide/deriving.html#id6...

 On 08/09/10 22:01, Kevin Jardine wrote:



  I have a generic object that I want to wrap in various newtypes to
  better facilitate type checking.

  For example,

  newtype Blog = Blog Obj
  newtype Comment = Comment Obj
  newtype User = User Obj

  Unlike Obj itself, whose internal structure is hidden in a library
  module, the newtype wrappings are purely to facilitate type checking.
  It is no secret that each is just a wrapper around Obj.

  It is obvious how to construct the various wrapper objects. It is not
  so obvious how to extract the Obj they contain in a reasonably generic
  way however. What I want is a getObj function that works on all of
  them.

  Of course this could work if someone using the library wrote an
  instance for each wrapper object:

  instance GetObject Blog where
      getObj (Blog obj) = obj

  but this is a pain in the neck to write for each newtype.

  I discovered that Foldable defines a handy toList function that
  extracts content from generic Foldable structures.

  So that I could write:

  toObj :: Foldable thing = thing Obj - Obj
  toObj w = head $ toList w

  Slightly kludgy but it works.

  Even better, recent versions of GHC will allow you to automatically
  derive Foldable.

  Unfortunately,

  newtype Blog = Blog Obj deriving Foldable

  returns a kind error.

  What does work is:

  newtype BlogF a = Blog a deriving Foldable
  type Blog = BlogF Obj

  After having spent close to a day on this, I am a bit baffled that
  such a seemingly trivial problem seems so hard to do.

  I am wondering if I am missing something really, really obvious.

  Any suggestions? Or is there perhaps a more Haskelly way to place type
  constraints on a more generic type?

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

 --
 Tony Morrishttp://tmorris.net/

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


Re: [Haskell-cafe] Re: Unwrapping newtypes

2010-09-08 Thread Tony Morris


On 08/09/10 22:19, Kevin Jardine wrote:
 Hi Tony,

 I stared at that specific section for at least half an hour earlier
 today but could not figure out how it applied in my specific case. The
 only examples I have see are for deriving Num. Do you have any more
 detail on how I could use that extension?

   
Here is an example:

{-# LANGUAGE GeneralizedNewtypeDeriving #-}

class C a where
  c :: a - Int

data G = G

instance C G where
  c _ = 7

newtype H = H G deriving C

-- 
Tony Morris
http://tmorris.net/


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


Re: [Haskell-cafe] Re: ANNOUNCE: grammar-combinators 0.1 (initial release): A parsing library of context-free grammar combinators

2010-09-08 Thread James Andrew Cook
On Sep 8, 2010, at 7:49 AM, Johannes Waldmann wrote:

 then you'll get more static guarantees (e.g., context-freeness)
 but you need extra (type-level, or even syntax-level) machinery
 to handle grammars. Convince me that it's worth it ...

Those guarantees, along with just the fact that the parser specification is 
data rather than a black-box function, explicitly make possible some very cool 
stuff, not least of which is true parser-generator-quality parsers.  Just like 
a regex can be compiled once and then run repeatedly very fast, a context-free 
grammar can be compiled once to a stack-machine specification and run 
repeatedly.  That compilation process is highly nonlocal and would never be 
possible with, e.g., the Parsec approach.  On the other hand, parser generators 
such as Happy (which perform just such a transformation) cannot allow you to 
construct a grammar at run-time.

Even if you end up deploying a parser using a different framework, the grammar 
transformation stuff is pretty cool too.  By specifying your grammar in this 
system, you get to play around with it, transform it, etc., and see what the 
transformed grammar looks like.

Incidentally, it'd be pretty nifty if someone made a Happy backend, or even 
just a TH snippet, that generated a grammar-combinators grammar and semantic 
action from a Happy parser specification.

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


Re: [Haskell-cafe] Re: Unwrapping newtypes

2010-09-08 Thread James Andrew Cook
On Sep 8, 2010, at 8:19 AM, Kevin Jardine wrote:

 Hi Tony,
 
 I stared at that specific section for at least half an hour earlier
 today but could not figure out how it applied in my specific case. The
 only examples I have see are for deriving Num. Do you have any more
 detail on how I could use that extension?
 
 Kevin
 
 On Sep 8, 2:05 pm, Tony Morris tonymor...@gmail.com wrote:
 I think you might want -XGeneralizedNewtypeDeriving
 
 http://haskell.org/ghc/docs/6.12.2/html/users_guide/deriving.html#id6...
 
 On 08/09/10 22:01, Kevin Jardine wrote:
 

I'm not sure if it's what he originally had in mind, but if your Obj class has 
a ToObj instance (which would be reasonable), then that extension allows your 
other classes to derive it:

 newtype Foo = Foo Obj deriving ToObj

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


[Haskell-cafe] Re: Unwrapping newtypes

2010-09-08 Thread Kevin Jardine
Hi Tony and James,

I'm having trouble constructing the ToObj instance.

The obvious code:

toObj (w o) = o

fails with a syntax error.

How do I unwrap the value?

Kevin

On Sep 8, 2:30 pm, James Andrew Cook mo...@deepbondi.net wrote:
 On Sep 8, 2010, at 8:19 AM, Kevin Jardine wrote:



  Hi Tony,

  I stared at that specific section for at least half an hour earlier
  today but could not figure out how it applied in my specific case. The
  only examples I have see are for deriving Num. Do you have any more
  detail on how I could use that extension?

  Kevin

  On Sep 8, 2:05 pm, Tony Morris tonymor...@gmail.com wrote:
  I think you might want -XGeneralizedNewtypeDeriving

 http://haskell.org/ghc/docs/6.12.2/html/users_guide/deriving.html#id6...

  On 08/09/10 22:01, Kevin Jardine wrote:

 I'm not sure if it's what he originally had in mind, but if your Obj class 
 has a ToObj instance (which would be reasonable), then that extension allows 
 your other classes to derive it:

  newtype Foo = Foo Obj deriving ToObj

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


Re: [Haskell-cafe] Re: ghc HEAD

2010-09-08 Thread James Andrew Cook
In many cases it would make quite a lot of sense for the developer to be able 
to specify default flags as well, preferably without resorting to including a C 
file.  Generally, the developer will know better than the user whether it makes 
sense to include -N, the various thread affinity options, the default 
stack/heap size, etc.  Bonus points for a sensible monoid allowing each library 
to contribute to the decision for an executable with no declared preference :).

Ideally, the user would be able to specify constraints on those sorts of things 
globally, once for all, perhaps in their cabal configuration (since I for one 
don't want any program to give itself a default stack size of 2G without my 
knowledge just because the author couldn't be bothered to track down a space 
leak).  The packages would specify what they want, and cabal would give it to 
them, within the bounds of the user's constraints.

It certainly would not be a trivial undertaking to define the proper behavior 
of such a system, but if I were gonna wish for a miracle in this area, I think 
that's the direction I'd be dreaming in.

-- James

On Sep 7, 2010, at 9:51 PM, Ivan Lazar Miljenovic wrote:

 On 8 September 2010 02:37, Brandon S Allbery KF8NH allb...@ece.cmu.edu 
 wrote:
 A better fix would be to identify safe settings and only allow those (and
 only via +RTS) when setuid.  OTOH that's pretty much the system
 configuration version of the Halting Problem :)
 
 Or optionally, allow the developer to specify which flags are safe
 (e.g. users are allowed to specify -N).
 
 -- 
 Ivan Lazar Miljenovic
 ivan.miljeno...@gmail.com
 IvanMiljenovic.wordpress.com
 ___
 Haskell-Cafe mailing list
 Haskell-Cafe@haskell.org
 http://www.haskell.org/mailman/listinfo/haskell-cafe
 

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


[Haskell-cafe] Re: Unwrapping newtypes

2010-09-08 Thread Kevin Jardine
Ah, I was missing an important piece of the puzzle.

If I write:

class ToObj a where
toObj :: a - Obj

instance ToObj Obj where
toObj a = a

then

newtype Blog = Blog Obj deriving ToObj

works!

Thanks.

On Sep 8, 2:36 pm, Kevin Jardine kevinjard...@gmail.com wrote:
 Hi Tony and James,

 I'm having trouble constructing the ToObj instance.

 The obvious code:

 toObj (w o) = o

 fails with a syntax error.

 How do I unwrap the value?

 Kevin

 On Sep 8, 2:30 pm, James Andrew Cook mo...@deepbondi.net wrote:

  On Sep 8, 2010, at 8:19 AM, Kevin Jardine wrote:

   Hi Tony,

   I stared at that specific section for at least half an hour earlier
   today but could not figure out how it applied in my specific case. The
   only examples I have see are for deriving Num. Do you have any more
   detail on how I could use that extension?

   Kevin

   On Sep 8, 2:05 pm, Tony Morris tonymor...@gmail.com wrote:
   I think you might want -XGeneralizedNewtypeDeriving

  http://haskell.org/ghc/docs/6.12.2/html/users_guide/deriving.html#id6...

   On 08/09/10 22:01, Kevin Jardine wrote:

  I'm not sure if it's what he originally had in mind, but if your Obj class 
  has a ToObj instance (which would be reasonable), then that extension 
  allows your other classes to derive it:

   newtype Foo = Foo Obj deriving ToObj

  -- James___
  Haskell-Cafe mailing list
  haskell-c...@haskell.orghttp://www.haskell.org/mailman/listinfo/haskell-cafe

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


[Haskell-cafe] Re: ANNOUNCE: grammar-combinators 0.1 (initial release): A parsing library of context-free grammar combinators

2010-09-08 Thread Johannes Waldmann

 That compilation process is highly nonlocal 
 and would never be possible with, e.g., the Parsec approach. 

Pipe dream: attach such a grammar object to every Parsec parser,
and include the compiler with the combinators,
and have them run at (Haskell) compile time (in ghc's specializer).
Should work for some subset (e.g., just let, not letrec, use
proper combinators instead) and with some future ghc version ...

When I teach parsing (in Compiler Construction), for lack of time 
it's either traditional (CFG - PDA) or combinator (not both),
and I'm not happy with that, since both are important concepts.
But then, semantics is more important than syntax ...

J.W.


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


[Haskell-cafe] Re: Unwrapping newtypes

2010-09-08 Thread Arie Peterson
On Wed, 8 Sep 2010 05:51:22 -0700 (PDT), Kevin Jardine
kevinjard...@gmail.com wrote:
 Ah, I was missing an important piece of the puzzle.
 
 If I write:
 
 class ToObj a where
 toObj :: a - Obj
 
 instance ToObj Obj where
 toObj a = a
 
 then
 
 newtype Blog = Blog Obj deriving ToObj
 
 works!

This post
http://www.haskell.org/pipermail/libraries/2006-October/005950.html
describes a general mini-library for this situation (having a
structure-indicating newtype of an underlying type). The 'Unpack' class
is a generalised version of your 'ToObj' class. Maybe it is useful to
compare (or even use), especially the smart ways in which you can use
this class to hide much of the wrapping/unwrapping.


Regards,

Arie

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


Re: [Haskell-cafe] Re: ANNOUNCE: grammar-combinators 0.1 (initial release): A parsing library of context-free grammar combinators

2010-09-08 Thread Dominique Devriese
Johannes,

(sorry for the double mail)

I will give some short answers below, but you can find more details in
the paper we are submitting to PADL 2011 [1].

2010/9/8 Johannes Waldmann waldm...@imn.htwk-leipzig.de:
 .. grammar-combinator library's approach ..
 am I reading this correctly: in the traditional combinator approach,
 a grammer (a parser) is a Haskell value,
 while in your approach, the grammar is a Haskell (GAD)type?

Not completely. A grammar-combinators grammar is a Haskell value with
a different (more complicated) type than a traditional parser
combinator value. It is actually a function that returns the
production rules for a given non-terminal. Because the non-terminals
are modelled using a GADT and do not have the same type, the grammar's
production rules' types can depend on the non-terminal in question.

 then you'll get more static guarantees (e.g., context-freeness)
 but you need extra (type-level, or even syntax-level) machinery
 to handle grammars. Convince me that it's worth it ...

The advantage of the grammar-combinators approach is that grammar
algorithms have a lot more power, because they can reason explicitly
about the recursion in the grammar, whereas the recursion is not
observable in the traditional parser combinators approach. The Parser
combinator model is in fact so limited that something simple as
pretty-printing a BNF representation of the grammar is fundamentally
impossible. More details in the PADL-submitted draft.

As James says below, a grammar algorithm using grammar-combinators
grammars can observe the recursion in the grammar and can therefore do
stuff for which you would otherwise have to use a parser generator.

 I guess the proper solution (TM) is to blur the distiction
 between types and values by switching to dependent types altogether...

There is actually some very interesting work about dependently typed
parser combinator libraries, I discuss this in the related work
section of the PADL paper.

Dominique

Footnotes:
[1]  http://projects.haskell.org/grammar-combinators/#background
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] Re: Unwrapping newtypes

2010-09-08 Thread Kevin Jardine
Thanks Arie,

I'm going to make some of my bare Obj functions accept a ToObj
typeclass constraint and do the conversions inside there to avoid
cluttering up the wrapped object code.

Now that I know how to do this I'm going to see what more
restructuring I can do to make the difference between wrapped and bare
objects less visible (except of course where it should matter).

Kevin

On Sep 8, 3:44 pm, Arie Peterson ar...@xs4all.nl wrote:
 On Wed, 8 Sep 2010 05:51:22 -0700 (PDT), Kevin Jardine



 kevinjard...@gmail.com wrote:
  Ah, I was missing an important piece of the puzzle.

  If I write:

  class ToObj a where
      toObj :: a - Obj

  instance ToObj Obj where
      toObj a = a

  then

  newtype Blog = Blog Obj deriving ToObj

  works!

 This post
 http://www.haskell.org/pipermail/libraries/2006-October/005950.html
 describes a general mini-library for this situation (having a
 structure-indicating newtype of an underlying type). The 'Unpack' class
 is a generalised version of your 'ToObj' class. Maybe it is useful to
 compare (or even use), especially the smart ways in which you can use
 this class to hide much of the wrapping/unwrapping.

 Regards,

 Arie

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


Re: [Haskell-cafe] Re: ANNOUNCE: grammar-combinators 0.1 (initial release): A parsing library of context-free grammar combinators

2010-09-08 Thread Dominique Devriese
Johannes,

2010/9/8 Johannes Waldmann waldm...@imn.htwk-leipzig.de:

 That compilation process is highly nonlocal
 and would never be possible with, e.g., the Parsec approach.

 Pipe dream: attach such a grammar object to every Parsec parser,
 and include the compiler with the combinators,
 and have them run at (Haskell) compile time (in ghc's specializer).

You can actually use a grammar-combinators parser with Parsec
(although the current implementation will use backtracking on every
branch), keeping the original grammar around for other purposes.

About the compile-time stuff, there is code in the library doing
compile-time transformations using Template-Haskell (but requiring a
grammar with embedded TH splices for injected values). You could also
do a similar compilation to a PDA parser in TH if you want, again
keeping the full grammar available for other stuff.

Additionally, I have noted that passing certain GHC inlining flags as
has been suggested for generic code [1] produces spectacular
(execution time/16) optimizations for a test grammar, but I have not
investigated what resulting code GHC actually produces in this case.
This is also related to what you talk about, since the compiler does
part of the transformation from abstract grammar at compile time.

 Should work for some subset (e.g., just let, not letrec, use
 proper combinators instead) and with some future ghc version ...

 When I teach parsing (in Compiler Construction), for lack of time
 it's either traditional (CFG - PDA) or combinator (not both),
 and I'm not happy with that, since both are important concepts.
 But then, semantics is more important than syntax ...

I actually think of the grammar-combinators approach as an attempt to
bring the power available in parser combinator libraries to the level
of what can be done in parser generators.

Dominique

Footnotes:
[1] http://www.cs.uu.nl/research/techreps/repo/CS-2009/2009-022.pdf
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] Haskell, arrows and signal processing

2010-09-08 Thread Rafael Gustavo da Cunha Pereira Pinto
Hi folks from the cafe!!

Last weekend, I was wondering on how hard it would be to use Haskell for
mixed-signal processing.

Here is an example of an digital integrator:


summation=zipWith (+)

delay xs=(fromIntegral 0):xs

integrator xs=let ws=summation (integrator xs) xs in delay ws



The input and output are  infinite streams. I have a few questions:

1) Is it possible to change it to use arrows? How would it look like?
2) How would one implement an continuous time version?

For 2) I would like to implement something like that digital integrator, so
I could create filters based on integrator loops like this one:

x(t) (+) Integrator --|--- y(t)
  ^|
  ||


Note that x(t) would be a function, and I would expect to create a function
y, based on this flow!

Rafael Gustavo da Cunha Pereira Pinto




-- 
Rafael Gustavo da Cunha Pereira Pinto
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] ANNOUNCE: Grempa 0.1.0, Embedded grammar DSL and LALR parser generator

2010-09-08 Thread Olle Fredriksson
Hello Paulo,

Glad to see some interest!

I just setup a repository over at github: http://github.com/ollef/Grempa

Fork away!

Kind regards,
Olle

On 8 September 2010 05:05, Paulo Tanimoto ptanim...@gmail.com wrote:

 Hi Olle,

 On Mon, Sep 6, 2010 at 12:45 PM, Olle Fredriksson
 fredriksson.o...@gmail.com wrote:
  There are a few other examples in the examples directory of the package,
  most
  notably a grammar and parser for a simple functional language similar to
  Haskell.
  It is possible to generate random input strings and their expected
 outputs
  for grammars written using Grempa which makes it possible to test the
  generated
  parsers with QuickCheck.
  The package and documentation (should be up soon) can be found here:
  http://hackage.haskell.org/package/Grempa-0.1.0

 Very nice job, I'm interested in using it.  I wonder why the
 documentation hasn't been generated on Hackage yet.  (I generated it
 for myself locally.)

 Do you plan to set up a repository somewhere?

 Thanks!

 Paulo

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


Re: [Haskell-cafe] ANNOUNCE: text 0.8.0.0, fast Unicode text support

2010-09-08 Thread Daniel Fischer
On Wednesday 08 September 2010 13:46:13, Daniel Fischer wrote:
 My timings are quite different, but that's probably because 6.12.3's
 inliner doesn't give the full fusion benefit, so it'll improve
 automatically with the next GHC release.


Or maybe not so much. Just built the latest source bundle from the HEAD 
branch and

6.12.3:
./nbench lazyText bigfile krkx rabi +RTS -s
   1,796,245,884 bytes allocated in the heap
   1,125,596 bytes copied during GC
 110,398,048 bytes maximum residency (8 sample(s))
  38,897,164 bytes maximum slop
 191 MB total memory in use (4 MB lost due to fragmentation)

  Generation 0:  3043 collections, 0 parallel,  3.06s,  3.17s elapsed
  Generation 1: 8 collections, 0 parallel,  0.00s,  0.01s elapsed

  INIT  time0.00s  (  0.00s elapsed)
  MUT   time6.03s  (  6.48s elapsed)
  GCtime3.07s  (  3.18s elapsed)
  EXIT  time0.00s  (  0.00s elapsed)
  Total time9.10s  (  9.66s elapsed)

  %GC time  33.7%  (33.0% elapsed)

  Alloc rate297,965,335 bytes per MUT second

  Productivity  66.3% of total user, 62.4% of total elapsed

6.13.20100831:
./hdbench lazyText bigfile krkx rabi +RTS -s

 543,409,296 bytes allocated in the heap

 699,364 bytes copied during GC 

 110,956,008 bytes maximum residency (8 sample(s))  

  38,893,040 bytes maximum slop 

 191 MB total memory in use (4 MB lost due to fragmentation)


  Generation 0:   652 collections, 0 parallel,  0.44s,  0.43s elapsed
  Generation 1: 8 collections, 0 parallel,  0.00s,  0.01s elapsed

  INIT  time0.00s  (  0.00s elapsed)
  MUT   time5.42s  (  5.77s elapsed)
  GCtime0.44s  (  0.44s elapsed)
  EXIT  time0.00s  (  0.00s elapsed)
  Total time5.86s  (  6.21s elapsed)

  %GC time   7.5%  (7.1% elapsed)

  Alloc rate100,327,729 bytes per MUT second

  Productivity  92.5% of total user, 87.2% of total elapsed


Sure, that's a significant improvement, but that's mostly the GC time, with 
-A64M, 6.12.3 is much closer.

However, for ByteStrings, performance got worse:

6.12.3:
./nbench lazyBS bigfile krkx rabi +RTS -s   
  
  90,127,112 bytes allocated in the heap
  
  31,116 bytes copied during GC 
  
 103,396 bytes maximum residency (1 sample(s))  
  
  39,964 bytes maximum slop 
  
   2 MB total memory in use (0 MB lost due to fragmentation)
  

  Generation 0:   158 collections, 0 parallel,  0.00s,  0.00s elapsed
  Generation 1: 1 collections, 0 parallel,  0.00s,  0.00s elapsed

  INIT  time0.00s  (  0.00s elapsed)
  MUT   time0.10s  (  0.20s elapsed)
  GCtime0.00s  (  0.00s elapsed)
  EXIT  time0.00s  (  0.00s elapsed)
  Total time0.11s  (  0.20s elapsed)

  %GC time   3.6%  (1.8% elapsed)

  Alloc rate834,456,211 bytes per MUT second

  Productivity  92.9% of total user, 50.9% of total elapsed

6.13.20100831:
./hdbench lazyBS bigfile krkx rabi +RTS -s  

 478,710,672 bytes allocated in the heap

 164,904 bytes copied during GC 

  86,992 bytes maximum residency (1 sample(s))  

  44,080 bytes maximum slop 

   2 MB total memory in use (0 MB lost due to fragmentation)


  Generation 0:   864 collections, 0 parallel,  0.00s,  0.01s elapsed
  Generation 1: 1 collections, 0 parallel,  0.00s,  0.00s elapsed

  INIT  time0.00s  (  0.00s elapsed)
  MUT   time0.17s  (  0.28s elapsed)
  GCtime0.00s  (  0.01s elapsed)
  EXIT  time0.00s  (  0.00s elapsed)
  Total time0.18s  (  0.29s elapsed)

  %GC time   2.3%  (4.1% elapsed)

  Alloc rate2,783,039,776 bytes per MUT second

  Productivity  95.5% of total user, 57.3% of total elapsed


Not only got it slower, it also allocates more than five times as much as 
before.

  Given that the space involved is just 121KB
  maximum residency while processing a 124MB file, I'm not concerned
  about it.

 I wouldn't either.


But it needs more space here, so I am concerned.

  And the time required isn't a bad place to start from, I think.
 
  By the way, as this implies, I can't reproduce your space behaviour at
  all.

 That's surprising.
 Have you made sure to replace a pattern which does not occur in the
 text? Can you 

[Haskell-cafe] interesting type families problem

2010-09-08 Thread Gábor Lehel
I'm bad at expositions so I'll just lead with the code:

{-# LANGUAGE EmptyDataDecls, TypeFamilies #-}

data True  :: *
data False :: *

class TypeValue a where
type ValueTypeOf a :: *
value :: ValueTypeOf a

instance TypeValue True where
type ValueTypeOf True = Bool
value = True

instance TypeValue False where
type ValueTypeOf False = Bool
value = False

main = print (value :: ValueTypeOf True)

(In case this is initially confusing, there are entirely distinct
type-level and value-level True and False involved which merely share
a name. The idea is to take type-level 'values' and reflect them down
to the corresponding value-level, er, values.)

Which results in the following error message:

Couldn't match expected type `Bool'
   against inferred type `ValueTypeOf a'
  NB: `ValueTypeOf' is a type function, and may not be injective
In the first argument of `print', namely
`(value :: ValueTypeOf True)'
In the expression: print (value :: ValueTypeOf True)
In the definition of `main':
main = print (value :: ValueTypeOf True)


This is strange and vaguely amusing to me. I get that type functions
are not injective, but I can't figure out how it applies to this
situation. Obviously if I had written `print (value :: Bool)` it would
rightly complain that there could be any number of instances which map
to Bool, and how in the world should it know which one I meant. But it
seems like in this case the compiler knows everything it needs to
know. And it even manages to deduce, from the exact same expression
(`print` isn't giving it any extra information), that it's
simultaneously a Bool and not necessarily a Bool.

Is this supposed to work? If not, why not?


-- 
Work is punishment for failing to procrastinate effectively.
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] interesting type families problem

2010-09-08 Thread Miguel Mitrofanov

On 8 Sep 2010, at 20:01, Gábor Lehel wrote:

 I'm bad at expositions so I'll just lead with the code:
 
 {-# LANGUAGE EmptyDataDecls, TypeFamilies #-}
 
 data True  :: *
 data False :: *
 
 class TypeValue a where
type ValueTypeOf a :: *
value :: ValueTypeOf a
 
 instance TypeValue True where
type ValueTypeOf True = Bool
value = True
 
 instance TypeValue False where
type ValueTypeOf False = Bool
value = False
 
 main = print (value :: ValueTypeOf True)
 
 (In case this is initially confusing, there are entirely distinct
 type-level and value-level True and False involved which merely share
 a name. The idea is to take type-level 'values' and reflect them down
 to the corresponding value-level, er, values.)
 
 Which results in the following error message:
 
Couldn't match expected type `Bool'
   against inferred type `ValueTypeOf a'
  NB: `ValueTypeOf' is a type function, and may not be injective
In the first argument of `print', namely
`(value :: ValueTypeOf True)'
In the expression: print (value :: ValueTypeOf True)
In the definition of `main':
main = print (value :: ValueTypeOf True)
 
 
 This is strange and vaguely amusing to me. I get that type functions
 are not injective, but I can't figure out how it applies to this
 situation. Obviously if I had written `print (value :: Bool)` it would
 rightly complain that there could be any number of instances which map
 to Bool, and how in the world should it know which one I meant.

Well, it's the same thing, actually. Since ValueTypeOf True is Bool,
value :: ValueTypeOf True is exactly the same as value :: Bool.

 But it
 seems like in this case the compiler knows everything it needs to
 know. And it even manages to deduce, from the exact same expression
 (`print` isn't giving it any extra information), that it's
 simultaneously a Bool and not necessarily a Bool.
 
 Is this supposed to work? If not, why not?
 
 
 -- 
 Work is punishment for failing to procrastinate effectively.
 ___
 Haskell-Cafe mailing list
 Haskell-Cafe@haskell.org
 http://www.haskell.org/mailman/listinfo/haskell-cafe

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


Re: [Haskell-cafe] interesting type families problem

2010-09-08 Thread Gábor Lehel
2010/9/8 Miguel Mitrofanov miguelim...@yandex.ru:

 On 8 Sep 2010, at 20:01, Gábor Lehel wrote:

 I'm bad at expositions so I'll just lead with the code:

 {-# LANGUAGE EmptyDataDecls, TypeFamilies #-}

 data True  :: *
 data False :: *

 class TypeValue a where
    type ValueTypeOf a :: *
    value :: ValueTypeOf a

 instance TypeValue True where
    type ValueTypeOf True = Bool
    value = True

 instance TypeValue False where
    type ValueTypeOf False = Bool
    value = False

 main = print (value :: ValueTypeOf True)

 (In case this is initially confusing, there are entirely distinct
 type-level and value-level True and False involved which merely share
 a name. The idea is to take type-level 'values' and reflect them down
 to the corresponding value-level, er, values.)

 Which results in the following error message:

    Couldn't match expected type `Bool'
           against inferred type `ValueTypeOf a'
      NB: `ValueTypeOf' is a type function, and may not be injective
    In the first argument of `print', namely
        `(value :: ValueTypeOf True)'
    In the expression: print (value :: ValueTypeOf True)
    In the definition of `main':
        main = print (value :: ValueTypeOf True)


 This is strange and vaguely amusing to me. I get that type functions
 are not injective, but I can't figure out how it applies to this
 situation. Obviously if I had written `print (value :: Bool)` it would
 rightly complain that there could be any number of instances which map
 to Bool, and how in the world should it know which one I meant.

 Well, it's the same thing, actually. Since ValueTypeOf True is Bool,
 value :: ValueTypeOf True is exactly the same as value :: Bool.

Oh. Hmm. That makes sense. So I gather there's absolutely no way to
specify which instance you mean, and hence to use `value` as any
concrete type?



 But it
 seems like in this case the compiler knows everything it needs to
 know. And it even manages to deduce, from the exact same expression
 (`print` isn't giving it any extra information), that it's
 simultaneously a Bool and not necessarily a Bool.

 Is this supposed to work? If not, why not?


 --
 Work is punishment for failing to procrastinate effectively.
 ___
 Haskell-Cafe mailing list
 Haskell-Cafe@haskell.org
 http://www.haskell.org/mailman/listinfo/haskell-cafe





-- 
Work is punishment for failing to procrastinate effectively.
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] interesting type families problem

2010-09-08 Thread Anthony Cowley
2010/9/8 Gábor Lehel illiss...@gmail.com:
 Oh. Hmm. That makes sense. So I gather there's absolutely no way to
 specify which instance you mean, and hence to use `value` as any
 concrete type?

Here's one way to indicate which value you are referring to.

Anthony

{-# LANGUAGE EmptyDataDecls, TypeFamilies #-}
data True
data False

class TypeValue a where
type ValueTypeOf a
value :: a - ValueTypeOf a

instance TypeValue True where
type ValueTypeOf True = Bool
value _ = True

instance TypeValue False where
type ValueTypeOf False = Bool
value _ = False

main = print (value (undefined::True))
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] interesting type families problem

2010-09-08 Thread Gábor Lehel
2010/9/8 Anthony Cowley acow...@seas.upenn.edu:
 2010/9/8 Gábor Lehel illiss...@gmail.com:
 Oh. Hmm. That makes sense. So I gather there's absolutely no way to
 specify which instance you mean, and hence to use `value` as any
 concrete type?

 Here's one way to indicate which value you are referring to.

 Anthony

 {-# LANGUAGE EmptyDataDecls, TypeFamilies #-}
 data True
 data False

 class TypeValue a where
    type ValueTypeOf a
    value :: a - ValueTypeOf a

 instance TypeValue True where
    type ValueTypeOf True = Bool
    value _ = True

 instance TypeValue False where
    type ValueTypeOf False = Bool
    value _ = False

 main = print (value (undefined::True))


Right. You can also use Tagged :) but I meant specifically with the
formulation I presented originally.

{-# LANGUAGE EmptyDataDecls, TypeFamilies #-}

import Data.Tagged
import Control.Applicative

data True  :: *
data False :: *

class TypeValue a where
type ValueTypeOf a :: *
value :: Tagged a (ValueTypeOf a)

instance TypeValue True where
type ValueTypeOf True = Bool
value = Tagged True

instance TypeValue False where
type ValueTypeOf False = Bool
value = Tagged False

main = untag $ print $ (value :: Tagged True (ValueTypeOf True))


-- 
Work is punishment for failing to procrastinate effectively.
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Unwrapping newtypes

2010-09-08 Thread Evan Laforge
Here's a different approach:

If you just want to make the typechecker distinguish between some
values but still have some functions that don't care what subtype
they are, you can use phantom types:

data Obj x = Obj X Y Z

data BlogObj
type Blog = Obj BlogObj

data CommentObj
type Comment = Obj CommentObj

data UserObj
type User = Obj UserObj

Now  you can write a function that takes a Blog, and it will refuse
other kinds of 'Obj'.  But you can still write a function that takes
'Obj x' and it will accept any kind of Obj.  So you don't need to do
any unwrapping if you leave the functions that matter polymorphic.
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] BPMN and BPEL

2010-09-08 Thread Hector Guilarte
Hello,

Does anybody knows if there is some work related to BPMN and/or BPEL done in
Haskell? Maybe some research or some papers?

I'm about to begin a mapper from BPMN to BPEL and Haskell is my first option
for doing it, but since my company is somehow married to .NET and nobody
else knows anything about Functional Programming or Haskell, using it might
be a problem for maintenance and scalability.

If somebody can point out really good reasons on why I should use Haskell to
do my work, please let me know them, they might help me convincing my
bosses. On the other hand, if you believe Haskell is a bad language for this
kind of task, and why C# or any other .NET language would be better, I'm
welcome to hear your reasons, they might convince me.

I know about F#, but the problem is not that Haskell is not .NET, the
problem is that it is functional programming and as I said before, nobody
here knows a bit about it. If I were to do it using FP, I would use Haskell
for sure, not F#.

Thank you very much,

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


Re: [Haskell-cafe] ANNOUNCE: AbortT-transformers version 1.0

2010-09-08 Thread Henning Thielemann
Gregory Crosswhite schrieb:
  For whatever reason, nobody seems to have gotten around to implementing
 an Abort monad transformer (outside the monadLib package), so I decided
 to write one myself since I wanted the functionality but I use
 transformers rather than monadLib.

Is AbortT different from ErrorT, ExceptionalT and friends?

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


Re: [Haskell-cafe] ANNOUNCE: GotoT-transformers version 1.0

2010-09-08 Thread Henning Thielemann
Gregory Crosswhite schrieb:
  People want to believe that Haskell is a better language than C, but
 how could this possibly be true when Haskell lacks the very basic goto
 feature???  If the world is going to take Haskell seriously, then this
 serious blight needs to be addressed immediately!  Thus I proud to
 present to you the GotoT-transformers package which provides this
 missing functionality and so finally makes Haskell a serious contender
 with C.

To be honest, when writing mutually depending functions that extensively
rely on tail recursion optimization, this often looks a lot like GOTO
already.

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


Re: [Haskell-cafe] ANNOUNCE: secure-sockets version 1.0

2010-09-08 Thread Mads Lindstrøm
Hi David

On Mon, 2010-09-06 at 13:50 -0700, David Anderson wrote:

 
 
  - Simple timing attacks: If code path A takes longer than code path B
 to execute, an attacker can use that information to reverse engineer
 the outcome of branching tests, and from there possibly recover secret
 key material. This is particularly nasty because the attack can be
 carried out remotely, by repeatedly executing the protocol in a way
 that exercises the vulnerable code path.
 
 

I do not know much about cryptography, so I may be writing nonsense
here, but it seems to me that it should not be too hard insuring that
all wrongly encrypted data takes equally long to process. One could use
an algorithm like:

* make interrupt/timer that will finish in one second
* process data from client
* If data is correctly encrypted, stop interrupt/timer and return
information to the client
* If data is wrongly encrypted, prepare error-result, (busy) wait for
interrupt/timer to finish, return result to client

That will mean that all clients, that uses a wrong key, will take one
second to finish. But as clients, with a correct key, finishes fast I do
not see any problems.

What am I missing here?


/Mads


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


Re: [Haskell-cafe] ANNOUNCE: secure-sockets version 1.0

2010-09-08 Thread David Anderson
On Wed, Sep 8, 2010 at 1:05 PM, Mads Lindstrøm mads.lindstr...@gmail.comwrote:

 Hi David

 On Mon, 2010-09-06 at 13:50 -0700, David Anderson wrote:

 
 
   - Simple timing attacks: If code path A takes longer than code path B
  to execute, an attacker can use that information to reverse engineer
  the outcome of branching tests, and from there possibly recover secret
  key material. This is particularly nasty because the attack can be
  carried out remotely, by repeatedly executing the protocol in a way
  that exercises the vulnerable code path.
 
 

 I do not know much about cryptography, so I may be writing nonsense
 here, but it seems to me that it should not be too hard insuring that
 all wrongly encrypted data takes equally long to process. One could use
 an algorithm like:

 * make interrupt/timer that will finish in one second
 * process data from client
 * If data is correctly encrypted, stop interrupt/timer and return
 information to the client
 * If data is wrongly encrypted, prepare error-result, (busy) wait for
 interrupt/timer to finish, return result to client

 That will mean that all clients, that uses a wrong key, will take one
 second to finish. But as clients, with a correct key, finishes fast I do
 not see any problems.

 What am I missing here?


Not much, that is an acceptable option. It's also nice in the sense that it
tarpits the attacker, slowing him down (assuming the server only allows one
in-flight auth attempt per IP or something to that effect). The downside is
that you're keeping resources open longer than necessary for attacking
connections, which makes it easier to DoS the service. Normally, a failed
authentication should kill the connection as quickly as possible, to not
waste resources on attackers.

You are correct though that inserting a long-ish delay on failure is a good
way to screw with timing attacks, but it does need to be balanced against
increasing the risk of resource exhaustion attacks. And either way, it would
be nice to have crypto primitives that are tamper-resistant by themselves,
rather than rely solely on the application designer to implement attack
resistance.

- Dave



 /Mads


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

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


Re: [Haskell-cafe] ANNOUNCE: AbortT-transformers version 1.0

2010-09-08 Thread Gregory Crosswhite
 On 09/08/10 12:54, Henning Thielemann wrote:
 Gregory Crosswhite schrieb:
  For whatever reason, nobody seems to have gotten around to implementing
 an Abort monad transformer (outside the monadLib package), so I decided
 to write one myself since I wanted the functionality but I use
 transformers rather than monadLib.
 Is AbortT different from ErrorT, ExceptionalT and friends?
Yes, for a couple of reasons.  First, computations in the AbortT monad
always succeed;  they just might succeed earlier than expected.  This
contrasts with the computations in the ErrorT, etc. monads where
aborting earlier is a signal that an error has occurred.  Second, AbortT
is not isomorphic to ErrorT because ErrorT requires that terminating
early returns not just any value but a value which is an instance of
Error;  furthermore, even if this were not a problem, it would be a
problem that pattern match failures would have the effect of stuffing a
string into your value that you probably didn't want and returning it
early as if it were the correct answer.

ExceptionT is a different matter because it handles fail as an
uncaught error and places no restrictions on the error type, so one
could implement the same functionality as AbortT by using ExceptionalT
and requiring the end result be a monadic value of type ExceptionalT e
m e, where the exception and result types are the same.  However, I
believe that it is better to have the AbortT functionality available as
a separate simple library specialized for this purpose than to have its
functionality buried inside a more general library that is really
intended to be used for a different purpose.

Cheers,
Greg

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


Re: [Haskell-cafe] ANNOUNCE: GotoT-transformers version 1.0

2010-09-08 Thread Gregory Crosswhite
 On 09/08/10 12:55, Henning Thielemann wrote:
 Gregory Crosswhite schrieb:
  People want to believe that Haskell is a better language than C, but
 how could this possibly be true when Haskell lacks the very basic goto
 feature???  If the world is going to take Haskell seriously, then this
 serious blight needs to be addressed immediately!  Thus I proud to
 present to you the GotoT-transformers package which provides this
 missing functionality and so finally makes Haskell a serious contender
 with C.
 To be honest, when writing mutually depending functions that extensively
 rely on tail recursion optimization, this often looks a lot like GOTO
 already.

True.  I guess we should make sure that nobody tells Dijkstra about
Haskell then.  :-)

Cheers,
Greg

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


Re: [Haskell-cafe] BPMN and BPEL

2010-09-08 Thread C. McCann
On Wed, Sep 8, 2010 at 3:38 PM, Hector Guilarte hector...@gmail.com wrote:
 If somebody can point out really good reasons on why I should use Haskell to
 do my work, please let me know them, they might help me convincing my
 bosses. On the other hand, if you believe Haskell is a bad language for this
 kind of task, and why C# or any other .NET language would be better, I'm
 welcome to hear your reasons, they might convince me.

Well, how comfortable are you with Haskell? If you're roughly as
proficient in it as you are in C#, you could probably bang out a
prototype using Haskell in a fraction of the time with fewer bugs.
Most software projects get massively revised from the initial version
anyway, so using a more productive language and then rewriting for the
production version can still be a net win, especially since you can
use the prototype as a specification or reference implementation
(e.g., you get some QA for free by running the two on identical input
and checking for identical output). And of course, maintenance and
scalability don't matter in a prototype.

If it goes well, you'll have proven that Haskell has value (without
forcing a long-term, up-front commitment to it), probably improved the
quality of the C# version, and gotten the chance to write Haskell at
work.

Furthermore, in this particular case, you say it's a mapper between
data description languages. While I obviously don't know the details,
applying transformations to complex, easily-inspected data structures
is a classic example of a problem ideally suited to a functional
language with pattern matching, be it Haskell, F#, or any other
ML-influenced language--thus making Haskell even more advantageous for
rapid prototyping.

Also helpful are various Haskell-inspired features added to C# in the
last few years, making it feasible to port a large subset of Haskell
to C# fairly directly.

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


[Haskell-cafe] recommendations for reading list?

2010-09-08 Thread David Leimbach
In my amazon shopping cart I currently have:

*Conceptual Mathematics: A First Introduction to
Categorieshttp://www.amazon.com/gp/product/052171916X/ref=ord_cart_shr?ie=UTF8m=ATVPDKIKX0DER
  *- F. William Lawvere

*Categories for the Working Mathematician (Graduate Texts in
Mathematics)http://www.amazon.com/gp/product/0387984038/ref=ord_cart_shr?ie=UTF8m=ATVPDKIKX0DER
 *- Saunders Mac Lane

*Categories and Computer Science (Cambridge Computer Science
Texts)http://www.amazon.com/gp/product/0521422264/ref=ord_cart_shr?ie=UTF8m=ATVPDKIKX0DER
 *- R. F. C. Walters

Are all 3 of these worthwhile?  Any of them?

I'm just trying to get a grasp on enough Category Theory to be able think
more deeply about programming in general, and maybe grasp more Haskell
terminology beyond the seemingly superficial meanings I understand today.

Thanks!

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


Re: [Haskell-cafe] ANNOUNCE: AbortT-transformers version 1.0

2010-09-08 Thread Henning Thielemann


On Wed, 8 Sep 2010, Gregory Crosswhite wrote:


ExceptionT is a different matter because it handles fail as an
uncaught error and places no restrictions on the error type, so one
could implement the same functionality as AbortT by using ExceptionalT
and requiring the end result be a monadic value of type ExceptionalT e
m e, where the exception and result types are the same.  However, I
believe that it is better to have the AbortT functionality available as
a separate simple library specialized for this purpose than to have its
functionality buried inside a more general library that is really
intended to be used for a different purpose.


If we get rid of the notion of an exception as being something bad, and 
instead consider an exception as being early exit for whatever reason, I 
see no problem. E.g. you may well use an exception to terminate a 
successful search, returning the search result as exception value.

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


Re: [Haskell-cafe] recommendations for reading list?

2010-09-08 Thread Николай Кудасов
Hi, Dave!

Consider this book:

*Basic Category Theory for Computer Scientists (Foundations of
Computing)http://www.amazon.com/Category-Computer-Scientists-Foundations-Computing/dp/0262660717--
*Benjamin C.Pierce

This is at the moment the only book about category theory I've read, but it
was easy for me as for programmer rather than mathematician to understand
most of the stuff. Now I am reading Categories for the Working
Mathematician and just can't go further 50-60 pages, cause for
understanding rest of the book I must understand examples given in the book,
and those are mainly from group theory, topology and functional analysis. As
I am slightly familiar with any, first I need to learn some other
mathematics.
So if you are rather programmer than mathematician, I think you'd better
start with book I mentioned above. Otherwise you should stock up with lots
of books about less abstract mathematics =)

With best regards,
Nick
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] recommendations for reading list?

2010-09-08 Thread Benedict Eastaugh
2010/9/9 Николай Кудасов crazy.fiz...@gmail.com:
 Consider this book:

 Basic Category Theory for Computer Scientists (Foundations of Computing)
 -- Benjamin C.Pierce

Hi David,

Николай Кудасов is quite right—Pierce's book is excellent. Apart from
being a good introduction to category theory, it's worth buying for
the fourth chapter alone, which is an annotated bibliography of
textbooks, introductory articles and reference works on category
theory. It would be an excellent guide to where to go next after
finishing Basic Category Theory.

Graham Hutton also taught a course on category theory at MGS 2010, and
his slides are online. I found them quite enlightening, and they move
at a good pace for a beginner, with an appropriate level of formality.

http://www.cs.nott.ac.uk/~gmh/cat.html

Category theorists tend to give lots of examples from abstract
algebra, so a basic understanding of some algebraic structures is,
I've found, a lot of help when trying to appreciate category-theoretic
ideas.

Hope this helps a little.

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


[Haskell-cafe] Re: Unwrapping newtypes

2010-09-08 Thread Ertugrul Soeylemez
Kevin Jardine kevinjard...@gmail.com wrote:

 I have a generic object that I want to wrap in various newtypes to
 better facilitate type checking.

 For example,

 newtype Blog = Blog Obj
 newtype Comment = Comment Obj
 newtype User = User Obj

 Unlike Obj itself, whose internal structure is hidden in a library
 module, the newtype wrappings are purely to facilitate type checking.
 It is no secret that each is just a wrapper around Obj.

 It is obvious how to construct the various wrapper objects. It is not
 so obvious how to extract the Obj they contain in a reasonably generic
 way however. What I want is a getObj function that works on all of
 them.

 Of course this could work if someone using the library wrote an
 instance for each wrapper object:

 instance GetObject Blog where
 getObj (Blog obj) = obj

 but this is a pain in the neck to write for each newtype.

Simple solution:

  data ObjContent = Blah

  data Obj
= Blog{ getObj :: !ObjContent }
| Comment { getObj :: !ObjContent }
| User{ getObj :: !ObjContent }


With your GetObject class this even becomes extensible:

  instance GetObject Obj where
getObject = getObj

  data OtherType = OtherType ObjContent

  instance GetObject OtherType where
getObject (OtherType obj) = obj


 I discovered that Foldable defines a handy toList function that
 extracts content from generic Foldable structures.

 So that I could write:

 toObj :: Foldable thing = thing Obj - Obj
 toObj w = head $ toList w

 Slightly kludgy but it works.

But it's not what you are looking for.  You are confusing constructor
types with type kinds.  Foldable expects a type of kind * - *, which
isn't quite what you want.  Also I would consider this to be abuse.
Also from a complexity standpoint it's nothing different from your
GetObject class anyway.  You still need to write the instances.


Greets,
Ertugrul


-- 
nightmare = unsafePerformIO (getWrongWife = sex)
http://ertes.de/


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


Re: [Haskell-cafe] Restricted type classes

2010-09-08 Thread wren ng thornton

On 9/7/10 12:33 AM, Ivan Lazar Miljenovic wrote:

On 7 September 2010 14:24, wren ng thorntonw...@freegeek.org  wrote:

On 9/7/10 12:04 AM, Ivan Lazar Miljenovic wrote:

Not quite sure what you mean by a mis-match


Just that they're not the same thing. For example, ZipList supports pure but
it has no meaningful instance of singleton since every ZipList is infinite.


Huh; didn't know that ZipList did that.  OK, so there's a definite
mis-match between what we'd want a singleton function to do and what
pure appears to do.  How can we specify such a hierarchy given that
for the majority of containers they will be the same?


The way I'd probably do it is to have one class for pointed functors 
which obeys the pointed law and interacts with Applicative and Monad in 
the expected way; and then have a separate class for singletons which 
has laws about how singleton, insert/cons, coinsert/snoc, and 
union/concat interact. Thus, we'd have two separate functions 
pure/return/unit and singleton, pulling in the class constraints as 
appropriate. For most containers it would just happen that they could 
define pure=singleton, though the class structure doesn't _require_ 
that. This would allow us to avoid excluding containers like ZipList 
(pure, but no singleton) and bloomfilters (singleton, but no pure).


I think the shape of the classes for singletons, insert, coinsert, and 
union still needs some work. For instance, the definitions I've given 
earlier were assuming a (multi)set-like or sequence-like container, but 
we can also reasonably extend it to include map-like containers. The 
only trick is that set/seq-like containers have a single type parameter 
and a single element argument, whereas map-like containers have a pair 
of type parameters and a key--value pair of elements. So we'd need to 
do something with MPTCs in order to unify them.


--
Live well,
~wren
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] Re: ANNOUNCE: GotoT-transformers version 1.0

2010-09-08 Thread Ertugrul Soeylemez
Gregory Crosswhite gcr...@phys.washington.edu wrote:

  People want to believe that Haskell is a better language than C, but
 how could this possibly be true when Haskell lacks the very basic
 goto feature???  If the world is going to take Haskell seriously,
 then this serious blight needs to be addressed immediately!  Thus I
 proud to present to you the GotoT-transformers package which
 provides this missing functionality and so finally makes Haskell a
 serious contender with C.

Have you looked at ContT from monadLib?  It's not just a goto, but in
fact a setjmp/longjmp, i.e. a goto with value.  I haven't used it for
anything yet, but it might come in handy for some algorithms:

  import Data.List
  import MonadLib
  import Text.Printf

  myComp :: ContT (Maybe Int) IO (Maybe Int)
  myComp = do
(i, beginning) - labelCC 0
inBase $ printf Current value: %i (type q to quit)\n i
query - inBase getLine
when (q `isPrefixOf` query) $ abort (Nothing :: Maybe Int)
when (i  10) $ jump (i+1) beginning
return $ Just i

  main :: IO ()
  main = runContT return myComp =
 printf Final result: %s\n . maybe none show


Greets,
Ertugrul


-- 
nightmare = unsafePerformIO (getWrongWife = sex)
http://ertes.de/


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


Re: [Haskell-cafe] Restricted type classes

2010-09-08 Thread wren ng thornton

On 9/7/10 7:26 AM, Neil Brown wrote:

On 07/09/10 05:24, wren ng thornton wrote:

Just that they're not the same thing. For example, ZipList supports
pure but it has no meaningful instance of singleton since every
ZipList is infinite.


I don't believe that every ZipList is infinite (if this should be the
case, the constructor shouldn't be exposed!), just that ZipLists created
by pure are infinite


Just so. I misremembered the data constructor as not being exported.


So ZipList does have a meaningful definition of singleton (singleton x =
ZipList [x];


Though we still have singleton /= pure, which is all I was arguing.

--
Live well,
~wren
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Restricted type classes

2010-09-08 Thread Ivan Lazar Miljenovic
On 9 September 2010 12:10, wren ng thornton w...@freegeek.org wrote:
 I think the shape of the classes for singletons, insert, coinsert, and union
 still needs some work. For instance, the definitions I've given earlier were
 assuming a (multi)set-like or sequence-like container, but we can also
 reasonably extend it to include map-like containers. The only trick is that
 set/seq-like containers have a single type parameter and a single element
 argument, whereas map-like containers have a pair of type parameters and a
 key--value pair of elements. So we'd need to do something with MPTCs in
 order to unify them.

Yes, I'm not sure if Map-like types of kind * - * - * should have a
value of type (a,b) or then have BiFunctor, BiBuildable, etc.

-- 
Ivan Lazar Miljenovic
ivan.miljeno...@gmail.com
IvanMiljenovic.wordpress.com
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Re: ANNOUNCE: GotoT-transformers version 1.0

2010-09-08 Thread Gregory Crosswhite
 On 09/08/10 19:14, Ertugrul Soeylemez wrote:
 Gregory Crosswhite gcr...@phys.washington.edu wrote:

  People want to believe that Haskell is a better language than C, but
 how could this possibly be true when Haskell lacks the very basic
 goto feature???  If the world is going to take Haskell seriously,
 then this serious blight needs to be addressed immediately!  Thus I
 proud to present to you the GotoT-transformers package which
 provides this missing functionality and so finally makes Haskell a
 serious contender with C.
 Have you looked at ContT from monadLib?  It's not just a goto, but in
 fact a setjmp/longjmp, i.e. a goto with value.  I haven't used it for
 anything yet, but it might come in handy for some algorithms:

   import Data.List
   import MonadLib
   import Text.Printf

   myComp :: ContT (Maybe Int) IO (Maybe Int)
   myComp = do
 (i, beginning) - labelCC 0
 inBase $ printf Current value: %i (type q to quit)\n i
 query - inBase getLine
 when (q `isPrefixOf` query) $ abort (Nothing :: Maybe Int)
 when (i  10) $ jump (i+1) beginning
 return $ Just i

   main :: IO ()
   main = runContT return myComp =
  printf Final result: %s\n . maybe none show


 Greets,
 Ertugrul



Whoa, that's cool!  I glanced at monadLib but I didn't realize that it
let you create labels that you could return to like that.  :-)  (I know
of callCC, but that isn't quite the same as this.)  Thanks for the pointer!

The limitation with continuation-based approaches to goto, though, is
that you can only jump back to points that you've seen before.  The
reason why I don't use a continuation-based approach in GotoT is because
I wanted the user (i.e., me, and maybe one or two other people if I'm
lucky :-) ) to be able to jump to an arbitrary point outside the
calculation that has never been visited before, rather than returning a
previously visited point of the same calculation.

Of course, if someone can prove to me that I am wrong and that GotoT
semantics can be implemented with continuations, then I would welcome
this information.  :-)

Cheers,
Greg

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


Re: [Haskell-cafe] Restricted type classes

2010-09-08 Thread wren ng thornton

On 9/7/10 4:21 AM, Daniel Fischer wrote:

On Tuesday 07 September 2010 05:22:55, David Menendez wrote:

In fact, I think *every* appropriately-typed function satisfies that
law. Does anyone know of a counter-example?


-- | Multiply the *Hask* category by its number of objects.
data E a where
E :: a - b - E a

-- | Maintain all the morphisms of *Hask* in each *E*-copy of
-- it, but keep the tag for which *E*-copy we were in.
instance Functor E where
fmap f (E a b) = E (f a) b

-- | Proof that f...@e maintains identities
fmap id _|_
== _|_
== id _|_

fmap id (E a b)
== E (id a) b
== E a b
== id (E a b)

-- | Proof that f...@e maintains compositions
fmap f (fmap g _|_)
== fmap f _|_
== _|_
== fmap (f . g) _|_

fmap f (fmap g (E a b))
== fmap f (E (g a) b)
== E (f (g a)) b
== E ((f.g) a) b
== fmap (f . g) (E a b)

-- | The object part of a functor to enter *E* along the diagonal.
impure :: a - E a
impure a = E a a

-- | Proof that impure is not p...@e
fmap f (impure a)
== fmap f (E a a)
== E (f a) a
/= E (f a) (f a)
== impure (f a)

And yet, impure has the correct type.

Of course, it is possible to define functions of type (a - E a) which 
do satisfy the law. Namely, choose any function where the second 
argument to E does not depend on the parameter. But the problem is that 
there are a whole bunch of them! And none of them is intrinsically any 
more natural or correct than any other. Unfortunately, impure is the 
most natural function in that type, but it breaks the laws.


Functors like this happen to be helpful too, not just as oddities. 
They're functors for tracking the evolution of a value through a 
computation (e.g., tracking the initial value passed to a function). In 
this example, the existential tag is restricted by observational 
equivalence to only allow us to distinguish bottom from non-bottom 
initial values. But we can add context constraints on the data 
constructor in order to extract more information; at the cost of 
restricting impure to only working for types in those classes.




class Functor f =  Pointed f where
 point :: a -  f a
  -- satisfying fmap f . point = point . f

notQuitePure :: Pointed f =  a -  f a
notQuitePure _ = point undefined

fmap (const True) . notQuitePure = point . const True

But I don't see how to violate that law without introducing undefined on
the RHS.


You can also break the law by defining a strictness functor[*]: pure=id; 
fmap=($!) ---or any newtype equivalent. It breaks the pointed law for 
the same kind of reason, namely by strictifying functions that ignore 
their parameters but doing so in different places.


[*] Unfortunately, that's not actually a functor, since it does not 
preserve bottom-eating compositions. I.e.,


($!)(const 42 . const undefined)
/= ($!)(const 42) . ($!)(const undefined)

We only get a monotonic relationship, not an equality. I tried playing 
around with it a bit, but I'm pretty sure there's no way to define any 
(non-trivial, full,... i.e., interesting) functor from *Hask* into 
*StrictHask* from within Haskell. The only functor that seems to work is 
the CBV functor which reinterprets Haskell terms via call-by-value 
semantics, which I don't think we can define from within Haskell. Of 
course, defining an embedding from *StrictHask* to *Hask* is trivial. 
These two points together seem like a compelling argument for 
laziness-by-default in language design.


--
Live well,
~wren
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] recommendations for reading list?

2010-09-08 Thread David Leimbach
Thank you for this suggestion.  I do have this book.  I found it to be a
little lacking in some areas in that it felt like I was reading a student's
lecture notes, not the professor's.

At some point, I'm left with questions that there's no one around to answer
:-).  This is why I'm trying to go deeper.  I think it's a great one to have
on your bookshelf though for quick refreshers!

Dave

2010/9/8 Николай Кудасов crazy.fiz...@gmail.com

 Hi, Dave!

 Consider this book:

 *Basic Category Theory for Computer Scientists (Foundations of 
 Computing)http://www.amazon.com/Category-Computer-Scientists-Foundations-Computing/dp/0262660717--
 *Benjamin C.Pierce

 This is at the moment the only book about category theory I've read, but it
 was easy for me as for programmer rather than mathematician to understand
 most of the stuff. Now I am reading Categories for the Working
 Mathematician and just can't go further 50-60 pages, cause for
 understanding rest of the book I must understand examples given in the book,
 and those are mainly from group theory, topology and functional analysis. As
 I am slightly familiar with any, first I need to learn some other
 mathematics.
 So if you are rather programmer than mathematician, I think you'd better
 start with book I mentioned above. Otherwise you should stock up with lots
 of books about less abstract mathematics =)

 With best regards,
 Nick
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] recommendations for reading list?

2010-09-08 Thread David Leimbach
2010/9/8 Benedict Eastaugh ionf...@gmail.com

 2010/9/9 Николай Кудасов crazy.fiz...@gmail.com:
  Consider this book:
 
  Basic Category Theory for Computer Scientists (Foundations of Computing)
  -- Benjamin C.Pierce

 Hi David,

 Николай Кудасов is quite right--Pierce's book is excellent. Apart from
 being a good introduction to category theory, it's worth buying for
 the fourth chapter alone, which is an annotated bibliography of
 textbooks, introductory articles and reference works on category
 theory. It would be an excellent guide to where to go next after
 finishing Basic Category Theory.

 Graham Hutton also taught a course on category theory at MGS 2010, and
 his slides are online. I found them quite enlightening, and they move
 at a good pace for a beginner, with an appropriate level of formality.

 http://www.cs.nott.ac.uk/~gmh/cat.html

 Category theorists tend to give lots of examples from abstract
 algebra, so a basic understanding of some algebraic structures is,
 I've found, a lot of help when trying to appreciate category-theoretic
 ideas.

 Hope this helps a little.


Thank you Benedict, it does help a bit.  I don't have really any significant
exposure to abstract algebra either.  I think that might help a bit.

If only there was a resource like Khan's Academy for this stuff.  (I don't
think he goes in this direction for abstract math).

Dave



 Benedict.

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


Re: [Haskell-cafe] Re: ANNOUNCE: GotoT-transformers version 1.0

2010-09-08 Thread Antoine Latter
On Wed, Sep 8, 2010 at 9:43 PM, Gregory Crosswhite
gcr...@phys.washington.edu wrote:

 Of course, if someone can prove to me that I am wrong and that GotoT
 semantics can be implemented with continuations, then I would welcome
 this information.  :-)


Here's an implementation of GotoT with double-continuations:
http://hpaste.org/fastcgi/hpaste.fcgi/view?id=29823

I also have a sketch of me trying to use a single-continuation, but I
was defeated:
http://hpaste.org/fastcgi/hpaste.fcgi/view?id=29824

The idea is that on 'goto', we throw away the passed down continuation
in favor of an alternate return. The double-continuation approach is a
bit overkill since we don't have the equivalent of 'catch', to add
local scope to an alternate return.

My single continuation approach has two type-check errors I haven't
been able to understand yet, but hopefully you can see what I was
going for.

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


Re: [Haskell-cafe] Handling platform- or configuration-specific code (or, my CPP complaints)

2010-09-08 Thread wren ng thornton

On 9/7/10 3:10 PM, Ben Millwood wrote:

So I wonder what people
think of the use of CPP in Haskell code, what alternatives people can
propose, or what people hope to see in future to make conditional
compilation of Haskell code more elegant and simple?


The only thing I ever use CPP for in Haskell is top-level conditional 
definitions.


* That is, say I have a function foo which has a vanilla Haskell 
definition, but also has a special definition for GHC performance 
hackery, or which needs a special definition on some compilers in order 
to correct compiler-specific bugs. I'll use #ifdef here to give the 
different versions. I'll also occasionally do this for things like 
choosing whether to use the FFI vs a native definition, for debugging 
purposes.


* Another example is when using GeneralizedNewtypeDeriving in GHC, but 
still wanting to give normal definitions for other compilers to use.


* The only other example I can think of is when defining Applicative 
instances, since I only want to do that when linking against versions of 
base which are new enough to have it. Occasionally you can get similar 
issues re ByteString vs base.


In general, I think using CPP for actual macro processing is extremely 
poor style and can easily make code inscrutable (and no doubt 
bug-prone). If the Haskell spec were to add support for this sort of 
top-level compiler/compiletime-flag conditional definition, I'd switch over.


This matches the style in most of the code I've looked at. And it also 
means that the incompatibilities are localized and hidden from most 
client code. Depending on the nature of your library API conflict, if 
you can localize things into a few definitions of the core functions you 
use in the rest of your code, then that'd be best. But that's not always 
possible. I've yet to run into the case where I really need to support 
incompatible versions of a library when it's that closely integrated, so 
I don't have much advice there.


--
Live well,
~wren
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] Re: ANNOUNCE: GotoT-transformers version 1.0

2010-09-08 Thread Ertugrul Soeylemez
Gregory Crosswhite gcr...@phys.washington.edu wrote:

  On 09/08/10 19:14, Ertugrul Soeylemez wrote:
  Have you looked at ContT from monadLib?  It's not just a goto, but
  in fact a setjmp/longjmp, i.e. a goto with value.  I haven't used it
  for anything yet, but it might come in handy for some algorithms:
 
  [...]

 Whoa, that's cool!  I glanced at monadLib but I didn't realize that it
 let you create labels that you could return to like that.  :-) (I know
 of callCC, but that isn't quite the same as this.)  Thanks for the
 pointer!

It is, in fact, callCC. ;)


 The limitation with continuation-based approaches to goto, though, is
 that you can only jump back to points that you've seen before.  The
 reason why I don't use a continuation-based approach in GotoT is
 because I wanted the user (i.e., me, and maybe one or two other people
 if I'm lucky :-) ) to be able to jump to an arbitrary point outside
 the calculation that has never been visited before, rather than
 returning a previously visited point of the same calculation.

 Of course, if someone can prove to me that I am wrong and that GotoT
 semantics can be implemented with continuations, then I would welcome
 this information.  :-)

I don't think you need 'goto' to implement jumps in Haskell.  Note that
functions as well as computations are first class:

  myComp :: ContT () IO ()
  myComp = do
input - inBase $ putStrLn Print something (y/n)?  getLine
unless (y `isPrefixOf` input) exit
inBase $ putStrLn Something.

input - inBase $ putStrLn Print more (y/n)?  getLine
unless (y `isPrefixOf` input) exit
inBase $ putStrLn More.

where
  exit = do
inBase $ putStrLn Ok, I'm exiting.
abort ()

You can interpret 'exit' as a label.  Binding can be interpreted as a
jump.


Greets,
Ertugrul


-- 
nightmare = unsafePerformIO (getWrongWife = sex)
http://ertes.de/


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


Re: [Haskell-cafe] Restricted type classes

2010-09-08 Thread David Menendez
On Wed, Sep 8, 2010 at 11:17 PM, wren ng thornton w...@freegeek.org wrote:
 On 9/7/10 4:21 AM, Daniel Fischer wrote:

 On Tuesday 07 September 2010 05:22:55, David Menendez wrote:

 In fact, I think *every* appropriately-typed function satisfies that
 law. Does anyone know of a counter-example?

    -- | Multiply the *Hask* category by its number of objects.
    data E a where
        E :: a - b - E a

    -- | Maintain all the morphisms of *Hask* in each *E*-copy of
    -- it, but keep the tag for which *E*-copy we were in.
    instance Functor E where
        fmap f (E a b) = E (f a) b
snip
    -- | The object part of a functor to enter *E* along the diagonal.
    impure :: a - E a
    impure a = E a a

    -- | Proof that impure is not p...@e
    fmap f (impure a)
    == fmap f (E a a)
    == E (f a) a
    /= E (f a) (f a)
    == impure (f a)

 And yet, impure has the correct type.

Fascinating. I figured there might be a counter-example involving seq,
but this is pretty subtle.

In particular, would it be fair to say that in Haskell-without-seq, E
(f a) a and E (f a) (f a) are indistinguishable?

 Functors like this happen to be helpful too, not just as oddities. They're
 functors for tracking the evolution of a value through a computation (e.g.,
 tracking the initial value passed to a function). In this example, the
 existential tag is restricted by observational equivalence to only allow us
 to distinguish bottom from non-bottom initial values. But we can add context
 constraints on the data constructor in order to extract more information; at
 the cost of restricting impure to only working for types in those classes.

...at which point, it no longer has the same type as pure. But your
point is taken.

-- 
Dave Menendez d...@zednenem.com
http://www.eyrie.org/~zednenem/
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] ANNOUNCE: AbortT-transformers version 1.0

2010-09-08 Thread Colin Paul Adams
 Henning == Henning Thielemann lemm...@henning-thielemann.de writes:

Henning On Wed, 8 Sep 2010, Gregory Crosswhite wrote:

 ExceptionT is a different matter because it handles fail as an
 uncaught error and places no restrictions on the error type, so
 one could implement the same functionality as AbortT by using
 ExceptionalT and requiring the end result be a monadic value of
 type ExceptionalT e m e, where the exception and result types
 are the same.  However, I believe that it is better to have the
 AbortT functionality available as a separate simple library
 specialized for this purpose than to have its functionality
 buried inside a more general library that is really intended to
 be used for a different purpose.

Henning If we get rid of the notion of an exception as being
Henning something bad, and instead consider an exception as being
Henning early exit for whatever reason, I see no problem. E.g. you
Henning may well use an exception to terminate a successful search,
Henning returning the search result as exception value.

So where is the exceptional nature? Is a successful conclusion to a
search so exceptional?

It seems to me that you want to get rid of the notion of an exception as
something exceptional, in which case it would be better to give it a
different name.
-- 
Colin Adams
Preston Lancashire
()  ascii ribbon campaign - against html e-mail
/\  www.asciiribbon.org   - against proprietary attachments
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] re: Oracle stored procedures

2010-09-08 Thread Leonel Fonseca
Hi Peter,

Yes, from Takusen you can call Oracle stored procedures, functions,
packaged stored procedures or functions, or execute an arbitrary
pl/sql block.

In the Takusen software release there is a directory called
Database\Oracle\Test. There,  Enumerator.lhs, among other code has
these helpers you may want to use:


wrapPLSQLFunc funcname parms =
  let sqltext = begin  ++ (head args) ++  :=  ++ funcname
 ++ ( ++ placeholders ++ ); end;
  placeholders = concat (intersperse , (tail args))
  args = take (length parms) (map (\n - :x ++ show n) [1..])
  in  cmdbind sqltext parms

wrapPLSQLProc procname parms =
  let sqltext = begin  ++ procname
 ++ ( ++ placeholders ++ ); end;
  placeholders = concat (intersperse , args)
  args = take (length parms) (map (\n - :x ++ show n) [1..])
  in  cmdbind sqltext parms


Please, be aware of the following points:

1) If the pl/sql code doesn't need parameters and has no results, you
can use execDDL. (execDML returns a counter of affected rows).
2) If the procedure/function receives parameter, you'll need to use
cmdbind (or similar to cmdbind) to pass the parameters.
3) If the pl/sql code returns values, you have this options:
    3.a) The returned value is a reference (cursor): Takusen supports
this very fine. Use doQuery or similar.
    3.b) The return value is an scalar value: You can collect the
result with an iteratee, even if it is a single value.
    3.c) The return value is a complex oracle object: As of Takusen
0.8.5 there is no support for table of records of ...
3.d) The return value is Boolean. You'll get an error.

Little examples:

For case #1:

 -- Example 1.a:  We set nls_language to  american english.
 set_NlsLang_Eng :: DBM mark Session ()
 set_NlsLang_Eng =  execDDL $ sql
  alter session set nls_language='AMERICAN'

 -- Example #1.b: Now we set session language parameter to spanish.
 set_NlsLang_Esp :: DBM mark Session ()
 set_NlsLang_Esp =  execDDL $ sql
  alter session set nls_language='LATIN AMERICAN SPANISH'

For case #2:

 -- Example 2.a: We use database string concat function
concat'  ::  String - String - DBM mark Session String
concat' a b  =   do
   let ite :: Monad m = String - IterAct m String
   ite v _ = return $ Left v
   sqlcmd = wrapPLSQLFunc concat
  [bindP $ Out (::String), bindP a, bindP b]
   doQuery sqlcmd ite undefined

 -- later on the program, you'd have...
 some_string - concat' a b

For case #3:

 -- Case 3.b: We collect a single scalar value.
 qNlsLang   ::  DBM mark Session [String]
 qNlsLang   =   doQuery s ite []
  where
  s   =   select value from nls_session_parameters \
  \ where parameter = 'NLS_LANGUAGE'
  ite ::  (Monad m) = String -  IterAct m [String]
  ite a acc = result' ( a:acc )

 mostrar_NlsLang  ::  DBM mark Session ()
 mostrar_NlsLang  =   qNlsLang = liftIO . print . head

 -- Another example for Case 3.b
 -- This time we don't use a list to accumulate results.
 s1 =  sql select systimestamp from dual

 sysTSasCTQ   ::  DBM mark Session CalendarTime
 sysTSasCTQ=  do

let ite :: (Monad m) = CalendarTime - IterAct m CalendarTime
ite x  _  =  result' x

t -  liftIO ( getClockTime = toCalendarTime)
doQuery s1 ite t


--

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


Re: [Haskell-cafe] Re: ANNOUNCE: GotoT-transformers version 1.0

2010-09-08 Thread Antoine Latter
On Wed, Sep 8, 2010 at 11:54 PM, Ertugrul Soeylemez e...@ertes.de wrote:
 Gregory Crosswhite gcr...@phys.washington.edu wrote:

  On 09/08/10 19:14, Ertugrul Soeylemez wrote:
  Have you looked at ContT from monadLib?  It's not just a goto, but
  in fact a setjmp/longjmp, i.e. a goto with value.  I haven't used it
  for anything yet, but it might come in handy for some algorithms:
 
  [...]

 Whoa, that's cool!  I glanced at monadLib but I didn't realize that it
 let you create labels that you could return to like that.  :-) (I know
 of callCC, but that isn't quite the same as this.)  Thanks for the
 pointer!

 It is, in fact, callCC. ;)


 The limitation with continuation-based approaches to goto, though, is
 that you can only jump back to points that you've seen before.  The
 reason why I don't use a continuation-based approach in GotoT is
 because I wanted the user (i.e., me, and maybe one or two other people
 if I'm lucky :-) ) to be able to jump to an arbitrary point outside
 the calculation that has never been visited before, rather than
 returning a previously visited point of the same calculation.

 Of course, if someone can prove to me that I am wrong and that GotoT
 semantics can be implemented with continuations, then I would welcome
 this information.  :-)

 I don't think you need 'goto' to implement jumps in Haskell.  Note that
 functions as well as computations are first class:


To recover from my overly complex previous post, here is a much simply
goto based on existing monad transformers:

 goto :: Monad m = ContT r m r - ContT r m a
 goto (ContT m) = ContT $ \_ -
m return

Reading your post, Ertugrul, made something click for me

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