Re: [Haskell-cafe] Java or C to Haskell

2006-09-20 Thread Donald Bruce Stewart
crespi.albert:
 
 I'm trying to write in Haskell a function that in Java would be something
 like this:
 
 char find_match (char[] l1, char[] l2, char e){
   //l1 and l2 are not empty
   int i = 0;
   while (l2){
   char aux = l2[i];
   char[n] laux = l2;
   while(laux){
   int j = 0;
   if(laux[j] = aux) laux[j] = e;
   j++;
   }
   if compare (l1, laux) return aux;
   else i++;
   }
 return '';
 }

Yikes!

 
 compare function just compares the two lists and return true if they are
 equal, or false if they are not.
 it is really a simple function, but I've been thinking about it a lot of
 time and I can't get the goal. It works like this:
 
 find_match 4*ha 4*5a 'h'  returns '5' (5 matches with the h)
 find_match 4*ns 4dhnn k  returns ''  (no match at all - lists
 are different anyway)

That's almost a spec there :)

How about:

  import Data.List
 
  findMatch s t c
  | Just n - elemIndex c s = Just (t !! n)
  | otherwise   = Nothing

Using it in GHCi:

 findMatch 4*ha 4*5a 'h'
Just '5'

 findMatch 4*ns 4dhnn 'k'
Nothing

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


Re: [Haskell-cafe] Java or C to Haskell

2006-09-20 Thread Andrea Rossato
On Wed, Sep 20, 2006 at 01:31:22AM -0700, Carajillu wrote:
 
 I'm trying to write in Haskell a function that in Java would be something
 like this:
 
 char find_match (char[] l1, char[] l2, char e){
   //l1 and l2 are not empty
   int i = 0;
   while (l2){
   char aux = l2[i];
   char[n] laux = l2;
   while(laux){
   int j = 0;
   if(laux[j] = aux) laux[j] = e;
   j++;
   }
   if compare (l1, laux) return aux;
   else i++;
   }
 return '';
 }
 
 compare function just compares the two lists and return true if they are
 equal, or false if they are not.


I know that this is far too simple. But I'm simple minded:

comp [] [] = True
comp (x:xs) (y:ys) = if x == y then comp xs ys else False

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


Re: [Haskell-cafe] Java or C to Haskell

2006-09-20 Thread Donald Bruce Stewart
dons:
 crespi.albert:
  
  I'm trying to write in Haskell a function that in Java would be something
  like this:
  
  char find_match (char[] l1, char[] l2, char e){
  //l1 and l2 are not empty
  int i = 0;
  while (l2){
  char aux = l2[i];
  char[n] laux = l2;
  while(laux){
  int j = 0;
  if(laux[j] = aux) laux[j] = e;
  j++;
  }
  if compare (l1, laux) return aux;
  else i++;
  }
  return '';
  }
 
 Yikes!
 
  
  compare function just compares the two lists and return true if they are
  equal, or false if they are not.
  it is really a simple function, but I've been thinking about it a lot of
  time and I can't get the goal. It works like this:
  
  find_match 4*ha 4*5a 'h'  returns '5' (5 matches with the h)
  find_match 4*ns 4dhnn k  returns ''  (no match at all - lists
  are different anyway)
 
 That's almost a spec there :)

Ah, I see I misread the spec :) Time for some tea.

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


Re: [Haskell-cafe] Java or C to Haskell

2006-09-20 Thread Andrea Rossato
On Wed, Sep 20, 2006 at 01:31:22AM -0700, Carajillu wrote:
 compare function just compares the two lists and return true if they are
 equal, or false if they are not.
 it is really a simple function, but I've been thinking about it a lot of
 time and I can't get the goal. 

I forgot, obviously, that lists are an instance of the Eq class...
so, this is enough:
comp l1 l2 = if l1 == l2 then True else False

You never stop learning!
andrea
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Java or C to Haskell

2006-09-20 Thread Carajillu

wow, the simpliest ever!


Andrea Rossato wrote:
 
 On Wed, Sep 20, 2006 at 01:31:22AM -0700, Carajillu wrote:
 compare function just compares the two lists and return true if they are
 equal, or false if they are not.
 it is really a simple function, but I've been thinking about it a lot of
 time and I can't get the goal. 
 
 I forgot, obviously, that lists are an instance of the Eq class...
 so, this is enough:
 comp l1 l2 = if l1 == l2 then True else False
 
 You never stop learning!
 andrea
 ___
 Haskell-Cafe mailing list
 Haskell-Cafe@haskell.org
 http://www.haskell.org/mailman/listinfo/haskell-cafe
 
 

-- 
View this message in context: 
http://www.nabble.com/Java-or-C-to-Haskell-tf2303820.html#a6404305
Sent from the Haskell - Haskell-Cafe mailing list archive at Nabble.com.

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


Re: [Haskell-cafe] Java or C to Haskell

2006-09-20 Thread Donald Bruce Stewart
mailing_list:
 On Wed, Sep 20, 2006 at 01:31:22AM -0700, Carajillu wrote:
  compare function just compares the two lists and return true if they are
  equal, or false if they are not.
  it is really a simple function, but I've been thinking about it a lot of
  time and I can't get the goal. 
 
 I forgot, obviously, that lists are an instance of the Eq class...
 so, this is enough:
 comp l1 l2 = if l1 == l2 then True else False
 
 You never stop learning!
 andrea

which you would just write as:
comp = (==)

and then you'd just use == anyway :)

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


Re: [Haskell-cafe] Java or C to Haskell

2006-09-20 Thread Carajillu

That works good, but I have a problem with the return type, I forgot to
mention... can it be a [char]??

Donald Bruce Stewart wrote:
 
 crespi.albert:
 
 I'm trying to write in Haskell a function that in Java would be something
 like this:
 
 char find_match (char[] l1, char[] l2, char e){
  //l1 and l2 are not empty
  int i = 0;
  while (l2){
  char aux = l2[i];
  char[n] laux = l2;
  while(laux){
  int j = 0;
  if(laux[j] = aux) laux[j] = e;
  j++;
  }
  if compare (l1, laux) return aux;
  else i++;
  }
 return '';
 }
 
 Yikes!
 
 
 compare function just compares the two lists and return true if they are
 equal, or false if they are not.
 it is really a simple function, but I've been thinking about it a lot of
 time and I can't get the goal. It works like this:
 
 find_match 4*ha 4*5a 'h'  returns '5' (5 matches with the h)
 find_match 4*ns 4dhnn k  returns ''  (no match at all - lists
 are different anyway)
 
 That's almost a spec there :)
 
 How about:
 
   import Data.List
  
   findMatch s t c
   | Just n - elemIndex c s = Just (t !! n)
   | otherwise   = Nothing
 
 Using it in GHCi:
 
 findMatch 4*ha 4*5a 'h'
 Just '5'
 
 findMatch 4*ns 4dhnn 'k'
 Nothing
 
 -- Don
 ___
 Haskell-Cafe mailing list
 Haskell-Cafe@haskell.org
 http://www.haskell.org/mailman/listinfo/haskell-cafe
 
 

-- 
View this message in context: 
http://www.nabble.com/Java-or-C-to-Haskell-tf2303820.html#a6404324
Sent from the Haskell - Haskell-Cafe mailing list archive at Nabble.com.

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


Re: [Haskell-cafe] Java or C to Haskell

2006-09-20 Thread Carajillu

Yes, they must be equal the whole way, I like this recursive solution :)

Ketil Malde-3 wrote:
 
 Carajillu [EMAIL PROTECTED] writes:
 
 compare function just compares the two lists and return true if they are
 equal, or false if they are not.
 
 find_match 4*ha 4*5a 'h'  returns '5' (5 matches with the h)
 find_match 4*ns 4dhnn k  returns ''  (no match at all - lists
 are different anyway)
 
 Must they be equal the whole way, or just up to the occurrence of the
 searched-for character?
 
   find_match (x:xs) (y:ys) c | x==c = Just y 
  | x/=y = Nothing
  | True = find_match xs ys c
   find_match [] [] _ = Nothing
 
 Or, to check the whole list:
 
   find_match (x:xs) (y:ys) c | x==c  xs == ys = Just y 
  | x/=y = Nothing
  | True = find_match xs ys c
   find_match [] [] _ = Nothing
 
 -k
 -- 
 If I haven't seen further, it is by standing in the footprints of giants
 
 ___
 Haskell-Cafe mailing list
 Haskell-Cafe@haskell.org
 http://www.haskell.org/mailman/listinfo/haskell-cafe
 
 

-- 
View this message in context: 
http://www.nabble.com/Java-or-C-to-Haskell-tf2303820.html#a6404344
Sent from the Haskell - Haskell-Cafe mailing list archive at Nabble.com.

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


Re: [Haskell-cafe] Java or C to Haskell

2006-09-20 Thread Ketil Malde
Andrea Rossato [EMAIL PROTECTED] writes:

 I forgot, obviously, that lists are an instance of the Eq class...
 so, this is enough:

 comp l1 l2 = if l1 == l2 then True else False

Or why not:

 comp l1 l2 = l1 == l2

Or simply:

 comp = (==)

:-)

-k
-- 
If I haven't seen further, it is by standing in the footprints of giants

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


Re: [Haskell-cafe] Java or C to Haskell

2006-09-20 Thread Andrea Rossato
On Wed, Sep 20, 2006 at 07:20:23PM +1000, Donald Bruce Stewart wrote:
  comp l1 l2 = if l1 == l2 then True else False
  
  You never stop learning!
  andrea
 
 which you would just write as:
 comp = (==)
 
 and then you'd just use == anyway :)

this is why I came to love haskell: it remembers me when I was doing
mathematics at the high school. The most challenging stuff, for me,
was finding a way to simplifying expressions...

It's just an endless chess game. 
Sending mails to this mailing list, I mean.
Andrea
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Java or C to Haskell

2006-09-20 Thread Matthias Fischmann

...  and if you want to search strings not single characters:

findmatch s t e = take m . drop n $ t
where
m' = length e
(n, m) = f 0 s
f i s | take m' s == e  = (i, m')
  | null s  = (0, 0)
  | otherwise   = f (i+1) (tail s)

findmatch asdfasdf asdfxvdf fas == fxv

(this one skips equality checks before *and* after the match.  feel
free post the necessary modifications.  :)

matthias



On Wed, Sep 20, 2006 at 02:22:29AM -0700, Carajillu wrote:
 To: haskell-cafe@haskell.org
 From: Carajillu [EMAIL PROTECTED]
 Date: Wed, 20 Sep 2006 02:22:29 -0700 (PDT)
 Subject: Re: [Haskell-cafe] Java or C to Haskell
 
 
 Yes, they must be equal the whole way, I like this recursive solution :)
 
 Ketil Malde-3 wrote:
  
  Carajillu [EMAIL PROTECTED] writes:
  
  compare function just compares the two lists and return true if they are
  equal, or false if they are not.
  
  find_match 4*ha 4*5a 'h'  returns '5' (5 matches with the h)
  find_match 4*ns 4dhnn k  returns ''  (no match at all - lists
  are different anyway)
  
  Must they be equal the whole way, or just up to the occurrence of the
  searched-for character?
  
find_match (x:xs) (y:ys) c | x==c = Just y 
   | x/=y = Nothing
   | True = find_match xs ys c
find_match [] [] _ = Nothing
  
  Or, to check the whole list:
  
find_match (x:xs) (y:ys) c | x==c  xs == ys = Just y 
   | x/=y = Nothing
   | True = find_match xs ys c
find_match [] [] _ = Nothing
  
  -k


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


Re: [Haskell-cafe] Java or C to Haskell

2006-09-20 Thread Cale Gibbard

How about something like this?

import Data.List

findMatch xs ys k = lookup k . concat $ zipWith zip (substrings xs)
(substrings ys)
   where substrings = nonempty . map (nonempty . inits) . tails
 where nonempty = filter (not . null)

On 20/09/06, Matthias Fischmann [EMAIL PROTECTED] wrote:


...  and if you want to search strings not single characters:

findmatch s t e = take m . drop n $ t
where
m' = length e
(n, m) = f 0 s
f i s | take m' s == e  = (i, m')
  | null s  = (0, 0)
  | otherwise   = f (i+1) (tail s)

findmatch asdfasdf asdfxvdf fas == fxv

(this one skips equality checks before *and* after the match.  feel
free post the necessary modifications.  :)

matthias



On Wed, Sep 20, 2006 at 02:22:29AM -0700, Carajillu wrote:
 To: haskell-cafe@haskell.org
 From: Carajillu [EMAIL PROTECTED]
 Date: Wed, 20 Sep 2006 02:22:29 -0700 (PDT)
 Subject: Re: [Haskell-cafe] Java or C to Haskell


 Yes, they must be equal the whole way, I like this recursive solution :)

 Ketil Malde-3 wrote:
 
  Carajillu [EMAIL PROTECTED] writes:
 
  compare function just compares the two lists and return true if they are
  equal, or false if they are not.
 
  find_match 4*ha 4*5a 'h'  returns '5' (5 matches with the h)
  find_match 4*ns 4dhnn k  returns ''  (no match at all - lists
  are different anyway)
 
  Must they be equal the whole way, or just up to the occurrence of the
  searched-for character?
 
find_match (x:xs) (y:ys) c | x==c = Just y
   | x/=y = Nothing
   | True = find_match xs ys c
find_match [] [] _ = Nothing
 
  Or, to check the whole list:
 
find_match (x:xs) (y:ys) c | x==c  xs == ys = Just y
   | x/=y = Nothing
   | True = find_match xs ys c
find_match [] [] _ = Nothing
 
  -k


-BEGIN PGP SIGNATURE-
Version: GnuPG v1.4.1 (GNU/Linux)

iD8DBQFFER17TXPx/Y0ym6oRAvNZAKCrLeJQxP0PjJAOz2KDi/S0hi7/ywCeMOfH
XIOJJcMs9yFsg2IajkmHX7Y=
=+bkI
-END PGP SIGNATURE-


___
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