Re: String literals

2006-11-11 Thread Bulat Ziganshin
Hello Lennart,

Saturday, November 11, 2006, 6:49:15 AM, you wrote:
 class IsString s where
  fromString :: String - s

 My guess is that the defaulting mechanism needs to be extended to
 default to the String type as well,

imho, it is MUST BE. this will allow to became ByteString and any
other alternative string implementation a first-class Haskell citizen

btw, String class is regularly debated and even implemented in fps-soc
project where it includes a lot of common string functionality. just a
head of this class:

class (Eq s) = Stringable s where
-- Introducing and eliminating

-- | The empty string.
empty :: s
-- | Create a string containing a single 'Char'.
singleton :: Char - s

-- | Convert a string into a standard Haskell 'String'.
toList :: s - [Char]
toList = foldr (:) []



this may be disputed as part of library reorganization


-- 
Best regards,
 Bulatmailto:[EMAIL PROTECTED]

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


Re[2]: String literals

2006-11-11 Thread Bulat Ziganshin
Hello Donald,

Saturday, November 11, 2006, 7:33:48 AM, you wrote:
 Yes, pattern matching is the issue that occurs to me too.
 While string literals :: ByteString would be nice (and other magic
 encoded in string literals,  I guess), what is the story for pattern
 matching on strings based on non-inductive types like arrays?

it's my day :)  i'm regularly propose to pass list syntax to the
special class which should define methods for building and analyzing
data in head/tail way:

class ListLike ce e | ce-e where
  -- Construction
  empty :: ce
  cons :: c - ce - ce

  -- Analyzing
  null :: ce - Bool
  head :: ce - e
  tail :: ce - ce

and then the following definition:

trim (' ':xs) = trim xs
trim xs = xs

would imply the following type constraints:

trim :: (ListLike ce Char, Eq Char) =  ce - ce



-- 
Best regards,
 Bulatmailto:[EMAIL PROTECTED]

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


lambda-match example - from parser combinators to grammar combinators

2006-11-11 Thread Claus Reinke

Some of you have asked me whether I could provide more convincing
examples for lambda-match, or whether the shortcomings of Haskell
addressed in this proposal will be of practical relevance to the typical
seasoned Haskeller without specific interests in language design.

There are of course the various themes of views, pattern abstractions,
and first-class patterns, which could be built on top of lambda-match,
but I'd like to follow a slightly different angle first, inspired by an 
interesting off-list remark in response to the lambda-match proposal:


   I do consider myself a fairly seasoned Haskell programmer, and 
   to be honest, I have to admit that I rarely if ever have missed 
   composable pattern matching at the source level. Of course, that 
   could be because I subconsciously just work around the problem, 
   being used to Haskell as it is.


I do indeed believe that the problem of non-compositional pattern
match has been around in Haskell for so long that many of today's
Haskellers are no longer even aware of the issue, and of how much
it affects them.

So, here is one slightly less trivial example of using lambda-match, 
which happens to stand for a large group of possible applications, 
and for one particular area where the lack of compositional patterns
has influenced the Haskeller's world-view: 

Ever since I took up Haskell, I have wondered why Haskellers tend 
to specify their grammars not just twice (abstract + concrete), but 
thrice (abstract + parsing + unparsing).


The majority of seasoned Haskellers seems to accept that there must 
be parsers+pretty-printers, read+show, serialize+de-serialize, etc., and
that changing concrete syntax must involve making fixes in two separate 
bits of code, often even following two separate coding patterns.


But if one looks at so-called parser combinators, there is very little in
them that is parser-specific - usually only the literal parsers determine
that we are talking about parsing, whereas the majority of combinators
can be used just as well for other syntax-directed tasks. Still, people
tend not to reuse their combinator-based grammars for anything but
parsing.

I submit that one of the main reasons for this is that Haskellers have
come to accept that they can construct, but not deconstruct algebraic 
types in a compositional way (hence the use of parser combinators

for converting Strings into algebraic data types, and the use of more
pedestrian means for showing the latter as Strings; pretty-printing
libraries do at least use combinators, but do not reuse the grammars
specified through parser combinators).

Please have a look at the example (which needs both syntax patch 
and library from the proposal ticket, if you actually want to run it *,
but the ideas should be reasonably obvious even without): 


it specifies a concrete and abstract syntax for lambda calculus, and
the relationships between the two levels of syntax, using an algebraic
data type for the abstract syntax, and a grammar built with monadic
combinators for the rest. fairly standard, but for the following:

language and library support for monadic data parsing via 
lambda-match allow us to mix data parsing and string parsing in the 
same monadic framework, using the same grammar combinators 
to specify the concrete syntax and its relation to the abstract syntax

just once, in one piece of code.

we can use that single grammar for parsing, unparsing, or indeed, 
for mixtures of both (see the examples). A long time ago, I used 
something like this (then sadly without language support) to 
implement a syntax-oriented editor, with parsing and formatted

printing from a single grammar.

Although I haven't worked this out, I suspect that the technique 
would also apply to protocol-based applications: instead of 
writing client and server separately (and then trying to prove 
that they fit together and follow two sides of the same protocol), 
one might try to write a single grammar for the protocol between 
them, toggling mode at the appropriate points, and then client 
and server would simply be two instances/uses of the same 
grammar in its two start modes (so the server would generate 
prompts, parse requests, and generate responses, and the 
client would expect prompts, generate requests, and parse 
responses).


have fun;-)
claus

* I have submitted the syntax patch for the GHC head repository,
*  but GHC HQ are reluctant to apply the patch as long as there
*  is no obvious general interest (someone else but myself, and 
*  not just in private email to myself;-) in using these features. If 
*  you want to investigate lambda-match in GHC, to make up your

*  mind about whether or not you like the proposal (at the moment,
*  we're only talking about the daily snapshots of GHC head, not 
*  about long-term support in GHC, let alone inclusion in Haskell'!), 
*  please let yourself be heard!


   (more adventurous souls can of course apply the patch from the
   ticket themselves