definition of take

2005-02-16 Thread Jorge Adriano Aires
Hi, 
I don't know much about the internals of GHC, but I like look around once in a 
while to learn a few things. I was wondering about the definition of take, 
which is, for Ints:

-
takeUInt :: Int# - [b] - [b]
takeUInt n xs
  | n =# 0#  =  take_unsafe_UInt n xs
  | otherwise =  []

take_unsafe_UInt :: Int# - [b] - [b]
take_unsafe_UInt 0#  _  = []
take_unsafe_UInt m   ls =
  case ls of
[] - []
(x:xs) - x : take_unsafe_UInt (m -# 1#) xs
-

Wouldn't pattern matching against 1# instead of 0#, like in the following 
definition, be better in terms of garbage collecting the list or what it 
depends on? 

---
takeUInt :: Int# - [b] - [b]
takeUInt 0# _ =  []
takeUInt n xs
  | n # 0#   =  take_unsafe_UInt n xs
  | otherwise =  []

take_unsafe_UInt :: Int# - [b] - [b]
take_unsafe_UInt 1#  (x:xs)  = [x]
take_unsafe_UInt m   ls  =
  case ls of
[] - []
(x:xs) - x : take_unsafe_UInt (m -# 1#) xs
--

My guess would be that, if we're consuming a (take n xs) lazily, with the 
first definition garbage collecting would happen when the last element had 
been consumed  and with the second, when the last element had been produced - 
(which is when we find out there are no more elements to consume in each 
case).

Thanks, and sorry if the question is to naive,
J.A.
___
Glasgow-haskell-users mailing list
Glasgow-haskell-users@haskell.org
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users


Re: [Haskell-cafe] mathematical notation and functional programming

2005-01-28 Thread Jorge Adriano Aires

 Things I'm unhappy about are for instance

 f(x) \in L(\R)
where f \in L(\R) is meant

 F(x) = \int f(x) \dif x
where x shouldn't be visible outside the integral

 O(n)
which should be O(\n - n) (a remark by Simon Thompson in
The Craft of Functional Programming)
 f(.)
which means \x - f x or just f

All of these are the same notation abuse,
sometimes f x is meant to be interpreted as \x-f x

In some cases it would be really tedious to add the extra lambdas, so the 
expression used in its definition is used to denote the function itself. 

 a  b  c
which is a short-cut of a  b \land b  c

Both, ambiguity and complex notation, can lead to (human) parsing problems, 
which is what we are trying to minimise here.

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


Re: [Haskell-cafe] Converting from Int to Double

2005-01-26 Thread Jorge Adriano Aires

  How can I convert an Int into a Double?
 
  You don't convert to, you convert from :-)
  The function 'fromIntegral' is probably what you want.

 And what function can I use to convert from Double to Int (the inverse of
 fromIntegral) ?

Use the functions in the RealFrac class.
http://www.haskell.org/onlinereport/standard-prelude.html#$tRealFrac

class  (Real a, Fractional a) = RealFrac a  where
 properFraction   :: (Integral b) = a - (b,a)
 truncate, round  :: (Integral b) = a - b
 ceiling, floor   :: (Integral b) = a - b

J.A.

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


Re: [Haskell-cafe] Re: what is inverse of mzero and return?

2005-01-25 Thread Jorge Adriano Aires
On Tuesday 25 January 2005 02:25, Jan-Willem Maessen wrote:
 On Jan 24, 2005, at 8:53 PM, Jorge Adriano Aires wrote:
  And it would say nothing about things like:
  return 4  return 5  ==?== return 5
  I can live with it.

 I feel obliged to point out (because the repeated references to the
 question are driving me up the wall) that this simple equality holds in
 every monad:


 return 4  return 5
 ...
 return 5

Opss, of course...

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


Re: [Haskell-cafe] using Map rather than FiniteMap

2005-01-25 Thread Jorge Adriano Aires

 Just did a search after my last post and learned
 that FiniteMap is bad.  Discoverd that Data.Map is
 the intended replacement.  Downloaded it and
 modified it to work with 6.2.  Blazingly fast!

 Yay.

Hi, just curious, 
How much trouble was getting it to work with ghc 6.2 and adapting your program 
to use the API of Data.Map instead of Data.FiniteMap?

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


Re: [Haskell-cafe] Re: what is inverse of mzero and return?

2005-01-24 Thread Jorge Adriano Aires

 Right, but we are dealing with the type system here. Remember Haskell
 monoids are functors on types, not on values ... (ie the base objects the
 'category theory' is applied to are the types not the values)...

 Therefore we only consider the types when considering Monads.

How so? Functors map morphisms and objects from one category into another.

class Functor f where 
  fmap :: (a-b) - f b - f a 

We have the two maps there. 
- The type constructor, maps the objects  (types).
- The fmap higher order function, maps the morphisms (function between types).

Monads are, in particular, functors. So again, the type constructor maps the 
objects (types) and the mapping on morphisms (functions from one type to the 
other) is given by liftM (that is, fmap = liftM).

Like Ashley Yakeley said, we can have many different functions (morphism) 
between two types, namely IO a types.

 As such if you wished to consider the examples you gave distinct, the
 type system would need to distinguish side effects... 

Why? I don't see how side effects make any difference here... How do you 
distinguish morphisms f and g:

f,g :: Int - Int
f n = 2*n
g n = 2+n

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


Re: [Haskell-cafe] Re: what is inverse of mzero and return?

2005-01-24 Thread Jorge Adriano Aires

 We face a severe problem here, not only that IO a is not an instance of Eq,
 which takes this whole discussion outside the realm of Haskell, on top of

 that we find the horrible fact that x /= x may be true in the IO Monad,
 consider

 x = getLine = putStrLn

 or anything similar  -- actually we already have getChar /= getChar

This isn't obvious to me. So x is an action, and it does not always produces 
the same side effects when executed. But why should that make x/=x? It is the 
same action, it gets one line from the input, and then prints it...

In fact, I do not agree. See Rant 2 below.


 The sad truth is that IO actions in general aren't well defined entities
 (unless we index them with the space-time-coordinates of their invocation).
 So I suggest ending the discussion by agreeing that the question whether or
 not
 x  mzero == mzero 
 holds in the IO-Monad is meaningless (at least, it's fruitless).
 If you cannot agree, I have another question: is

 return 4  return 5 == return 5

 true in the IO-Monad?

Yeap, I thought about it too, have no idea, and cannot afford to spend much 
time thinking about it now either, since I got work to do... :-/ 

--- Rant 1
My gut feeling would be no. I think my intuitive reasoning is too just 
consider that, every IO action is equal to itself, then take the closure with 
respect to function application, and assume all others cannot be proved. That 
is,

x === x,  for all   x :: IO a 
f x === g x, for all   x :: a  and  f,g :: a - IO b,  such that f === g

Where equality between functions is defined the usual way.


--- Rant 2

Nope, we have to have getChar === getChar.

I think you'll agree if I say that we have:
1. return === return 
2- return 5 === return 5 
return 5   return 5 ===  return 5  return 5

Because this has nothing to do with IO.  
1. We have that, return :: a-IO a  is a function, not an action, so it must 
be equal to itself. 

2. We have that, return :: a-IO a  is a function, not an action, so it must 
return the same value when applied to the same element.  

3.  () :: (Monad m) = m a - m b - m b   
It is also a function, so  () x ===  () x. 
And by the same reasoning () x y ===  () x y. 
So from 2 we have 3.

A constant c :: a  is just morphism(function) c : 0 - a, where 0 is the 
initial object (empty set).  So we must have c === c. 
Which means getChar === getChar.

In other words, by questioning wether you can have  x ==/= x for x :: IO a, 
you are questioning wether we really have f === f for all functions f::a-b.
---

  return hello = putStrLn
 
  this does not only have the same type as putStrLn hello, and return
  the same value (), but it also carries out exactly the same actions.

 But does it really? hugs thinks otherwise:
 Prelude putStrLn hello
 hello
 ()
 (28 reductions, 55 cells)
 Prelude return hello = putStrLn
 hello
 ()
 (31 reductions, 56 cells)
 Prelude putStrLn hello
 hello
 ()
 (26 reductions, 50 cells)

 even the same input does not necessarily lead to exactly the same actions,
 depending on whether hello is already known or not.

This I don't agree with, I think you are using the word actions for two 
different things, the elements of type IO a, and their execution. What you 
just showed is that those IO () elements (actions) when executed, always 
created different side effects in the real world. Not that the actions 
themselves are different. 

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


Re: [Haskell-cafe] Re: what is inverse of mzero and return?

2005-01-24 Thread Jorge Adriano Aires

 A constant c :: a  is just morphism(function) c : 0 - a, where 0 is the
 initial object (empty set). 

--- Rant2 correction
Opss I messed up here. Should be terminal should 1- a  (terminal object/unit 
set). At least that's how I usually think of constants  in haskell  1 is 
()... so I think I don't know what is a constant in Haskell... Anyway, 
stopping now.

J.A.

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


Re: [Haskell-cafe] Re: what is inverse of mzero and return?

2005-01-24 Thread Jorge Adriano Aires

 This isn't obvious to me. So x is an action, and it does not always
  produces the same side effects when executed. But why should that make
  x/=x? It is the same action, it gets one line from the input, and then
  prints it...

 OK, but then the different side-effects could not be used to distinguish
 putStrLn hello  mzero
 and mzero. So I still believe, if you say these two are different, because
 they produce different output, you cannot easily insist on x === x.

Agree. But I don't say that. 

  This I don't agree with, I think you are using the word actions for two
  different things, the elements of type IO a, and their execution. What
  you

 You're right, but one of my problems is to identify elements of type IO a.
 If the returned value isn't the thing, the execution must matter, but which
 parts of the execution are to be taken into account?

How can we tell if  functions f === g? They must have the same domain, 
codomain and return the same result for every element of the domain. This is 
just the mathematical definition. For any two arbitrary functions f,g, can 
you tell if they are the same or not?

As a definition, I'd be happy to have, x,y :: IO a are the same if, given the 
same, real world, they produce the same effects and return the same result. 

Now I'm not saying we can derive that x === x, for x ::IO, from that, but it 
is certainly consistent with that point of view, so we can take it as an 
axiom. Which I think we already do. We also have that if f === g than  f x 
=== g x. That includes functions of type  f,g :: a - IO b. All seems 
consistent. 

Any other equality relation should include that one. 

Is it enough? It's enough to be able to tell that:
putStrLn hello  return 3 === putStrLn (he++llo) =\ _ return (1+2)

And it would say nothing about things like: 
return 4  return 5  ==?== return 5 
I can live with it.


To prove that two functions are in deed the same, we may use, say, number 
theory knowledge, which falls outside the scope of haskell. I find it 
sensible to do the same with actions. Maybe (not sure) it is sensible to 
specify return::(a - IO a), as an action with no side effects such that  
return x === return x  iff  x === x. If we add that to our knowledge of IO, 
along with an appropriate specification for (=), then we would have:
return 4  return 5  === return 5 

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


Re: [Haskell-cafe] Re: what is inverse of mzero and return?

2005-01-24 Thread Jorge Adriano Aires
(Sorry about the recurrent self answers)

 Maybe (not sure) it is sensible to
 sapecify return::(a - IO a), as an action with no side effects such that

 return x === return x  iff  x === x. 
return x === return y iff x === y-- this is what I meant to write.

But even that is not enough, should be:
return x is an action with no side effects and that always returns x 

The previous specification is be a consequence of this one, and it failed to 
specify that the returned value was always x.

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


Re: [Haskell-cafe] Re: what is inverse of mzero and return?

2005-01-23 Thread Jorge Adriano Aires
 What would happen if this was the definition?
 
 instance MonadPlus [] where
mzero = []
mplus a b
 
| a == [] = b
| otherwise = a

 Isn't the above a monoid as well?

Yes.

 Is there only on correct definition of a monad/monoid on lists - or does
 anything that satisfies the monad laws count? I got the impression you
 could define anthing you liked for mzero and mplus - providing the laws
 are upheld?

I'm not arguing that definition would be wrong. It is a monoid. This is the 
instance for ():

instance MonadPlus() where
  mzero = ()
  mplus a b = ()


And this would be correct too:

instance MonadPlus Maybe where
  mzero = Nothing
  mplus a b = Nothing

instance MonadPlus [] where
  mzero = []
  mplus a b = []

Which are not really useful. I'm claiming that the fact that Maybe is a 
trivial Monoid doesn't mean we should dumb down other instances, like the 
one on lists. The usual definition of Monoid on lists is [] as identity and 
++ as the monoid operation. That is how it's defined  in class monoid, and I 
expect this relation to hold:

instance MonadPlus m = Monoid (m a) where
   mempty = mzero
   mappend = mplus


 Then, I'd say you're not thinking of monadic sums, but of catching errors,
  and the appropriate place for that is the class MonadError.

 I am thinking about how some monads are summed - like Maybe and
 the Parser monad.

But, this is not how monadic parsers are summed. Just look into the instace of 
MonadError for Text.ParserCombinators.ReadP.P. Again it would be the case for 
parsers that would return just one possible parsing, but not for parsers that 
return [(a,String)].

J.A.

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


Re: [Haskell-cafe] Re: what is inverse of mzero and return?

2005-01-23 Thread Jorge Adriano Aires

  One common example is using MonadPlus for some backtracking algorithm,
  then instantiatiating it to Maybe or List instance depending on wether
  you just want one solution or all of them.

 Backtracking only works with the first kind, even if you're only
 interested in the first solution. This must hold:

   (mplus a b) = c = mplus (a = c) (b = c)

Not really. If the recursive call is something like msum 
[all_possible_paths], then you are backtracking. The difference is that by 
using Maybe you'll stop as soon as you succeed, and with list you will find 
all possible paths. 

I don't have a small, self-contained, example at hand so I'll use one by 
Carsten Schultz that I once saw posted in comp.lang.functional. Hope he 
doesn't mind. 

http://groups-beta.google.com/group/comp.lang.functional/msg/d7ac1fe1684ef840
-- ---
-- knapsack problem 

module Subset2 where
import Control.Monad

sss :: MonadPlus m = Int - [Int] - m [Int]
sss n [] | n0 = mzero
sss n (x:xs) = 
case compare n x 
of LT - mzero
   EQ - return [x]
   GT - liftM (x:) (sss (n-x) xs) `mplus` sss n xs
-- ---
sss 40 [3, 8, 9, 13, 14, 15, 17, 19] :: [[Int]]
[[3,8,14,15],[3,9,13,15],[8,13,19],[8,15,17],[9,14,17]]

sss 40 [3, 8, 9, 13, 14, 15, 17, 19] :: Maybe [Int]
Just [3,8,14,15]


  [*] For instance, I've missed Maybe being an instance of MonadError.
 You could define your own instance, of course.

Yes of course, and I did ;)  But I think it should be provided nontheless, and 
I even find the fact that it isn't is playing a big part in all this 
confusion. Since there is no MonadError instance for Maybe, we end up using 
its MonadPlus instance, which just happens to be the same. But it cannot be 
generalized, for other types.

Lets forget about lists, think (Either e). It's usual to move from (Maybe a) 
to (Either e a) to consider more than one kind of error. But, there is no 
natural instance of MonadPlus for (Either e a). What would mzero be? 

Yet, the Maybe like, mplus operation makes perfect sense in (Either e) or 
any other MonadError, though. You don't need Monoids at all, what you need is 
the concept of error. Just define it as:

skipError x y = catchError x (\_-y)

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


Re: [Haskell-cafe] Re: what is inverse of mzero and return?

2005-01-23 Thread Jorge Adriano Aires

 I think it would be helpful if all these classes came with their laws
 prominently attached in their Haddock documentation or wherever. 
Agree.

 The  trouble with MonadPlus is that the precise set of associated laws is
 either unspecified or not the most useful (I assume there's a paper on
 the class somewhere). I think everyone can agree on these:

   mplus mzero a = a
   mplus a mzero = a
   mplus (mplus a b) c = mplus a (mplus b c)
snip
   (mplus a b) = c = mplus (a = c) (b = c)

I just checked the paper,
A monadic Interpretation of Tatics, by Andrew Martin and Jeremy Gibbons
http://web.comlab.ox.ac.uk/oucl/work/jeremy.gibbons/publications/tactics.pdf

And in deed, these are the listed laws for MonadPlus. On the other hand, Maybe 
is said to be an instance of MonadPlus.

So now I'm lost. 

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


Re: [Haskell-cafe] Re: what is inverse of mzero and return?

2005-01-23 Thread Jorge Adriano Aires

 Am Sonntag, 23. Januar 2005 15:58 schrieb Jorge Adriano Aires:
  I'm not arguing that definition would be wrong. It is a monoid. This is
  the instance for ():
 
  instance MonadPlus() where
mzero = ()
mplus a b = ()

 Maybe I'm stupid, but:

 class Monad m = MonadPlus m where
 mzero :: m a
 mplus :: m a - m a - m a

 How does () fit into this, () isn't of kind * - *, as far as I know
 () Int is meaningless -- just checked, gives Kind Error.


Nope, I am. Sorry! I was alternating between monoids and monadplus, and came 
up with that nonsense. I was obviously thinking about Monoid () and not 
MonadPlus (). 


  And this would be correct too:
 
  instance MonadPlus Maybe where
mzero = Nothing
mplus a b = Nothing
 
  instance MonadPlus [] where
 
mzero = []
mplus a b = []

 Both aren't correct, since mzero `mplus` x == x
 doesn't hold (they're syntactically correct, though).

Yeap. You are right again. Sorry for this terrible example, please ignore it.

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


Re: [Haskell-cafe] Re: what is inverse of mzero and return?

2005-01-22 Thread Jorge Adriano Aires
 But only some instances (such as []) satisfy this:

   (mplus a b) = c = mplus (a = c) (b = c)

 Other instances (IO, Maybe) satisfy this:

   mplus (return a) b = return a

 I think mplus should be separated into two functions. 

How would we implement the first kind in the Maybe instance of MonadPlus?

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


Re: [Haskell-cafe] Re: what is inverse of mzero and return?

2005-01-22 Thread Jorge Adriano Aires
snip
 Only the monoid Maybe a is not very nice (nor is the monoid IO a),since the 
 second argument of the composition is in  general ignored. 

snip

 So I think, rather than separating mplus, one should think about whether it
 is sensible to make Maybe and IO instances of MonadPlus in the first place.
 I don't know nearly enough of the innards of Haskell to form a valuable
 opinion of that, but perhaps somebody could enlighten me?

My humble opinion follows. 

It's still a Monoid, being boring should be no reason not to include it [*]. 
By taking advantage of typeclasses, we can easily alternate between more 
elaborate approaches and dull ones (if we have the dull ones available too). 

One common example is using MonadPlus for some backtracking algorithm, then 
instantiatiating it to Maybe or List instance depending on wether you just 
want one solution or all of them. 

[*] For instance, I've missed Maybe being an instance of MonadError. 

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


Re: Implicit parameters:

2005-01-19 Thread Jorge Adriano Aires
Isn't it just the monomorphism restriction at work?
This works fine:

 f () = do
    a - get_unique
    putStr (showInt a \n)
    b - get_unique
    putStr (showInt b \n)
    c - get_unique
    putStr (showInt c \n)                                                    
              
                                                            

 get_unique :: (?global_counter :: IORef Int) = IO Int
 get_unique = readIORef ?global_counter


J.A.
___
Glasgow-haskell-users mailing list
Glasgow-haskell-users@haskell.org
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users


Re: [Haskell-cafe] Top Level etc.

2005-01-19 Thread Jorge Adriano Aires
 Perhaps one could have top-level implicit parameters (or top-level
 contexts in general):

 module (?myvar :: IORef Int) = Random where

Hi!
I suggested something very similar to this some months ago, syntax and all. 
Nice to see I'm not the only one thinking along this lines.
http://www.mail-archive.com/haskell%40haskell.org/msg14884.html


 module Main where
   import MyMain

   -- mymain :: (?myvar :: IORef Int) = IO () -- outside

   main = do
  var - newIORef 1   -- initialisers in the order you want
  let ?myvar = var in mymain

By then I also suggest that maybe we could also bind the implicit on import,  
something like:

 module (?par :: Parameter) = A where 
 ...

 module B where
 import A -- simple, ?par unbound
 import qualified A as Ak where ?par = k -- ?par bound to k
 import qualified A as Am where ?par = m -- ?par bound to m

Seemed fine as long as the parameters didn't depend on the imported modules. 
But on hindsight, making an import depend on valued defined in the body of 
the module is probably quite clumsy, unfortunately (right?). Still, 

 import qualified A as Ak where ?par = 1
or 
 import qualified A as Ak where ?par = newIORef
or even 
 import C(k)
 import qualified A as Ak where ?par = k 

Doesn't sound that bad though. 

J.A.

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


Re: [Haskell-cafe] Some random newbie questions

2005-01-09 Thread Jorge Adriano Aires
On Friday 07 January 2005 12:03, Ketil Malde wrote:
 Naive use of foldl.  I tend to think the default foldl should be
 strict (ie. replaced by foldl') -- are there important cases where it
 needs to be lazy?

Hi, 
One simple example would be,
 reverse = foldl (flip (:)) []

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


Re: [Haskell-cafe] Some random newbie questions

2005-01-09 Thread Jorge Adriano Aires

 On Friday 07 January 2005 12:03, Ketil Malde wrote:
  Naive use of foldl.  I tend to think the default foldl should be
  strict (ie. replaced by foldl') -- are there important cases where it
  needs to be lazy?

 Hi,
 One simple example would be,
  reverse = foldl (flip (:)) []

A better example would be building some other lazy structure that is strict 
on it's elements...
J.A.

---
module Test where
import Data.List 

data L = E | !Int :+: L deriving Show

-- my head
h (x:+:xs) = x 
h E= error ops

-- 
rev1 = foldl  (flip (:+:)) E
rev2 = foldl' (flip (:+:)) E

l= [error , error , 1::Int]
--

*Test h (rev1 l)
1
(0.00 secs, 264560 bytes)
*Test h (rev2 l)
*** Exception:
(0.01 secs, 264524 bytes)

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


Re: [Haskell-cafe] Some random newbie questions

2005-01-09 Thread Jorge Adriano Aires

 No, it would work with strict foldl too. In fact in the absence
 of optimization it would work better (uses less time and space).
 The optimization required is inlining and strictness analysis.

Is this also true if your just going to use the first few elements after 
reversing it?

 A function which requires lazy foldl for correctness would have
 to be sometimes lazy in its first argument, and at the same time
 some partial results would have to be undefined. By function
 I mean the first argument of foldl, treated as a binary function.

 Here this doesn't apply because flip (:) x y is always defined. And
 another common case for foldl, sum, doesn't apply because (+) is
 usually strict on both arguments (although in principle it does not
 have to be true because of overloading, which implies that a compiler
 can only optimize particular specializations of sum, not generic sum).

 I don't know of any real-life example.

Yes you are right, my bad. I was thinking as if lists were not lazy on their 
elements, therefore my second example... But yes, now it is not a common 
example anymore. 

 Perhaps there are cases where evaluating partial results is correct
 but inefficient. I don't know such case either.

Just replace the errors on my second example by some big computations...

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


Re: [Haskell-cafe] Some random newbie questions

2005-01-09 Thread Jorge Adriano Aires
On Sunday 09 January 2005 21:30, Marcin 'Qrczak' Kowalczyk wrote:
 Jorge Adriano Aires [EMAIL PROTECTED] writes:
  No, it would work with strict foldl too. In fact in the absence
  of optimization it would work better (uses less time and space).
  The optimization required is inlining and strictness analysis.
 
  Is this also true if your just going to use the first few elements after
  reversing it?

 Yes. A strict fold would evaluate cons cells of the result while they
 are constructed, not list elements. They are all defined (flip (:) x y
 is always defined), so a strict foldl is correct.

Yes, now I was refering to the efficiency issue only. 

 Making a cons cell should be not more expensive than making a thunk
 which will make a cons cell when evaluated. 

Ok, I wasn't sure about this...

 Well, unless the 
 implementation doesn't inline flip and thus making these thunks
 is actually faster than running them. In this case a lazy foldl is
 more efficient than a strict foldl, as long as a sufficiently small
 part of the result is used; it's always less efficient if the whole
 result is examined.

Right.

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


Re: [Haskell-cafe] Some random newbie questions

2005-01-09 Thread Jorge Adriano Aires
 (+) is
 usually strict on both arguments (although in principle it does not
 have to be true because of overloading, which implies that a compiler
 can only optimize particular specializations of sum, not generic sum).

Since you mention it, there was some talk about this in the #haskell channel, 
and I wondered why aren't sum and product members of Num with default 
instances, just like mconcat is also a member of Data.Monoid.Monoid. 
From the docs: 

mconcat :: [a] - a
Fold a list using the monoid. For most types, the default definition for 
mconcat will be used, but the function is included in the class definition so 
that an optimized version can be provided for specific types

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


Re: [Haskell-cafe] Class Synonyms - example 2

2004-12-11 Thread Jorge Adriano Aires

 Jorge,

  Besides the case where 'a' is the same as 'b', there is also another
  interesting case. That is when you have both, Foo A B and Foo B A.
  This is a
  known property (named DoubleFoo) [...]

 Again, with -fallow-undecidable-instances:

 \begin{code}
 class (Foo a b, Foo b a) = DoubleFoo a b
 instance (Foo a b, Foo b a) = DoubleFoo a b
 \end{code}

Ah! Got it.
Thanks  Stefan,

J.A.
___
Haskell-Cafe mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] Class Synonyms

2004-12-10 Thread Jorge Adriano Aires
Hello! 

I got a multi-parameter type class:

 class Foo a b | a - b where
foo_method1 :: ...
foo_method2 :: ...
...

And some particular cases are important on their own, like the one where 'a' 
and 'b' are the same, I call elements with this property, Bar. So I defined:

class Foo a a = Bar a where

This is nice, now I can replace (F a a) for (Bar a) in the context of many 
functions. Less typing and it's more readable. Still, I have to define 
instances as:
 
 instance Foo A A where
foo_method1 = bla1
foo_method2 = bla2
 
 instance Bar A where


I'd like to achieve something better than this. I was looking for something 
like class synonyms. So if I declared an instance Foo A A, I automagicaly 
had Bar A, because they'd be the same. Or even better, I could declare

 instance Bar A where
foo_method1 = bla1
foo_method2 = bla2


Is anything like this possible at all?
Thanks,

J.A.
___
Haskell-Cafe mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] Class Synonyms - example 2

2004-12-10 Thread Jorge Adriano Aires
Maybe I should have included a more interesting example in the previous mail. 
So I had this class:

 class Foo a b | a - b where
foo_method1 :: ...
foo_method2 :: ...
...

Besides the case where 'a' is the same as 'b', there is also another 
interesting case. That is when you have both, Foo A B and Foo B A. This is a 
known property (named DoubleFoo), so I'd like to type contexts as,

 DoubleFoo a b =

instead of,

 (Foo a b, Foo b a) =

so I tried:
 class (Foo a b, Foo b a) = DoubleFoo a b where

This works fine if I'm going to define functions which need both instances of 
Foo. Something like:

 testDouble :: DoubleFoo a b = a - b - c 
 testDouble a b = foo_method1 a b  ... foo_method1 b a 

but it doesn't help me with:

 testDouble2 :: DoubleFoo a b = a - b - c 
 testDouble2 a b = foo_method1 a b  ... testDouble2 b a 

now I need DoubleFoo b a as well. Seems to me like there is no way of saying:
 Foo a b , Foo b a = DoubleFoo a b 

right?

J.A.

___
Haskell-Cafe mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell] why no strictness annotations in labelled fields?

2004-12-01 Thread Jorge Adriano Aires

 Is there a good reason one can't do:
   data Foo = Foo {bar::!String}

Just add a space after the ::
{bar:: !String}

J.A.
___
Haskell mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell


Re: [Haskell-cafe] foldlWhile

2004-11-20 Thread Jorge Adriano Aires
(opss just noticed I did a reply-to)

  The following is closer to the original, but doesn't work when the whole
  list is folded (i.e., p always satisfied):
  foldlWhile f p a = head . dropWhile p . scanl f a

 Serge's version returns the last 'a' that satisfies 'p', while yours
Not really.

 returns the first 'a' that does not satisfy 'p'.  This should be an
 equivalent version:
Yeap, just like his, 

foldlWhile :: (a - b - a) - (a - Bool) - a - [b] - a
foldlWhilefp  abs  =
snip
(_, False) - a
snip

It tests the accumulator with p, and returns it on false.

J.A.
___
Haskell-Cafe mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] FiniteMap-like module for unordered keys?

2004-11-09 Thread Jorge Adriano Aires
Hello, 

 A hash-table becomes rather useless without mutable state AFAICS.
 Without it, one might almost just as well use a list of pairs...

Could you please elaborate? Is there motive why an Hash Table, implemented as 
FiniteMap of Lists, for instance, wouldn't be worth to using over a simple 
List? (This wouldn't help G. Klyne of course). I've always wondered why a 
non-monadic version of is not provided in the GHC libs... 

J.A.
___
Haskell-Cafe mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] QuickCheck - Extracting data values from tests

2004-09-04 Thread Jorge Adriano Aires

 The generate function is exported:

 generate :: Int - StdGen - Gen a - a

Thanks, that's the one I was missing.

J.A.
___
Haskell-Cafe mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] QuickCheck - Extracting data values from tests

2004-09-02 Thread Jorge Adriano Aires

  Hello all,
  When using Quickcheck, is there some way to extract generated data values
  to the IO Monad?
 
  I know I can collect and print information about test cases, but that's
  not enough. Data may be pretty complex, and there may be no parsers for
  it. If a test suddenly goes wrong, just having it displayed doesn't seem
  that useful.

 You may be interested in a QuickCheck hack of mine that saves the offending
 data value to use immediately in the next test run.

Nice!
It's different from what I was looking for but also quite usefull.

 You can get the current version with
 darcs get http://thunderbird.scannedinavian.com/repos/quickcheck;
 I've only used this for my own code, so I'd be interested in any feedback.

Ok.

 In some cases it's a lot easier to generate a value from a seed and size
 rather than saving the value in some way that you can restore (ie
 functions).

 I've been investigating doing test-driven-development with QuickCheck,
 saving failing test cases is one step towards that goal. If you have more
 ideas on that topic, I'd like to hear about it.

Well, returning (part of) the generated data is one of them :)

  Also, even when I'm implementing a generator, I want to see how it is
  working. Running a verboseCheck on some dummy property helps, but I may
  want to analyse the data, or some parts of it better - for instance, for
  many data structures I have alternative show functions that take
  parameters as arguments.

 This isn't clear to me, can you give other examples?


Not sure which part is not clear... I'll just try to explain each of them.
Lets say I'm implementing a generators for Graphs.

  Also, even when I'm implementing a generator, I want to see how it is
  working.
I want to check if the generated Graphs are like I intended them to be.

  Running a verboseCheck on some dummy property helps, but I may
verboseCheck by default prints all the data.
I can run it on a dummy function that always returns True to see what kind of 
data I'm getting.


  want to analyse the data, or some parts of it better
May want to print the 'actual graphs' on the screen (ASCII art, or maybe using 
some function that calls Gnuplot). Then I may want to check in more detail 
the info in contained in some of the nodes. Then I may decide to run some 
functions on it.

  many data structures I have alternative show functions that take
  parameters as arguments.
Like I just said, I may want to show the graph in many ways.


But there are more possibilities.
Why limitate the usefulness of QuickCheck? Suppose I just implemented 
generators for a few kinds of terms and formulas to test some properties. Now 
I want to benchmark a couple of different unification functions... I'd expect 
to be able to use my generator for that. Unless I'm missing something, I 
cannot. Am I right?

J.A.

___
Haskell-Cafe mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] QuickCheck - Extracting data values from tests

2004-09-01 Thread Jorge Adriano Aires
Hello all,
When using Quickcheck, is there some way to extract generated data values to 
the IO Monad? 

I know I can collect and print information about test cases, but that's not 
enough. Data may be pretty complex, and there may be no parsers for it. If a 
test suddenly goes wrong, just having it displayed doesn't seem that useful.

I'd expect quickCheck to have type:
quickCheck :: forall a. (Testable a) = a - IO [a]

Show I could just get the offending data with:
please_be_empty - quickCheck prop_foo

Also, even when I'm implementing a generator, I want to see how it is working. 
Running a verboseCheck on some dummy property helps, but I may want to 
analyse the data, or some parts of it better - for instance, for many data 
structures I have alternative show functions that take parameters as 
arguments. 

Thanks in advance,
J.A.
___
Haskell-Cafe mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: Problem with Unboxed Types

2004-08-27 Thread Jorge Adriano Aires

 Just to be sure, I've just compiled and run this code with GHC 6.2.1, on
 a Linux system.  I can't account for your difficulty I'm afraid.

 Simon

Thanks, and nevermind, I think I figured out what was happening. Working now. 

J.A.



 {-# OPTIONS -fglasgow-exts #-}

 module Main where

 import GHC.Exts

 showUnboxedInt :: Int# - String
 showUnboxedInt n = (show $ I# n) ++ #

 main = print (showUnboxedInt 3#)

 | -Original Message-
 | From: [EMAIL PROTECTED]

 [mailto:glasgow-haskell-users-

 | [EMAIL PROTECTED] On Behalf Of Jorge Adriano Aires
 | Sent: 27 August 2004 02:55
 | To: [EMAIL PROTECTED]
 | Subject: Problem with Unboxed Types
 |
 | Hello,
 | I'd like to try using Unboxed types, but I always get a parse error

 on input

 | `#' error. To make sure I wasn't making some mistake I tried the

 example in

 | the wiki:
 |
 | http://www.haskell.org/hawiki/UnboxedType
 | 
 | module Main where
 | import GHC.Exts
 |
 | showUnboxedInt :: Int# - String
 | showUnboxedInt n = (show $ I# n) ++ #
 | 
 |
 | Even tried adding fglasgow-exts, nothing works though. I'm using GHC

 6.2.1 on

 | a SuSE 8.2 system (glibc 2.3) installed using the available RPMs. Any

 idea?

 | Thanks in advance,
 | J.A.
 |
 | ___
 | Glasgow-haskell-users mailing list
 | [EMAIL PROTECTED]
 | http://www.haskell.org/mailman/listinfo/glasgow-haskell-users
___
Glasgow-haskell-users mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users


Problem with Unboxed Types

2004-08-26 Thread Jorge Adriano Aires
Hello, 
I'd like to try using Unboxed types, but I always get a parse error on input 
`#' error. To make sure I wasn't making some mistake I tried the example in 
the wiki:

http://www.haskell.org/hawiki/UnboxedType

module Main where 
import GHC.Exts

showUnboxedInt :: Int# - String
showUnboxedInt n = (show $ I# n) ++ #


Even tried adding fglasgow-exts, nothing works though. I'm using GHC 6.2.1 on 
a SuSE 8.2 system (glibc 2.3) installed using the available RPMs. Any idea?

Thanks in advance,
J.A.

___
Glasgow-haskell-users mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users


Re: How do I specify the source search path?

2004-06-30 Thread Jorge Adriano Aires
On Wednesday 30 June 2004 16:15, S. Alexander Jacobson wrote:
 I have the working code for my Haskell App Server
 Framework in ~/HAppS/HAppS.hs.  If I want to
 start working on an app that uses this framework
 in e.g. ~/MyApp, how do I tell GHCi to resolve
 import HAppS?

 Note: The HAppS code is in active development so I
 don't want to put it in the system GHC lib
 hierarchy.  I just want to use it add hoc from the
 command line.

Using the -i flag. Unfortunatly relative paths (using '~') don't seem to work, 
so you have to type the full path: ghci -i/home/user/HAppS/

As far as I know, there is also no way to specify the search path in an 
environment var, so my solution was to add to my .alias:
alias ghci='ghci -i/home/jadrian/Program/Haskell/MyLibs'
alias ghc='ghc -i/home/jadrian/Program/Haskell/MyLibs'

J.A.

J.A.

___
Glasgow-haskell-users mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users


Re: [Haskell] Initialisation without unsafePerformIO

2004-06-04 Thread Jorge Adriano Aires

 What ideas do people have for getting rid of unsafePerformIO?

Hope my suggestion is not too naive. 
I get along quite fine using implicit parameters in many cases, it's just 
tedious explicitly typing them in every function context. I'd be pretty happy 
if it was possible to define the 'scope' of some implicit parameters in a 
module and/or define their scope as being a whole module. The 2nd option 
would be something like:

 module (?par :: Parameter) = A where 
 ...

Functions in A could have ?par in their context without having it explicitly 
typed. Now the import of A could be done with:

 module B where 

 import A  -- simple, ?par unbound
 import A as Ak where ?par = k -- ?par bound to k
 import A as Am where ?par = m -- ?par bound to m

 ...

 k :: Parameter
 k = ...
 
 m :: Parameter
 m = ...
 ...

Also,

 module (?par :: Parameter) = C where 
 import A  -- both A and C paremeterised by ?par

Since both modules share the same parameter, instantiation on ?par in the 
import of C would propagate to the import of A.

At first glance it seems simple syntactic sugar and therefore doable. 
Along with some options in the interpreter to hide/show (this kind of) 
implicit parameters when displaying signatures, check module context, etc. 
probably also quite usable.

J.A.
___
Haskell mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell


Re: Namespace trouble

2004-05-20 Thread Jorge Adriano Aires

 Jorge Adriano Aires [EMAIL PROTECTED] writes:
  I have the following structure:
   MyProgram/A.hs
   MyProgram/Aux/B.hs
   MyProgram/Aux/C.hs

 You have already received replies to your question, so let me make a
 different point.  If you ever intend your program to work on Windows,
 do not use Aux as a file or directory name!  The libraries mailing
 list has some recent experience of this.  (Apparently Aux is a
 reserved filename on Windows and you get strange behaviour if you
 try to use it for anything else.)

Thanks for the tip, I'm working in linux though and Aux was really just an 
example :)

J.A.
___
Glasgow-haskell-users mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users


Namespace trouble

2004-05-19 Thread Jorge Adriano Aires
Hello,
I have the following structure:

 MyProgram/A.hs
 MyProgram/Aux/B.hs
 MyProgram/Aux/C.hs

and:
 A imports C
 B imports C

Can I make this work using namespaces only (i.e. no -i flag)? 
I expected this to work:

 MyProgram/A.hsname: Aimport Aux.C
 MyProgram/Aux/B.hsname: Aux.Bimport C
 MyProgram/Aux/C.hsname: Aux.C

But complains when importing C from B since its name is Aux.C.
What is the most elegant way to deal with such cases?

J.A.
___
Glasgow-haskell-users mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users


Re: Namespace trouble

2004-05-19 Thread Jorge Adriano Aires
 I expected this to work:
  MyProgram/A.hsname: Aimport Aux.C
  MyProgram/Aux/B.hsname: Aux.Bimport C
  MyProgram/Aux/C.hsname: Aux.C

 But complains when importing C from B since its name is Aux.C.
 What is the most elegant way to deal with such cases?


Answering myself, this works:
 MyProgram/A.hsname: Aimport Aux.C
 MyProgram/Aux/B.hsname: Aux.Bimport Aux.C
 MyProgram/Aux/C.hsname: Aux.C

I just have to load B from MyProgram when testing it in ghci, instead of 
loading it in MyProgram/Aux. Thanks to Lunar for the tip.

J.A.
___
Glasgow-haskell-users mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users


Re: [Haskell-cafe] Monadic Composition

2004-05-12 Thread Jorge Adriano Aires
 So, yes, it is useful, but should it be included in a standard Monad
 module? After all, this module contains mostly trivial functions ;)

 BTW. You can write this function using foldM:

 compM l a = foldM (#) a l

 where # is an often used reverse application operator:
 x # f = f x

Right. Now that I look at it, someone probably tried to give me this advice 
before but I failed to understand... (sorry monotonom!). It's all clear now. 
One more question. Isn't the foldM description a bit misleading? From the 
Report and also in GHC documentation:

The foldM function is analogous to foldl, except that its result is 
encapsulated in a monad.(...)
foldM f a1 [x1, x2, ..., xm ] == 
  do
  a2 - f a1 x1
  a3 - f a2 x2
  ...
  f am xm

After reading this I expected left associativity, just like in my first 
definition. That'd mean a fail wouldn't stop a computation immediately but 
instead be passed from function to function. By checking its definition in 
the report I can see this is not the case though.

Cheers,
J.A.
___
Haskell-Cafe mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] Monadic Composition

2004-05-11 Thread Jorge Adriano Aires
Hello,
I needed to compose monadic functions, since I couldn't find anything in 
Control.Monad so I defined my own. I first came up with a left associative 
version:

compLM [f1,..., fn] a = (f1 a = f2) = ... = fn
 compLM:: Monad m = [a-m a] - (a-m a)
 compLM mfs a  = foldl (=) (return a) mfs

Later a right associative version, which I believe to be more efficient, 
particularly when some computation returns fail:

compRM [f1,..., fn] a = \x-f1 x = (\x-f2 x = ... = \x-fn x) a
 compRM   :: Monad m = [a-m a] - (a-m a)
 compRM = foldr (\f g- (\x -f x = g)) return 

This higher order function seems quite useful to me and not trivial, so I  
expected it to be available. When this happens I wonder if I'm missing 
something. Am I complicating things? Is it actually available (or some other 
that does the trick) ? Or is it just me who finds this usefull enough to be in 
the libs?
 
J.A.

___
Haskell-Cafe mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: int to float problem

2003-03-02 Thread Jorge Adriano

 Mike T. Machenry [EMAIL PROTECTED] writes:
  I recently desided I wanted a bunch function to return
  float instead of Int. [...] I found fromInteger but it
  didn't seem to work on the return value of the cardinality
  function for instance.

 Try fromIntegral, which works for Int and Integer, too.


Casting an Integral value to a Fractional value to perform arithmetic 
operations, is a very common need and I don't like adding fromIntegral 
everywhere, so ended up writing a (very simple) module with generalized 
arithmetic operators (see attachment). The » next to the operations indicate 
a cast from an Integral to a Fractional value. 

J.A.


module CrossTypeOps where


-- Addition
(+«) :: (Fractional a, Integral b)= a - b - a
(+«) x n = x+fromIntegral n

(»+) :: (Integral a, Fractional b)= a - b - b
(»+) n x = fromIntegral n + x

(»+«) :: (Integral a, Fractional b)= a - a - b
(»+«) m n = fromIntegral m+fromIntegral n


-- Difference
(-«) :: (Fractional a, Integral b)= a - b - a
(-«) x n = x-fromIntegral n

(»-) :: (Integral a, Fractional b)= a - b - b
(»-) n x = fromIntegral n - x

(»-«) :: (Integral a, Fractional b)= a - a - b
(»-«) m n = fromIntegral m-fromIntegral n


-- Multiplication
(*«) :: (Fractional a, Integral b)= a - b - a
(*«) x n = x*fromIntegral n

(»*) :: (Integral a, Fractional b)= a - b - b
(»*) n x = fromIntegral n * x

(»*«) :: (Integral a, Fractional b)= a - a - b
(»*«) m n = fromIntegral m*fromIntegral n


-- Division 
(/«) :: (Fractional a, Integral b)= a - b - a
(/«) x n = x / fromIntegral n

(»/) :: (Integral a, Fractional b)= a - b - b
(»/) n x = fromIntegral n / x

(»/«) :: (Integral a, Fractional b)= a - a - b
(»/«) m n = fromIntegral m / fromIntegral n


-- Priorities
infixl 6  +«, »+, »+«, -«, »-, »-«
infixl 7  *«, »*, »*«, /«, »/, »/«





Pattern matching with implicit par. bug

2003-02-13 Thread Jorge Adriano
There it goes,
J.A.


type CTPar = ([Double],Int,Int)
us :: (?ctPar :: CTPar) = [Double]
us = let (us',_,_) = ?ctPar in us'


ghc-5.04: panic! (the `impossible' happened, GHC version 5.04):
tcSplitTyConApp
{?ctPar{-r2kd-} :: ([GHCziFloat.Double{-3u-}],
GHCziBase.Int{-3J-},
GHCziBase.Int{-3J-})}

Please report it as a compiler bug to [EMAIL PROTECTED],
or http://sourceforge.net/projects/ghc/.


___
Glasgow-haskell-bugs mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/glasgow-haskell-bugs



Pattern matching, implict par. question

2003-02-13 Thread Jorge Adriano
Hello, When trying 

type CTPar = ([Double],Int,Int)
ctPar  ::(?ctPar::CTPar)=CTPar 
ctPar@(us,n,j) = ?ctPar

I got this error message in ghci is:
Illegal overloaded type signature(s)
in a binding group for ctPar, us, n, j
that falls under the monomorphism restriction
When generalising the type(s) for ctPar, us, n, j
Failed, modules loaded: CrossTypeOps.

Should the monomorphis restriction really apply here?
The values of us,j,n do depend on the context, but not their types (right?).

J.A.


___
Haskell-Cafe mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell-cafe



Very simple question

2003-02-11 Thread Jorge Adriano
On style, yes. A concrete example of what I asked before.
The following doesn't type check for obvious reasons. 
In your opinion what is the most elegant way to fix it? 

Like I said, I'm starting to feel like defining my own operators is the way to 
go. On the other hand, this kind of situation seems quite common and there 
are no such operators in the standard libraries, so I might be wrong here.
Opinions anyone?

J.A.
--
Source Code:
--

module TypeCheck where
import Data.Array
import Data.Ix

bigR :: Double
bigR = sum[a!(i,j)*(r!i - n*b!i)*(r!j-n*b!j) | (i,j)-range(bounds a)]/n


a :: Array (Int,Int) Double
b :: Array Int Double
r :: Array Int Int
n :: Int

a=undefined
b=undefined
r=undefined
n=undefined
___
Haskell-Cafe mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell-cafe



Ints as ints and floats - Question on style

2003-02-08 Thread Jorge Adriano
Hello, 
Lately I've been coding functions where I have to use Int elements, both as 
Ints (e.g. as an array or list index) and Doubles/Floats (e.g. when 
performing arithmetic operations with Doubles/Floats).

How do you usually deal with this? Some options I can think of are,
1. using fromIntegral when needed (some formulas become unredable). 
2. duplicating all those ints to float elements. (not very readable either, 
you end up with two distinct elements that mean the same thing).
3. creating new operators perform arithmetic operations with Ints/Integers and 
Float/Doubles.

Cheers,
J.A.
___
Haskell-Cafe mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell-cafe



Re: Global variables?

2003-01-31 Thread Jorge Adriano

 Hello,
 Is it even possible to make a global variable in Haskell?
 If yes, how?
 Thanks.

(short answer, no time now...)
Look here:
http://www.haskell.org/pipermail/haskell-cafe/2002-January/002589.html

Hope it helps ;)

J.A.
___
Haskell-Cafe mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell-cafe



Ambiguous type variable

2003-01-22 Thread Jorge Adriano
Hi all, 

This works fine, as expected
 f :: (Num a, Random a) = Int - [a]
 f = randomRs (0,1).mkStdGen

If I skip the type signature, though, I get the following error messages:
Main.hs:14:
Ambiguous type variable(s) `a' in the constraint `Random a'
arising from use of `randomRs' at Main.hs:14
In the first argument of `(.)', namely `randomRs (0, 1)'
In the definition of `f': (randomRs (0, 1)) . mkStdGen

Main.hs:14:
Ambiguous type variable(s) `a' in the constraint `Num a'
arising from the literal `1' at Main.hs:14
In the first argument of `randomRs', namely `(0, 1)'
In the first argument of `(.)', namely `randomRs (0, 1)'

Why exctly can't ghci figure how the type of f?

This just happens when loading the code from a file, 
 :t randomRs (0,1).mkStdGen
in ghci works fine.

J.A.
___
Glasgow-haskell-users mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users



Re: ANNOUNCE: GHC version 5.04.2 released

2002-12-17 Thread Jorge Adriano
Hi,
Are there going to be SuSE rpms available anytime soon? Anyone working on 
them? Thanks,

J.A.
___
Glasgow-haskell-users mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users



Re: ANNOUNCE: GHC version 5.04.2 released

2002-12-17 Thread Jorge Adriano
Hi,
Are there going to be SuSE rpms available anytime soon? Anyone working on 
them? Thanks,

J.A.
___
Haskell mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell



Re: slide: useful function?

2002-11-27 Thread Jorge Adriano

Doesn't seem that usefull to me, you can get the several consecutive ones by 
applying tails to your list.


 I want to propose the following function slide, which is like map, but
 depends not on one value of
 a list, but on several consecutive ones.

 slide :: ([a] - b) - [a] - [b]
 slide f [] = []
 slide f xs = f xs : slide f (tail xs)

slide f = map f.init.tails
The init is needed because you don't apply f to the empty List.
If you did, then it would be just.

 slide :: ([a] - b) - [a] - [b]
 slide f [] = f [] ---
 slide f xs = f xs : slide f (tail xs)

slide f = map f.tails


J.A.
___
Haskell mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell



Re: Why no findM ? simple Cat revisited

2002-11-20 Thread Jorge Adriano

 Simple Cat (revisitied)

 \begin{code}

 import IO

 findM f [] = return Nothing
 findM f (x:xs) = do { v - x; if f v then return (Just v) else findM f xs }

 isLeft (Left _) = True
 isLeft _ = False

 main = findM (isLeft) (hCat stdin) where hCat h = try (hGetLine h) : hCat h

 \end{code}

Seems to me like the name findM could be misleading
mapM :: (Monad m) = (a - m b) - [a] - m [b]
filterM :: (Monad m) = (a - m Bool) - [a] - m [a]

These take a monadic function and a list of elements. Yours works the other 
way around (takes a function and a list of 'monadic elements').
I'd expect the definition of findM to be:

findM'  :: (Monad m) = (a - m Bool) - [a] - m (Maybe a)
findM' f [] = return Nothing
findM' f (x:xs) = do { b - f x; if b then return (Just x) else findM' f xs }

This one doesn't serve your purpose though.
J.A.



___
Haskell mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell



Re: Why no findM ? simple Cat revisited

2002-11-20 Thread Jorge Adriano

 Simple Cat (revisitied)

 \begin{code}

 import IO

 findM f [] = return Nothing
 findM f (x:xs) = do { v - x; if f v then return (Just v) else findM f xs }

 isLeft (Left _) = True
 isLeft _ = False

 main = findM (isLeft) (hCat stdin) where hCat h = try (hGetLine h) : hCat h

 \end{code}

Seems to me like the name findM could be misleading
mapM :: (Monad m) = (a - m b) - [a] - m [b]
filterM :: (Monad m) = (a - m Bool) - [a] - m [a]

These take a monadic function and a list of elements. Yours works the other 
way around (takes a function and a list of 'monadic elements').
I'd expect the definition of findM to be:

findM'  :: (Monad m) = (a - m Bool) - [a] - m (Maybe a)
findM' f [] = return Nothing
findM' f (x:xs) = do { b - f x; if b then return (Just x) else findM' f xs }

This one doesn't serve your purpose though.
J.A.



___
Haskell-Cafe mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell-cafe



library of monadic functions [was: Why no findM ? simple Cat revisited]

2002-11-20 Thread Jorge Adriano

 I appreciate your comment.
 I agree that the type of findM should be the one you suggested,
 and it still fits my original purpose. It's no more than a step arout.

 \begin{code}

 import IO
 findM f [] = return Nothing
 findM f (x:xs) = do { b - f x; if b then return (Just x) else findM f xs }

 isLeft (Left _) = True
 isLeft _ = False

 main = findM (=return.isLeft) (hCat stdin)
 where hCat h = try (hGetLine h=putStrLn) : hCat h

 \end{code}

Yes, you are right. 
It was enough because, you don't really care about what you found, you just 
want to search and stop when you do find something. You are returning the 
action that returned an element that satisfied your 
condition, not the actual element like before.

 I expetct the next Haskell Library Report includes findM.
 It's obviously useful.

I think both versions can be very useful:
findM  :: (Monad m) = (a - m Bool) - [a] - m (Maybe a)
findM'  :: (Monad m) = (a - Bool) - [m a] - m (Maybe a)

Same can be said for,
takeWhileM :: (Monad m) = (a - m Bool) - [a] - m [a]
takeWhileM' :: (Monad m) = (a - Bool) - [m a] - m [a]

both would be usefull for different purposes.
Oh and since we're on it I also miss,
iterateM  :: (Monad m) = (a - m a) - a - m [a]
untilM :: (Monad m) = (a - m a) - a - m [a]
etc etc...

I've just been coding them as I need them, like many of you I suppose.
J.A.
___
Haskell-Cafe mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell-cafe



Re: Bug? [was: Implicit params]

2002-11-18 Thread Jorge Adriano

 Now fixed in the HEAD, and will be in 5.04.2

 Thanks for pointing it out.

 Simon

Thanks :)
J.A.
___
Glasgow-haskell-users mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users



Re: Bug? [was: Implicit params]

2002-11-18 Thread Jorge Adriano

 Now fixed in the HEAD, and will be in 5.04.2

 Thanks for pointing it out.

 Simon

Thanks :)
J.A.
___
Haskell-Cafe mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell-cafe



Bug? [was: Implicit params]

2002-11-14 Thread Jorge Adriano
On Thursday 14 November 2002 18:47, Iavor S. Diatchki wrote:
 hello,

  Well, actually you must be right since the pure field defines a pure
  (projection) function... Hmmm, ok, can someone explain this to me,
 
  data E s = E{
refi :: STRef s Int,
refc :: STRef s Char,
m:: Int
  }
 
  -- this is fine, obviously...
  pure   :: E s - Int
  pure e = m e
 
  -- but this is not...
  pure2 :: (?e :: E s) = Int
  pure2 = m (?e)
 
  Why exactly isn't this allowed? What is the workaround?
  Error msg:
  
  Ambiguous constraint `?e :: E s'
  At least one of the forall'd type variables mentioned by the
  constraint
  must be reachable from the type after the '='
  In the type: forall s. (?e :: E s) = Int
  While checking the type signature for `pure2'
  Failed, modules loaded: none.
  -
 -

 this seems like a bug in GHC.   Hugs is happy with it.  The s in the
 pure2 signature is not ambiguous because it is determined when you give
 the value of the implicit parameter.  in fact the way i think about
 implicit parameters is simply as a nice notation for computations in the
 environment monad, so in my mind the above two definitions are pretty
 much the same.

Thanks Iavor! 
GHC people, can you confirm this, Is it a bug? I'm using Ghc 5.0.4 SuSE rpms.
Is there a workaround? 

Thanks,
J.A.



___
Glasgow-haskell-users mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users



Bug? [was: Implicit params]

2002-11-14 Thread Jorge Adriano
On Thursday 14 November 2002 18:47, Iavor S. Diatchki wrote:
 hello,

  Well, actually you must be right since the pure field defines a pure
  (projection) function... Hmmm, ok, can someone explain this to me,
 
  data E s = E{
refi :: STRef s Int,
refc :: STRef s Char,
m:: Int
  }
 
  -- this is fine, obviously...
  pure   :: E s - Int
  pure e = m e
 
  -- but this is not...
  pure2 :: (?e :: E s) = Int
  pure2 = m (?e)
 
  Why exactly isn't this allowed? What is the workaround?
  Error msg:
  
  Ambiguous constraint `?e :: E s'
  At least one of the forall'd type variables mentioned by the
  constraint
  must be reachable from the type after the '='
  In the type: forall s. (?e :: E s) = Int
  While checking the type signature for `pure2'
  Failed, modules loaded: none.
  -
 -

 this seems like a bug in GHC.   Hugs is happy with it.  The s in the
 pure2 signature is not ambiguous because it is determined when you give
 the value of the implicit parameter.  in fact the way i think about
 implicit parameters is simply as a nice notation for computations in the
 environment monad, so in my mind the above two definitions are pretty
 much the same.

Thanks Iavor! 
GHC people, can you confirm this, Is it a bug? I'm using Ghc 5.0.4 SuSE rpms.
Is there a workaround? 

Thanks,
J.A.



___
Haskell-Cafe mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell-cafe



Re: Record of STRefs better than STRef to a Record?

2002-11-13 Thread Jorge Adriano

  If I use an STRef to a record, will a new record be created
  each time I want
  to update a single field? Or can I expect GHC to optimize it
  and have the field of the record updated in place?

 You'll get a new record for each update.  This might not be so bad
 though, depending on the number of fields in your record.
One of them has 4, the other 3, but they might grow bigger...


 Here's another trick if you use this route:
added some parenthesis
  data E s = E{
refi ::  !(STRef s Int),
refc ::  !(STRef s Char)
  }

 and compile with -funbox-strict-fields.  This will eliminate the boxing
 of the STRefs.

Nice, thanks :)


One more question. 
I'm passing that 'record' around as an implicit value. The record as STRefs 
that I use to collect info, but it also has some pure fields with 'read-only' 
info. Something like,

data E s = E{
  refi :: STRef s Int,
  refc :: STRef s Char,
  max  :: Int
}

In some functions I might need only some pure fields, and none of the STRefs, 
but since I pass something of type 'E s' around, everything ends up beeing 
monadic. Is using two records (on with STRefs and one with pure fields) the 
only/best way to avoid this? 
I would like to use two records, doesn't seem natural, but I also don't like 
to end up using monadic functions when they are, in fact, pure...

Thanks,
J.A.




___
Glasgow-haskell-users mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users



Re: Record of STRefs better than STRef to a Record?

2002-11-13 Thread Jorge Adriano

  I'm passing that 'record' around as an implicit value. The record as
  STRefs that I use to collect info, but it also has some pure fields with
  'read-only' info. Something like,

opss let me change 'max' to 'm' 
  data E s = E{
refi :: STRef s Int,
refc :: STRef s Char,
m:: Int  
  }
 
  In some functions I might need only some pure fields, and none of the
  STRefs, but since I pass something of type 'E s' around, everything ends
  up beeing monadic.

 there is no reason why that should be the case.  you only need to be
 within the ST monad when you read the references, so if in some function
 you only look at the pure values, it can have a pure type.
 hope this helped
 iavor

That's what I thought, untill I tried it. 
Well, actually you must be right since the pure field defines a pure 
(projection) function... Hmmm, ok, can someone explain this to me,

data E s = E{
  refi :: STRef s Int,
  refc :: STRef s Char,
  m:: Int
}

-- this is fine, obviously...
pure   :: E s - Int
pure e = m e

-- but this is not...
pure2 :: (?e :: E s) = Int
pure2 = m (?e)

Why exactly isn't this allowed? What is the workaround?
Error msg:

Ambiguous constraint `?e :: E s'
At least one of the forall'd type variables mentioned by the 
constraint
must be reachable from the type after the '='
In the type: forall s. (?e :: E s) = Int
While checking the type signature for `pure2'
Failed, modules loaded: none.
--

Thanks,
J.A.
___
Glasgow-haskell-users mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users



Re: Record of STRefs better than STRef to a Record?

2002-11-13 Thread Jorge Adriano

  If I use an STRef to a record, will a new record be created
  each time I want
  to update a single field? Or can I expect GHC to optimize it
  and have the field of the record updated in place?

 You'll get a new record for each update.  This might not be so bad
 though, depending on the number of fields in your record.
One of them has 4, the other 3, but they might grow bigger...


 Here's another trick if you use this route:
added some parenthesis
  data E s = E{
refi ::  !(STRef s Int),
refc ::  !(STRef s Char)
  }

 and compile with -funbox-strict-fields.  This will eliminate the boxing
 of the STRefs.

Nice, thanks :)


One more question. 
I'm passing that 'record' around as an implicit value. The record as STRefs 
that I use to collect info, but it also has some pure fields with 'read-only' 
info. Something like,

data E s = E{
  refi :: STRef s Int,
  refc :: STRef s Char,
  max  :: Int
}

In some functions I might need only some pure fields, and none of the STRefs, 
but since I pass something of type 'E s' around, everything ends up beeing 
monadic. Is using two records (on with STRefs and one with pure fields) the 
only/best way to avoid this? 
I would like to use two records, doesn't seem natural, but I also don't like 
to end up using monadic functions when they are, in fact, pure...

Thanks,
J.A.




___
Haskell-Cafe mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell-cafe



Record of STRefs better than STRef to a Record?

2002-11-12 Thread Jorge Adriano
Hi all, 
If I use an STRef to a record, will a new record be created each time I want 
to update a single field? Or can I expect GHC to optimize it and have the 
field of the record updated in place?

Right now I'm using a record of STRefs, like:
data E s = E{
  refi ::  STRef s Int,
  refc ::  STRef s Char
}

but it can get a little messy, since thread s propagates to every datatype 
that uses the record type in it's definition.
Thanks,
J.A.
___
Glasgow-haskell-users mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users



Re: producing and consuming lists

2002-11-06 Thread Jorge Adriano

  But like I just showed, sometimes paring them may not be a natural
  approach though...

 Yeah, I understand what you mean.  In the examples you give, you could
 always try to make the appended stuff (the zs, etc) the same length by
 appending Nothings, but probalby not a general solution.

Yes maybe, I was hoping I could find a more elegant solution though.


 I wonder if, given you original function which returns ([Int],[Int]), you
 couldn't do something really ugly like using unsafeInterleaveIO on writing
 the first list, and then write the second list by hand.

 Just a thought.

If consuming is just writing stuff to files I think Trace (which uses 
unsafeInterleaveIO) would be just fine, but consuming might be more than 
that. In that case I'd have to fuse the functions that consume each of the 
streams, with the function that produces them. 

J.A.



___
Haskell-Cafe mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell-cafe



Re: Dealing with configuration data

2002-09-25 Thread Jorge Adriano


 Evening,

 I'm trying to write a utility that reads in some user preferences from
 a pre-determined file, does some work, and exits. Sounds simple enough.

 The problem I'm having is with the preferences: How do I make it
 available throughout the entire program? (FWIW, most of the work is
 effectively done inside the IO monad.) I could explicitly pass the
 record around everywhere, but that seems a trifle inelegant.

 My current solution is to use a global ('scuse my terminology, I'm not
 sure that's the right word to use here) variable of type IORef Config
 obtained through unsafePerformIO. It works, but strikes me as a rather
 barbaric solution to a seemingly tame enough problem...

 Intuition tells me I should be able to `embed', if you will, the config
 record somehow within or alongside the IO state, and retrieve it at
 will. (Is this what MonadState is for?) However it also tells me that
 this will /probably/ involve lots of needless lifting and rewriting of
 the existing code, which makes it even less enticing than passing
 everything around explicitly.

This is how I usually do it:
http://www.mail-archive.com/haskell@haskell.org/msg10565.html
(ignore the last part of the post...)

J.A.

___
Haskell-Cafe mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell-cafe



Re: mutable records

2002-09-10 Thread Jorge Adriano


 Hi,
 thx for this reply.
 Is there any overhead using this mutable?

I just thought I should point out that Mutable is not an haskell type.
You can see in the Utils module that it is just a type synonim for IORef:
http://icfpcontest.cse.ogi.edu/simulator/pfe.cgi?Utils#Mutable
http://haskell.cs.yale.edu/ghc/docs/latest/html/base/Data.STRef.html
I think that sometimes STRef might be a better choice...


 Are you also using Templates ?
 With this mutable I can adapt a lot of software from Ocamel.

I think this John Hughes paper Global Variables in Haskell might be usefull 
to you: http://www.math.chalmers.se/~rjmh/Globals.ps


 But the gnawing question remains: Shall it be possible to be almost as
 efficient (in native code) as Ocamel's code, I refer here to Doug Bagley's
 comparison of programming languages. Remarkably the fibonacci numbers test
 scores almost as well. But the code is not the same. Comparable code would
 have been to use the same code of Ocamel, to be more specific: how
 efficiently is recusivity implemented in Haskell. I cannot compare this on
 my Windows XP since I need MSVC6.0 on this machine which I don't have. On
 the other hand I have cygwin installed now. Unfortunately I can't make
 makefiles. Probably on the web I can find an explanation. In this way I can
 recompile Ocamel with Cygwin and compare the results a bit.
 There are also 5(?) failures of Haskell programms . Is there a flaw in
 these programms?
 P.S. does anyone know a good Haskell  IDE for Windows XP?

I don't really use windows but I know there is support for the windows version 
of JCreator: http://www.students.cs.uu.nl/people/rjchaaft/JCreator/

You can always use Xemacs :)
http://www.xemacs.org/Download/win32/
http://www.haskell.org/haskell-mode/

J.A.
___
Haskell-Cafe mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell-cafe



Re: A problem with haskell-mode

2002-09-06 Thread Jorge Adriano

 Hi, all, I installed the latest version of Haskell mode for emacs.
 Whenever I load haskell major mode by opening a haskell file, Xemacs gives
 me the following error message:

 (1) (error/warning) Error in `post-command-hook' (setting hook to nil):
 (void-variable imenu--index-alist)

 My Xemacs version is 21.4.8. It works well under GNU emacs though. Anybody
 has an idea how to get around it? Thanks.

 Deling



I had the same problem, and I found a fix somewhere. 
Don't reember what exactly I had to change so I'll just send you my Haskell 
section of xemacs init.el.

By the way I get an error whenever I type undefined. Anyone else noticed it?
(1) (error/warning) Error in `post-command-hook' (setting hook to nil): 
(wrong-type-argument listp a )

J.A.

---
(setq load-path (cons /usr/share/emacs/site-lisp/haskell-mode-1.41 
load-path))

(setq auto-mode-alist
  (append auto-mode-alist
  '((\\.[hg]s$  . haskell-mode)
(\\.hi$ . haskell-mode)
(\\.l[hg]s$ . literate-haskell-mode

(autoload 'haskell-mode haskell-mode
  Major mode for editing Haskell scripts. t)
(autoload 'literate-haskell-mode haskell-mode
  Major mode for editing literate Haskell scripts. t)


;(add-hook 'haskell-mode-hook 'turn-on-haskell-ghc)
(add-hook 'haskell-mode-hook 'turn-on-haskell-font-lock)
(add-hook 'haskell-mode-hook 'turn-on-haskell-decl-scan)

(require 'imenu)
(add-hook 'haskell-mode-hook 'turn-on-haskell-doc-mode)
(add-hook 'haskell-mode-hook 'turn-on-haskell-indent)

;(add-hook 'haskell-mode-hook 'turn-on-haskell-simple-indent)
;(add-hook 'haskell-mode-hook 'turn-on-haskell-hugs)


___
Haskell-Cafe mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell-cafe



Re: Docs missing?

2002-07-24 Thread Jorge Adriano


 The doc RPM package for Red Hat 7.3 suffers the same problem as the
 SuSE one.  Could someone please give a hand-holding guide so that we
 can fix it ourselves?  Please?  Please?

It's easy ;)
Go to http://haskell.cs.yale.edu/ghc/documentation.html and in the 
downloadable/printable documentation section you'll find tar.gzs with the 
HTML files missing. Just untar/gunzip them in the appropriate dir (the on 
that contains the main index.html file)

J.A.
___
Glasgow-haskell-users mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users



Re: DeepSeq

2002-07-19 Thread Jorge Adriano

On Friday 19 July 2002 12:10, George Russell wrote:
 Would it be possible to bring the DeepSeq library into the libraries
 distributed with GHC?  (I think Dean Herington is responsible for it.)

 Of course it's easy enough to drop it into one's own program (I am just
 about to do this) but
 (1) It is fairly common to want to force deeper evaluation.
 (2) DeepSeq is simple enough to be dropped in the GHC distribution, without
 it causing much trouble or making it much bigger.
 (3) At the same time, it is not so simple that it can be reimplemented in a
 couple of lines.

Agree. 
Beeing able to derive instances of DeepSeq would be nice too.

J.A.
___
Glasgow-haskell-users mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users



Re: State monads don't respect the monad laws in Haskell

2002-05-14 Thread Jorge Adriano


 One may ask the question: what is seq useful for not in conjunction with
 unsafePerformIO, other than efficiency.  That, I don't know the answer to.

Here is an example.

 main::IO()
 main=do
  time1 - getCPUTime
  w - return $! calcSomething
  time2 - getCPUTime
...

J.A.

___
Haskell mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell



Re: SUGGESTION: haskell-announce mailing list

2002-05-11 Thread Jorge Adriano

On Saturday 11 May 2002 11:41, Jose Romildo Malaquias wrote:
  I Would also be moderately in favor of merging the haskell and
  haskell-cafe lists back into one, mainly because I always felt the
  distinction was somewhat arbitrary, who knows what discussions will turn
  out to be too long or have interesting tangents until it is too late and
  everyone has said everything on haskell? but this is a different issue.
  I wonder how many addresses are on haskell and not haskell-cafe or vice
  versa.

 I am in favor of both sugestions.

I like the actual haskell/haskell-cafe situation.
J.A.
___
Haskell mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell



Re: updating labelled fields

2002-05-07 Thread Jorge Adriano

On Tuesday 07 May 2002 02:07, John Meacham wrote:
 DrIFT which i am now maintaining can derive such utility functions out
 of the box. just add a {-!deriving: update -} to get update functions
 for every labeled field in a datatype. quite useful, I have not updated
 the web page yet, but the new DrIFT homepage will be at

 http://homer.netmar.com/~john/computer/haskell/DrIFT/

Very nice :)
I'll check it out.

J.A.
___
Haskell mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell



Re: updating labelled fields

2002-05-06 Thread Jorge Adriano


 I often create structures like:
 data MyData = MyData { foo :: ..., bar :: ...,  }
That makes 2 of us :-)

 and most of the time i do one of two things:
   1) read values from the structure, as in:
  let x = (foo myData) in ...
   2) update values in the structure, as in:
  let myData' = myData { foo = (foo myData)+1 }

1) 
I've used datatypes with labeled fields mostly to pass around implicit values.
If that is your case then there is a way around it.

Declare the datatype as 
 data MyData = MyData { foo_ :: fooType, bar_ :: ...,  }

and then declare
 foo :: (?implicitdata :: MyData)= fooType
 foo = foo_ ?yourdata

So when you work in a contex that depends on some implicit data you can just 
use foo. I've used this *a lot* lately.


2)
Yes. My method now is declaring set and apply functions to every field of my 
data structure.
fooAp f ni=ni{foo=f(foo ni)}
fooSet x = fooAp (const x)



 Only very rarely (usually only during intializization) do I actually put
 values into the structure that *don't* depend on their previous value.  I
 end up with expresions like:

 ... myData { foo = (foo myData) + 1 ;
  bar = (bar myData) ++ bar ;
  ick = (ick myData) ! n ; ... }

Yeap quite ugly isn't it?  :-)


 I was wondering if there existed any sort of update syntax.  Obviously
Nope, not that I know of. 

 not real update, but enough to get rid of the (foo myData) parts of my
 epxression which really serve to just clutter up with expression.  Perhaps
 something like:

 ... myData { foo - (+1) ; bar - (++bar) ; ick - (!n) ; ... }

Yes looks nice, thought about something like that before too.

 or the like, where x { ... y - e ... } is translated to x { ... y = e
 (y x) ... }  (i only use - because that seems to be the default
 extension symbol, i guess because we don't want to trample symbols people
 might actually use.)

Anyway I'd prefer to have some way to 'derive' apply and set functions.
Something like 
 data MyData = MyData { foo :: fooType, bar :: ...,  }
  deriving (Set, Apply)

Using the keyword deriving would probably be a bad idea though :)
The set and apply functions could be derived with a standard postfix or maybe 
prefix... fooAp or apFoo.
Maybe we could introduce sintax to specify it...
 deriving (Set with set, Apply with ap)

I don't know... I'm just brainstorming right now.
Having actual functions is important. I don't think I have to explain why to 
people in this mailing list :-)

 Anyway, does such a thing exist, and, if not, is there any chance it could
 exist, or is it just syntactic salt to too many people? :)
I whish you better luck than I've had so far whenever making posts about this 
same issue ;)

J.A.

___
Haskell mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell



Re: updating labelled fields

2002-05-06 Thread Jorge Adriano

On Monday 06 May 2002 23:28, Hal Daume III wrote:
 I wouldn't at all mind making this addition if I had a sense that it would
 actually be accepted and that people weren't going to go crazy over the
 syntax.  Would something like - be preferred or something like $=?

I'd still prefer having some way to automaticly derive 'apply' functions.
There is already nice syntax for setting a field value and I always end up 
defining 'set' functions to each and every field because I want to pass them 
as arguments. 

Imagine you have an STRef to a labeled datatype, lets call it stdata.  
You want to apply some function g to field foo of that structure.
 modifySTRef (fooAp g) stdata

Changing its value to x
 modifySTRef (fooSet x) stdata

With syntatic sugar only you'd have to read the reference, apply the function 
to the field and then update it. 

IMO, 'set field' and 'apply to field' functions are as usefull as the 'field 
projection' functions that are derived from the definition of the labeled 
datatype. Anyway I agree that it would be nice to have special syntax for 
updates. I'll use it if I have it available. 

On Monday 06 May 2002 23:42, David Feuer wrote:
 Why not $= ?
Yeap very nice in deed. I'd vote for this one.

J.A.
___
Haskell mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell



Re: Syntax highlighting for KDE's Kate

2002-05-05 Thread Jorge Adriano


 Dear KDE users,

 I've hacked syntax highlighting files for Kate, KDE's editor.
 Feel free to use or to modify them.

   http://www.informatik.uni-bonn.de/~ralf/software.html#syntax

Great!
To bad the literate haskell mode doesn't work with the LaTeX kind of literate 
programming - \begin{code} ... \end{code} - that's how I've been coding all 
my haskell programs lately :)
I'll probably hack it myself if/when I have the time.


J.A.


___
Haskell mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell



Re: Read File

2002-05-01 Thread Jorge Adriano


-
[moving to haskell-cafe]

  I want to read some data from a text file. I accomplished it but I want to
 read data from file as a Integer list for example text file has [1,2,3,5]
-
Wait you actually have [1,2,3,5]

-
 and when I read this data from file  I handeled it as string. What can I do
 to get it as integer list.

Hint:
map read [1,2,3]  ::[Int]
---

this would be helpfull if you had 1 2 3 5.
It's easier then

Hint:
read [1,2,3,5]::[Int]

J.A.
___
Haskell-Cafe mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell-cafe



Re: order of computation in 'do' notation

2002-04-25 Thread Jorge Adriano

NOTE: Even the examples are correct in the H98 libraries documentation in the 
IO module section, they are incorrect in the H98 Report:
http://www.haskell.org/onlinereport/io-13.html
Scroll down, to 7.2. 


snip
 when I put the same code through ghc, it waits for a command first, and
 then when the command has been entered it displays the prompt, which is
 just silly.  Surely the 'do' notation was designed to sequence
 computations, but it obviously isn't behaving quite right here!

The problem is that stdout is buffered by default and *not flushed when you're 
waiting for input in stdin*, IMO it should be. IIRC this was a change that 
happened between the somwhere between 5.00.1 and  5.02.2. I remember suddenly 
all my programs not working correctly anymore...

 I'd be very grateful for any suggestions as to how to fix this.
 thanks,
One way is to *import IO*  and  set stdout to NoBuffering

 mainLoop :: IO TRS - IO ()
 mainLoop t = do putStr \n 
 hSetBuffering stdout NoBuffering   -- HERE!!!
 (c,a) - getCommand 0
 case c of
help - do putStr help
 mainLoop t
load - do trs - load a
 putStr 
 mainLoop (return trs)
show - ...and so on...

You may also flush stdout every time you want using hflush.
Check the haskell libraries documentation for the IO module for more info.

J.A.


___
Glasgow-haskell-users mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users



Re: defining (- Bool) as a set

2002-04-22 Thread Jorge Adriano

On Monday 22 April 2002 23:31, Hal Daume III wrote:
 I'd like to be able to define something like

 instance Eq a = Coll (- Bool) a where
   empty= \_ - False
   single x = \y - if x == y then True else False
   union a b = \x - a x || b x
   insert s x = \y - x == y || s y

 and the like

 However, this seems to be impossible.  Is this the type lambda restriction
 that's been discussed recently on the mailing list?

  - Hal

Hi Hal, 
I'd do it like this, hope it helps.
--
module Test where

newtype  BinClass a = BC (a-Bool)


class  Coll c a where
  empty  :: c a
  single :: a-c a
  union  :: c a-c a-c a
  insert :: c a-a-c a

instance Eq a = Coll BinClass a where
empty= BC(\_-True)
single x = BC(\y - if x == y then True else False)
union  (BC a) (BC b) = BC(\x - a x || b x)
insert (BC s) x  = BC(\y - x == y || s y)




___
Haskell mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell



Re: defining (- Bool) as a set

2002-04-22 Thread Jorge Adriano


 class Collection e ce | ce - e where
 empty :: ce
 insert :: e - ce - ce
 member :: e - ce - Bool

 instance Eq a = Collection a (a - Bool) where
 empty = (\x - False)
 insert e f = (\x - if x == e then True else f x)
 member e f = f e

This is way better than my solution... 

I had never used multi-parameter classes before, so I forgot the functional 
dependency (right name? the |ce-e), and there was obviously no need for my 
extra constructor.

J.A.
___
Haskell mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell



Bugs?

2002-04-17 Thread Jorge Adriano

I've sent this msg to the ghc main mailing list, but this one is more 
adequate. I've tried this with both ghc 5.02.3/5.02.2, SuSE RPMs.
Thanks in advance,
J.A.

---
[1] Bug1?
This declaration:
 data A = (,) Int Int
is accepted by ghci. Is this behaveour correct,
1. It kind of shadows (,) is defined in PrelTup meaning that you can no longer 
use (,) prefix to refer to tuples - like (,) 1 2.
2. Seems to me like (,) is not correct syntax for a consym as defined in the 
H98 Report so we shouldn't be able to redefine it.

Note: didn't check any other interpreter/compiler.


[2] Bug2?
- Step 1
Load this in ghci,
---
module Test where
data C = C ((,) Int Int)

data A = (,) !Int !Int 
h :: A
h =  (,) 1 2

{-
f :: C
f = C ((,) 3 4)
-}

- Step 2
Uncomment the f function. (you'll get an error)

- Step 3
To get rid of the error comment out the 'data A' declaration and function 'h'.

Now you should get this error message:
-
Failed to find interface decl for `Teste.A'
from module `Teste'
-
Quiting ghci and then reloading the file works fine.

J.A.



___
Glasgow-haskell-bugs mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/glasgow-haskell-bugs



Re: Bug?

2002-04-17 Thread Jorge Adriano

On Wednesday 17 April 2002 03:15, Jorge Adriano wrote:
 [1] Bug1?
 This declaration:
  A = (,) Int Int


Opsss cut and paste problems :)
 data A = (,) Int Int
 is accepted by ghci. Is this behaveour correct,


This is what I meant.
Anyway in Bug 2 I used the 'correct' declaration

 [2] Bug2?
 - Step 1
 Load this in ghci,
 ---
 module Test where
 data C = C ((,) Int Int)

 data A = (,) !Int !Int --   --- There it is
snip

J.A.

___
Glasgow-haskell-users mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users



Re: Bug?

2002-04-17 Thread Jorge Adriano

On Wednesday 17 April 2002 03:15, Jorge Adriano wrote:
 [1] Bug1?
 This declaration:
  A = (,) Int Int


Opsss cut and paste problems :)
 data A = (,) Int Int
 is accepted by ghci. Is this behaveour correct,


This is what I meant.
Anyway in Bug 2 I used the 'correct' declaration

 [2] Bug2?
 - Step 1
 Load this in ghci,
 ---
 module Test where
 data C = C ((,) Int Int)

 data A = (,) !Int !Int --   --- There it is
snip

J.A.

___
Haskell mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell



Bug?

2002-04-16 Thread Jorge Adriano


[1] Bug1?
This declaration:
 A = (,) Int Int
is accepted by ghci. Is this behaveour correct,
1. It kind of shadows (,) is defined in PrelTup meaning that you can no longer 
use (,) prefix to refer to tuples - like (,) 1 2.
2. Seems to me like (,) is not correct syntax for a consym as defined in the 
H98 Report so we shouldn't be able to redefine it.

Note: didn't check any other interpreter/compiler.


[2] Bug2?
- Step 1
Load this in ghci,
---
module Test where
data C = C ((,) Int Int)

data A = (,) !Int !Int 
h :: A
h =  (,) 1 2

{-
f :: C
f = C ((,) 3 4)
-}

- Step 2
Uncomment the f function. (you'll get an error function)

- Step 3
To get rid of the error comment out the 'data A' declaration and function 'h'.

Now you should get this error message:
-
Failed to find interface decl for `Teste.A'
from module `Teste'
-


[3] Strict Pairs question
I really miss them :-)
I know I can do something like

data A a b= A !a !b
But then you can't use zips fst etc etc...
One possible solution would be to add some Class Pair, with default instances 
for these functions. Is this a bad idea for any particular reason?

It would also be nice to be able to generalize the idea syntatic sugar for 
standar tuples and be able to define constructors like, say
(:,:) and (#:, , :#) etc. Is this feasable?


J.A.







___
Glasgow-haskell-users mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users



Bug?

2002-04-16 Thread Jorge Adriano


[1] Bug1?
This declaration:
 A = (,) Int Int
is accepted by ghci. Is this behaveour correct,
1. It kind of shadows (,) is defined in PrelTup meaning that you can no longer 
use (,) prefix to refer to tuples - like (,) 1 2.
2. Seems to me like (,) is not correct syntax for a consym as defined in the 
H98 Report so we shouldn't be able to redefine it.

Note: didn't check any other interpreter/compiler.


[2] Bug2?
- Step 1
Load this in ghci,
---
module Test where
data C = C ((,) Int Int)

data A = (,) !Int !Int 
h :: A
h =  (,) 1 2

{-
f :: C
f = C ((,) 3 4)
-}

- Step 2
Uncomment the f function. (you'll get an error function)

- Step 3
To get rid of the error comment out the 'data A' declaration and function 'h'.

Now you should get this error message:
-
Failed to find interface decl for `Teste.A'
from module `Teste'
-


[3] Strict Pairs question
I really miss them :-)
I know I can do something like

data A a b= A !a !b
But then you can't use zips fst etc etc...
One possible solution would be to add some Class Pair, with default instances 
for these functions. Is this a bad idea for any particular reason?

It would also be nice to be able to generalize the idea syntatic sugar for 
standar tuples and be able to define constructors like, say
(:,:) and (#:, , :#) etc. Is this feasable?


J.A.







___
Haskell mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell



Re: about downloading

2002-04-14 Thread Jorge Adriano

On Sunday 14 April 2002 17:34, julie madec wrote:
 where can I download a version of Haskell? Thank you

http://www.haskell.org/implementations.html
J.A.
___
Haskell mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell



Re: GHC 5.02.3, SuSE rpms

2002-04-09 Thread Jorge Adriano

On Tuesday 09 April 2002 08:38, Ralf Hinze wrote:
 I've uploaded SuSE 7.3 rpms for the patchlevel release of the Glasgow
 Haskell Compiler (GHC), version 5.02.3.

   http://www.informatik.uni-bonn.de/~ralf/ghc-5.02.3-1.src.rpm
   http://www.informatik.uni-bonn.de/~ralf/ghc-5.02.3-1.i386.rpm
   http://www.informatik.uni-bonn.de/~ralf/ghc-prof-5.02.3-1.i386.rpm

 Enjoy, Ralf

Thanks for maintaning the Ghc SuSE Rpms :)
Is there any chance to make this available in SuSEs ftp server?
I ask this becouse it would be nice to have ghc ugrades listed in YOU (Yast 
Online Update) and apt (there is already apt for SuSE, I'm using it and it is 
great). This way every SuSE users of ghc would be able to keep their ghc 
version up to date easily even if they're not on haskell mailing lists. 

Thanks,
J.A.
___
Glasgow-haskell-users mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users



Re: I need some help

2002-03-26 Thread Jorge Adriano

[Obs: moving to haskell cafe]
[beware, huge answer follows]

 Hello
   I am writing a whole program which is analyz a elegtromagnetic wave. This
 is ok but in the program I use a lot of constant for example pi,epsilon
 etc. I want to ask that
   how I use a constant in Haskell ?

Defining constants it's easy, examples.
-- with no type signature
epsilon = 3.1

-- with explicit type signature
epsilon2 :: Double
epsilon2 = 3.1
 
-- specifying the type but no type signature
epsilon3 = 3.1 :: Double
 
(by the way, wouldn't it make sense not to get a warning about missing type 
signature in this last case. I know there is no signature there but still...)


 However the user of the program give some argument then program is
 starting. And I want to use this arguments for example at the end of the
 program. What will I do.
Good question. I've had a bad time with this, some in this list proably got 
tired of me saying the same thing over and over again... those of you might 
want to skip the rest of my mail :-)

If you want the user to be able to chose those values, then they are NOT 
constants, period. Yes their values won't chnage during the rest of the 
algorithm, but that doesn't makes it constants, so you can't declare them 
that way.

What *can* you do.
1. One *awfull* option is to pass thos values as arguments to all your 
functions. Yes signatures will get monstruous, it will complicate the 
developing process etc,

2. Instead of passing all those variables, group them in a record - data type 
with named fields - and pass that record arround.
(http://www.haskell.org/onlinereport/exps.html#sect3.15)
Signatures will get better. It's kind of weird though, to always have to pass 
around that record. Things can get quite messy, IMO.
-- foo
f :: Double - Double - Double
f x y = eta*x - epsilon^2*y

-- foo2
f :: Options - Double - Double - Double
f opt x y = (eta opt)* (epsilon opt)^2*y

And this is just a very simple example, it can get much worst. 

3. Implicit parameters. (At least in Ghc, what about others?)
Now this is the closest to an elegant solution. 
*Read both*: 
http://citeseer.nj.nec.com/246042.html
http://www.cs.chalmers.se/~rjmh/Globals.ps


f :: (?eta::Double, ?epsilon::Double)= Double - Double - Double
f x y = ?eta*x - ?epsilon^2*y

Now you don't have to specify eta and epsilon in the type signature itself, 
but in the context - no passing around extra (not natural) parameters. It 
makes an huge diference IMO when developing your algorithms. 


Still signatures wil get even bigger than if you just passed them as 
parameters, you can't even type the context like: (?eta, ?epsilon::Double)
So that is just awfull!

Once again records will help.
f :: (?opt::Options)= Double - Double - Double
f x y = (eta ?opt) *x - (epsilon ?opt)^2*y


It still lokes quite bad. I *hate* the field projection functions, and I hate 
the '?'!! So you could simply rename you data opt fields and declare,

eta :: (?opt:: Options) = Double
eta = etaF ?opt

epsilon :: (?opt:: Options) = Double
epsilon = epsilonF ?opt

Now f could be written like:
f :: (?opt::Options)= Double - Double - Double
f x y = eta*x - epsilon^2*y

Which differs from the first f function only in the context.
It is *almost* good enough for me :-)
Why the almost? you ask... 

Well, implicit parameters are not only non-standard features, but also 
experimental features (right?), so you they can change anytime.
--
NOTE: some of you might wanna quit reading here, I keep complaining about 
this stuff, you are probably tired of it :-)
--

In a couple of days you will also want to use more than one record, because 
grouping certain constants together doesn't feel right, and contexts will get 
bigger.
Also, you will want to use global variables and instead of a record you will 
use an STRef to a record, and very small signatures will have in they're 
context something like: (?opt :: STRef s Opt). And then you will need to 
update some option fields, and you will want to use modifySTRef, and you will 
need to create an applyField function to every damn field of the record...
So you will start asking
1. (when) will we have implicit contexts available? 
2. wouldn't it be good to have, besides the data projection functions, some 
update  and apply field functions, automaticly derived when declaring the 
data type? [yes am actually *asking* if *anyone agrees* with me? haven't had 
any feedback on this one, so I don't no wether it is a good or just plain 
dumb idea]

IMVHO, it is of extreme importance and *urgent* to get implicit parameters 
right. This question about how to use this 'user difined constants' is a 
*simple* question and should have a *very simple* and standard answer.
The same goes to global variables. We need them in certain situations and it 
is supposed to be, and it can be from my 

Re: first-class modules

2002-03-26 Thread Jorge Adriano

 On Tuesday 26 March 2002 17:31, you wrote:
 A number of people have discussed the use of implicit parameters to
 mimic global variables in Haskell.  I am wondering if any have done the
 same for a first-class module system such as that proposed by Shields
 and Jones.  It seems to make a tremendous amount of sense to do it that
 way:

 1.  semi-constant values:  Things that are calculated or input at the
 beginning of the program could be handled by Main.main, which would pass
 the results to the Second module, whose main function it could then
 call.  This seems much more natural than the implicit parameter approach
 for this purpose.


It seems nice for that *specific* purpose. What I like about implicit 
parameters is the fact that they are a more general approach, and that is IMO 
very important.
You, might for instance, decide that maybe it would be a good idea to, under 
certain specific conditions, change one of those semi-constant values.
Imagine some AI algortithm, you iterate some learning function 'learnF' over 
and over again. Now you realize that under certain conditions maybe the 
learning rate (used in learnF) should be changed. 
Chaging your implementation would be easy with implicit parameters. 
J.A.

___
Haskell mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell



Re: I need some help

2002-03-26 Thread Jorge Adriano


  However the user of the program give some argument then program is
  starting. And I want to use this arguments for example at the end of the
  program. What will I do.

 Good question. I've had a bad time with this, some in this list proably got
 tired of me saying the same thing over and over again... those of you might
 want to skip the rest of my mail :-)

huh? what is this line doing here.. I thought I had cut/pasted it below, 
but instead I copy/pasted it (then changed it). Most of the is pretty 
readble, I just complain about stuff in the last part of the e-mail :-)

J.A.

___
Haskell-Cafe mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell-cafe



literate haskell (again)

2002-03-22 Thread Jorge Adriano

Tried using Andrew Cookes haskell.sty and liked it a lot, but seems like the 
(X)emacs haskell mode doesn't support the \begin{code} \end{code}  literate 
programming style, just the one where code is preceded by ' '.

Anyone has got an hack available for this?
J.A.
___
Haskell-Cafe mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell-cafe



Re: literate haskell (again)

2002-03-22 Thread Jorge Adriano

On Friday 22 March 2002 16:31, you wrote:
 Jorge Adriano [EMAIL PROTECTED] writes:
  Tried using Andrew Cookes haskell.sty and liked it a lot, but seems like
  the (X)emacs haskell mode doesn't support the \begin{code} \end{code} 
  literate programming style, just the one where code is preceded by ' '.
 
  Anyone has got an hack available for this?

 According to my haskell-mode.el:
(...)
 So you probably want to change this as per the instructions.

Seems like it was not a .emacs (in fact .init.el here) problem. 
I just noticed that if you got to add a line break *right after* the 
\begin{code}
and right after the 
\end{code}
If you add a space after the '{code}' it will not toggle comment/code modes.

Where should I report this bug?

Since I'm on haskell-mode bugs, when typing undefined in xemacs I get
(1) (error/warning) Error in `post-command-hook' (setting hook to nil): 
(wrong-type-argument listp a )

Thanks,
J.A.
___
Haskell-Cafe mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell-cafe



literal haskell mode (nice :)

2002-03-22 Thread Jorge Adriano

I got some tips from some people at #xemacs in openprojects.org and cam up 
with the file in attachment. I know nothing about e-lisp so beware!!

I just have one major problem now. I wanted it to load x-symbol instead of 
just LaTeX mode (and x-symbol-fontify after loading the mode). If anyone can 
do that I'd be really gratefull :-)

J.A.
P.S.: put the attached file in the directory wher you have the .el and add 
to you ~/.emacs (or ~/.xemacs/init.el), (require 'two-mode-mode).

(I think :)





;; two-mode-mode.el -- switches between tcl and sgml(html) modes
;; $Id: two-mode-mode.el,v 1.3 2001/12/12 16:18:53 davidw Exp $

;; two-mode-mode.el is Copyright David Welton [EMAIL PROTECTED]
;; 1999, 2000, 2001

;; two-mode-mode.el may be distributed under the terms of the Apache
;; Software License, Version 1.1

;; As I'm sure is painfully obvious, I don't know much about elisp,
;; but I thought it would be cool to do this mode, for mod_dtcl.  So
;; if you have any comments or suggestions, please email me!

;; These same concepts could be used to do a number of neat 2-mode
;; modes, for things like PHP, or anything else where you have a
;; couple of modes you'd like to use.

;; Use of 'psgml-mode' is highly recommended.  It is, of course, a
;; part of Debian GNU/Linux.

;; Modified by Marco Pantaleoni [EMAIL PROTECTED]
;; to allow execution of an hook on mode switching.
;; Also added a standard mode hook and some documentation strings.

;; Modified by Jorge Adriano [EMAIL PROTECTED]
;; to work with LaTeX and Literate Haskell modes instead of HTML/PHP
;; WARNING: I don't really know what I'm doing here... :-)
;; changes: 1. changed ? to \\begin{code} (and similar with ?
;;  2. changed (turn-on-font-lock-if-enabled)
;; to  (font-lock-default-fontify-buffer)
;; the 1st one caused an error msg with my xemacs version
;; I thought that was the appropriate xemacs command
;;
;; If anyone can change this in order to load x-symbol and fontify it
;; instead of just LaTeX mode, please send the patch to me :-)


;; configure these:
(defvar two-mode-lmatch \\begin{code}
  Open tag for `second' mode.)
(defvar two-mode-rmatch \\end{code}
  Close tag for `second' mode.)

(defvar default-mode (list 'LaTeX-mode LaTeX)
  Default mode.)
(defvar second-mode  (list 'literate-haskell-mode Haskell)
  Second mode: mode used inside special tags.)
;; 

(defvar two-mode-update 0)
(defvar two-mode-mode-idle-timer nil)
(defvar two-mode-bool nil)
(defvar two-mode-mode-delay (/ (float 1) (float 8)))

;; Two mode hook
(defvar two-mode-hook nil
  *Hook called by `two-mode'.)
(setq two-mode-hook nil)

;; Mode switching hook
(defvar two-mode-switch-hook nil
  *Hook called upon mode switching.)
(setq two-mode-switch-hook nil)

(defun two-mode-mode-setup ()
  (make-local-hook 'post-command-hook)
  (add-hook 'post-command-hook 'two-mode-mode-need-update nil t)
  (make-local-variable 'minor-mode-alist)
  (make-local-variable 'two-mode-bool)
  (setq two-mode-bool t)
  (when two-mode-mode-idle-timer
(cancel-timer two-mode-mode-idle-timer))
  (setq two-mode-mode-idle-timer (run-with-idle-timer two-mode-mode-delay t 
'two-mode-mode-update-mode))
  (or (assq 'two-mode-bool minor-mode-alist)
  (setq minor-mode-alist
(cons '(two-mode-bool  two-mode) minor-mode-alist

(defun two-mode-mode-need-update ()
  (setq two-mode-update 1))

(defun two-mode-change-mode (to-mode)
  (if (string= to-mode mode-name)
  t
(progn
  (save-excursion
(if (string= to-mode (cadr second-mode))
(funcall (car second-mode))
(funcall (car default-mode
  (two-mode-mode-setup)
  (if two-mode-switch-hook
  (run-hooks 'two-mode-switch-hook))
  (if (eq font-lock-mode t)
  (font-lock-fontify-buffer))
  (font-lock-default-fontify-buffer

(defun two-mode-mode-update-mode ()
  (when (and two-mode-bool two-mode-update)
(setq two-mode-update 0)
(let ((lm -1)
  (rm -1))
  (save-excursion
(if (search-backward two-mode-lmatch nil t)
(setq lm (point))
  (setq lm -1)))
  (save-excursion
(if (search-backward two-mode-rmatch nil t)
(setq rm (point))
  (setq rm -1)))
  (if (and (= lm -1) (= rm -1))
  (two-mode-change-mode (cadr default-mode))
(if (= lm rm)
(two-mode-change-mode (cadr second-mode))
  (two-mode-change-mode (cadr default-mode)))

(defun two-mode-mode ()
  Turn on two-mode-mode
  (interactive)
  (funcall (car default-mode))
  (two-mode-mode-setup)
  (if two-mode-hook
 (run-hooks 'two-mode-hook)))

(provide 'two-mode-mode)




Re: literal haskell mode (nice :)

2002-03-22 Thread Jorge Adriano

On Friday 22 March 2002 23:27, Jorge Adriano wrote:
 I got some tips from some people at #xemacs in openprojects.org and cam up
 with the file in attachment. I know nothing about e-lisp so beware!!



Opss I forgot:
The original file is Copyrighted by David Welton and it is located here:
http://www.dedasys.com/freesoftware/
http://www.dedasys.com/freesoftware/files/two-mode-mode.el

J.A.
___
Haskell-Cafe mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell-cafe



Re: literal haskell mode (nice :)

2002-03-22 Thread Jorge Adriano

 I got some tips from some people at #xemacs in openprojects.org and cam up
 with the file in attachment. I know nothing about e-lisp so beware!!

Last e-mail today. Forgot to actually tell what was this for (need ti get 
some sleep :)... It's easy to guess by looking at the file anyway the idea is 
to change xemacs modes acording to context. I changed the orginal file to 
work with literate haskell + latex. It works (for me at least) with the 
\begin{code} \end{code} kind of lhs files.

J.A.
___
Haskell-Cafe mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell-cafe



Re: literate haskell

2002-03-21 Thread Jorge Adriano

Thanks for all your answers :-)
J.A.
___
Haskell-Cafe mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell-cafe



literate haskell

2002-03-20 Thread Jorge Adriano

Why is it necessary to leave a blank line between comments and code?
I'm using LaTeX  in my lhs files, with the code inside a verbatim 
environment, and I'd rather start writing my code right after the 
\begin{verbatim}.

I'd also like to know if anyone as changed is xemacs configuration file in 
such a way that is easy to change from haskell to LaTeX mode from within lhs 
files, and compile (latex compile) them.
I always have to change to latex mode, the change the syntax highlight, and 
even then I can't compile the from the included lhs files - it always calls 
view instead of compile, even if I specify the correct Master file.

Thanks in advance 
J.A.
___
Haskell-Cafe mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell-cafe



Re: pattern-matching with labelled types

2002-03-08 Thread Jorge Adriano

On Friday 08 March 2002 01:52, you wrote:
 Andre W B Furtado writes:
  | Of course, it is possible to do something like
  |
  |  update :: MyType - Int - MyType
  |  update mt newValue = MT {x = newValue, y = oldValue}
  |  where oldValue = y mt
  |
  | but this really annoys me when MyType has too many fields. Suggestions?

 update mt newValue = mt {x = newValue}

Since we are on the subject, I have some questions about labeled datatypes 
updates.
You can in deed update like that mt {x = newValue}, but whenever I use 
labeled datatypes I always end up with Andres problem, having to define not 
only an 'update' function but also an 'apply' function for every field.
I need them becouse I want to pass them as arguments to other funtions.

This happens to me all the time, but one very good example IMO is having a 
STRef to a labeled data type. Now you want to update some field and you want 
to to be able to use,
modifySTRef (updField1 3)
or
modifySTRef (appField1 (+1))

It would be extremely usefull IMO to have not only field projection funtions, 
but also apply and update funtions. That, and not beeing possible to specify 
contexts partialy, makes it particulary complicated for me to follow John 
Hughes strategy to simulate global variables in haskell 
(http://www.cs.chalmers.se/~rjmh/Globals.ps)

J.A.
___
Haskell mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell



Re: strange behavior with ghci version 5.02.2

2002-02-14 Thread Jorge Adriano

 After loading a module with

 :l Module

 you can't use the Prelude functions unqualified, you just get things
 like

 interactive:1: Variable not in scope: `show'

 I am pretty sure that this worked some days ago, and I was using the
 same version then.

 I feel totally confused. Has this happened to anyone else?

Yes, for some modules it happens for others it doesn't. Kind of strange.
SuSE 7.3 rpms here, v. 5.02.2
J.A.
___
Glasgow-haskell-users mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users



Re: Sendind mail

2002-02-13 Thread Jorge Adriano


 Hi,
I'd like to know if there's any Hugs compatible library with
 functionalities to send mail.

I don't think so. If all you want to do is send mail from within an haskell 
program why not just make system calls. I did something like that a long time 
ago. I've sent you the module in attachment.

(suposed to work in *nixes)
J.A.



 import System


Este ficheiro contem fucoes para eu enviar mails aos meus alunos
 type Mail = String


Mails das Turmas P3 e P4 - posso ter que alterar para filtrar alunos
 mails_P3 :: [Mail]
 mails_P3 =  [mp0 ++ show(n) ++ @mat.uc.pt | n - [301.. 336] ]

 mails_P4 :: [Mail]
 mails_P4 =  [mp0 ++ show(n) ++ @mat.uc.pt | n - [401.. 407] ]



Mails das minhas turmas Praticas
 mails_TP :: [Mail]
 mails_TP =  mails_P3 ++ mails_P4



Enviar mails:
 type Subject = String
 type Path= String
 type Message = String
 

Envia dados:
- Subject da mensagem
- Path do ficheiro com a mensagem 
- Endereco de e-mail

Envia o mail com subj. e mensagens dadas para o endereco.
 sendmail :: Subject - Path - Mail - IO ExitCode
 sendmail sub msgfile e_mail
 = do 
   --putStrLn(comando)
   system( comando ) 

   where comando = mail -s \ ++ sub ++\ ++ e_mail ++++ msgfile 


 send_to_list :: Subject - Path - [Mail] - IO [ExitCode]
 send_to_list sub msgfile e_mails
 = do
	sequence (map (sendmail sub msgfile) e_mails) 







Re: efficiency question

2002-02-11 Thread Jorge Adriano

On Monday 11 February 2002 02:10, Hal Daume III wrote:
 So instaed of storing 1 and 2 in the list, it stores pointers to
 them.  The reason it does this is so that it makes it easy to generate
 code for polymorhpic functions.  (,) being boxed means that instead of
 storing a pair of element, you're storing a pair of pointers.  That means
 you get worse performance because you have to chase more pointers.

 (at least that's my impression)
Thanks, I knew the concept but not the name.


On Sunday 10 February 2002 18:48, Kirsten Chevalier wrote:
 I'd guess that it's not just that you have to apply the (,) constructor --
 it also has to do with the fact that the tuples it's constructing here are
 boxed.
This brings another question to my mind, isn't it toupling a standard 
technique used in functional programming? I'm pretty sure I've seen it 
focused in some papers/text books.
I for one would not expect that folding the list twice would be more 
efficient...

J.A.
___
Glasgow-haskell-users mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users



Re: efficiency question

2002-02-10 Thread Jorge Adriano

On Sunday 10 February 2002 18:48, Kirsten Chevalier wrote:
 I'd guess that it's not just that you have to apply the (,) constructor --
 it also has to do with the fact that the tuples it's constructing here are
 boxed.

could you elaborate a little more on that (boxed / unboxed) or provide a link 
on the subject?

thanks
J.A.
___
Glasgow-haskell-users mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users



  1   2   >