[Haskell-cafe] (Pre-) Announce: Data.GDS 0.1.0

2009-05-31 Thread Uwe Hollerbach
Hello, all,

I'm hereby announcing Data.GDS, a small module to write and
(eventually -- that's part of the "pre") read GDS files. For those of
you not in the semiconductor biz, GDS-II is one of the classic formats
of the industry. It's perhaps ever so slightly obsolete at this point,
as the OASIS format is in the process of displacing it, but there are
still huge numbers of designs in GDS format, and lots and lots of
tools deal with it.

Since I'm a sad sick weirdo(*), I spent a perfectly nice & sunny
NorCal day hacking up this initial version of this module. It is to
the point where it can generate a GDS file of your devising, although
your specification of it still has to be at a very low level. It would
be, and eventually will be, nicer to specify things at a higher level
of abstraction. Also, it will eventually be nice to be able to read
GDS files, returning an array of GDSRecord. I know how to do that, and
I plan to, but I haven't got there yet.

This ought to already be properly cabalized, and there's a small test
program included; run it, save the output somewhere, and compare that
with the sample GDS file which I also included in the tarball. If you
examine the GDS file itself, you will see that, although it is small,
it does in fact contain vital bits of design which will no doubt
enable the biz to continue Moore's law for at least another century or
so.

Once I've implemented the reader, I'll upload this to hackage; in the
meantime, if any of you are especially  interested in what the rest of
the interface to this should look like, I'm happy to hear your
suggestions!

Uwe

(*) In point of fact, I am neither sad nor sick; I am in fact mostly
happy & healthy. The reason I wasn't out taking a long walk today was
because, alas, I dinged one achilles tendon a few days ago, and wanted
to let it heal a bit... as to the "weirdo" charge, I beg you, gentle
readers, avert your eyes while I plead no contest! :-)


gds-0.1.0.tar.gz
Description: GNU Zip compressed data
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] How to implement this? A case for scoped record labels?

2009-05-31 Thread Iavor Diatchki
Hi,
Using a type class in the way Wren suggests seems to be the right way
to do this in Haskell, as it is at the moment.  I don't think that
this an inappropriate use of type classes at all---in fact, it is
exactly what type classes were designed to do (i.e., allow you to
reuse the same name at different types).  Note that you can combine
type classes and records to cut down on the typing:

data Request = Request { request_channel :: Channel, ... }
data Response = Response { response_channel :: Channel, ... }

class HasChannel t where
  get_channel :: t -> Channel
  set_channel :: Channel -> t -> t

instance HasChannel Request where
  get_channel = request_channel
  set_channel x t = t { response_channel = x }

and so on.  It is a bit verbose, but you only have to do it once for
your protocol, and then you get the nice overloaded interface.
Actually, having the non-overloaded names might also be useful in some
contexts (e.g., to resolve ambiguities).

-Iavor






On Mon, May 25, 2009 at 7:32 PM, wren ng thornton  wrote:
> ntu...@googlemail.com wrote:
>>
>> This however does not work because record selectors have module scope,
>> so the compiler will complain that channel et. al. are defined
>> multiple times. As a workaround I could put each type into its own
>> module, but at least GHC requires a file per module (which is *very*
>> inconvenient IMO). If we would have scoped labels (e.g. like proposed
>> here: http://legacy.cs.uu.nl/daan/pubs.html#scopedlabels) it seems
>> like it would have been straightforward.
>>
>> So certainly I am missing something and there is a better way to
>> design this. Hence this e-mail. I welcome any advice how this would
>> best be done in Haskell with GHC.
>
> One alternative is to use Haskell's support for ad-hoc overloading. Define a
> typeclass for each selector (or group of selectors that must always occur
> together) which is polymorphic in the record type. Combine this with the
> separate constructor types to get something like:
>
>    data HandshakeRequest = HandshakeRequest String ...
>    data HandshakeResponse = HandshakeResponse String Bool ...
>    ...
>    data BayeuxMessage
>        = HSReq HandshakeRequest
>        | HSRes HandshakeResponse
>        ...
>
>    class BayeuxChannel r where
>        channel :: r -> String
>    instance BayeuxChannel HandshakeRequest where
>        channel (HandshakeRequest ch ...) = ch
>    instance BayeuxChannel HandshakeResponse where
>        channel (HandshakeResponse ch _ ...) = ch
>    ...
>    class BayeuxSuccessful r where
>        successful :: r -> Bool
>    ...
>
>
> It's not pretty, but it gets the job done. Many people decry this as
> improper use of typeclasses though (and rightly so). A better approach would
> probably be to use GADTs or the new data families which give a sort of dual
> of typeclasses (typeclasses give a small set of functions for a large set of
> types; GADTs give a large set of functions for a small set of types[0]).
> Someone more familiar with those approaches should give those versions.
>
> If you want to be able to set the fields as well as read them then the
> classes should be more like lenses than projectors. For instance, this[1]
> discussion on Reddit. The two obvious options are a pair of setter and
> getter functions: (Whole->Part, Whole->Part->Whole); or a factored version
> of the same: Whole->(Part, Part->Whole).
>
> You should also take a look at the data-accessor packages[2][3] which aim to
> give a general solution to the lens problem. Also take a look at hptotoc[4],
> the Haskell implementation of Google's Protocol Buffers which has many
> similar problems to your Bayeaux protocol. In general, protocols designed
> for OO are difficult to translate into non-OO languages.
>
>
>
> [0] http://blog.codersbase.com/tag/gadt/
> [1]
> http://www.reddit.com/r/haskell/comments/86oc3/yet_another_proposal_for_haskell_the_ever_growing/c08f4bp
> [2] http://hackage.haskell.org/cgi-bin/hackage-scripts/package/data-accessor
> [3]
> http://hackage.haskell.org/cgi-bin/hackage-scripts/package/data-accessor-template
> [4] http://hackage.haskell.org/cgi-bin/hackage-scripts/package/hprotoc
>
> --
> Live well,
> ~wren
> ___
> 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] Umlauts in command line arguments

2009-05-31 Thread Gwern Branwen
On Sun, May 31, 2009 at 8:24 PM, GüŸnther Schmidt  wrote:
> Hi all,
>
> When a command line argument contains an umlaut that argument gets garbled.
>
> I'm using ghc 6.10.2 on Win XP. Are there any known solutions for this
> problem?
>
> Günther

GHC mangles UTF by default. You probably want to use one of the utf8
packages; eg. 
http://hackage.haskell.org/cgi-bin/hackage-scripts/package/utf8-string
or http://hackage.haskell.org/cgi-bin/hackage-scripts/package/utf8-light

(Neither of them seems to allow for accessing *arguments* rather than
stdin/stdout, but you could probably do something with the
encoding/decoding functions.)

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


[Haskell-cafe] Umlauts in command line arguments

2009-05-31 Thread GüŸnther Schmidt

Hi all,

When a command line argument contains an umlaut that argument gets garbled.

I'm using ghc 6.10.2 on Win XP. Are there any known solutions for this 
problem?


Günther

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


Re: [Haskell-cafe] How to implement this? A case for scoped record labels?

2009-05-31 Thread Brandon S. Allbery KF8NH

On May 25, 2009, at 08:20 , ntu...@googlemail.com wrote:

data HandshakeRequest = HandshakeRequest { channel :: String , ... }
data HandshakeResponse = HandshakeResponse { channel :: String,
successful :: Bool, ... }
...

data BayeuxMessage = HSReq HandshakeRequest
   | HSRes HandshakeResponse
   ...

This however does not work because record selectors have module scope,
so the compiler will complain that channel et. al. are defined
multiple times. As a workaround I could put each type into its own


Try -XDisambiguateRecordFields?

--
brandon s. allbery [solaris,freebsd,perl,pugs,haskell] allb...@kf8nh.com
system administrator [openafs,heimdal,too many hats] allb...@ece.cmu.edu
electrical and computer engineering, carnegie mellon universityKF8NH




PGP.sig
Description: This is a digitally signed message part
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] ANN: new version of uu-parsinglib

2009-05-31 Thread Ross Paterson
On Sun, May 31, 2009 at 09:40:38PM +0200, S. Doaitse Swierstra wrote:
> A new version of the uu-parsinglib has been uploaded to hackage. It is  
> now based on Control.Applicative where possible.
>
> Be warned that functions like some and many will be redefined in the  
> future.

Perhaps we should make some and many methods of Alternative, <* and *>
methods of Applicative and <$ a method of Functor, all with the current
definitions as defaults.  (John Meacham was also asking for the first
of these.)
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Re: Error message reform (was: Strange type error with associated type synonyms)

2009-05-31 Thread Henning Thielemann


On Thu, 28 May 2009, Claus Reinke wrote:


Just, please, keep in mind that there is no one-size-fits-all:
improving a message for one group of users might well make
it less useful for another group.


I once thought, that error messages must be configurable by libraries, 
too. This would be perfect for EDSLs that shall be used by non-Haskellers. 
But I have no idea how to design that.

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


Re: [Haskell-cafe] Parsec float

2009-05-31 Thread wren ng thornton

Jason Dusek wrote:

2009/05/30 Bartosz Wójcik :

...reading RWH I could not memorize what those liftM funtions
meant.


  The basic one, `liftM`, means `fmap`, though specialized for
  functors that are monads.

Prelude Control.Monad> :t liftM
liftM :: forall a b (m :: * -> *). (Monad m) => (a -> b) -> m a -> m b
Prelude Control.Monad> :t fmap
fmap :: forall a b (f :: * -> *). (Functor f) => (a -> b) -> f a -> f b



Category theoretically, all the following are (or should be!) equal: 
fmap, (<$>), liftA, liftM.


Type theoretically, they differ in whether they require Functor, 
Applicative, or Monad. Unfortunately there's a clash between the current 
types and their CT backing. That is, Monad doesn't require Applicative 
(or Functor), so people will often use liftM to avoid extra type 
constraints.


Operationally, fmap and (<$>) are potentially more efficient. The liftA 
and liftM functions re-engineer fmap by using pure/(<*>) or return/ap, 
thanks to CT. The (<$>) function is just an alias for fmap. But the fmap 
function is part of a type class and so it may have a specific 
implementation which is more efficient than the generic one provided by CT.


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


Re[2]: [Haskell-cafe] Bool as type class to serve EDSLs.

2009-05-31 Thread Henning Thielemann


On Thu, 28 May 2009, Bulat Ziganshin wrote:


i use another approach which imho is somewhat closer to interpretation
of logical operations in dynamic languages (lua, ruby, perl):

a ||| b | isDefaultValue a = b
   | otherwise= a

a &&& b | isDefaultValue a = defaultValue
   | otherwise= b

-- Class of types having default value:
classDefaults a  where defaultValue :: a
instance Defaults () where defaultValue = ()
instance Defaults Bool   where defaultValue = False
instance Defaults [a]where defaultValue = []



The absence of such interpretations and thus the increased type safety was 
one of the major the reasons for me to move from scripting languages to 
Haskell.

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


Re: [Haskell-cafe] Re: Error message reform

2009-05-31 Thread wren ng thornton

Tillmann Rendel wrote:

wren ng thornton wrote:
> (Though it doesn't necessarily generalize to cover similar messages like:
>
> Prelude> :t (\x -> x) :: a -> b
> :1:7:
> Couldn't match expected type `b' against inferred type `a'
>   `b' is a rigid type variable bound by
>   the polymorphic type `forall a b. a -> b' at :1:0
>   `a' is a rigid type variable bound by
>   the polymorphic type `forall a b. a -> b' at :1:0
> In the expression: x

I find this slightly more complicated case quite confusing with the 
current wording:


  Prelude> :t (\x -> x) :: (a -> b) -> (a -> a)
  :1:7:
  Couldn't match expected type `a' against inferred type `b'
`a' is a rigid type variable bound by
an expression type signature at :1:14
`b' is a rigid type variable bound by
an expression type signature at :1:19
  In the expression: x
  In the expression: (\ x -> x) :: (a -> b) -> (a -> a)

This message suggests that ghc has inferred type b for x.



I agree with Claus that this (both of these, actually) are symptoms of 
not giving enough type information for the user to reconstruct what the 
problem actually is.


I think an initial solution should be to print out _some_ type inferred 
for x. We can't print out "the" type, because the error is that there 
isn't one. As for which type to print for x, it'd be most informative 
(though perhaps not most helpful) to print both types that are being 
unified, and to alter the rigidity messages to indicate which type 
they're rigid for. For example, perhaps something like this:


Couldn't match expected type `a' against inferred type `b'
In the expression: x
which should have type: (a -> a)
where `a' is a rigid type variable bound by
an expression with type signature at :1:14
but actually has type: (a -> b)
where `b' is a rigid type variable bound by
an expression with type signature at :1:19
In the expression: (\ x -> x) :: (a -> b) -> (a -> a)

It's too wordy, but it's a start. This is also prime ground for wanting 
to have configurable levels of error reports, since some users will find 
it helpful to see both types but others will find it confusing.



Sometimes, even when the complete type is given, that's not enough 
information because each of the type variables are non-linear and so 
it's not clear where exactly the problem crept up. We can see a little 
of this in the above example where, even with the new message, `a' 
occurs twice in the first type. By presenting both types, users can 
figure it out here--- though with only the last type signature given it 
wouldn't be clear whether it wants ((b->b)->a->a) or ((a->b)->a->b) or 
even ((a->b)->b->a).


In more complex examples I've often found non-linearity to be the most 
uninformative part of the current messages. Perhaps a message like above 
which gives both types will be enough in practice to clear it up. If 
not, then it may be worth providing some sort of metasyntax to 
distinguish what subpart of the type is being discussed (e.g. bold face, 
or an underlining carrot on the next line, etc).


For really intricate type hacking, even this isn't enough because the 
programming errors often happen far from where the type errors are 
finally caught. In an ideal world, ghc could dump the entire proof 
forest generated by inference, so an external tool[1] could be used to 
browse through it and track the complete history of where inferred types 
came from. This gives a partial view of the inferred types for a 
compilation unit, something I've often wanted (rather than the manual 
comment/reload/uncomment routine). The proof forest could even be used 
as an interlingua over which people can write filters to generate 
messages they find most helpful.


Ah the joys of ideal worlds... ;)


[1] Something like the Dynasty[2] debugger for logic programming in Dyna.

[2] http://www.cs.jhu.edu/~jason/papers/eisner+al.infovis06-poster.pdf

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


[Haskell-cafe] Re: Lazy Parsing

2009-05-31 Thread S . Doaitse Swierstra

Dear Gunther,


I am providing my solution, on which one can of course specialise in  
making sure that a valid date is parsed, which would be a bit more  
cumbersome; how should e.g. error correction be done. I prefer to test  
afterwards in such situations.


Best,
Doaitse



module Guenther where
import Text.ParserCombinators.UU.Parsing
import Text.ParserCombinators.UU.BasicInstances
import Text.ParserCombinators.UU.Examples hiding (main)
import Control.Applicative hiding ((<*), (*>), (<$))

{- The first decision we have to make is what kind of input we are  
providing. The simplest case is just to assume simple characters,  
hence for our input type we will use the standard provided stream of  
Characters: Str Char, so we use the type of our parsers to be the type  
used  in the Examples module; since we do not know whether we wil be  
using the parsers in a monadic mode too we stay on the safe side ans  
use the type P_m -}


type GP a = P_m (Str Char) a  -- GP stands for GuenterParser

{- Once we know that our input contains characters, but that in our  
output we what to have integer values, we start out by building a  
parser for a single integer , for which we use the function pNatural  
form the examples-}


pDate = (,,) <$> pNatural <* pDot <*> pNatural <* pDot <*>  
(pNatural ::GP Int)

pDot  = pSym '.'
{-
main = do print (test pDate "3.4.1900")
  print (test pDate "3 4 1900")
  print (test pDate "..1900")-}

-- end of Module Guenther

By playing with insertion and deletion costs (e.g. by building a more  
picky pNatural) one can control the error recovery. Another option to  
get better error recovery would be to define a specialised instance of  
Provides which removes spaces. You might even temporarily pSwitch to  
the use of this state





Period.

I do not even manage to write a parser for even a mere digit or a  
simple character. I have read the tutorial from a to a to z and from  
z to a and there were a few words I recognized.


I mean I'd like to be able to turn "12.05.2009" into something like  
(12, 5, 2009) and got no clue what the code would have to look like.  
I do know almost every variation what the code must not look like :).


I am guessing here that when one does define a parsing function,  
since all the parser combinators aren't function but methods, one  
*must* also provide a type signature so that the compiler knows the  
actual *instance* method?



Günther


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


Re: [Haskell-cafe] ANN: new version of uu-parsinglib

2009-05-31 Thread Conor McBride


On 31 May 2009, at 20:40, S. Doaitse Swierstra wrote:

A new version of the uu-parsinglib has been uploaded to hackage. It  
is now based on Control.Applicative where possible.


It's mutual.

Cheers

Conor

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


[Haskell-cafe] ANN: new version of uu-parsinglib

2009-05-31 Thread S. Doaitse Swierstra
A new version of the uu-parsinglib has been uploaded to hackage. It is  
now based on Control.Applicative where possible.


Be warned that functions like some and many will be redefined in the  
future.


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


Re: [Haskell-cafe] Re: Lazy Parsing

2009-05-31 Thread Stephen Tetley
Hi Günther


I suspect the problem you were having is that there are various
'parsers' (more correctly 'parser types') defined in
Text.ParserCombinators.UU.Parsing and the code you had in your running
example didn't always have enough information to allow GHC to pick a
particular one.

The /test/ function in Examples demands the parser to be of type 'P_m
state a' [1], so if you were running your parsers with /test/ in your
main function this would be give the parsers a concrete, inferable
type (if you hadn't given then a type signature). Once you comment out
main, the parsers have a more general type than 'P_m state a', which
can't be inferred due to class constraints.

Maybe the 'haskeller's inituition' in this instance is to define the
type signatures and the functions at the same time, admittedly this
can be difficult for functions with heavy use of type classes.

Best wishes

Stephen


[1] I'm afraid I don't know the intricacies of the particular types in
the new UU parsing library, until this morning I'd only used the
previous version in uulib.


2009/5/31 Guenther Schmidt :
> Dear Doaitse,
>
> thank you very much for your help.
>
>>
>> I am curious to know what made you go wrong with the tutorial, and caused
>> that you could not find the solution below?
>>
> Well let's first agree that I'm not very bright. I hate to admit it, but
> it's a simple fact ;-).
>
> Second let's agree that the uu-parsinglib is a *very* sophisticated beast, I
> have not seen anything else like it out there, my sincere congratulations
> for it. Thirdly the tutorial is also a very sophisticated beast, and
> forthly, well just see point 1 :-).
>
> And I just figured out why I was unable to write even that simple parser.
>
> The code you sent me works just fine, I copied and pasted it, no problems.
>
> But, as soon as I comment out the "main" function the type checker
> complains, because now the ghci's type checker can no longer infer the types
> of pDate or pDot. And this is exactly what happened. I kept getting error
> messages from ghci, eventhough I had defined my parsers possible correctly,
> but, *minus* the type signatures *and* minus any main function that called
> it.
>
> In hindsight I realize that this is a trap I have walked into many times
> before, I guess I still have not acquired a Haskellers intuition.
>
> I promise to do better next time :)
>
> Günther
>
>
> ___
> 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: Lazy Parsing

2009-05-31 Thread Gü?nther Schmidt

Dear Malcom,

thanks for helping.

I had actually come to Haskell originally because of a parsing problem. 
I had been using Smalltalk until I started a project which required 
parsing files. Until then I had not done any RW parsing.


Well the route was more a Parsec -> Haskell, wtf is Haskell? Anyway 
eventually I dropped Smalltalk and got addicted to Haskell. And managed 
 familiarize myself with Haskell and Parsec, the latter as it turned 
out I didn't even need to solve my original problem.


Anyway polyparse certainly is an option, but there are a few things that 
despite my "list of failures" to use it give uu-parsinglib a special 
appeal, the breadth-first approach with choice, I find that terrible 
elegant. Due to some kicks in my behind it seems that I might be able to 
use Doaitse's combinators now, some more details on that are in another 
post.



Günther


Malcolm Wallace schrieb:
It is my pleasure to announce that after 5 days of experimenting with 
uu-parsinglib I have absolutely no clue, whatsoever, on how to use it.


I do not even manage to write a parser for even a mere digit or a 
simple character.


I don't know whether you will be willing to change over to polyparse 
library, but here are some hints about how you might use it.


Given that you want the input to be a simple character stream, rather 
than use a more elaborate lexer, the first thing to do is to specialise 
the parser type for your purposes:


 > type TextParser a = Parser Char a

Now, to recognise a "mere digit",

 > digit :: TextParser Char
 > digit = satisfy Char.isDigit

and for a sequence of digits forming an unsigned integer:

 > integer :: TextParser Integer
 > integer = do ds <- many1 digit
 >  return (foldl1 (\n d-> n*10+d)
 > (map (fromIntegral.digitToInt) ds))
 >   `adjustErr` (++("expected one or more digits"))

I mean I'd like to be able to turn "12.05.2009" into something like 
(12, 5, 2009) and got no clue what the code would have to look like. I 
do know almost every variation what the code must not look like :).


 > date = do a <- integer
 >   satisfy (=='.')
 >   b <- integer
 >   satisfy (=='.')
 >   c <- integer
 >   return (a,b,c)

Of course, that is just the standard (strict) monadic interface used by 
many combinator libraries.  Your original desire was for lazy parsing, 
and to achieve that, you must move over to the applicative interface.  
The key difference is that you cannot name intermediate values, but must 
construct larger values directly from smaller ones by something like 
function application.


 > lazydate = return (,,) `apply` integer `discard` dot
 >`apply` integer `discard` dot
 >`apply` integer
 >where dot = satisfy (=='.')

The (,,) is the constructor function for triples.  The `discard` 
combinator ensures that its second argument parses OK, but throws away 
its result, keeping only the result of its first argument.


Apart from lazy space behaviour, the main observable difference between 
"date" and "lazydate" is when errors are reported on incorrect input.  
For instance:


  > fst $ runParser date "12.05..2009"
  *** Exception: In a sequence:
  Parse.satisfy: failed
  expected one or more digits

  > fst $ runParser lazydate "12.05..2009"
  (12,5,*** Exception: In a sequence:
  Parse.satisfy: failed
  expected one or more digits

Notice how the lazy parser managed to build the first two elements of 
the triple, whilst the strict parser gave no value at all.


I know that the error messages shown here are not entirely satisfactory, 
but they can be improved significantly just by making greater use of the 
`adjustErr` combinator in lots more places (it is rather like Parsec's 
).  Errors containing positional information about the input can be 
constructed by introducing a separate lexical tokenizer, which is also 
not difficult.


Regards,
Malcolm



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


[Haskell-cafe] Re: Lazy Parsing

2009-05-31 Thread Guenther Schmidt

Dear Doaitse,

thank you very much for your help.



I am curious to know what made you go wrong with the tutorial, and 
caused that you could not find the solution below?


Well let's first agree that I'm not very bright. I hate to admit it, but 
it's a simple fact ;-).


Second let's agree that the uu-parsinglib is a *very* sophisticated 
beast, I have not seen anything else like it out there, my sincere 
congratulations for it. Thirdly the tutorial is also a very 
sophisticated beast, and forthly, well just see point 1 :-).


And I just figured out why I was unable to write even that simple parser.

The code you sent me works just fine, I copied and pasted it, no problems.

But, as soon as I comment out the "main" function the type checker 
complains, because now the ghci's type checker can no longer infer the 
types of pDate or pDot. And this is exactly what happened. I kept 
getting error messages from ghci, eventhough I had defined my parsers 
possible correctly, but, *minus* the type signatures *and* minus any 
main function that called it.


In hindsight I realize that this is a trap I have walked into many times 
before, I guess I still have not acquired a Haskellers intuition.


I promise to do better next time :)

Günther


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


Re: [Haskell-cafe] Re: Lazy Parsing

2009-05-31 Thread Malcolm Wallace
It is my pleasure to announce that after 5 days of experimenting  
with uu-parsinglib I have absolutely no clue, whatsoever, on how to  
use it.


I do not even manage to write a parser for even a mere digit or a  
simple character.


I don't know whether you will be willing to change over to polyparse  
library, but here are some hints about how you might use it.


Given that you want the input to be a simple character stream, rather  
than use a more elaborate lexer, the first thing to do is to  
specialise the parser type for your purposes:


> type TextParser a = Parser Char a

Now, to recognise a "mere digit",

> digit :: TextParser Char
> digit = satisfy Char.isDigit

and for a sequence of digits forming an unsigned integer:

> integer :: TextParser Integer
> integer = do ds <- many1 digit
>  return (foldl1 (\n d-> n*10+d)
> (map (fromIntegral.digitToInt) ds))
>   `adjustErr` (++("expected one or more digits"))

I mean I'd like to be able to turn "12.05.2009" into something like  
(12, 5, 2009) and got no clue what the code would have to look like.  
I do know almost every variation what the code must not look like :).


> date = do a <- integer
>   satisfy (=='.')
>   b <- integer
>   satisfy (=='.')
>   c <- integer
>   return (a,b,c)

Of course, that is just the standard (strict) monadic interface used  
by many combinator libraries.  Your original desire was for lazy  
parsing, and to achieve that, you must move over to the applicative  
interface.  The key difference is that you cannot name intermediate  
values, but must construct larger values directly from smaller ones by  
something like function application.


> lazydate = return (,,) `apply` integer `discard` dot
>`apply` integer `discard` dot
>`apply` integer
>where dot = satisfy (=='.')

The (,,) is the constructor function for triples.  The `discard`  
combinator ensures that its second argument parses OK, but throws away  
its result, keeping only the result of its first argument.


Apart from lazy space behaviour, the main observable difference  
between "date" and "lazydate" is when errors are reported on incorrect  
input.  For instance:


  > fst $ runParser date "12.05..2009"
  *** Exception: In a sequence:
  Parse.satisfy: failed
  expected one or more digits

  > fst $ runParser lazydate "12.05..2009"
  (12,5,*** Exception: In a sequence:
  Parse.satisfy: failed
  expected one or more digits

Notice how the lazy parser managed to build the first two elements of  
the triple, whilst the strict parser gave no value at all.


I know that the error messages shown here are not entirely  
satisfactory, but they can be improved significantly just by making  
greater use of the `adjustErr` combinator in lots more places (it is  
rather like Parsec's ).  Errors containing positional information  
about the input can be constructed by introducing a separate lexical  
tokenizer, which is also not difficult.


Regards,
Malcolm

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


Re: [Haskell-cafe] Type families in export lists

2009-05-31 Thread Lee Duhem
On Sun, May 31, 2009 at 7:10 PM, Manuel M T Chakravarty
 wrote:
> Lee Duhem:
>>
>> On Sat, May 30, 2009 at 7:35 PM, Maurí cio 
>> wrote:
>>>
>>> Hi,
>>>
>>> How do I include type families (used as associated
>>> types) in a module export list? E.g.:
>>>
>>> class MyClass a where
>>>   type T a :: *
>>>   coolFunction :: Ta -> a
>>>   (...)
>>>
>>> If I just include MyClass and its functions in the
>>> list, instances in other modules complain they don't
>>> know T, but I wasn't able to find how (where) to
>>> include T in the list.
>>>
>>
>> In export list, you can treat 'type T a' as normal type declaration, ie,
>> write
>> T(..)  in export list.
>
> There is also special syntax to export associated types.  You can write
>
>  MyClass (type T)
>
> in the export list; cf,
>
>  http://haskell.org/haskellwiki/GHC/Type_families#Import_and_export
>

This is a better way.

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


Re: [Haskell-cafe] Type families in export lists

2009-05-31 Thread Manuel M T Chakravarty

Lee Duhem:
On Sat, May 30, 2009 at 7:35 PM, Maurí cio   
wrote:

Hi,

How do I include type families (used as associated
types) in a module export list? E.g.:

class MyClass a where
   type T a :: *
   coolFunction :: Ta -> a
   (...)

If I just include MyClass and its functions in the
list, instances in other modules complain they don't
know T, but I wasn't able to find how (where) to
include T in the list.



In export list, you can treat 'type T a' as normal type declaration,  
ie, write

T(..)  in export list.


There is also special syntax to export associated types.  You can write

  MyClass (type T)

in the export list; cf,

  http://haskell.org/haskellwiki/GHC/Type_families#Import_and_export

Manuel

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


Re: [Haskell-cafe] (no subject)

2009-05-31 Thread Claus Reinke

--
type F a = Int

class A a where
 foo :: A b => a (F b)
--

GHC - OK
Hugs - Illegal type "F b" in constructor application


This time, I'd say Hugs is wrong (though eliminating that initial
complaint leads back to an ambiguous and unusable method 'foo').


I only just recognized the horrible error message from the first
example.. what Hugs is trying to tell us about is a kind error!

The kind of 'a' in 'F' defaults to '*', but in 'A', 'F' is applied to
'b', which, via 'A b' is constrained to '*->*'. So Hugs is quite
right (I should have known!-).

The error message can be improved drastically, btw:

   :set +k
   ERROR file:.\hugs-vs-ghc.hs:19 - Kind error in constructor application
   *** expression : F b
   *** constructor : b
   *** kind : a -> b
   *** does not match : *

See http://cvs.haskell.org/Hugs/pages/hugsman/started.html and
search for '+k' - highly recommended if you're investigating kinds.

Claus


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


Re: [Haskell-cafe] Re: Lazy Parsing

2009-05-31 Thread Stephen Tetley
Hi Günther

The code below should work for your simple example, provided it hasn't
lost formatting when I pasted it in to the email.

I was a bit surprised that there is no pSatisfy in this library, but
there are parsers for digits, lower case, upper case letters etc. in
the Examples module that would otherwise be achieved with pSatisfy.

Best wishes

Stephen



{-# LANGUAGE FlexibleContexts   #-}

module Demo1 where

import Text.ParserCombinators.UU.Examples
import Text.ParserCombinators.UU.Parsing


-- here's a simple character '@' parser
pAtSym :: Symbol p Char Char => p Char
pAtSym = pSym '@'

test_simple_char  = test pAtSym "@"
test_simple_char2 = test pAtSym "@"


-- pDigit is supplied in Text.ParserCombinators.UU.Examples
test_any_digit= test pDigit "6"

-- pNatural is supplied in Text.ParserCombinators.UU.Examples
-- It looks like the most likely candidate to parse a
-- sequence of digits...

test_natural   = test pNatural "1234"

--  ... and it is!

-- parse a date "12.05.2009" as a triple (Int,Int,Int)
pDateTriple :: (Symbol p (Char,Char) Char, Applicative p, ExtApplicative p st,
Provides st Char Char)
=> p (Int,Int,Int)
pDateTriple = (,,) <$> pNatural <* pDot <*> pNatural <* pDot <*> pNatural

pDot :: (Symbol p Char Char, Applicative p) => p [Char]
pDot = lift <$> pSym '.'

test_date = test pDateTriple "12.05.2009"
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] GHCi vs. Hugs (record syntax)

2009-05-31 Thread Claus Reinke

head[[]{}]

GHCi: []
Hugs: ERROR - Empty field list in update

What is the correct behavior?


Seems as if GHC interprets []{} as labelled construction instead
of labelled update - 3 Expressions (the grammar productions):

   | qcon { fbind1 , ... , fbindn } (labeled construction, n>=0) 
   | aexp { fbind1 , ... , fbindn } (labeled update, n >= 1) 


But the grammar (3.2) makes [] and () into exceptions (gcon, not qcon)

   gcon -> () 
   | [] 
   | (,{,}) 
   | qcon 


(though interpreting them as nullary constructors may be more
consistent..).

Btw, the language report is recommended browsing for all Haskellers:
http://www.haskell.org/haskellwiki/Language_and_library_specification

In addition to fun puzzles like the above, it also answers many beginner 
questions frequently asked on this list and provides lots of small code

snippets.

What do I win?-)
Claus


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


Re: [Haskell-cafe] (no subject)

2009-05-31 Thread Claus Reinke

--
type F a = Int

class A a where
 foo :: A b => a (F b)
--

GHC - OK
Hugs - Illegal type "F b" in constructor application


This time, I'd say Hugs is wrong (though eliminating that initial
complaint leads back to an ambiguous and unusable method 'foo').

4.2.2 Type Synonym Declarations, lists only class instances as
exceptions for type synonyms, and 'Int' isn't illegal there.


--
type F a = Int

class A a where
 foo :: F a

instance A Bool where
 foo = 1

instance A Char where
 foo = 2

xs = [foo :: F Bool, foo :: F Char]
--

GHC:

M.hs:14:6:
   Ambiguous type variable `a' in the constraint:
 `A a' arising from a use of `foo' at M.hs:14:6-8
   Probable fix: add a type signature that fixes these type variable(s)

M.hs:14:21:
   Ambiguous type variable `a1' in the constraint:
 `A a1' arising from a use of `foo' at M.hs:14:21-23
   Probable fix: add a type signature that fixes these type variable(s)

Hugs: [1,2]


Neither seems correct? 4.3.1 Class Declarations, says:

   The type of the top-level class method vi is: 
   vi :: forall u,w. (C u, cxi) =>ti 
   The ti must mention u; ..


'foo's type, after synonym expansion, does not mention 'a'.

Claus


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


Re: [Haskell-cafe] Which type variables are allowed in a context?

2009-05-31 Thread Claus Reinke

--
class A a where
 foo :: A (b d) => a (c b)
--

GHC compiles it successfully, but Hugs rejects it:

Ambiguous type signature in class declaration
*** ambiguous type : (A a, A (b c)) => a (d b)
*** assigned to: foo


'd' ('c' in the error message) does not occur in any position that
would allow to determine it, so you'll have a hard time using 'foo'.


What is the correct behavior, and which part of the haskell 98 report
explains this?


4.3.4 Ambiguous Types, .. (?)

strictly speaking, that only rules out expressions of ambiguous
types, so GHC can defer complaining until you try to use 'foo',
and Hugs might give a dead code warning instead of an error,
but the late errors can be really confusing:

   Could not deduce (A (b d)) from the context (A (b d1)) ..

so GHC's no-error, no-warning approach for the class method
isn't optimal

Claus


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


Re: [Haskell-cafe] Question on kind inference

2009-05-31 Thread Claus Reinke

---
class A a where
 foo :: a b

class B a

class (A a, B a) => C a
---

GHC compiles it without errors, but Hugs rejects it: "Illegal type in
class constraint".


The error message is horribly uninformative.


What is the correct behavior, and which part of the haskell 98 report
explains this?


4.6 Kind Inference, combined with 4.5(.1) dependency analysis.

My interpretation: 'A' and 'B' are not in the same dependency group,
so 'a's kind in 'B' defaults to '*', so 'C' is ill-kinded. Try moving 'B'
into a separate module to get the same effect in GHC (which, in the
single-module case, uses 'A' and 'C' to determine the kind of 'B's 'a').

Claus


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


Re: [Haskell-cafe] Parsing command lines

2009-05-31 Thread Kalman Noel
Patai Gergely schrieb:
> is there a function that can safely split a command line into a FilePath
> to the executable and its parameters? 

In the yi source code, in HConf.Utils, there's a function that does part
of what you want, but maybe incorrectly (because I wrote it, and it
traverses the string in a rather primtive way).

-- | Break up a string the way a shell breaks up a command into arguments.
-- Similar to 'words', but respects quotes and escaped spaces.  TODO: Verify
-- this function.

shellWords :: String -> [String]
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] GHCi vs. Hugs (record syntax)

2009-05-31 Thread Ryan Ingram
Hi Vladimir,

I don't have any answers for your questions, but what are you trying
to do that's causing you to play with the edges of the parser/type
system?

  -- ryan

On Sun, May 31, 2009 at 12:41 AM, Vladimir Reshetnikov
 wrote:
> Hi,
>
> I tried to evaluate this expression:
>
> head[[]{}]
>
> GHCi: []
> Hugs: ERROR - Empty field list in update
>
> What is the correct behavior?
>
> Thanks,
> Vladimir
> ___
> 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] GHCi vs. Hugs (record syntax)

2009-05-31 Thread Vladimir Reshetnikov
Hi,

I tried to evaluate this expression:

head[[]{}]

GHCi: []
Hugs: ERROR - Empty field list in update

What is the correct behavior?

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


[Haskell-cafe] (no subject)

2009-05-31 Thread Vladimir Reshetnikov
Hi,

Seems that Haskell allows to specify "dummy" type variables in a
declaration of a type synonym, which do not appear in its right-hand
side. This can lead to interesting effects, which appears differently
in GHC and Hugs. I would like to know, what behavior is correct
according to the haskell 98 report.

1)
--
type F a = Int

class A a where
  foo :: A b => a (F b)
--

GHC - OK
Hugs - Illegal type "F b" in constructor application

2)
--
type F a = Int

class A a where
  foo :: F a

instance A Bool where
  foo = 1

instance A Char where
  foo = 2

xs = [foo :: F Bool, foo :: F Char]
--

GHC:

M.hs:14:6:
Ambiguous type variable `a' in the constraint:
  `A a' arising from a use of `foo' at M.hs:14:6-8
Probable fix: add a type signature that fixes these type variable(s)

M.hs:14:21:
Ambiguous type variable `a1' in the constraint:
  `A a1' arising from a use of `foo' at M.hs:14:21-23
Probable fix: add a type signature that fixes these type variable(s)

Hugs: [1,2]



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


[Haskell-cafe] Which type variables are allowed in a context?

2009-05-31 Thread Vladimir Reshetnikov
Hi,

Consider this (a bit pathological) Haskell code:

--
class A a where
  foo :: A (b d) => a (c b)
--

GHC compiles it successfully, but Hugs rejects it:

Ambiguous type signature in class declaration
*** ambiguous type : (A a, A (b c)) => a (d b)
*** assigned to: foo

What is the correct behavior, and which part of the haskell 98 report
explains this?

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


[Haskell-cafe] Question on kind inference

2009-05-31 Thread Vladimir Reshetnikov
Hi,

Consider this Haskell code:

---
class A a where
  foo :: a b

class B a

class (A a, B a) => C a
---

GHC compiles it without errors, but Hugs rejects it: "Illegal type in
class constraint".
What is the correct behavior, and which part of the haskell 98 report
explains this?

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


Re: [Haskell-cafe] Haskell and symbolic references

2009-05-31 Thread Matt Morrow
(i always forget to reply-to-all)

If you'd like to reference C functions with Strings, one possible way is to
use System.Posix.DynamicLinker and the wrapper over libffi that's been
uploaded to hackage recently:

[...@monire asdf]$ ghci
GHCi, version 6.10.1: http://www.haskell.org/ghc/  :? for help
Loading package ghc-prim ... linking ... done.
Loading package integer ... linking ... done.
Loading package base ... linking ... done.

ghci> :m + Foreign.LibFFI
ghci> :m + Foreign.Ptr Foreign.Storable
ghci> :m + Foreign.C.Types Foreign.C.String
ghci> :m + System.Posix.DynamicLinker

ghci> malloc <- dlsym Default "malloc"
Loading package unix-2.3.1.0 ... linking ... done.
ghci> syscall <- dlsym Default "syscall"

ghci> :! echo -ne "#include \n__NR_execve\n" | cpp | tac | grep
-E "^[0-9]+$" | head -1 > NOODLES
ghci> nr_execve :: CLong <- (read . head . words) `fmap` readFile "NOODLES"
ghci> :! rm -f NOODLES

ghci> let sizeOfPtrCChar = sizeOf(undefined::Ptr())
ghci> argv <- callFFI malloc (retPtr (retPtr retCChar)) [argCSize
(2*fromIntegral sizeOfPtrCChar)]
Loading package bytestring-0.9.1.4 ... linking ... done.
Loading package libffi-0.1 ... linking ... done.

ghci> sh <- newCString "/bin/sh"
ghci> poke argv sh
ghci> poke (argv`plusPtr`sizeOfPtrCChar) 0

ghci> callFFI syscall retCLong [argCLong nr_execve, argPtr sh, argPtr argv,
argCInt 0] {-never returns-}
sh-3.2$ echo $0
/bin/sh
sh-3.2$ exit
exit
[...@monire asdf]$

Matt

On Fri, May 29, 2009 at 11:41 AM, Khudyakov Alexey <
alexey.sklad...@gmail.com> wrote:

> On Friday 29 of May 2009 19:34:44 Patrick LeBoutillier wrote:
> > Hi all,
> >
> > Is it possible with Haskell to call a function whose name is contained
> > in a String?
> > Something like:
> >
> > five = call_func "add" [2, 3]
> >
> > If not, perhaps this is acheivable using FFI?
> >
> Or maybe you are asking for template haskell[1]. With it you can actually
> generate function at compile time. It depends on waht you actually need.
>
> > {-# LANGUAGE TemplateHaskell #-}
> > import Language.Haskell.TH
> >
> > five = $( foldl appE (varE $ mkName "+") [ litE $ integerL 2
> >  , litE $ integerL 3 ] )
>
>
> [1] http://haskell.org/haskellwiki/Template_Haskell
>
> --
>   Khudyakov Alexey
> ___
> 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