Re: [Haskell-cafe] Using _ on the RHS of an equation?

2011-04-05 Thread Paul Keir
Hi Jason,

I like the idea. I've seen some code from Oleg Kiselyov which
uses __ (two underscores) in this way.

The thing that stops me though, is when I get it wrong, and
undefined fires somewhere, but I don't know where. Something
like you propose, but with a line number, would be sweet.

Paul

The University of Glasgow, charity number SC004401

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


[Haskell-cafe] Largest types in SYB

2009-12-18 Thread Paul Keir
I was looking for a simple generic technique targeting and transforming
the largest terms of a particular type. For example, with Expr and
Val declared as:

data Expr = Val Val | Add Expr Expr | Sub Expr Expr
  deriving (Show, Eq, Typeable, Data)

data Val = Var String | Struct [Expr]
  deriving (Show, Eq, Typeable, Data)

and a test Expr e,

e = Sub (Val $ Var A)
(Add (Val $ Var X1)
 (Val $ Struct [Add (Val $ Var Y1)
(Val $ Var Y2)]))

I wanted to replace only the inner Add expression
  Add (Val $ Var Y1) (Val $ Var Y2)
because its parent is not of the same type as itself (it's a list),
using a function such as chopAdd:

chopAdd (Add _ _)  = Val $ Var AddChop
chopAdd e  = e

But using everywhere from Scrap Your BoilerPlate (SYB):
everywhere (mkT repAdd) e
I'd get:
Sub (Val (Var A)) (Val (Var AddChop))
while I was hoping for:
Sub (Val (Var A)) (Add (Val (Var X1)) (Val (Struct [Val (Var AddChop)])))

The Haskell.org SYB wiki presents listifyWholeLists. This is relevant, though
it applies queries rather than transformations. It uses a function called
synthesize, which I was ultimately unable to properly reference, or
apply to the problem at hand.

So here is my solution:

everywhereBar :: GenericQ Bool - GenericT - GenericT
everywhereBar q f x
 | q x   =   (gmapT (everywhereBar (typeEq x) f) x)
 | otherwise = f (gmapT (everywhereBar (typeEq x) f) x)

 where typeEq p c = typeOf p == typeOf c

It's like SYB's everywhereBut, except
1. The consequence of q x being True is only to remove
   the application of f to the parent; not to stop traversal.
2. q is not constant. Instead it is the partial application of
   a local function, typeEq.

An application looks like:
everywhereBar (const False) (mkT repAdd) e
with (const False) the user is choosing the outcome of the very first q x
in everywhereBar.

I'm enjoying using SYB, and had hoped to use only functions from the package,
but couldn't find a way; and this does the job for now. I've also seen that
there are many other approaches to generic programming than SYB (even for AST
transformations in particular) but I wanted to understand SYB first. I'm
interested to know if anyone has a more elegant SYB solution.

And here's the monadic version:

everywhereBarM :: Monad m = GenericQ Bool - GenericM m - GenericM m
everywhereBarM q f x
 | q x   =  gmapM (everywhereBarM (typeEq x) f) x
 | otherwise = do x' - gmapM (everywhereBarM (typeEq x) f) x
  f x'
 where typeEq p c = typeOf p == typeOf c

Cheers,
Paul

The University of Glasgow, charity number SC004401
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] [: Where the bracket things are? :]

2009-06-29 Thread Paul Keir
I'd like to add my own custom list delimiters to ghc; such as the [: and :] of 
Data Parallel Haskell. The purpose is mainly to learn a little about GHC's 
internals.

Any suggestions on the GHC files I should look at first? Alternatively, maybe 
this is actually possible from outside the compiler.

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


[Haskell-cafe] ghci and applicative

2009-06-12 Thread Paul Keir
Hi,

I'm finding that some data types which use Applicative to
instantiate the Num class, give responses I wasn't expecting
at the ghci prompt. A simple example is list:

import Control.Applicative

instance (Num a) = Num [a] where
 as + bs = (+) $ as * bs
 (*) = undefined;abs = undefined
 signum = undefined; fromInteger = undefined

f1 = let op = (+) in [1,2,3] `op` [1,1,1]
f2 = let op = (+) in op [1,2,3] [1,1,1]

Functions f1 and f2 give no problems at the ghci prompt.
However if I instead type the body of either interactively,
I get an error:

*Main let op = (+)
*Main [1,2,3] `op` [1,1,1]

interactive:1:0:
Couldn't match expected type `Integer' against inferred type `[a]'
In the first argument of `op', namely `[1, 2, 3]'
In the expression: [1, 2, 3] `op` [1, 1, 1]
In the definition of `it': it = [1, 2, 3] `op` [1, 1, 1]

I get the same error message with op [1,2,3] [1,1,1]. Any thoughts?

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


RE: [Haskell-cafe] ghci and applicative

2009-06-12 Thread Paul Keir
Thanks Ryan, I'm slowly becoming aware of the effects of Monomorphism. I'll look
again at Neil Mitchell's blog post.

I guess it's the same thing when I try:

 let a = 1
 a + 1.0

I'm taking the mono as a clue that the type inferencing will complete after
each ghci carriage return; once only. In this example when a is set, it is
to an Integer. One might imagine ghci could wait until I use a somewhere, but
that's not how things are.
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] Nested Lists

2009-06-04 Thread Paul Keir
Hi all,

If I have a list, and I'd like to convert it to a list of lists,
each of length n, I can use a function like bunch:

bunch _ [] = []
bunch n as = let (c,cs) = splitAt n as in c:bunch n cs

 bunch 8 [1..16]
[[1,2,3,4,5,6,7,8],[9,10,11,12,13,14,15,16]]

If I now want to do the same for the nested lists, I can compose
an application involving both map and bunch:

 map (bunch 4) . bunch 8 $ [1..16]
[[[1,2,3,4],[5,6,7,8]],[[9,10,11,12],[13,14,15,16]]]

and I can bunch the new length 4 lists again:

 map (map (bunch 2)) . map (bunch 4) . bunch 8 $ [1..16]
1,2],[3,4]],[[5,6],[7,8]]],[[[9,10],[11,12]],[[13,14],[15,16

Clearly there is a pattern here involving the bunch function and
latterly, three Int parameters; 2, 4 and 8. My question is, can I
create a function that will take such parameters as a list, and
give the same result, for example:

 f [2,4,8] [1..16]
1,2],[3,4]],[[5,6],[7,8]]],[[[9,10],[11,12]],[[13,14],[15,16

or perhaps:

 f [bunch 2, bunch 4, bunch 8] [1..16]
1,2],[3,4]],[[5,6],[7,8]]],[[[9,10],[11,12]],[[13,14],[15,16

I think it may not be possible because the type signature of f would
depend on the length of its list parameter; but I'm not sure.

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


[Haskell-cafe] RE: Nested Lists

2009-06-04 Thread Paul Keir
Emil, Felipe,

Thanks. I don't know Type Families, but take the point that
the input can be parameterised with something something other
than a list. i.e. (8 :+: 4 :+: 2 :+: ()) presumably has the
same type as (4 :+: 2 :+: ()).

My intention was to use common list functions on the sublists,
but always then a concat for each level, to return to a flat list.
With that in mind I made the following oddity, which in any case
doesn't compile due to its use of infinite types.

app (f:fs) es = appUp (f:fs) es

  where len = genericLength (f:fs)
appUp   [] es = appDown es len
appUp   (f:fs) es = appUp (map map fs) (f es)
appDown es len= appDown (concat es) (len - 1)
appDown es 0  = es

Henning,

I agree with you, a tree would be much better for this. Thanks.

-Paul

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


[Haskell-cafe] iota

2009-06-01 Thread Paul Keir
Hi all,

 

I was looking for an APL-style iota function for array indices. I
noticed

range from Data.Ix which, with a zero for the lower bound (here
(0,0)),

gives the values I need:

 

 let (a,b) = (2,3)

 index ((0,0),(a-1,b-1))

 [(0,0),(0,1),(0,2),(1,0),(1,1),(1,2)]

 

However, I need the results as a list of lists rather than a list of
tuples; and

my input is a list of integral values. I ended up writing the following
function

instead. The function isn't long, but longer than I first expected. Did
I miss a

simpler approach?

 

iota :: (Integral a) = [a] - [[a]]

iota is = let count = product is

   tups = zip (tail $ scanr (*) 1 is) is

   buildRepList (r,i) = genericTake count $ cycle $

   [0..i-1]
= genericReplicate r

   lists = map buildRepList tups

 in transpose lists

 

 length $ iota [2,3,4]

 24

 

Thanks,

Paul

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


[Haskell-cafe] RE: iota

2009-06-01 Thread Paul Keir
That is quite spectacular. I revised my knowledge of sequence

with a little function, akin to sequence [xs1,xs2]:

 

seq2 xs1 xs2 = do x1 - xs1

x2 - xs2

return [x1,x2]

 

 seq2 [0,1] [0,1,2]

 [[0,0],[0,1],[0,2],[1,0],[1,1],[1,2]]

 

I like your point-free style too; and that's a nice use of pred.

 

Many thanks,

Paul

 

The iota function you're looking for can be a whole lot simpler if you
know about monads (list monad in particular) and sequence. For lists,
sequence has the following behaviour:

 

sequence [xs1,xs2, ... xsn] =

   [[x1,x2, ... , xn] | x1 - xs1, x2 - xs2, ... , xn - xsn]

 

 

Using this, you can reduce your iota function to a powerful one-liner:

 

iota = sequence . map (enumFromTo 0 . pred)

 

 

Kind regards,

 

Raynor Vliegendhart

 

 

From: Paul Keir 
Sent: 01 June 2009 10:01
To: haskell-cafe@haskell.org
Subject: iota

 

Hi all,

 

I was looking for an APL-style iota function for array indices. I
noticed

range from Data.Ix which, with a zero for the lower bound (here
(0,0)),

gives the values I need:

 

 let (a,b) = (2,3)

 index ((0,0),(a-1,b-1))

 [(0,0),(0,1),(0,2),(1,0),(1,1),(1,2)]

 

However, I need the results as a list of lists rather than a list of
tuples; and

my input is a list of integral values. I ended up writing the following
function

instead. The function isn't long, but longer than I first expected. Did
I miss a

simpler approach?

 

iota :: (Integral a) = [a] - [[a]]

iota is = let count = product is

   tups = zip (tail $ scanr (*) 1 is) is

   buildRepList (r,i) = genericTake count $ cycle $

   [0..i-1]
= genericReplicate r

   lists = map buildRepList tups

 in transpose lists

 

 length $ iota [2,3,4]

 24

 

Thanks,

Paul

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


[Haskell-cafe] [] == []

2009-05-29 Thread Paul Keir
Hi all,

GHC is not happy with this:

f = [] == []

nor this:

f' = ([]::(Eq a) = [a]) == ([]::(Eq a) = [a])

but this is OK:

f'' = ([]::[Integer]) == ([]::[Integer])

GHCI is comfortable with [] == [], so why not GHC? 'Just curious.

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


RE: [Haskell-cafe] [] == []

2009-05-29 Thread Paul Keir
f''' = ([]::[()]) == ([]::[()])

(Very pretty.)

So why doesn't ghc have 'default' instances?

-Original Message-
From: Eugene Kirpichov [mailto:ekirpic...@gmail.com]
Sent: Fri 29/05/2009 10:51
To: Paul Keir
Cc: haskell-cafe@haskell.org
Subject: Re: [Haskell-cafe] [] == [][MESSAGE NOT SCANNED]
 
2009/5/29 Paul Keir pk...@dcs.gla.ac.uk:
 Hi all,

 GHC is not happy with this:

 f = [] == []

This fails because GHC doesn't know which 'a' you mean, and can't
choose an Eq instance.


 nor this:

 f' = ([]::(Eq a) = [a]) == ([]::(Eq a) = [a])


This fails for the same reason.

 but this is OK:

 f'' = ([]::[Integer]) == ([]::[Integer])

 GHCI is comfortable with [] == [], so why not GHC? 'Just curious.

Because GHCI has some 'default' instances, whereas GHC doesn't. This
time, it probably chooses a=().


 Cheers,
 Paul

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





-- 
Eugene Kirpichov
Web IR developer, market.yandex.ru


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


[Haskell-cafe] Floating instance and pi

2009-05-29 Thread Paul Keir
Hi,

I'd like to make my ADT an instance of the Floating class,
but I'm not sure what to put for pi, and GHC gives a warning
without it:

Warning: No explicit method nor default method for `GHC.Float.pi'

I tried setting it to undefined, but that gives an error:

`pi' is not a (visible) method of class `Floating'

Any idea?

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


RE: [Haskell-cafe] Floating instance and pi

2009-05-29 Thread Paul Keir
Oops, I was hiding the Prelude's pi. My apologies.

-Original Message-
From: Deniz Dogan [mailto:deniz.a.m.do...@gmail.com]
Sent: Fri 5/29/2009 5:01 PM
To: Paul Keir
Cc: haskell-cafe@haskell.org
Subject: Re: [Haskell-cafe] Floating instance and pi[MESSAGE NOT SCANNED]
 
2009/5/29 Paul Keir pk...@dcs.gla.ac.uk:
 Hi,

 I'd like to make my ADT an instance of the Floating class,
 but I'm not sure what to put for pi, and GHC gives a warning
 without it:

 Warning: No explicit method nor default method for `GHC.Float.pi'

 I tried setting it to undefined, but that gives an error:

 `pi' is not a (visible) method of class `Floating'

 Any idea?

 Paul

Are you sure that your ADT fits into the Floating class in the first
place?  I reckon if it did, defining pi for it wouldn't be a
problem.  Could you show us the code you have?

-- 
Deniz Dogan

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


RE: [Haskell-cafe] Type class context propagation investigation[MESSAGE NOT SCANNED]

2009-05-28 Thread Paul Keir
Thanks. GHC at one stage suggested I add (Num a) =
to my Num instance (after I'd added (Eq a) = to my Eq
instance) and I didn't make the connection.


-Original Message-
From: Ryan Ingram [mailto:ryani.s...@gmail.com]
Sent: Thu 28/05/2009 01:18
To: Paul Keir
Cc: haskell-cafe@haskell.org
Subject: Re: [Haskell-cafe] Type class context propagation 
investigation[MESSAGE NOT SCANNED]
 
Think of classes like data declarations; an instance with no context
is a constant, and one with context is a function.  Here's a simple
translation of your code into data; this is very similar to the
implementation used by GHC for typeclasses:

 data EqDict a = EqDict { eq :: a - a - Bool }
 data ShowDict a = ShowDict { show :: a - String }
 data NumDict a = NumDict { num_eq :: EqDict a, num_show :: ShowDict a, plus 
 :: a - a - a }

The goal of the compiler is to turn your instance declarations into
these structures automatically.  Here's a translation of your original
instance:

 eq_foo :: EqDict (Foo a)
 eq_foo = EqDict { eq = undefined }

 show_foo :: ShowDict (Foo a)
 show_foo = ShowDict { show = undefined }

 num_foo :: NumDict (Foo a)
 num_foo = NumDict { num_eq = eq_foo, num_show = show_foo, plus = undefined }

Now if you add a constraint on the Eq instance, this means that eq
from eq_foo might refer to eq in the dictionary for a.  How do we
get that dictionary?  We just pass it as an argument!

 eq_foo :: EqDict a - EqDict (Foo a)
 eq_foo eq_a = EqDict { eq = undefined }

However, you don't have a similar constraint on the Num instance:

 num_foo :: NumDict (Foo a)
 num_foo = NumDict { num_eq = eq_foo something, num_show = show_foo, plus = 
 undefined }

The compiler wants to fill in something, but it can't; it doesn't
have a dictionary of the type EqDict a.  So it tells you so, saying
that Eq a is missing!

Once you add the (Eq a) constraint to the Num instance, it works:

 num_foo :: EqDict a - NumDict (Foo a)
 num_foo eq_a = NumDict { num_eq = eq_foo eq_a, num_show = show_foo, plus = 
 undefined }

You can also add a (Num a) constraint instead, and the compiler can
use it to get the Eq instance out:

 num_foo :: NumDict a - NumDict (Foo a)
 num_foo num_a = NumDict { num_eq = eq_foo (num_eq num_a), num_show = 
 show_foo, plus = undefined }

Of course, I'm glossing over the interesting details of the search,
but the basic idea is to attempt to fill in the blanks in these
definitions.

  -- ryan

On Wed, May 27, 2009 at 2:10 PM, Paul Keir pk...@dcs.gla.ac.uk wrote:
 Hi,

 How does the context of a class instance declaration affect its subclasses?

 The Num class instance outlined below has its requirement for Eq and Show
 satisfied on the preceding lines, and the code will compile. But if I, say,
 add an (Eq a) constraint to the Eq instance, in preparation for a simple
 (==) definition, I find that the Num instance declaration is left lacking.
 If I add the same (Eq a) constraint now to Num, calm is restored.

 data Foo a = F a

 instance Eq (Foo a) where
  (==) = undefined

 instance Show (Foo a) where
  show = undefined

 instance Num (Foo a)
  (+) = undefined
  ... etc.

 The thing that confuses me with this is that it seems like Num knows that
 an (Eq a) context has been applied, and so what it sees as a problem, is
 somehow also the solution. Any advice/rules of thumb? Does this situation
 occur elsewhere? How do these constraints propagate?

 Thanks,
 Paul

 ___
 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] Type class context propagation investigation

2009-05-28 Thread Paul Keir
Thanks Wren, that makes sense.

Ryan Ingram wrote:
 Think of classes like data declarations; an instance with no context
 is a constant, and one with context is a function.  Here's a simple
 translation of your code into data; this is very similar to the
 implementation used by GHC for typeclasses:
 
  data EqDict a = EqDict { eq :: a - a - Bool }
  data ShowDict a = ShowDict { show :: a - String }
  data NumDict a = NumDict { num_eq :: EqDict a, num_show :: ShowDict a, plus 
  :: a - a - a }
 
 The goal of the compiler is to turn your instance declarations into
 these structures automatically.

Another way of explaining this, if you're a Curry--Howard fan, is that 
the compiler is looking for a proof that the type belongs to the class, 
where = is logical implication. This is very similar to how Prolog 
searches for proofs, if you're familiar with logic programming.

Classes declare the existence of logical predicates, along with the form 
of what a proof of the predicate looks like. Instances declare a 
particular proof (or family of proofs if there are free type variables).


Thus, the Num class is declared as,

 class (Eq a, Show a) = Num a where ...

which says: for any type |a|, we can prove |Num a| if (and only if) we 
can prove |Eq a| and |Show a|, and can provide definitions for all the 
functions in the class using only the assumptions that |Eq a|, |Show a|, 
and |Num a|.


When you declare,

 instance Eq b = Eq (Foo b) where ...

you're providing a proof of |Eq b = Eq (Foo b)|. That is, you can 
provide a conditional proof of |Eq (Foo b)|, given the assumption that 
you have a proof of |Eq b|.

Notice how the context for instances is subtly different from the 
context for classes. For instances you're saying that this particular 
proof happens to make certain assumptions; for classes you're saying 
that all proofs require these assumptions are valid (that is, providing 
the functions isn't enough to prove membership in the class).


Later on you declare,

 instance Num (Foo b) where ...

but remember that this proof must have the same form as is declared by 
the class definition. This means that you must have proofs of |Eq (Foo 
b)| and |Show (Foo b)|. Unfortunately, you don't actually have a proof 
of |Eq (Foo b)|, you only have a proof of |Eq b = Eq (Foo b)|. In order 
to use that proof you must add the |Eq b| assumption to this proof as well:

 instance Eq b = Num (Foo b) where ...

When the compiler is complaining about the original one, what it's 
telling you is that the |Num (Foo b)| proof can never exist because you 
can never provide it with a proof of |Eq (Foo b)| in order to fulfill 
its requirements.

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


RE: [Haskell-cafe] The essence of my monad confusion

2009-05-27 Thread Paul Keir
Thanks for all the help. The simplified example indeed threw away too
much. There were no side effects.

Brent, of course I couldn't create your function; though I gained
through trying. I then found it useful to consider the type of:

fmap (\x - putStrLn x) getLine

which is IO (IO ()) and hence displays nothing to the screen.

Felipe, your recursive example was also compelling and concise.

Antoine, I see how the join capacity of a Monad can be useful in this
issue. I'm also reminded of what * can bring to fmap/$.

On reflection, I often trip up when learning by comparing IO to simpler
monads such as [] and Maybe. But [] and Maybe never have effects, and so
are poor foils. The ((-) t) monad is henceforth in my toolbox.

Paul


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


[Haskell-cafe] Type class context propagation investigation

2009-05-27 Thread Paul Keir
Hi,

How does the context of a class instance declaration affect its subclasses?

The Num class instance outlined below has its requirement for Eq and Show 
satisfied on the preceding lines, and the code will compile. But if I, say, add 
an (Eq a) constraint to the Eq instance, in preparation for a simple (==) 
definition, I find that the Num instance declaration is left lacking. If I add 
the same (Eq a) constraint now to Num, calm is restored.

data Foo a = F a

instance Eq (Foo a) where
 (==) = undefined

instance Show (Foo a) where
 show = undefined

instance Num (Foo a)
 (+) = undefined
 ... etc.

The thing that confuses me with this is that it seems like Num knows that an 
(Eq a) context has been applied, and so what it sees as a problem, is somehow 
also the solution. Any advice/rules of thumb? Does this situation occur 
elsewhere? How do these constraints propagate?

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


[Haskell-cafe] The essence of my monad confusion

2009-05-02 Thread Paul Keir
On the wiki page for Applicative Functors 
(http://www.haskell.org/haskellwiki/Applicative_functor) a familiar 
characteristic of monads is quoted; that they allow you to run actions 
depending on the outcomes of earlier actions. I feel comfortable with Functors 
and Applicative Functors, but I don't yet get that extra power that monads 
provide.

An example immediately follows that quotation on the wiki:

do text - getLine
   if null text
 then putStrLn You refuse to enter something?
 else putStrLn (You entered  ++ text)

For simplicity's sake, I modified it to avoid using the IO monad; the text 
binding is now provided by the first parameter, and (=) is used due to its 
similarity to fmap:

bar :: Monad m = m String - m String
bar as = (=)  (\a - if null a then return nothing else return something) 
 as

This works fine, so bar [Blah] gives [something], and bar (Just ) gives 
[nothing].

But, I can get the same effect using a Functor (replacing (=) with fmap):

bar2 :: Functor f = f String - f String
bar2 as = fmap (\a - if null a then nothing else something) as

Can anyone help me out of the swamp?

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


RE: [Haskell-cafe] fromInteger for Lists

2009-05-02 Thread Paul Keir
Thanks Andy, et al. I can stop hacking for now then. I'm using a simple 
fromList function already which seems like a reasonable, and at least 
semi-standard solution (http://www.haskell.org/hoogle/?hoogle=fromList)
Paul


-Original Message-
From: sploin...@gmail.com on behalf of andy morris
Sent: Sat 02/05/2009 00:13
To: Paul Keir
Cc: haskell-cafe@haskell.org
Subject: Re: [Haskell-cafe] fromInteger for Lists[MESSAGE NOT SCANNED]
 
2009/5/1 Paul Keir pk...@dcs.gla.ac.uk:
 There's nothing better than making a data type an instance of Num. In
 particular, fromInteger is a joy. But how about lists?

 For example, if I have

 data Foo a = F [a]

 I can create a fromInteger such as
 fromInteger i = F [fromInteger i]

 and then a 19::(Foo Int), could become F [19].

 Is it possible to do something similar for lists? So could
 [1,2,3]::(Foo Int) become something slightly different, say,

 F [1,2,3]

 Paul

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



If you mean what I think you're referring to, you can't. The only
reason it works for integer literals is that the compiler replaces
occurrences of, say, 19 with (fromInteger 19).

There's no function that's automatically applied to list literals, so
([1,2,3] :: Foo Int) isn't able to do anything useful, unfortunately.
However, there's an extension in GHC, OverloadedStrings, which lets
you use the method fromString of class Data.String.IsString to
overload literals. (That's not what you asked, though, I know. :) )

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


[Haskell-cafe] fromInteger for Lists

2009-05-01 Thread Paul Keir
There's nothing better than making a data type an instance of Num. In 
particular, fromInteger is a joy. But how about lists?

For example, if I have

data Foo a = F [a]

I can create a fromInteger such as
fromInteger i = F [fromInteger i]

and then a 19::(Foo Int), could become F [19].

Is it possible to do something similar for lists? So could
[1,2,3]::(Foo Int) become something slightly different, say,

F [1,2,3]

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


[Haskell-cafe] Unary Minus

2009-04-06 Thread Paul Keir
If I use :info (-) I get information on the binary minus. Is unary minus
also a function?

Thanks,

Paul

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


[Haskell-cafe] Infix tuple comma query (,)

2009-04-06 Thread Paul Keir
module Main where

 

data (:%^) a b = a :%^ bderiving (Show)

 

main = do

  print $ 18 :%^ (Just 99)

  print $ (,) 9 10

  print $ 9 , 10

 

The last line in the code above causes a compile error.

Why does infix use of the comma (tuple constructor?) function fail
without brackets?

 

Thanks,

Paul

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


RE: [Haskell-cafe] GLUT (glutGet undefined reference)

2009-01-22 Thread Paul Keir
Thanks Kazuya, that link is perfect.

Basically, I have to explicitly add -lglut :

ghc -package GLUT -lglut HelloWorld.hs -o HelloWorld

Great. GLUT (and now FreeGLUT) remains the simplest
and most reliable standard cross-platform OpenGL
windowing API.

(It seems from the link that the information used by
ghc-pkg is wrong, and stems from the GLUT package's
relationship to libraries known as Xmu and Xi.)

Cheers,
Paul


-Original Message-
From: Kazuya Sakakihara [mailto:kaz...@gmail.com]
Sent: Thu 22/01/2009 02:14
To: Paul Keir
Cc: haskell-cafe@haskell.org
Subject: Re: [Haskell-cafe] GLUT (glutGet undefined reference)[MESSAGE NOT 
SCANNED]
 
Check this thread:
http://groups.google.com/group/fa.haskell/browse_thread/thread/1716fa5e5643541e/38373ec65e2537fd?lnk=gst

Kazuya

2009/1/20 Paul Keir pk...@dcs.gla.ac.uk:
 Hi all,

 I was hoping to introduce my old pal OpenGL
 with my new chum, Haskell. I used cabal to
 install GLUT on my 64-bit Ubuntu machine with
 GHC 6.8.2 (installed via apt-get/synaptic).

 I followed the wiki OpenGLTutorial1 until:
 ghc -package GLUT HelloWorld.hs -o HelloWorld
 at which point my screen is filled with errors.
 The errors begin with:

 /home/paul/.cabal/lib/GLUT-2.1.1.2/ghc-6.8.2/libHSGLUT-2.1.1.2.a(Begin.o):
 In function `szEn_info':
 (.text+0x26c): undefined reference to `glutGet'

 This surprised me a little because I've already
 seen these same errors recently on two separate
 Windows boxes. Somehow I'd got the idea it was
 (on Windows) due to installing from a binary; though
 I guess the story is the same with apt-get. Should
 I look for an apt-get switch to reinstall GHC from
 source instead?

 Regards,
 Paul


 ___
 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] GLUT (glutGet undefined reference)

2009-01-19 Thread Paul Keir
Hi all,

I was hoping to introduce my old pal OpenGL
with my new chum, Haskell. I used cabal to
install GLUT on my 64-bit Ubuntu machine with
GHC 6.8.2 (installed via apt-get/synaptic).

I followed the wiki OpenGLTutorial1 until:
ghc -package GLUT HelloWorld.hs -o HelloWorld
at which point my screen is filled with errors.
The errors begin with:

/home/paul/.cabal/lib/GLUT-2.1.1.2/ghc-6.8.2/libHSGLUT-2.1.1.2.a(Begin.o): In 
function `szEn_info':
(.text+0x26c): undefined reference to `glutGet'

This surprised me a little because I've already
seen these same errors recently on two separate
Windows boxes. Somehow I'd got the idea it was
(on Windows) due to installing from a binary; though
I guess the story is the same with apt-get. Should
I look for an apt-get switch to reinstall GHC from
source instead?

Regards,
Paul

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


RE: [Haskell-cafe] forkIO on multicore[MESSAGE NOT SCANNED]

2008-12-23 Thread Paul Keir
Hi Duncan,

I'm following the story regarding (parallel) GC in this example
with interest, but forgive me if I ask a more minor question
regarding your modification of an extra parameter, n, to
heavytask. Does this really help (to ensure that each core
does work independently)? Surely, with fibs now described in a
where clause, the 0:1:etc. form would not be shared among the
(8) instantiations of heavytask?

 heavytask m n = putMVar m $! (fibs !! 10)
   where
 fibs = n : (n+1) : zipWith (+) fibs (tail fibs)

Regards,
Paul





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


RE: [Haskell-cafe] forkIO on multicore

2008-12-21 Thread Paul Keir
 So this benchmark is primarily a stress test of the parallel garbage
 collector since it is GC that is taking 75-80% of the time. Note that
 the mutator elapsed time goes down slightly with 2 cores compared to 1
 however the GC elapsed time goes up slightly.

Thanks Duncan, Jake et al. I'm more familiar with MPI and OpenMP for
parallelism; it seems I've got a lot more thinking to do when it comes
to Haskell. I'll look at some more tutorials, and then most likely
Data Parallel Haskell.

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


[Haskell-cafe] forkIO on multicore

2008-12-19 Thread Paul Keir
Hi all,

I'm seeing no performance increase with a simple coarse-grained
2-thread code using Control.Concurrent. I compile with:

  hc conc.hs -o conc --make -threaded

and I run with

  time ./conc +RTS -N2

But using either -N1 or -N2, the program runs in about 1.8secs.
(I'd prefer a longer running thread task, but my fib function
currently runs out of memory).

Anyway, my program is below, and I'm using GHC version 6.8.2 on
a 2-core Pentium D. Can anyone help?

module Main where

import Control.Concurrent

fibs = 0 : 1 : zipWith (+) fibs (tail fibs)

heavytask m = putMVar m (fibs !! 10)

main = do ms - sequence $ replicate 2 newEmptyMVar
  mapM_ (forkIO . heavytask) $ tail ms
  heavytask $ head ms
  ms' - mapM takeMVar ms
  mapM_ print ms'

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


RE: [Haskell-cafe] forkIO on multicore[MESSAGE NOT SCANNED]

2008-12-19 Thread Paul Keir
Thanks Luke, and everyone else. Ok, back to the drawing board.

Paul

 

 

From: Luke Palmer [mailto:lrpal...@gmail.com] 
Sent: 19 December 2008 16:44
To: Paul Keir
Cc: haskell-cafe@haskell.org
Subject: Re: [Haskell-cafe] forkIO on multicore[MESSAGE NOT SCANNED]

 

On Fri, Dec 19, 2008 at 9:27 AM, Paul Keir pk...@dcs.gla.ac.uk wrote:

module Main where

import Control.Concurrent

fibs = 0 : 1 : zipWith (+) fibs (tail fibs)

heavytask m = putMVar m (fibs !! 10)


Oh, also, heavytask is not very heavy at all.  It just writes the thunk
(fibs !! 10) into the MVar.  Not a single number is added in this
thread.

You probably meant to have the thread evaluate its argument _before_
writing it to the variable:

heavytask m = putMVar m $! (fibs !! 10)

(Or more transparently)

heavytask m = let answer = fibs !! 10 in answer `seq` putMVar m
answer

But as per my other comments, you will not see a speedup (in fact, you
will probably see some slowdown as two threads compete to compute the
same value).

Luke
 



main = do ms - sequence $ replicate 2 newEmptyMVar
 mapM_ (forkIO . heavytask) $ tail ms
 heavytask $ head ms
 ms' - mapM takeMVar ms
 mapM_ print ms'

Regards,
Paul
___
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] forkIO on multicore

2008-12-19 Thread Paul Keir
I did indeed intend for the threads to evaluate before writing to the
two variables, thanks.

 heavytask m = putMVar m $! (fibs !! 10)

I now see a time difference, but as you suggested, in the wrong
direction (1.5s for one, and 3.6s for two threads). I was hoping
for each thread to independently calculate a fib number (but only
to easily give them something to do) . Are the threads really in
competition though? I'm hoping for each thread to write its own result;
so giving the same answer twice. With the -N2 and -threaded
switches,
can I not expect each thread to run on a separate core?

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


[Haskell-cafe] Multi-parameter Type Class

2008-12-11 Thread Paul Keir
Hi all,

I've been trying to refactor my tree conversion code to make
better use of type classes; and I've discovered multi-parameter
type classes and functional dependencies. I have a class with a
function a2b, and I'd like map to be used when it's a list of
type a.

I've created a simple failing example:

data Foo = Foo Barderiving(Show)
data Bar = Bar String deriving(Show)

class ZOT a b | a - b where
  zot :: a - b

instance ZOT Foo Integer where
  zot x = 17

instance ZOT Bar String where
  zot x = Eighteen

instance ZOT [x] [y] where   -- This bit
  zot xs = map zot xs-- fails

main = do print $ zot $ Foo $ Bar Blah
  print $ zot $ Bar Blah
  print $ zot $ [Bar Blah, Bar Blah] -- No map here please

I know this would work if the third instance of zot
explicitly took [Bar] and [String]. Can I not instead generalise
for all the ADTs in my tree in the way I've outlined? Must I
instantiate for the type of each list pair?

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


RE: [Haskell-cafe] Multi-parameter Type Class[MESSAGE NOT SCANNED]

2008-12-11 Thread Paul Keir
I took your suggestion and it worked exactly as I had hoped. Thankyou.

GHCI (6.8.2) was though a little concerned, and told me
I had an: Illegal instance declaration for `ZOT [x] [y]'
and recommended I use -fallow-undecidable-instances. I did,
and it worked. What have I done though? The word undecidable
scares me a little :)

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


RE: [Haskell-cafe] Multi-parameter Type Class[MESSAGE NOT SCANNED]

2008-12-11 Thread Paul Keir
Thanks to you both, that also looks fantastic. I'll print it out;
put it under my pillow; let it brew overnight and then push in
tomorrow ;)


-Original Message-
From: Thomas DuBuisson [mailto:[EMAIL PROTECTED]
Sent: Thu 11/12/2008 15:30
To: Paul Keir
Cc: haskell-cafe@haskell.org
Subject: Re: [Haskell-cafe] Multi-parameter Type Class[MESSAGE NOT SCANNED]
 
I see Lennart answered your question.  For more fun you could also do this
with TypeFamilies, which are the new hot thing in Haskell type level logic.
Since you are just getting into MPTC, FunDeps etc I figured you'd be
interested.

-- START CODE --
{-# LANGUAGE MultiParamTypeClasses, FunctionalDependencies,
TypeSynonymInstances, FlexibleInstances, TypeFamilies #-}

data Foo = Foo Barderiving(Show)
data Bar = Bar String deriving(Show)

-- A family of types will evaluate from one type to another.
-- Here, I chose the word 'Eval', which you could make more meaningful.
-- It is basically a function over types.
type family Eval b

-- This is three definitions for the type function 'Eval'
type instance Eval Foo = Integer
type instance Eval Bar = String
type instance Eval [x] = [Eval x]

-- And instead of a functional dependency
-- you have a type level function (Eval) that operates on the type 'a'.
class ZOT a where
  zot :: a - Eval a

instance ZOT Foo where
  zot x = 17

instance ZOT Bar where
  zot x = Eighteen

-- And don't forget that x must be an instance of ZOT to apply zot.
instance (ZOT x) = ZOT [x] where
  zot xs = map zot xs

main = do print $ zot $ Foo $ Bar Blah
  print $ zot $ Bar Blah
  print $ zot $ [Bar Blah, Bar Blah] -- No map here please


2008/12/11 Paul Keir [EMAIL PROTECTED]

  Hi all,

 I've been trying to refactor my tree conversion code to make
 better use of type classes; and I've discovered multi-parameter
 type classes and functional dependencies. I have a class with a
 function a2b, and I'd like map to be used when it's a list of
 type a.

 I've created a simple failing example:

 data Foo = Foo Barderiving(Show)
 data Bar = Bar String deriving(Show)

 class ZOT a b | a - b where
   zot :: a - b

 instance ZOT Foo Integer where
   zot x = 17

 instance ZOT Bar String where
   zot x = Eighteen

 instance ZOT [x] [y] where   -- This bit
   zot xs = map zot xs-- fails

 main = do print $ zot $ Foo $ Bar Blah
   print $ zot $ Bar Blah
   print $ zot $ [Bar Blah, Bar Blah] -- No map here please

 I know this would work if the third instance of zot
 explicitly took [Bar] and [String]. Can I not instead generalise
 for all the ADTs in my tree in the way I've outlined? Must I
 instantiate for the type of each list pair?

 Cheers,
 Paul

 ___
 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] followedBy parser in Parsec

2008-11-27 Thread Paul Keir
Hi,

Is there a way in Parsec to check what the next token is, and if it is what 
you're hoping for, leave it there.

This is an example of something which doesn't work at all:

testpar =  try $
   do ae - array_element
  option [] $ try $ satisfy (\c - c /= '(')  unexpected 
  return ae

I'm finding this totally confusing by now %0 Can I invert notFollowedBy 
somehow, or maybe there's a peek function I don't know about? Help!

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


RE: [Haskell-cafe] followedBy parser in Parsec

2008-11-27 Thread Paul Keir
'lookAhead' is exactly what I needed:

try $ array_element = \ae - lookAhead (reservedOp ()  return ae

Many thanks,
Paul

Maybe you're looking for 'lookAhead'?

 
 [...]

//Stephan

-- 

Früher hieß es ja: Ich denke, also bin ich.
Heute weiß man: Es geht auch so.

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


RE: [Haskell-cafe] Searching for ADT patterns with elem and find

2008-11-12 Thread Paul Keir
Thanks Tom,

That is indeed a very elegant solution; I too often forget about the wonders of 
list comprehension.

I guess one drawback compared to Neil's suggested use of any (and staying 
with a separate isTypeB) is that your solution will iterate over the entire 
list, regardless of an early hit.

But I don't think your second (as-pattern) solution for findBs is ugly; I quite 
like it actually.

Cheers,
Paul


-Original Message-
From: Tom Nielsen [mailto:[EMAIL PROTECTED]
Sent: Wed 12/11/2008 12:39
To: Paul Keir
Cc: haskell-cafe@haskell.org
Subject: Re: [Haskell-cafe] Searching for ADT patterns with elem and find
 
somebody pointed out a few months back that list comprehensions do this nicely:

containsTypeB ts = not $ null [x | (B x) - ts]

no need for defining isTypeB.


not quite sure how you would write findBs :: [T]-[T] succinctly; maybe

findBs ts = [b | b@(B _) - ts]

or

findBs ts = [B x | (B x) - ts]

both of them compile but the first is ugly and the second is
inefficient (Tags a new T for every hit).


Tom


2008/11/12 Paul Keir [EMAIL PROTECTED]:
 Hi All,

 If I have an ADT, say

 data T
  = A String Integer
  | B Double
  | C
  deriving(Eq)

 and I want to find if a list (ts) of type T contains an element of subtype
 B Double, must my containsTypeX function use a second isTypeX function
 as follows:

 isTypeB :: T - Bool
 isTypeB (B _) = True
 isTypeB _ = False

 containsTypeB :: [T] - Bool
 containsTypeB ts = maybe False (\x - True) (find isTypeB ts)

 I understand that while something like find C ts will work, find (isTypeB
 _) ts will not, but is there no such thing as a pattern combinator(?), or
 lambda that could help with this situation. I find I have many individual
 isTypeB functions now.

 Regards,
 Paul

 ___
 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] Searching for ADT patterns with elem and find

2008-11-12 Thread Paul Keir
Hi All,

If I have an ADT, say

data T
 = A String Integer
 | B Double
 | C
 deriving(Eq)

and I want to find if a list (ts) of type T contains an element of subtype B 
Double, must my containsTypeX function use a second isTypeX function as 
follows:

isTypeB :: T - Bool
isTypeB (B _) = True
isTypeB _ = False

containsTypeB :: [T] - Bool
containsTypeB ts = maybe False (\x - True) (find isTypeB ts)

I understand that while something like find C ts will work, find (isTypeB _) 
ts will not, but is there no such thing as a pattern combinator(?), or lambda 
that could help with this situation. I find I have many individual isTypeB 
functions now.

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


RE: [Haskell-cafe] Searching for ADT patterns with elem and find

2008-11-12 Thread Paul Keir
Thanks Neil,

Great. I hadn't noticed isJust, and I'd forgotten any. Actually I was 
browsing Prelude just the other day and picked up zipWith f as bs as a 
replacement for map f $ zip as bs.

Cheers, Paul


-Original Message-
From: Mitchell, Neil [mailto:[EMAIL PROTECTED]
Sent: Wed 12/11/2008 10:23
To: Paul Keir; haskell-cafe@haskell.org
Subject: RE: [Haskell-cafe] Searching for ADT patterns with elem and find
 
Hi Paul,
 
maybe False (\x - True) (find isTypeB ts)

This can be more neatly expressed as:
 
isJust (find isTypeB ts)
 
But your entire thing can be expressed as:
 
containsTypeB ts = any isTypeB ts
 
I recommend reading through the Prelude interface and the List
interface, it has many useful functions that will help.
 
Thanks
 
Neil
 




From: [EMAIL PROTECTED]
[mailto:[EMAIL PROTECTED] On Behalf Of Paul Keir
Sent: 12 November 2008 10:09 am
To: haskell-cafe@haskell.org
Subject: [Haskell-cafe] Searching for ADT patterns with elem and
find



Hi All,

If I have an ADT, say

data T
 = A String Integer
 | B Double
 | C
 deriving(Eq)

and I want to find if a list (ts) of type T contains an element
of subtype B Double, must my containsTypeX function use a second
isTypeX function as follows:

isTypeB :: T - Bool
isTypeB (B _) = True
isTypeB _ = False

containsTypeB :: [T] - Bool
containsTypeB ts = maybe False (\x - True) (find isTypeB ts)

I understand that while something like find C ts will work,
find (isTypeB _) ts will not, but is there no such thing as a pattern
combinator(?), or lambda that could help with this situation. I find I
have many individual isTypeB functions now.

Regards,
Paul 


==
Please access the attached hyperlink for an important electronic communications 
disclaimer: 

http://www.credit-suisse.com/legal/en/disclaimer_email_ib.html
==


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


[Haskell-cafe] Simple Table Update

2008-10-08 Thread Paul Keir
Hi,

I'd like to create a new list based on an original list, using information from 
a second (symbol) list. That second list should be updated as each element in 
the new list is added. I've been using map a lot, but that's not an option 
here, and I'm having trouble obtaining a good recursive structure for my 
function.

The minimal fixpus function below shows the problem. I have sts on both 
sides of the : list construct, but I'd like the second sts to be a version 
modified by the where (singular) function, fixpu.

fixpus :: [ProgUnit] - [ProgUnitSymbolTable] - [ProgUnit]
fixpus []   _  = []
fixpus (pu:pus) sts = fixpu pu sts : fixpus pus sts

  where fixpu pu sts = pu

(Below) I tried making fixpu return a tuple, and then use fst, snd and 
let, but I think it looks strange. I know it's quite basic, but I'd like a 
strong foundation for what's likely to become a medium-scale project. Can 
anyone offer advice?

fixpus :: [ProgUnit] - [ProgUnitSymbolTable] - [ProgUnit]
fixpus []   _  = []
fixpus (pu:pus) sts = let a = (fixpu pu sts) in fst a : fixpus pus (snd a)

  where fixpu pu sts = (pu,sts ++ [(,[])])

Regards,
Paul

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


RE: [Haskell-cafe] Simple Table Update

2008-10-08 Thread Paul Keir
It brings tears to my eyes to see such a beautiful function ;) You've hit the 
nail on the head Ryan. The new version of my second previous code snippet now 
no longer requires fixpu*, and is:

typeCheckAST (Program pus) = Program $ snd $ mapAccumL f [] pus

  where f st pu = (st ++ [(,[])],pu)

Many thanks,
Paul

-Original Message-
From: Ryan Ingram [mailto:[EMAIL PROTECTED]
Sent: Wed 08/10/2008 18:03
To: Paul Keir
Cc: haskell-cafe@haskell.org
Subject: Re: [Haskell-cafe] Simple Table Update
 
Prelude :t Data.List.mapAccumL
Data.List.mapAccumL :: (acc - x - (acc, y)) - acc - [x] - (acc, [y])

I'm sure you can fill in the details :)

  -- ryan

2008/10/8 Paul Keir [EMAIL PROTECTED]:
 Hi,

 I'd like to create a new list based on an original list, using information
 from a second (symbol) list. That second list should be updated as each
 element in the new list is added. I've been using map a lot, but that's not
 an option here, and I'm having trouble obtaining a good recursive structure
 for my function.

 The minimal fixpus function below shows the problem. I have sts on both
 sides of the : list construct, but I'd like the second sts to be a
 version modified by the where (singular) function, fixpu.

 fixpus :: [ProgUnit] - [ProgUnitSymbolTable] - [ProgUnit]
 fixpus []   _  = []
 fixpus (pu:pus) sts = fixpu pu sts : fixpus pus sts

   where fixpu pu sts = pu

 (Below) I tried making fixpu return a tuple, and then use fst, snd and
 let, but I think it looks strange. I know it's quite basic, but I'd like a
 strong foundation for what's likely to become a medium-scale project. Can
 anyone offer advice?

 fixpus :: [ProgUnit] - [ProgUnitSymbolTable] - [ProgUnit]
 fixpus []   _  = []
 fixpus (pu:pus) sts = let a = (fixpu pu sts) in fst a : fixpus pus (snd a)

   where fixpu pu sts = (pu,sts ++ [(,[])])

 Regards,
 Paul


 ___
 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] One liner?

2008-10-02 Thread Paul Keir
Hi all,

There's a common little situation I keep bumping up against. I don't understand 
where I'm going wrong, so I've made a little example. It's to do with binding a 
result to a variable name using -. This code works fine:

--
module Main where

import System.Directory (getDirectoryContents)

main = do dc - getDirectoryContents ./foo/
  mapM_ putStrLn dc
--

But if I try to avoid the use of the bind to dc, I fail:

--
mapM_ putStrLn (getDirectoryContents ./foo/)
--

I've tried using map instead of mapM_, and inserted returns here and there, 
but no luck. Can anyone tell me where and why I'm going wrong? The error 
message is below.

Cheers,
Paul


Couldn't match expected type `[String]'
   against inferred type `IO [FilePath]'
In the second argument of `mapM_', namely
`(getDirectoryContents ./foo/)'
In the expression: mapM_ putStrLn (getDirectoryContents ./foo/)
In the definition of `main':
main = mapM_ putStrLn (getDirectoryContents ./foo/)
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


RE: [Haskell-cafe] One liner?

2008-10-02 Thread Paul Keir
Thanks, and to Ketil too. I did see past the missing ./foo/. That's certainly 
a solution I'm happy with, and I didn't know the term eta reduction, so thanks 
for that too.
Paul


-Original Message-
From: Mitchell, Neil [mailto:[EMAIL PROTECTED]
Sent: Thu 02/10/2008 16:26
To: Paul Keir; haskell-cafe@haskell.org
Subject: RE: [Haskell-cafe] One liner?
 
Hi
 
You can translate this step by step.
 
main = do dc - getDirectoryContents ./foo/
  mapM_ putStrLn dc

Translating out the do notation
(http://www.haskell.org/haskellwiki/Keywords#do):

main = getDirectoryContents = \dc -
   mapM_ putStrLn dc

Then we can chop out the dc argument, as its \x -  x, and can be
removed (eta reduction):

main = getDirectoryContents = 
   mapM_ putStrLn

And finally we just remove the newline:

main = getDirectoryContents = mapM_ putStrLn  

Alternatively, we can flip the = for = and write:

main = mapM_ putStrLn = getDirectoryContents

This is now one line, and mirrors how you would write the function if it
was pure using function composition.

Thanks

Neil
 

This material is sales and trading commentary and does not constitute
investment research. Please follow the attached hyperlink to an
important disclaimer 
www.credit-suisse.com/emea/legal
outbind://31/www.credit-suisse.com/emea/legal  

 




From: [EMAIL PROTECTED]
[mailto:[EMAIL PROTECTED] On Behalf Of Paul Keir
Sent: 02 October 2008 4:20 pm
To: haskell-cafe@haskell.org
Subject: [Haskell-cafe] One liner?



Hi all,

There's a common little situation I keep bumping up against. I
don't understand where I'm going wrong, so I've made a little example.
It's to do with binding a result to a variable name using -. This
code works fine:

--
module Main where

import System.Directory (getDirectoryContents)

main = do dc - getDirectoryContents ./foo/
  mapM_ putStrLn dc
--

But if I try to avoid the use of the bind to dc, I fail:

--
mapM_ putStrLn (getDirectoryContents ./foo/)
--

I've tried using map instead of mapM_, and inserted returns
here and there, but no luck. Can anyone tell me where and why I'm going
wrong? The error message is below.

Cheers,
Paul


Couldn't match expected type `[String]'
   against inferred type `IO [FilePath]'
In the second argument of `mapM_', namely
`(getDirectoryContents ./foo/)'
In the expression: mapM_ putStrLn (getDirectoryContents
./foo/)
In the definition of `main':
main = mapM_ putStrLn (getDirectoryContents ./foo/)



==
Please access the attached hyperlink for an important electronic communications 
disclaimer: 

http://www.credit-suisse.com/legal/en/disclaimer_email_ib.html
==


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


[Haskell-cafe] Pretty Print, text or ++?

2008-08-15 Thread Paul Keir
Hi there,

I'm writing a pretty printer using the Text.PrettyPrint library, and there's a 
pattern I'm coming across quite often. Does anyone know whether,

text (a ++ b ++ c ++ d)
or
text a + text b + text c + text d

runs quicker?

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


RE: [Haskell-cafe] Pretty Print, text or ++?

2008-08-15 Thread Paul Keir
Thanks,

So you're recommending:

text (concat [a,b,c,d,e])

Might this not transform my pretty printing into ugly printing; when longer 
strings are used?

Paul


-Original Message-
From: [EMAIL PROTECTED] on behalf of John Van Enk
Sent: Fri 15/08/2008 14:31
To: Paul Keir
Cc: haskell-cafe@haskell.org
Subject: Re: [Haskell-cafe] Pretty Print, text or ++?
 
Paul,

Something tells me you might want to look at `concat':

concat :: [[a]] - [a]

/jve


2008/8/15 Paul Keir [EMAIL PROTECTED]

  Hi there,

 I'm writing a pretty printer using the Text.PrettyPrint library, and
 there's a pattern I'm coming across quite often. Does anyone know whether,

 text (a ++ b ++ c ++ d)
 or
 text a + text b + text c + text d

 runs quicker?

 Cheers,
 Paul

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




-- 
/jve

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


[Haskell-cafe] RE: Pretty Print, text or ++?

2008-08-15 Thread Paul Keir
Awesome! Thanks to you all. I'll start with

hsep[map a, b, c, d]

and then I can try changing hsep for other things.

Paul


-Original Message-
From: Benedikt Huber [mailto:[EMAIL PROTECTED]
Sent: Fri 15/08/2008 14:53
To: Paul Keir
Cc: haskell-cafe@haskell.org
Subject: Re: Pretty Print, text or ++?
 
Paul Keir schrieb:
  Hi there,
 
  I'm writing a pretty printer using the Text.PrettyPrint library, and
  there's a pattern I'm coming across quite often. Does anyone know 
whether,
 
  text (a ++ b ++ c ++ d)
  or
  text a + text b + text c + text d
 
  runs quicker?

Hi Paul,

  text (a ++ b ++ c ++ d)

is the same as

  hcat (map text [a,b,c,d])

(horizontal concatenation without seperating spaces)
while

  text a + text b + text c + text d

corresponds to

  hsep (map text [a,b,c,d])

or

  text (unwords [a,b,c,d])

With +, hsep or hcat, pretty printing won't choose the best layout -
you tell the pretty printer to layout documents 'beside'.
For autolayout, see sep,cat and the paragraph-fill variants fsep and fcat.

Regarding performance: `unwords` will propably be a little faster 
(untested), but less flexible. There is no asymptotic overhead when 
using the pretty printer.

cheers,
benedikt

 
  Cheers,
  Paul
 
 
  
 
  ___
  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] Parsec expressions with alphaNum operators

2008-04-08 Thread Paul Keir
Thanks Chris,

When I looked at the Fortran alphaNum operators (.and. .or. etc.) I had
hoped that supplying Parsec's opStart with a dot would have been
hitting the nail on the head. Oh well.

I have noticed something interesting though. If I simply omit the a
from opLetter, the problem is gone. In fact, leaving opStart,
opLetter, and reservedOpNames all empty works fine too.

Perhaps I should aim to leave aside the Language part of Parsec
altogether.

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


RE: [Haskell-cafe] Parsec Expected Type

2008-04-07 Thread Paul Keir
Thanks. reservedOp is a better fit; :+ should only be :+.

I also overcame my type issues in an ad-hoc manner, adding

 return ()

whenever I needed to.

-Original Message-
From: Tillmann Rendel [mailto:[EMAIL PROTECTED] 
Sent: 30 March 2008 12:30
To: Paul Keir; haskell-cafe@haskell.org
Subject: Re: [Haskell-cafe] Parsec Expected Type

Paul Keir wrote: 
 What I'd like is to parse either the string parameter, or the 
 string :. I'm using 'reserved' and 'symbol' because they seem to 
 correspond well to the concepts in the language I'm parsing. 

You may consider using reservedOp for :, depending on how :+ should
be parsed:

  for :+ use reservedOp
  for : + use symbol

If you use reserved, then :name will be parsed as :name not :
name as you probably expect. generally, reserved is for
identifier-like keywords, and reservedOp for operator-like keywords.

 Perhaps I'd express my confusion better if I ask: Why are 'reserved'
 and 'symbol' different types?

I have no idea. They aren't in the Parsec manual on Daans site:

  http://legacy.cs.uu.nl/daan/download/parsec/parsec.html

You can fix this by defining

  reserved name = ParsecToken.reserved tokenParser name  return name

instead of

  reserved = ParsecToken.reserved tokenParser

to import the reserved component from the tokenParser to the toplevel.
Now,

  reserved :: String - CharParser st String

Another option is to fix it the other way, by defining

  symbol name = ParsecToken.symbol tokenParser name  return ()

or to fix it in a ad-hoc manner, by defining

  ignored = ( return ())

and using it in the approbiate places, like

  parameterOrColon = reserved parameter | ignored (symbol :)

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


[Haskell-cafe] Parsec expressions with alphaNum operators

2008-04-07 Thread Paul Keir
Hi,

 

I'm using buildExpressionParser, and I'd like to use alphanumeric
operator characters. I get an (unexpected a) error though. With a test
string like -a if a is used in any of the reservedOpNames. I'm
aiming for the Fortran operators like .and..

 

The listing below may be helpful. It's taken from the Haskell wiki's
Parsing expressions and statements article (minus the statement
part).I've added an :a: operator. The article uses ~ as a unary
operator (I'm heading for +/-). It can be tested with:

$ parseTest exprparser ~a

 

-- code begins

 

module Main where

 

import Control.Monad(liftM)

 

import Text.ParserCombinators.Parsec

import Text.ParserCombinators.Parsec.Expr

import Text.ParserCombinators.Parsec.Token

import Text.ParserCombinators.Parsec.Language

 

data Expr = Var String | Con Bool | Uno Unop Expr | Duo Duop Expr Expr

deriving Show

data Unop = Not deriving Show

data Duop = And | Iff deriving Show

data Stmt = Nop | String := Expr | If Expr Stmt Stmt | While Expr Stmt

  | Seq [Stmt]

deriving Show

 

def = emptyDef{ commentStart = {-

  , commentEnd = -}

  , identStart = letter

  , identLetter = alphaNum

  , opStart = oneOf ~=:

  , opLetter = oneOf ~=:a

  , reservedOpNames = [~, , =, :=, :a:]

  , reservedNames = [true, false, nop,

 if, then, else, fi,

 while, do, od]

  }

 

TokenParser{ parens = m_parens

   , identifier = m_identifier

   , reservedOp = m_reservedOp

   , reserved = m_reserved

   , semiSep1 = m_semiSep1

   , whiteSpace = m_whiteSpace } = makeTokenParser def

 

exprparser :: Parser Expr

exprparser = buildExpressionParser table term ? expression

 

table = [ [Prefix (m_reservedOp ~  return (Uno Not))]

, [Infix (m_reservedOp   return (Duo And)) AssocLeft]

, [Infix (m_reservedOp =  return (Duo Iff)) AssocLeft]

, [Infix (m_reservedOp :a:  return (Duo Iff)) AssocLeft]

]

 

term = m_parens exprparser

   | liftM Var m_identifier

   | (m_reserved true  return (Con True))

   | (m_reserved false  return (Con False))

 

play :: String - IO ()

play inp = case parse exprparser  inp of

 { Left err - print err

 ; Right ans - print ans

 }

 

-- code ends

 

Cheers,

 

 

 

Paul Keir

Research Student

University of Glasgow

Department of Computing Science

[EMAIL PROTECTED]

 

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


RE: [Haskell-cafe] Parsec Expected Type

2008-03-29 Thread Paul Keir
Many thanks guys, you've really taught me how to catch a fish here!
Paul


-Original Message-
From: Brandon S. Allbery KF8NH [mailto:[EMAIL PROTECTED]
Sent: Sat 3/29/2008 1:41 AM
To: haskell-cafe@haskell.org Cafe
Cc: Paul Keir
Subject: Re: [Haskell-cafe] Parsec Expected Type
 

On Mar 28, 2008, at 21:12 , Ryan Ingram wrote:
 On 3/28/08, Paul Keir [EMAIL PROTECTED] wrote:
 What I'd like is to parse either the string parameter, or the  
 string :.
 I'm using 'reserved' and 'symbol' because they seem to correspond  
 well to
 the concepts in the language I'm parsing. I could try,

 tester3 = reserved parameter | do { symbol :; return () }

 Or you could factor this behavior out into a new combinator:

 or_ :: Parser a - Parser b - Parser ()
 or_ x y = (x  return ()) | (y  return ())

 tester3 = reserved parameter `or_` symbol :

Or if you'd like to be inscrutable:

import Data.Function

or_ = ( return ()) `on` (|)

-- 
brandon s. allbery [solaris,freebsd,perl,pugs,haskell] [EMAIL PROTECTED]
system administrator [openafs,heimdal,too many hats] [EMAIL PROTECTED]
electrical and computer engineering, carnegie mellon universityKF8NH



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


RE: [Haskell-cafe] Parsec Expected Type

2008-03-28 Thread Paul Keir
Thanks, I'd thought it was something to do with incompatible types. I can now 
create a simpler problem:

tester2 = reserved parameter | symbol :

Certainly I could use reserved : instead of symbol, but where is my thinking 
with symbol here going wrong? Surely the above example isn't so odd?

Paul


-Original Message-
From: Luke Palmer [mailto:[EMAIL PROTECTED]
Sent: Fri 3/28/2008 12:26 AM
To: Paul Keir
Cc: haskell-cafe@haskell.org
Subject: Re: [Haskell-cafe] Parsec Expected Type
 
Hi Paul,

2008/3/27 Paul Keir [EMAIL PROTECTED]:
 Hi,

  Does anyone know why this reduced Parsec production stops compilation, and
 how I can fix it?

  tester = reserved parameter
   | do { reserved dimension; symbol : }

Look at the types of reserved and symbol (from
http://www.haskell.org/ghc/docs/latest/html/libraries/parsec/Text-ParserCombinators-Parsec-Token.html):

  symbol :: String - CharParser st String
  reserved :: String - CharParser st ()

The type of a do block is the same as the type of its last statement.
But (reserved parameter) and (symbol ;) do not have the same type.

Luke

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


RE: [Haskell-cafe] Parsec Expected Type

2008-03-28 Thread Paul Keir
Could tester2 return some kind of base type, which the two inherit from? I 
don't know. I'm really only presenting the ugly tester2 function because I'm 
looking for a Parsec-concordant solution to what appears a simple problem.

What I'd like is to parse either the string parameter, or the string :. I'm 
using 'reserved' and 'symbol' because they seem to correspond well to the 
concepts in the language I'm parsing. I could try,

tester3 = reserved parameter | do { symbol :; return () }

but that's feels a bit contrived; or I could use 'reserved' twice.

Perhaps I'd express my confusion better if I ask: Why are 'reserved' and 
'symbol' different types?

Paul (Haskell Novice)




-Original Message-
From: Jonathan Cast [mailto:[EMAIL PROTECTED]
Sent: Fri 3/28/2008 2:05 PM
To: Paul Keir
Cc: Luke Palmer; haskell-cafe@haskell.org
Subject: Re: [Haskell-cafe] Parsec Expected Type
 
On 28 Mar 2008, at 2:02 AM, Paul Keir wrote:

 Thanks, I'd thought it was something to do with incompatible types.  
 I can now create a simpler problem:

 tester2 = reserved parameter | symbol :

 Certainly I could use reserved : instead of symbol, but where is  
 my thinking with symbol here going wrong? Surely the above example  
 isn't so odd?

What type do you expect tester2 to return?

jcc


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


RE: [Haskell-cafe] No newlines in the whitespace for Parsec lexeme parsers

2008-03-27 Thread Paul Keir
Thankyou all. Once I get more familiar with Parsec I might do my own
lexeme parser. For now I've changed its definition of simpleSpace to 

simpleSpace =
   skipMany1 (satisfy (\c - (c /= '\n')  (isSpace c)))

so that it skips whitespace, but not newlines. My parser then explicitly
matches newlines whenever I need to.

Cheers,
Paul

-Original Message-
From: Brandon S. Allbery KF8NH [mailto:[EMAIL PROTECTED] 
Sent: 26 March 2008 11:48
To: haskell-cafe@haskell.org Cafe; Paul Keir
Subject: Re: [Haskell-cafe] No newlines in the whitespace for Parsec
lexeme parsers


On Mar 26, 2008, at 7:42 , Bulat Ziganshin wrote:
 Wednesday, March 26, 2008, 2:32:53 PM, you wrote:
  I'm looking to parse a Fortran dialect using Parsec, and was

 afair, some months ago BASIC parsing was discussed here.

 the first solution one can imagine is to add preprocessing stage
 replacing line ends with ';'-alike

FWIW I just ignored the lexeme parser and did my own on top of the  
basic Parsec primitives.

You may need to do that anyway if you want to support older variants  
of Fortran, which don't actually have keywords and ignore spaces  
outside of string constants (Hollerith constants) --- Parsec's lexeme  
stuff doesn't even pretend to support this.

-- 
brandon s. allbery [solaris,freebsd,perl,pugs,haskell] [EMAIL PROTECTED]
system administrator [openafs,heimdal,too many hats] [EMAIL PROTECTED]
electrical and computer engineering, carnegie mellon universityKF8NH


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


[Haskell-cafe] Parsec Expected Type

2008-03-27 Thread Paul Keir
Hi,

Does anyone know why this reduced Parsec production stops compilation, and how 
I can fix it?

tester = reserved parameter
 | do { reserved dimension; symbol : }

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


[Haskell-cafe] No newlines in the whitespace for Parsec lexeme parsers

2008-03-26 Thread Paul Keir
Hi,

I'm looking to parse a Fortran dialect using Parsec, and was hoping to use the 
ParsecToken module. Fortran though is unlike the Parsec examples, and prohibits 
default line continuation (requiring instead an explicit ampersand token ). 
The lexical parsers of the ParsecToken module skip whitespace after each symbol 
parsed (lexeme parsers); including the newline.

I was thinking of making a minor change to Parsec: In Token.hs, lexeme, 
whiteSpace, and simpleSpace are defined. lexeme uses whiteSpace which uses 
simpleSpace. simpleSpace is defined:

simpleSpace = skipMany1 (satisfy isSpace)

I could replace this locally with:

simpleSpace = skipMany1 (satisfy isSpacePlusAmpersandMinusNewline)

This approach may have other problems though. Has anyone experience of using 
Parsec to parse such a language? For example assembly or a preprocessor?

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


[Haskell-cafe] Parsec (Zero or One of)

2008-03-25 Thread Paul Keir
Hi,

 

I'm having some difficulty using the Parsec library, perhaps you could
help. I've reduced my problem as shown below. I would like the
'only_prod' parser to require the reserved string only, _optionally_
followed by an identifier. As part of 'mytest', this should then be
followed by the reserved string end.

 

mytest = do { only_prod; end }

only_prod = do { reserved only; try identifier }

end = reserved end

 

i.e. I'd like both

 parseTest mytest only end

and

parseTest mytest only green end

to parse successfully. As it stands, only the second is successful. The
first fails with:

 

parse error at (line 1, column 9):

unexpected end of input

expecting letter or digit or end

 

Does anyone have an idea how I could repair the situation?

 

Thanks in advance,

Paul

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


RE: [Haskell-cafe] Parsec (Zero or One of)

2008-03-25 Thread Paul Keir
Thanks. I can't find optionMaybe in my version 2.1 of Parsec, but in any case, 
defining my only_prod as

only_prod = do { reserved only; option [] identifier }

or

only_prod = do { reserved only; identifier | return [] }

gives the same error responses as before. I will anyway look closer at option.

You're right that I don't understand try, but it's not for lack of trying. My 
examples' use of try though was just a stab at a readable failure. Maybe I 
should refactor my example.

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


RE: [Haskell-cafe] Parsec (Zero or One of)

2008-03-25 Thread Paul Keir
Thankyou. Yes, I'd also noticed that only end could result in the end part 
being taken as an identifier. The language I'm parsing actually doesn't have 
reserved words though; so end and only are both possible valid identifiers. 
I should then probably replace my use of say, reserved only, with string 
only; whiteSpace; for clarity. Still stuck though...

P


-Original Message-
From: Brandon S. Allbery KF8NH [mailto:[EMAIL PROTECTED]
Sent: Tue 25/03/2008 19:58
To: Paul Keir; haskell-cafe@haskell.org Cafe
Subject: Re: [Haskell-cafe] Parsec (Zero or One of)
 

On Mar 25, 2008, at 12:43 , Paul Keir wrote:
 Thanks. I can't find optionMaybe in my version 2.1 of Parsec, but  
 in any case, defining my only_prod as

 only_prod = do { reserved only; option [] identifier }

 or

 only_prod = do { reserved only; identifier | return [] }

 gives the same error responses as before. I will anyway look closer  
 at option.

The other problem here is that just using a given string in  
reserved doesn't prevent it from being parsed elsewhere by  
identifier.  (Note the character offset of the error was 9, i.e.  
just past only end, and it was looking for end or more identifier  
characters.)

Are you using the higher level parser facilities from  
Text.ParserCombinators.Parsec.Token, or rolling your own?  If the  
latter, you will need to modify identifier to not accept keywords.

-- 
brandon s. allbery [solaris,freebsd,perl,pugs,haskell] [EMAIL PROTECTED]
system administrator [openafs,heimdal,too many hats] [EMAIL PROTECTED]
electrical and computer engineering, carnegie mellon universityKF8NH



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


RE: [Haskell-cafe] Parsec (Zero or One of)

2008-03-25 Thread Paul Keir
Many thanks.

-Original Message-
From: Brandon S. Allbery KF8NH [mailto:[EMAIL PROTECTED]
Sent: Tue 25/03/2008 20:29
To: Paul Keir; haskell-cafe@haskell.org Cafe
Subject: Re: [Haskell-cafe] Parsec (Zero or One of)
 

On Mar 25, 2008, at 16:26 , Paul Keir wrote:
 Thankyou. Yes, I'd also noticed that only end could result in the  
 end part being taken as an identifier. The language I'm parsing  
 actually doesn't have reserved words though; so end and only  
 are both possible valid identifiers. I should then probably replace  
 my use of say, reserved only, with string only; whiteSpace; for  
 clarity. Still stuck though...



But now you have an ambiguity in your language, which is exactly why  
the parse is failing:  only end could be waiting for end, or for  
end of file / whatever tokens might follow this clause.  In the worst  
case, the latter might lead to a situation where an unambiguous parse  
is impossible.

You might want to provide a better description of the full language  
--- and think about how it would need to be implemented to avoid  
ambiguity.

-- 
brandon s. allbery [solaris,freebsd,perl,pugs,haskell] [EMAIL PROTECTED]
system administrator [openafs,heimdal,too many hats] [EMAIL PROTECTED]
electrical and computer engineering, carnegie mellon universityKF8NH



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