RE: lazy comparison for equality ?

2002-04-24 Thread Konst Sushenko

In addition to what Hal said,

I think that even assuming that you want to write a function like that
that is only supposed to be applied to finite lists (like, say,
prelude's 'and' function, which does not terminate on an infinite list
of True values) you still cannot do it because haskell lists are not
like C lists.

There is no notion, to my understanding, of list circularity. There are
finite and infinite lists. Your example of a list that you call a
circular list is just a definition of a recursive function that produces
an infinite list.

So what you are almost asking is how to write a function that checks if
a list has repeated sub-sequences, which is not of course precisely the
same that you asked (because even a finite list can have repeated
sub-sequences), but close. And this is just one of many problems taken
care of by various string search algorithms.

konst

 -Original Message-
 From: Hal Daume III [mailto:[EMAIL PROTECTED]] 
 Sent: Wednesday, April 24, 2002 12:38 PM
 To: [EMAIL PROTECTED]
 Cc: [EMAIL PROTECTED]
 Subject: Re: lazy comparison for equality ?
 
 
 I don't think you can write such a function.  For instance, 
 how would you
 know whether [1..] is circular or not?  In order to know that it's not
 you'd need to evaluate it fully.
 
 --
 Hal Daume III
 
  Computer science is no more about computers| [EMAIL PROTECTED]
   than astronomy is about telescopes. -Dijkstra | www.isi.edu/~hdaume
 
 On Wed, 24 Apr 2002 [EMAIL PROTECTED] wrote:
 
  
  Hi -
  I'm a Haskell beginner and I have a problem. 
  
  Let's have a list which may be normal list
  list1 = [1,2,3]
  or a circular list
  list2 = 1:2:list2
  
  Now I'd like to have a function which tells me whether the 
  given list is circular or not. This doesn't work:
  
  circ l = l l
  circ2 l [] = False
  circ2 l (_:as) | l==as = True
 | True = (circ2 l as)
  
  
  It seems that comparison l==as really compares element by 
 element thus
  falling into an infinite loop. I would need to compare 
 pointers instead of
  values.
  
  Does anybody know how this could be done ?
  
  Thanks.
  
  
  
  
  
  ___
  Haskell-Cafe mailing list
  [EMAIL PROTECTED]
  http://www.haskell.org/mailman/listinfo/haskell-cafe
  
 
 ___
 Haskell-Cafe mailing list
 [EMAIL PROTECTED]
 http://www.haskell.org/mailman/listinfo/haskell-cafe
 
___
Haskell-Cafe mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell-cafe



RE: finding ....

2002-03-19 Thread Konst Sushenko

Moved to haskell café

I do not have a code example, but how about a system that compiles different (and say 
independent) software projects in parallel, and which uses the same code to create 
temporary files needed for compilation?

konst

 -Original Message-
 From: David Sankel [mailto:[EMAIL PROTECTED]] 
 Sent: Tuesday, March 19, 2002 6:38 PM
 To: Pixel; Lennart Augustsson
 Cc: [EMAIL PROTECTED]
 Subject: Re: finding 
 
 
 --- Pixel [EMAIL PROTECTED] wrote:
  Lennart Augustsson [EMAIL PROTECTED] writes:
  
Diego Yanivello wrote:

 hi,is there (in Haskell) a function like  
   existFile :: FilePath -
 IO (Bool) ? Thanks!
   
   Using such a function is generally a bad idea
  because of race conditions.
  
  however, real world programs use those tests since
  you don't need to care
  *everytime* about race conditions. (of course using
  this existFile before
  creating a temporary file is wrong, but existFile
  has *many* other
  applications)
 
 Could someone post an example of the creation of a
 temporary file where race conditions are important?
 
 Thanks,
 
 David J. Sankel
 
 __
 Do You Yahoo!?
 Yahoo! Sports - live college hoops coverage
 http://sports.yahoo.com/
 ___
 Haskell mailing list
 [EMAIL PROTECTED]
 http://www.haskell.org/mailman/listinfo/haskell
 
___
Haskell-Cafe mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell-cafe



RE: Hiring Haskell programmers

2002-03-11 Thread Konst Sushenko

I have always been wondering what exactly does quickly learn Haskell
mean? Quickly learn Haskell syntax? Can one learn how to paint quickly?

konst

 -Original Message-
 From: Eray Ozkural [mailto:[EMAIL PROTECTED]] 
 Sent: Monday, March 11, 2002 4:24 PM
 To: Mark Carroll; [EMAIL PROTECTED]
 Subject: Re: Hiring Haskell programmers
 
 
 -BEGIN PGP SIGNED MESSAGE-
 Hash: SHA1
 
 On Tuesday 12 March 2002 01:17, Mark Carroll wrote:
  How easy is it to hire reasonable Haskell programmers? Of 
 course, this may
  mean, hiring people with the aptitude and interest to quickly learn
  Haskell. Has anyone any experience of this that they can share?
 
 
 I know it's easy. Try me. ;)
 
 Sincerely,
 
 - -- 
 Eray Ozkural (exa) [EMAIL PROTECTED]
 Comp. Sci. Dept., Bilkent University, Ankara
 www: http://www.cs.bilkent.edu.tr/~erayo
 GPG public key fingerprint: 360C 852F 88B0 A745 F31B  EA0F 
 7C07 AE16 874D 539C
 -BEGIN PGP SIGNATURE-
 Version: GnuPG v1.0.6 (GNU/Linux)
 Comment: For info see http://www.gnupg.org
 
 iD8DBQE8jUqcfAeuFodNU5wRAt1/AKCaN881FMXqzpx+xh1EpnFa/b6k9ACeNuPX
 aYrkL3CfiF2C6uBzH+3chPs=
 =U7Xm
 -END PGP SIGNATURE-
 
 ___
 Haskell-Cafe mailing list
 [EMAIL PROTECTED]
 http://www.haskell.org/mailman/listinfo/haskell-cafe
 
___
Haskell-Cafe mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell-cafe



order of evaluation ?

2002-02-17 Thread Konst Sushenko
Title: Message



hello,

below is the 
code that i wrote as an excercise for myself (I am still learning 
haskell).

it 
implements a straighforward way to simplify boolean expressions, and should be 
self-explanatory.

my question 
is, if i have an expression such as ((Const False) :: subexp), will 
subexp be reduced first (according to the definition 
'simplify (x :: y) = simplify' ((simplify x) :: (simplify y))') 
or will laziness do the right thing, and emit (Const False) without looking into 
exp?

i think the 
latter, but would appreciate a word from an expert.

thanks
konst

PS: any 
coding suggestions, etc. are also welcome




infixr 3 ::infixr 2 :|:

data Exp = Const 
Bool | Sym 
String | Not 
Exp | Exp :: 
Exp | Exp :|: 
Exp

instance Eq Exp where 
(Const x) == (Const y) = x==y (Sym x) == (Sym 
y) = x==y (Not x) == (Not 
y) = x==y (x :: y) == (u :: v) = 
x==u  y==v || x==v  y==u (x :|: y) == 
(u :|: v) = x==u  y==v || x==v  y==u 
_ == 
_ = False

simplify (x :: y) = simplify' 
((simplify x) :: (simplify y))simplify (x :|: y) = simplify' ((simplify 
x) :|: (simplify y))simplify (Not x) = simplify' (Not (simplify 
x))simplify x = 
x

simplify' (Not (Const 
True)) = Const Falsesimplify' (Not (Const 
False)) = Const True

simplify' (Not (Not 
x)) = x

simplify' ((Not x) :: y) | x==y = 
Const Falsesimplify' (x :: (Not y)) | x==y = Const Falsesimplify' 
((Not x) :|: y) | x==y = Const Truesimplify' (x :|: (Not y)) | x==y = Const 
True

simplify' ((Const False) :: _) = 
Const Falsesimplify' (_ :: (Const False)) = Const 
Falsesimplify' ((Const True) :: x) = xsimplify' (x 
:: (Const True)) = x

simplify' ((Const True) :|: _) 
= Const Truesimplify' (_ :|: (Const True)) = Const 
Truesimplify' ((Const False) :|: x) = xsimplify' (x :|: (Const 
False)) = x

simplify' (x :: y) | 
x==y = xsimplify' (x :|: y) | 
x==y = x

simplify' 
x 
= x



RE: efficiency question

2002-02-08 Thread Konst Sushenko

(moved to haskell-café)

I ran Hal's code on my computer, and with test2 I get a stack overflow (so I had to 
use +RTS option for it to finish). test1 does not overflow stack (of standard size, I 
mean without +RTS). Which implies that test2 uses more stack space than test1. why 
would it use more stack if not because of laziness?

konst

 -Original Message-
 From: Hal Daume III [mailto:[EMAIL PROTECTED]] 
 Sent: Friday, February 08, 2002 4:35 PM
 To: Jorge Adriano
 Cc: Konst Sushenko; [EMAIL PROTECTED]
 Subject: Re: efficiency question
 
 
 I agree that it's the overhead of (,), but I don't see why 
 there would be
 any overhead for doing this.
 
 --
 Hal Daume III
 
  Computer science is no more about computers| [EMAIL PROTECTED]
   than astronomy is about telescopes. -Dijkstra | www.isi.edu/~hdaume
 
 On Sat, 9 Feb 2002, Jorge Adriano wrote:
 
  On Friday 08 February 2002 23:52, Hal Daume III wrote:
   I've tried using a strict fold:
  
   foldl' f a [] = a
   foldl' f a (x:xs) = (foldl' f $! f a x) xs
  
   but that has no effect (or minimal effect).
  
  That wouldn't work even if if laziness is the problem 
 because that would only 
  cause the elements of the list to be evaluated to head 
 normal form, the 
  elements of the pair would not be evaluated so you'd have a 
 'suspension of  
  (minus and plus) operations'.
  
  instead of 
   (\x (a,b) - (x+a,x-b))
  try 
   (\x (a,b) - (((,) $! x-a)$! x-b) )
  
  I just noticed that you were the one who sent me the DeepSeq module.
  This is the kind of place where I want to use it.
  Instead of $!, try $!!.
  
  
  And Konst Sushenko wrote:
  My guess is that it is due to the laziness of the 
 addition/subtraction
  in (,)
  
  Seems to me like lazyness is not the right guess because 
 both functions Hall 
  first posted were lazy. So I think it's just the overhead 
 of applying (,) 
  besides (+) and (-) in each step. Do I make sense or am I 
 missing something?
  
  J.A.
  
 
 
___
Haskell-Cafe mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell-cafe



examples using built-in state monad

2001-02-26 Thread Konst Sushenko



hello,

in my 
program i used my own parameterised state transformer monad, which iswell 
described in literature:

newtype 
State s m a = ST (s - m 
(a,s))
ghc and hugs 
contain built in implementation of state monad ST.

is it the 
same thing? the documentation is not clear on that.

if it is the 
same, is it faster?

also, could 
someoneplease recommend any samples that use the built in ST 
monad?

thanks
konst


RE: newbie: running a state transformer in context of a state reader

2001-02-20 Thread Konst Sushenko

Marcin,

thanks for your help.

to implement the lift functionality i added these well
known definitions:


class (Monad m, Monad (t m)) = TransMonad t m where
lift   :: m a - t m a

instance (Monad m, Monad (State s m)) = TransMonad (State s) m where
lift m  = ST (\s - m = (\a - return (a,s)))



but my lookahead function

lookahead p = do { s - fetch
 ; lift (evalState p s)
 }

is typed as

lookahead :: State MyState Maybe a - State MyState Maybe (a,MyState)

but i need

lookahead :: State MyState Maybe a - State MyState Maybe a

apparently, the (=) and return used in the definition of lift above are
for the monad (State s m), and not monad m...

everything works if i do not use the TransMonad class, but define lift
manually as:

lift :: Parser a - Parser a
lift m = ST (\s - unST m s = (\(a,_) - return (a,s)))

but this looks like a special case of the lift above, except the right hand
side of
'bind' is executed in the right context.

i am still missing something

konst


-Original Message-
From: Marcin 'Qrczak' Kowalczyk [mailto:[EMAIL PROTECTED]]
Sent: Tuesday, February 20, 2001 10:17 AM
To: [EMAIL PROTECTED]
Subject: Re: newbie: running a state transformer in context of a state
reader


Mon, 19 Feb 2001 18:07:17 -0800, Konst Sushenko [EMAIL PROTECTED] pisze:

 now i am curious if it is possible to run the given parser (state
 transformer) in a context of a state reader somehow, so as the state
 gets preserved automatically. something that would let me omit the
 calls to fetch and set methods.

It should be possible to do something like this:

lookahead:: Parser a - Parser a
lookahead p = do { s - fetch
 ; lift (evalState p s)
 }

where evalState :: Monad m = State s m a - s - m a
  lift  :: Monad m = m a - State s m a
are functions which should be available or implementable in a monad
transformer framework. I don't have the Hutton/Meijer's paper at hand
so I don't know if they provided them and under which names. Such
functions are provided e.g. in the framework provided with ghc (by
Andy Gill, inspired by Mark P Jones' paper "Functional Programming
with Overloading and Higher-Order Polymorphism").

This definition of lookahead uses a separate state transformer thread
instead of making changes in place and undoing them later. I don't
think that it could make sense to convert a state transformer to
a state reader by replacing its internals, because p does want to
transform the state locally; a value of type Parser a represents
a state transformation. The changes must be isolated from the main
parser, but they must happen in some context.

-- 
 __("  Marcin Kowalczyk * [EMAIL PROTECTED] http://qrczak.ids.net.pl/
 \__/
  ^^  SYGNATURA ZASTEPCZA
QRCZAK


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

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



need help w/ monad comprehension syntax

2001-02-15 Thread Konst Sushenko



hello,

i am having 
troublegetting my program below to work.
i think i 
implemented the monad methods correctly, but
the function 
'g' does not type as i would expect. Hugs
thinks that 
it is just a list (if i remove the explicit
typing). i 
want it to be functionally identical to the
function 
'h'.

what am i 
missing?

thanks
konst


 newtype 
State s a = ST (s - (a,s))

 unST 
(ST m) = m

 
instance Functor (State s) where  fmap f m = ST (\s 
- let (a,s') = unST m s in (f a, s'))

 
instance Monad (State s) where  return a = ST (\s 
- (a,s))  m = f = ST (\s - let 
(a,s') = unST m s in unST (f a) s')

 --g :: 
State String Char g = [ x | x - return 'a' ]

 h :: 
State String Char h = return 'a'