[Haskell-cafe] take the keywords from a string
Bulat Ziganshin
bulat.ziganshin at gmail.com
Sun Jun 18 01:46:16 EDT 2006
Hello Sara,
Sunday, June 18, 2006, 9:04:05 AM, you wrote:
you should write stop alternatives first, because Haskell tries
alternatives just sequentially, topmost first:
listOfString :: [(String,String)] -> [String]
listOfString [("","")] = []
listOfString [(s1,s2)] = s1: listOfString (lex s2)
> I tried to write function lexList by using an intermediate function
> lisOfString as below:
> module Lex where
> lexList :: String -> [String]
> lexList str = listOfString (lex str)
> lexList [] =[]
> listOfString :: [(String,String)] -> [String]
> listOfString [(s1,s2)] = s1: listOfString (lex s2)
> listOfString [("","")] = []
> When I try function lisOfString as below, it runs forever (non-stop)
> although I have the stop criteria for it ??
Lex>> lisOfString ["test1","test2(test3)"]
> Thanks in advance.
> S.
>> On 6/17/06, Neil Mitchell <ndmitchell at gmail.com> wrote:
>> > Hi
>> >
>> > On 6/18/06, Sara Kenedy <sarakenedy at gmail.com> wrote:
>> > > Sorry, I am not clear at some point in your answer:
>> > >
>> > > 1) The function
>> > > lex :: String -> [(String,String)]
>> > > and
>> > > filter :: (a -> Bool) -> [a] -> [a]
>> > > So, I did not see how filter can use the list of tuple string of lex.
>> >
>> > You can write a function lexList, of type String -> [String], by
>> > repeatedly calling lex - its not too hard. Once you have this the
>> > filter will work.
>> >
>> > Thanks
>> >
>> > Neil
>> >
>>
> _______________________________________________
> Haskell-Cafe mailing list
> Haskell-Cafe at haskell.org
> http://www.haskell.org/mailman/listinfo/haskell-cafe
--
Best regards,
Bulat mailto:Bulat.Ziganshin at gmail.com
More information about the Haskell-Cafe
mailing list