Re: [Haskell-cafe] do notation strangeness

2007-12-08 Thread Ilya Tsindlekht
On Sat, Dec 08, 2007 at 02:59:16PM -0200, Felipe Lessa wrote:
 Hello!
 
 I see from 
 http://www.haskell.org/haskellwiki/Monads_as_computation#Do_notation
 that
 
 do { v - x ; stmts }
   = x = \v - do { stmts }
 
 However, look at this GHCi session:
 
 Prelude let return' = return :: a - Maybe a
 Prelude do {1 - return 1; return' ok}
 Just ok
 Prelude return 1 = \1 - return' ok
 Just ok
 Prelude do {1 - return 3; return' ok}
 Nothing
 Prelude return 3 = \1 - return' ok
 *** Exception: interactive:1:13-30: Non-exhaustive patterns in lambda
What seems confusing to you?

\1 - foo
is the same as
\x - case x of {1 - foo;}

When this function is evaluated with parameter different from 1, Haskell
fails to find matching pattern for x and exception occurs.
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] do notation strangeness

2007-12-08 Thread Ilya Tsindlekht
On Sat, Dec 08, 2007 at 03:28:58PM -0200, Felipe Lessa wrote:
 On Dec 8, 2007 3:12 PM, Ilya Tsindlekht [EMAIL PROTECTED] wrote:
  On Sat, Dec 08, 2007 at 02:59:16PM -0200, Felipe Lessa wrote:
   Prelude do {1 - return 3; return' ok}
   Nothing
   Prelude return 3 = \1 - return' ok
   *** Exception: interactive:1:13-30: Non-exhaustive patterns in lambda
  What seems confusing to you?
 
  \1 - foo
  is the same as
  \x - case x of {1 - foo;}
 
  When this function is evaluated with parameter different from 1, Haskell
  fails to find matching pattern for x and exception occurs.
 
 The problem is that with the do notation it doesn't raise an
 exception. In the example you quoted,
Yes, I have already understood it from your reply to the original
poster.
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Israel Haskell Programmers

2007-09-16 Thread Ilya Tsindlekht
On Sun, Sep 16, 2007 at 06:11:03PM +0200, B K wrote:
 Hello,
 Are there any Haskell Hackers on this mailing list who live in Israel?
 I am interested in starting an Israel Haskell User Group.
I am here, although I probably do not really count for Haskell Hacker.
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Very simple parser

2007-07-04 Thread Ilya Tsindlekht
On Thu, Jul 05, 2007 at 12:58:06AM +1000, Alexis Hazell wrote:
 On Tuesday 03 July 2007 09:51, Arie Peterson wrote:
 
  No, there is a 'State s' monad provided (for arbitrary state type 's'),
  which implements the 'get' and 'put' methods. In other words, 'State s' is
  an instance of the 'MonadState s' class. This terminology can be really
  confusing at first.
 
  For now, you may forget about the MonadState class. Simply use 'get' 
  friends and everything will work fine.
 
 This may be a stupid question, but i don't understand how (indeed, if) one 
 can 
 maintain multiple states using the State monad, since 'get' etc. don't seem 
 to require that one specify which particular copy of a State monad one wishes 
 to 'get' from, 'put' to etc.? Does one have to use (say) a tuple or a list to 
 contain all the states, and when one wishes to change only one of those 
 states, pass that entire tuple or list to 'put' with one element changed and 
 the rest unchanged?
 
 
 Alexis.
A value of type 'State t' contains an incapsulated function can be
de-encapsulated using runState and when evaluated, performs the actual
computation. This function maintains state internally, so for each
invocation of this function (such functions from other values of type
'State t') state is preserved separately. 

Hope this clarifies your confusion.
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Haskell's

2007-07-03 Thread Ilya Tsindlekht
On Tue, Jul 03, 2007 at 10:53:33AM +, Peter Verswyvelen wrote:
 Ah, thanks for the correction. So if I understand it correctly, this is 
 currying:
 
 when
 
 f :: (a,b) - c
 
 then
 
 g :: a - (b,c)
g :: a-b-c
 
 is the curried form of f? So currying has to do with tuples? 
 
 And partial application is just leaving away some tail arguments?
 
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Redefining Disjunction

2007-06-13 Thread Ilya Tsindlekht
On Wed, Jun 13, 2007 at 02:37:37PM +0100, PR Stanley wrote:
 Hi
 Can you think of a fourth way of redefining disjunct using pattern matching?
 vee :: Bool - Bool - Bool
 vee _ True = True
 vee True _ = True
 vee _ _ = False
 
 ve :: Bool - Bool - Bool
 ve True True = True
 ve True False = True
 ve False True = True
 ve False False = False
 
 v :: Bool - Bool - Bool
 v True b = True
 v b True = True
 v b False = b
 v False b = b
 
Most obvious is
v :: Bool-Bool-Bool
v False False = False
v _ _ = True
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Finding points contained within a convex hull.

2007-06-06 Thread Ilya Tsindlekht
On Wed, Jun 06, 2007 at 12:23:03PM +1200, Daniel McAllansmith wrote:
 Hello.
 
 I've got a system of linear inequalities representing half-spaces.  The 
 half-spaces may or may not form a convex hull.
 
 I need to find the integral coordinates that are contained within the convex 
 hull, if there is one.
 
 For example, given
 0 = x = 4
 0 = y = 3
 0 = 2x - y
 0 = 1.2y - x
 
 I want the following (x,y) coordinates
 [(0,0),(1,1),(1,2),(2,2),(2,3),(3,3)]
 
 
 Anybody have any suggestions, or libraries, for solving this in many 
 dimensions and equations?
 
 
If I am not mistaken, this problem is called integer programming and it is 
NP-complete
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Newbie Q: Monad 'fail' and 'error'

2007-06-06 Thread Ilya Tsindlekht
On Wed, Jun 06, 2007 at 01:39:32PM +0400, Dmitri O.Kondratiev wrote:
 Monad class contains declaration
 
 *fail* :: String - m a
 
 and provides default implementation for 'fail' as:
 
 fail s = error s
 
 On the other hand Prelude defines:
 *
 error* :: String - a
 
 which stops execution and displays an error message.
 
 Questions:
 1) What value and type 'error' actually returns in:
 error some message ?
'a' here is a type variable, therefore 'error' is a polymorphic function
which can return value of any type.
 
 2) How declaration
 String - m a
 matches with
 String - a ?
as I said above, 'String-a' means that the return value can have any type.
'String- m a' means that return value may be of type 'm a' where 'a'
can be any type.
 
 3) In Maybe monad:
 fail = Nothing
'Nothing' is constructor which returns value of type 'Maybe a' where 'a'
is any type. 
 
 When and how 'fail' is used in Maybe monad?
Values of type 'Maybe a' can be either 'Just x' where x is value of type
'a' or 'Nothing'. The Maybe monad is used to represent computations
which may fail, 'Just x' represents successful computation yielding
value x, and 'Nothing' represents failing computation.
 
 Thanks!
 
 -- 
 Dmitri O. Kondratiev
 [EMAIL PROTECTED]
 http://www.geocities.com/dkondr

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

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


Re: [Haskell-cafe] standard function

2007-06-06 Thread Ilya Tsindlekht
On Wed, Jun 06, 2007 at 03:48:18PM +0200, Steffen Mazanek wrote:
 Hello,
 
 is there a function f::[a-b]-a-[b] in the libraries? Couldn't find one
 using
 hoogle although this seems to be quite a common thing...
 
 
 Steffen


Just to add to what others have said, yet another way to implement it is
to use list comprehension:

mapApply fs x = [f x | f - fs]
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] newbie question on Parsers from Programming In Haskell

2007-06-05 Thread Ilya Tsindlekht
On Mon, Jun 04, 2007 at 05:42:35PM +0300, Juozas Gaigalas wrote:
 Hello,
 
 I am a somewhat experienced programmer and a complete Haskell newbie, so I
 hope this is the correct ML for my question.
 
 I have decided to learn Haskell and started with  Graham Hutton's book.
 Everything was going nicely until section 8.4, on sequencing functional
 parsers. I am trying to write an elementary parser that produces the 1st and
 3d elements from a string. I am using the code from the book.
 
 -
 
 type Parser a = String - [(a, String)]
 
 return :: a - Parser a
 return v = \inp - [(v, inp)]
 
 failure :: Parser a
 failure = \inp - []
 
 
 item :: Parser Char
 item = \inp - case inp of
  [] - []
  (x:xs) - [(x, xs)]
 
 
 parse :: Parser a - String - [(a, String)]
 parse p inp = p inp
 
 
 (=) :: Parser a - (a - Parser b) - Parser b
 p = f = \inp - case parse p inp of
  [] - []
  [(v, out)] - parse (f v) out
 
 
 p :: Parser (Char, Char)
 p = do x - item
   item
   y - item
   return (x, y)  -- LINE 34
 
 
 BUT, when I try to :load parse.hs from hugs I get the following error:
 
 ERROR parse.hs:34 - Last generator in do {...} must be an expression
 
 
 I have no idea what I am doing wrong and why Hugs is complaining.  I hope
 this question is not too simply for this mailing list, but I have honestly
 googled for an answer and had found nothing.
 
 
If you wish to use 'do' notation with your parser, you must declare it
as an instance of Monad class.
 
 Juozas Gaigalas

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

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


Re: [Haskell-cafe] OK, so this VIM thing -- how do I make it actually work?

2007-06-05 Thread Ilya Tsindlekht
On Tue, Jun 05, 2007 at 10:41:44AM +0100, Rodrigo Queiro wrote:
 To back him up, it seems that the lhaskell.vim syntax highlighter is broken
 with Vim 7.1. Here, it is definitely using lhaskell.vim, but doesn't seem to
 be parsing the code in between \begin{code} and \end{code} as Haskell.
 
Works fine for me on Debian. The dpkg describes vim as:
ii  vim1:7.1-000+1Vi IMproved - enhanced vi editor
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Language extensions

2007-05-28 Thread Ilya Tsindlekht
On Sun, May 27, 2007 at 05:34:33PM -0400, Brandon S. Allbery KF8NH wrote:
 
 On May 27, 2007, at 17:23 , Andrew Coppin wrote:
 
 Personally, I try to avoid ever using list comprehensions. But  
 every now and then I discover an expression which is apparently not  
 expressible without them - which is odd, considering they're only  
 sugar...
 
 They are.  But they're sugar for monadic operations in the list  
 monad, so you have to use (=) and company to desugar them.  [x |  
 filter even x, x - [1..10]] becomes do { x - [1..10]; return  
 (filter even x) } becomes ([1..10] = return . filter even).
 
The list monad is easily defineable in pure Haskell, so one can do 
without monadic operation as well if one wishes to.
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Re: Debunking tail recursion

2007-05-19 Thread Ilya Tsindlekht
On Sat, May 19, 2007 at 04:10:29PM +0100, Jon Fairbairn wrote:
[...]
 
  foldl f z l = case l of
 (x:xs) - foldl f (f z x) xs
 [] - z
 
 which reveals that foldl in the RHS isn't really the
 leftmost outermost function, but case is -- the tail call is
 to case. It happens that case is a kind of function that
 makes a choice -- it returns one of its arguments but
 doesn't do anything more to it. In a strict language only
 some predefined operators like case and if have this
 property, but lazy languages allow the definition of new
 ones, which is why we need more care when thinking about
 tail calls.
By definition, tail recursive function is recursive function in which
the value returned from a recursive call is immediately returned without
modification as value of the top-level invocation, which is true for
foldl defined as above.
 
 -- 
 Jón Fairbairn [EMAIL PROTECTED]
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Re: Debunking tail recursion

2007-05-19 Thread Ilya Tsindlekht
On Sat, May 19, 2007 at 09:16:46PM +0100, Jon Fairbairn wrote:
 Ilya Tsindlekht [EMAIL PROTECTED] writes:
  By definition, tail recursive function is recursive function in which
  the value returned from a recursive call is immediately returned without
  modification as value of the top-level invocation, which is true for
  foldl defined as above.
 
 Sure. Did I say otherwise?
Sorry, I thought you were saying foldl is not tail-recursive. I must
have not read your message carefully enough, mea culpa.
 
 -- 
 Jón Fairbairn [EMAIL PROTECTED]
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] Re: Monad definition question

2007-05-05 Thread Ilya Tsindlekht
On Sat, May 05, 2007 at 12:09:03AM -0700, [EMAIL PROTECTED] wrote:
 
 Ilya Tsindlekht wrote:
  Does the definition of monad silently assume that if f and f' are equal
  in the sense that they return the same value for any argument o correct
  type then m = f = m = f'
 
 Of course NOT! Here's an example, in a State monad
 
   f  x = put True
   f' x = put False
 Clearly, _by the definition above_, f and f' are the same -- for any
 argument of correct type, they return the same value, namely,
They aren't - they return different values of type State Bool ()
 (). However, if we perform the observation
 
   execState (return 'a' = f) True
   execState (return 'a' = f') True
 
 we quite clearly see the difference. 
Of course - because f 'a' and f' 'a' are different values.
(return 'a' = f is by laws of monad the same as f 'a')
 
 Robin Green wrote:
  How could it be otherwise? How are you going to distinguish between f
  and f' if they are indistinguishable functions, in Haskell?
 
 Because f and f' are NOT referentially transparent functions. They are
 NOT pure functions, their application may have _an effect_. And
They ARE pure functions (just as all Haskell functions)
They return values of monad type. 
 comparing effectful computations is quite difficult. It's possible: I
 believe (bi)simulation is the best approach; there are other
 approaches.
 
 It may be useful to relate to imperative programming:
   m1 = (\x - m2)
 is
   let x = m1 in m2
The analogy is not always straight-forward - try the list monad.
 Indeed, monadic 'bind' is *exactly* equivalent to 'let' of 
 impure eager languages such as ML. The first monadic law
   return x = f === f x
 is trivial because in eager languages, any value (which is
 an effectful-free computation) is by default injected into the world of
 possibly effectful expressions: Any value is an expression. The second
 law   m = (\x - return x) === m 
 becomes
   let x = e in x  === e
 and the third law
   (m1 = (\x - m2)) = (\y - m3) === 
   m1 = (\x - m2 = \y - m3)   provided x is not free in m3
 becomes
   let y = (let x = m1 in m2) in m3 ===
   let x = m1 in let y = m2 in m3
 
 So, `bind' is `let' and monadic programming is equivalent to
 programming in the A-normal form. That is indeed all there is to
 monads.
 
 Here's the paragraph from the first page of Filinski's `Representing
 Monads' (POPL94)
 
 It is somewhat remarkable that monads have had no comparable impact on
 ``impure'' functional programming. Perhaps the main reason is that --
 as clearly observed by Moggi, but perhaps not as widely appreciated in
 the ``purely functional'' community -- the monadic framework is
 already built into the semantic core of eager functional languages
 with effects, and need not be expressed explicitly. ``Impure''
 constructs, both linguistic (e.g., updatable state, exceptions, or
 first-class continuations) and external to the language (I/O, OS
 interface, etc.), all obey a monadic discipline. The only aspect that
 would seem missing is the ability for programmers to use their own,
 application-specific monadic abstractions -- such as nondeterminism or
 parsers [31] -- with the same ease and naturality as built-in
 effects.
 
 Filinski then showed that the latter seemingly missing aspect
 indeed only appears to be missing.
Would this require some kind of macros doing extensive pre-processing
of the code?
 
 
 It is important to understand that once we come to monads, we lost
 referential transparency. Monadic code is more difficult to reason
 about -- as any imperative code. One often sees the slogan that
 Haskell is the best imperative language. And with monad, it is. One
 often forgets that 'best' here has the down-side. Haskell amplifies
 both advantages _and_ disadvantages of imperative programming. At
 least imperative programmers don't have to think about placing seq at
 the right place to make sure a file is read from before it is closed,
 and don't have to think about unsafeInterleaveIO. It seems the latter
 has become so indispensable that it is recommended to Haskell novices
 without a second thought. One may wonder if functional programming
 still matters.
 
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] Monad definition question

2007-05-04 Thread Ilya Tsindlekht
Does the definition of monad silently assume that if f and f' are equal
in the sense that they return the same value for any argument o correct
type then m = f = m = f'

More specifically, the definition says x = return = x. How does one
justify from this that x = (return . id) = x?

Are values of type a - b in general assumed to be maps from the set of
values of type a into the set ov values of type b? (What bothers me is
that the problem whether two lambda-expressions define the same map is
clearly undecidable.)

More generally, is some kind of logic without equality more appropriate
for formalisation of Haskell then the usual kind(s) of logic with
equality?
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe