
Thanks for your answer. The lines where as you asnwered me. When I post my mail the layout was tottally ruined. Here I post the program again but I have replaced all spaces with underscores ( _ ) This is the error that I have: ERROR "c:\textanalysis.HS":48 - Syntax error in declaration (unexpected `->') Thanks in advance for all the help that you can give me module Main where import IO import System import List import Maybe import Char import Numeric type Word=String type WordCount=Int type WordTup=(word,wordCount) type WordList=[WordTup] main=do args<-getArgs ________textLines<-getText ________switchArgs args textLines ________where ________switchArgs args textLines ________________________|(isMemberOf "-f" args) && (isMemberOf "-i" args) _________________________=printFreq(sortWordCount(parseLcLine textLines)) ________________________|(isMemberOf "-f" args) _________________________=printFreq(sortWordCount (parseLine textLines)) ________________________|(isMemberOf "-i" args) _________________________=printFreq(sortWordCount (parseLcLine textLines)) ________________________|otherwise _________________________=printFreq(sortName (parseLine textLines)) ________getText::IO String ________getText=do c<-getChar ___________________e<-isEOF ___________________if (e) _______________________then return "" else _______________________(do nc<-getText ___________________________return (:nc)) ________parseLine::String->Wordlist ________parseLine line __________________|(line/="")&&(isWantedChar (headline)) ___________________=fillWordList w(parseLine newLine) __________________|(line/="")&&(not(isWantedChar (headline))) ___________________=parseLine(tail line) ________isMemberOf::String->[String]->Bool ________isMemberOf arg args ___________________=[]/=[a|a<-args,a==arg] ________printFreq::WordList->IO() ________printFreq wl=do sequence (map putWordStat wl) ________________________where ________________________putWordStat(Word,WordCount)->IO() ________________________putWordStat(w,wc) ________________________do putStr w ___________________________putSpc (20 (length w) (length(show wc))) ___________________________putStr (show wc) ___________________________putSpc 8 ___________________________putStr (showFFloat (Just 2) (fromIntegral (wc) * 100.0/fromIntegral (wLength))"") ___________________________putChar '%' ___________________________putChar '\n' ________________________return() ________________________wlLength-countWords wl; ________putSpc::Int->IO() ________putSpc n _______________|n>1 do putChar '' _______________________putSpc (n-1) ________________return() _______________|otherwise=putChar '' ________countWords:Wordlist->Int ________countWords [ ] ________countWords ((w,wc):wl)=wc+countWords wl ________sortName::WordList->WordList ________sortName [ ] = [ ] ________sortName (wn:ws)=sortName [(w,wc) (w,wc) <-ws,not (isGreater (w,wc)wc)] __________________++[wn]++sortName[(w,wc)|(w,wc)<-ws, isGreater (w,wc) wn] __________________where __________________isGreater (wl,wcl) (w2,wc2) _____________________________|ord(head(wl))-ord(head(x2))>0=True _____________________________|ord(head(wl))-ord(head(x2))<0=False _____________________________|length wl>l && length w2>l ______________________________=isGreater(tail(wl),wcl) (tail(w2,wc2) _____________________________|otherwise = [] _____________________________where _____________________________w=parseWord line _____________________________newline=drop (length w) line ________parseLcLine::String->WordList ________parseLcLine line ____________________|(line/="") && (isWantedChar (head line))=fillWordList w (parseLcLine newline) ____________________|(line/="") && (not (isWantedChar (head line)))=parseLcLine (tail line) ____________________|otherwise = [] ____________________where ____________________w=map toLower (parseWord line) ____________________newline=drop (lenfth w) line ________parseWord::Word->Word ________parseWord w __________________|(w/="") && (isWantedChar (head w))=(head w): parseWord (tail w)) __________________|otherwise = "" ________isWantedChar::Char->Bool ________isWantedChar c _____________________| (c=='a'|| c=='b'|| c=='c'|| c=='d'|| c=='e'|| c=='f' || c=='g'|| c=='h'|| c=='i'||__c=='j'|| c=='k'|| c=='l'|| c=='m'|| c=='n'|| c=='o'|| c=='p'|| c=='q'|| c=='r'|| c=='s'|| c=='t'|| c=='u'|| c=='v'|| c==' w'|| c=='x'|| c=='y'|| c=='z'||c=='A'|| c=='B'|| c=='C'|| c=='D'|| c=='E'|| c=='F'|| c=='G'|| c=='H'|| c=='I'||__c=='J'|| c=='K'|| c=='L'|| c=='M'|| c== 'N'|| c=='O'|| c=='P'|| c=='Q'|| c=='R'|| c=='S'|| c=='T'|| c=='U'|| c=='V' || c=='W'|| c=='X'|| c=='Y'|| c=='Z'|| = True) _____________________|otherwise = False _______fillWordList::Word->WordList->WordList _______fillWordList w wordlistl ____________________|cWord/= [] =cWord++[wordl,wordCountl)|(wordl,wordCountl<-wordListl,wordl/=w] ____________________|otherwise = (w,l):wordListl ____________________where ____________________cWord=[(wordl,(wordCountl-l)) | (wordl,wordCountl)<-wordListl,wordl==w] __________________________________________________|length w1>1 && length w2==1=True __________________________________________________|otherwise = False ________sortWordCount::WordList->WordList ________sortWordCount [] = [] ________sortWordCount ((wn,wcn):ws=sortWordCount [(w,wc|cw,wc)<-ws,ws<=wvn++ _______________________[(wn,wcn)]++sortWordCount [(cw,wc)|(w,wc)<-ws,wcs,wcn]

"Ãéþñãïò Êïóìßäçò"
This is the error that I have: ERROR "c:\textanalysis.HS":48 - Syntax error in declaration (unexpected `->')
Line 48:
________________________putWordStat(Word,WordCount)->IO()
There is a :: missing between the function name and its type.
________________________putWordStat::(Word,WordCount)->IO()
The function definition is also missing an = sign:
________________________putWordStat(w,wc) ________________________do
should be
________________________putWordStat(w,wc)= ________________________do
Finally, in this whole block:
________printFreq wl=do sequence (map putWordStat wl) ________________________where ________________________putWordStat::(Word,WordCount)->IO() ________________________putWordStat(w,wc)= ________________________do ... ________________________return() ________________________wlLength-countWords wl;
the indentation is incorrect. You probably meant to write something along these lines:
________printFreq wl=do sequence (map putWordStat wl) ____________________________where ______________________________putWordStat::(Word,WordCount)->IO() ______________________________putWordStat(w,wc)= ________________________________do ... ___________________________________return() ________________________wlLength-countWords wl;
but even this has two faults. First, a `where' clause can only be attached to a whole definition, not to a single statement within a `do'. Second, the final statement of the outer `do' should be a statement e.g. "return (wlLength-countWords wl)", not a simple value. Regards, Malcolm

at least i passed that line! unfortunatelly i stack again :( This is the error this time. What can i say.I cannot understand the error the compiler returns.it is not much help. ERROR "c:\1.hs":69 - Syntax error in expression (unexpected `<-') module_Main_where import_IO import_System import_List import_Maybe import_Char import_Numeric type_Word=String type_WordCount=Int type_WordTup=(word,wordCount) type_WordList=[WordTup] main=do_args<-getArgs ________textLines<-getText ________switchArgs_args_textLines ________where ________switchArgs_args_textLines ________|(isMemberOf_"-f"_args)_&&_(isMemberOf_"-i"_args) _________________________=printFreq(sortWordCount(parseLcLine_textLines)) ________________________|(isMemberOf_"-f"_args) _________________________=printFreq(sortWordCount_(parseLine_textLines)) ________________________|(isMemberOf_"-i"_args) _________________________=printFreq(sortWordCount_(parseLcLine_textLines)) ________________________|otherwise _________________________=printFreq(sortName_(parseLine_textLines)) ________getText::IO_String ________getText=do_c<-getChar ___________________e<-isEOF ___________________if_(e) _______________then_return_""_else _______________________(do_nc<-getText ___________________________return_(:nc)) ________parseLine::String->Wordlist ________parseLine_line __________________|(line/="")&&(isWantedChar_(headline)) ___________________=fillWordList_w(parseLine_newLine) __________________|(line/="")&&(not(isWantedChar_(headline))) ___________________=parseLine(tail_line) ________isMemberOf::String->[String]->Bool ________isMemberOf_arg_args_ ___________________=[]/=[a|a<-args,a==arg] ________printFreq::WordList->IO() ________printFreq_wl=do_sequence_(map_putWordStat_wl) _________________________________where_ ______________________________________putWordStat::(Word,WordCount)->IO() ______________________________________putWordStat(w,wc)=do_putStr_w ___________________________________________________________putSpc_(20_(lengt h_w)_(length(show_wc))) ___________________________________________________________putStr_(show_wc) ___________________________________________________________putSpc_8 ___________________________________________________________putStr_(showFFloa t_(Just_2)_(fromIntegral_(wc)_*_100.0/fromIntegral_(wLength))"") ___________________________________________________________putChar_'%' ___________________________________________________________putChar_'\n' ___________________________________________________________return(wlLength-c ountWords_wl) ________putSpc::Int->IO() ________putSpc_n _______________|(n>1)_=_do_putChar_'_' ___________________________putSpc_(n-1) ___________________________return() _______________|otherwise_=_putChar_'_' ________countWords::Wordlist->Int ________countWords_[] ____________________countWords_((w,wc):wl)=wc+countWords_wl ________sortName::WordList->WordList ________sortName_[]_=_[]_ ________sortName_(wn:ws)=sortName_[(w,wc)_(w,wc)_<-_ws,not_(isGreater_(w,wc) _wc)] _________________________++[wn]++sortName[(w,wc)|(w,wc)<-ws,_isGreater_(w,wc )_wn] __________________where __________________isGreater_(wl,wcl)_(w2,wc2) _____________________________|ord(head(wl))-ord(head(x2))>0=True _____________________________|ord(head(wl))-ord(head(x2))<0=False _____________________________|length_wl>l_&&_length_w2>l ______________________________=isGreater(tail(wl),wcl)_(tail(w2,wc2) _____________________________|otherwise_=_[] _____________________________where _____________________________w=parseWord_line _____________________________newline=drop_(length_w)_line ________parseLcLine::String->WordList ________parseLcLine_line ____________________|(line/="")_&&_(isWantedChar_(head_line))=fillWordList_w _(parseLcLine_newline) ____________________|(line/="")_&&_(not_(isWantedChar_(head_line)))=parseLcL ine_(tail_line) ____________________|otherwise_=_[] ____________________where ____________________w=map_toLower_(parseWord_line) ____________________newline=drop_(lenfth_w)_line ________parseWord::Word->Word ________parseWord_w __________________|(w/="")_&&_(isWantedChar_(head_w))=(head_w):_parseWord_(t ail_w)) __________________|otherwise_=_"" ________isWantedChar::Char->Bool ________isWantedChar_c _____________________|_(c=='a'||_c=='b'||_c=='c'||_c=='d'||_c=='e'||_c=='f' ||_c=='g'||_c=='h'||_c=='i'||__c=='j'||_c=='k'||_c=='l'||_c=='m'||_c=='n' ||_c=='o'||_c=='p'||_c=='q'||_c=='r'||_c=='s'||_c=='t'||_c=='u'||_c=='v' ||_c=='w'||_c=='x'||_c=='y'||_c=='z'||c=='A'||_c=='B'||_c=='C'||_c=='D' ||_c=='E'||_c=='F'||_c=='G'||_c=='H'||_c=='I'||__c=='J'||_c=='K'||_c=='L' ||_c=='M'||_c=='N'||_c=='O'||_c=='P'||_c=='Q'||_c=='R'||_c=='S'||_c=='T' ||_c=='U'||_c=='V'||_c=='W'||_c=='X'||_c=='Y'||_c=='Z'||_=_True) _____________________|otherwise_=_False _______fillWordList::Word->WordList->WordList _______fillWordList_w_wordlistl ____________________|cWord/=_[]_=cWord++[wordl,wordCountl)|(wordl,wordCountl <-wordListl,wordl/=w] ____________________|otherwise_=_(w,l):wordListl ____________________where ____________________cWord=[(wordl,(wordCountl-l))_|_(wordl,wordCountl)<-word Listl,wordl==w] __________________________________________________|length_w1>1_&&_length_w2= =1=True __________________________________________________|otherwise_=_False ________sortWordCount::WordList->WordList ________sortWordCount_[]_=_[] ________sortWordCount_((wn,wcn):ws=sortWordCount_[(w,wc|cw,wc)<-ws,ws<=wvn++ _ _______________________[(wn,wcn)]++sortWordCount_[(cw,wc)|(w,wc)<-ws,wcs,wcn ]

ERROR "c:\1.hs":69 - Syntax error in expression (unexpected `<-')
Line 69:
sortName (wn:ws)=sortName [(w,wc) (w,wc) <- ws,not (isGreater (w,wc) wc)] ++[wn]++sortName[(w,wc)|(w,wc)<-ws, isGreater (w,wc) wn]
The first list comprehension expression [ (w,wc) (w,wc) <- ... ] is missing a vertical bar, i.e. [ (w,wc) | (w,wc) <- ... ] Regards, Malcolm

I am new to haskell. I am trying to do some "excersise" but i can't make anything work :( This is my code.I replaced spaces with underscores ( _ ) Thanks for any suggestions or correctrions import IO import System import List import Maybe import Char import Numeric type Name=String type Room=Int type Dr=String type PatientTup=(Name,(Room,Dr)) type PatientList=[PatientTup] main=do userText<-getText ---------------------------------------------------------------------------- ------- ________getText::IO String ________getText=do nc<-getText _______________________return (:nc) ---------------------------------------------------------------------------- ------- ________PatientList::[(String,(Int,String))] ________PatientList=[("Robson, Brian",(2,"MJH")), _____________________("Hitchin, Linda",(1,"ILR")), _____________________("Reeve, Paul", (2,"ILR"))] ---------------------------------------------------------------------------- ------- ________getWards::Int ________getWards PatientList=[Room | (Name,(Room,Dr)) <- PatientList, Room==getText] _________________do putSpc (length Room) _________________return(RoomLength) ---------------------------------------------------------------------------- ------- ________printFreq::WordList->IO() ________printFreq wl=do sequence (map putWards wl) _________________________________where ______________________________________putWards::(getWards)->IO() ______________________________________putWards(w)=do putStr w _____________________________________________________putChar '\n' _____________________________________________________return(w)

Among other things, please make sure your layout lines up. Also, you cannot have the definition of getText at the same indentation of "userText<-getText" otherwise your compiler will think this is part of the do statement (I believe):
main=do userText<-getText ---------------------------------------------------------------------------- ------- ________getText::IO String ________getText=do nc<-getText _______________________return (:nc)
these need to be lined up
_________________do putSpc (length Room) _________________return(RoomLength)
It would help if you also posted the error messaage the compiler gave you and the line number and (perhaps) a shorter version of the program. - Hal
participants (4)
-
G?????? ??sµ?d??
-
Hal Daume III
-
Malcolm Wallace
-
Γιώργος Κοσμίδης