At 12:12 PM -0700 9/13/02, Richard Barth wrote:
>I'm just learning Haskell with Hugs98. I can't understand why the
>line defining "foo" is acceptable while the line defining "bar"
>(only difference is the unary minus) generates the error message at
>the end. If someone could explain this, or, better yet, tell me how
>I can figure this out for myself. Thanks.
>
>
>
>data Entry = Ent {date :: String, amount :: Double}
>
>foo = [Ent "baz" 1.0]
>
>bar = [Ent "baz" -1.0]
>
>
>
>Type checking......
>
>ERROR "...test.hs":7 - Unresolved top-level overloading
>
>*** Binding : bar
>
>*** Outstanding context : Fractional (Double -> Entry)
Recall that function application has a higher priority than all the
operators --including unary (-).
--Ham
--
------------------------------------------------------------------
Hamilton Richards Department of Computer Sciences
Senior Lecturer The University of Texas at Austin
512-471-9525 1 University Station C0500
Taylor Hall 5.138 Austin, Texas 78712-1188
ham@cs.utexas.edu hrichrds@swbell.net
------------------------------------------------------------------
From gkosmidis@epsilon7.gr Wed Sep 18 14:32:35 2002
From: gkosmidis@epsilon7.gr (=?iso-8859-7?B?w+n+8ePv8iDK7/Ps3+Tn8g==?=)
Date: Wed, 18 Sep 2002 16:32:35 +0300
Subject: layout problem
Message-ID: <008901c25f17$dd549670$6000000a@dbserver>
This is a multi-part message in MIME format.
------=_NextPart_000_0086_01C25F30.FEC22340
Content-Type: text/plain;
charset="iso-8859-7"
Content-Transfer-Encoding: quoted-printable
Hello everyone.
I have a problem with a assessment.
The problem is with the layout.
I cannot understand what is wrong.
Here is the code
module Main where
import IO
import System
import List
import Maybe
import Char
import Numeric
type Word=3DString
type WordCount=3DInt
type WordTup=3D(word,wordCount)
type WordList=3D[WordTup]
main=3Ddo args<-getArgs
textLines<-getText
switchArgs args textLines
where
switchArgs args textLines
|(isMemberOf "-f" args) && (isMemberOf "-i" args)
=3DprintFreq(sortWordCount(parseLcLine =
textLines))
|(isMemberOf "-f" args)
=3DprintFreq(sortWordCount (parseLine =
textLines))
|(isMemberOf "-i" args)
=3DprintFreq(sortWordCount (parseLcLine =
textLines))
|otherwise
=3DprintFreq(sortName (parseLine textLines))
getText::IO String
getText=3Ddo c<-getChar
e<-isEOF
if (e)
then return "" else
(do nc<-getText
return (:nc))
parseLine::String->Wordlist
parseLine line
|(line/=3D"")&&(isWantedChar (headline))
=3DfillWordList w(parseLine newLine)
|(line/=3D"")&&(not(isWantedChar (headline)))
=3DparseLine(tail line)
isMemberOf::String->[String]->Bool
isMemberOf arg args=20
=3D[]/=3D[a|a<-args,a=3D=3Darg]
printFreq::WordList->IO()
printFreq wl=3Ddo sequence (map putWordStat wl)
where=20
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=3DputChar ''
countWords:Wordlist->Int
countWords [ ]
countWords ((w,wc):wl)=3Dwc+countWords wl
sortName::WordList->WordList
sortName [ ] =3D [ ]=20
sortName (wn:ws)=3DsortName [(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=3DTrue
|ord(head(wl))-ord(head(x2))<0=3DFalse
|length wl>l && length w2>l
=3DisGreater(tail(wl),wcl) (tail(w2,wc2)
|otherwise =3D []
where
w=3DparseWord line
newline=3Ddrop (length w) line
parseLcLine::String->WordList
parseLcLine line
|(line/=3D"") && (isWantedChar (head =
line))=3DfillWordList w (parseLcLine newline)
|(line/=3D"") && (not (isWantedChar (head =
line)))=3DparseLcLine (tail line)
|otherwise =3D []
where
w=3Dmap toLower (parseWord line)
newline=3Ddrop (lenfth w) line
parseWord::Word->Word
parseWord w
|(w/=3D"") && (isWantedChar (head w))=3D(head w): =
parseWord (tail w))
|otherwise =3D ""
isWantedChar::Char->Bool
isWantedChar c
| (c=3D=3D'a'|| c=3D=3D'b'|| c=3D=3D'c'|| =
c=3D=3D'd'|| c=3D=3D'e'|| c=3D=3D'f'|| c=3D=3D'g'|| c=3D=3D'h'|| =
c=3D=3D'i'|| c=3D=3D'j'|| c=3D=3D'k'|| c=3D=3D'l'|| c=3D=3D'm'|| =
c=3D=3D'n'|| c=3D=3D'o'|| c=3D=3D'p'|| c=3D=3D'q'|| c=3D=3D'r'|| =
c=3D=3D's'|| c=3D=3D't'|| c=3D=3D'u'|| c=3D=3D'v'|| c=3D=3D'w'|| =
c=3D=3D'x'|| c=3D=3D'y'|| c=3D=3D'z'||c=3D=3D'A'|| c=3D=3D'B'|| =
c=3D=3D'C'|| c=3D=3D'D'|| c=3D=3D'E'|| c=3D=3D'F'|| c=3D=3D'G'|| =
c=3D=3D'H'|| c=3D=3D'I'|| c=3D=3D'J'|| c=3D=3D'K'|| c=3D=3D'L'|| =
c=3D=3D'M'|| c=3D=3D'N'|| c=3D=3D'O'|| c=3D=3D'P'|| c=3D=3D'Q'|| =
c=3D=3D'R'|| c=3D=3D'S'|| c=3D=3D'T'|| c=3D=3D'U'|| c=3D=3D'V'|| =
c=3D=3D'W'|| c=3D=3D'X'|| c=3D=3D'Y'|| c=3D=3D'Z'|| =3D True)
|otherwise =3D False
fillWordList::Word->WordList->WordList
fillWordList w wordlistl
|cWord/=3D [] =
=3DcWord++[wordl,wordCountl)|(wordl,wordCountl<-wordListl,wordl/=3Dw]
|otherwise =3D (w,l):wordListl
where
cWord=3D[(wordl,(wordCountl-l)) | =
(wordl,wordCountl)<-wordListl,wordl=3D=3Dw]
|length w1>1 && length =
w2=3D=3D1=3DTrue
|otherwise =3D False
sortWordCount::WordList->WordList
sortWordCount [] =3D []
sortWordCount ((wn,wcn):ws=3DsortWordCount =
[(w,wc|cw,wc)<-ws,ws<=3Dwvn++=20
[(wn,wcn)]++sortWordCount =
[(cw,wc)|(w,wc)<-ws,wcs,wcn]
------=_NextPart_000_0086_01C25F30.FEC22340
Content-Type: text/html;
charset="iso-8859-7"
Content-Transfer-Encoding: quoted-printable
Hello=20
everyone.
I have a =
problem with a=20
assessment.
The problem =
is with the=20
layout.
I cannot =
understand what is=20
wrong.
Here is the=20
code
module Main =
where
import=20
IO
import System
import List
import Maybe
import =
Char
import=20
Numeric
type =
Word=3DString
type=20
WordCount=3DInt
type WordTup=3D(word,wordCount)
type=20
WordList=3D[WordTup]
main=3Ddo=20
args<-getArgs
=20
textLines<-getText
=
switchArgs=20
args textLines
=20
where
switchArgs args=20
textLines
=
|(isMemberOf=20
"-f" args) && (isMemberOf "-i"=20
args)
&nbs=
p;  =
; =20
=3DprintFreq(sortWordCount(parseLcLine=20
textLines))
&nbs=
p;  =
; =20
|(isMemberOf "-f"=20
args)
&nbs=
p;  =
; =20
=3DprintFreq(sortWordCount (parseLine=20
textLines))
&nbs=
p;  =
; =20
|(isMemberOf "-i"=20
args)
&nbs=
p;  =
; =20
=3DprintFreq(sortWordCount (parseLcLine=20
textLines))
&nbs=
p;  =
; =20
|otherwise
 =
; =
=20
=3DprintFreq(sortName (parseLine=20
textLines))
getText::IO=20
String
getText=3Ddo=20
c<-getChar
&n=
bsp; =20
e<-isEOF
&nbs=
p; =20
if=20
(e)
=
=20
then return ""=20
else
 =
; =20
(do=20
nc<-getText
&=
nbsp; &n=
bsp; =20
return (:nc))
=20
parseLine::String->Wordlist
&nb=
sp;=20
parseLine=20
line
 =
; =20
|(line/=3D"")&&(isWantedChar=20
(headline))
&nbs=
p; =20
=3DfillWordList w(parseLine=20
newLine)
&=
nbsp; =20
|(line/=3D"")&&(not(isWantedChar=20
(headline)))
&nb=
sp; =20
=3DparseLine(tail line)
=20
isMemberOf::String->[String]->Bool
 =
; =20
isMemberOf arg args=20
&nb=
sp; =20
=3D[]/=3D[a|a<-args,a=3D=3Darg]
=20
printFreq::WordList->IO()
 =
;=20
printFreq wl=3Ddo sequence (map putWordStat=20
wl)
=
=
where=20
&nb=
sp; =20
putWordStat(Word,WordCount)->IO()
&nb=
sp; &nbs=
p; =20
putWordStat(w,wc)
&nbs=
p;  =
; =20
do putStr=20
w
&n=
bsp; &nb=
sp; =20
putSpc (20 (length w) (length(show=20
wc)))
&nbs=
p;  =
; =20
putStr (show=20
wc)
=
&=
nbsp; =20
putSpc=20
8
&n=
bsp; &nb=
sp; =20
putStr (showFFloat (Just 2) (fromIntegral (wc) * 100.0/fromIntegral=20
(wLength))"")
&n=
bsp; &nb=
sp; =20
putChar=20
'%'
=
&=
nbsp; =20
putChar=20
'\n'
 =
; =
=20
return()
&=
nbsp; &n=
bsp;=20
wlLength-countWords wl;
=20
putSpc::Int->IO()
=
putSpc=20
n
&n=
bsp; =20
|n>1 do putChar=20
''
&=
nbsp; =20
putSpc=20
(n-1)
&nbs=
p; =20
return()
&=
nbsp; =20
|otherwise=3DputChar ''
=20
countWords:Wordlist->Int
=
=20
countWords [ ]
countWords=20
((w,wc):wl)=3Dwc+countWords =
wl
=20
sortName::WordList->WordList
&n=
bsp;=20
sortName [ ] =3D [ ]
=
sortName=20
(wn:ws)=3DsortName [(w,wc) (w,wc) <-ws,not (isGreater=20
(w,wc)wc)]
 =
; =20
++[wn]++sortName[(w,wc)|(w,wc)<-ws, isGreater (w,wc)=20
wn]
=
=20
where
&nbs=
p; =20
isGreater (wl,wcl)=20
(w2,wc2)
&=
nbsp; &n=
bsp; =20
|ord(head(wl))-ord(head(x2))>0=3DTrue
 =
; =
=20
|ord(head(wl))-ord(head(x2))<0=3DFalse
&nbs=
p;  =
; =20
|length wl>l && length=20
w2>l
&n=
bsp; &nb=
sp; =20
=3DisGreater(tail(wl),wcl)=20
(tail(w2,wc2)
&n=
bsp; &nb=
sp; =20
|otherwise =3D=20
[]
&=
nbsp; &n=
bsp; =20
where
&nbs=
p;  =
; =20
w=3DparseWord=20
line
 =
; =
=20
newline=3Ddrop (length w) =
line
=20
parseLcLine::String->WordList
&=
nbsp;=20
parseLcLine=20
line
 =
; =20
|(line/=3D””) && (isWantedChar (head =
line))=3DfillWordList w (parseLcLine=20
newline)
&=
nbsp; =20
|(line/=3D””) && (not (isWantedChar (head =
line)))=3DparseLcLine (tail=20
line)
&nbs=
p; =20
|otherwise =3D=20
[]
&=
nbsp; =20
where
&nbs=
p; =20
w=3Dmap toLower (parseWord=20
line)
&nbs=
p; =20
newline=3Ddrop (lenfth w) =
line
=20
parseWord::Word->Word
=
parseWord=20
w
&n=
bsp; =20
|(w/=3D””) && (isWantedChar (head w))=3D(head w): =
parseWord (tail=20
w))
=
=20
|otherwise =3D “”
=20
isWantedChar::Char->Bool
=
=20
isWantedChar=20
c
&n=
bsp; =20
| (c=3D=3D’a’|| c=3D=3D’b’|| =
c=3D=3D’c’|| c=3D=3D’d’|| =
c=3D=3D’e’|| c=3D=3D’f’|| =
c=3D=3D’g’|| c=3D=3D’h’||=20
c=3D=3D’i’|| c=3D=3D’j’|| =
c=3D=3D’k’|| c=3D=3D’l’|| =
c=3D=3D’m’|| c=3D=3D’n’|| =
c=3D=3D’o’|| c=3D=3D’p’||=20
c=3D=3D’q’|| c=3D=3D’r’|| =
c=3D=3D’s’|| c=3D=3D’t’|| =
c=3D=3D’u’|| c=3D=3D’v’|| =
c=3D=3D’w’|| c=3D=3D’x’|| =
c=3D=3D’y’||=20
c=3D=3D’z’||c=3D=3D’A’|| =
c=3D=3D’B’|| c=3D=3D’C’|| =
c=3D=3D’D’|| c=3D=3D’E’|| =
c=3D=3D’F’|| c=3D=3D’G’|| =
c=3D=3D’H’||=20
c=3D=3D’I’|| c=3D=3D’J’|| =
c=3D=3D’K’|| c=3D=3D’L’|| =
c=3D=3D’M’|| c=3D=3D’N’|| =
c=3D=3D’O’|| c=3D=3D’P’||=20
c=3D=3D’Q’|| c=3D=3D’R’|| =
c=3D=3D’S’|| c=3D=3D’T’|| =
c=3D=3D’U’|| c=3D=3D’V’|| =
c=3D=3D’W’|| c=3D=3D’X’|| =
c=3D=3D’Y’||=20
c=3D=3D’Z’|| =3D=20
True)
&nbs=
p; =20
|otherwise =3D False
=20
fillWordList::Word->WordList->WordList
&=
nbsp; =20
fillWordList w=20
wordlistl
=
=20
|cWord/=3D []=20
=3DcWord++[wordl,wordCountl)|(wordl,wordCountl<-wordListl,wordl/=3Dw]<=
BR> &nbs=
p; =20
|otherwise =3D=20
(w,l):wordListl
=
=20
where
&nbs=
p; =20
cWord=3D[(wordl,(wordCountl-l)) |=20
(wordl,wordCountl)<-wordListl,wordl=3D=3Dw]
 =
; =
&=
nbsp; &n=
bsp; =20
|length w1>1 && length=20
w2=3D=3D1=3DTrue
 =
; =
&=
nbsp; &n=
bsp; =20
|otherwise =3D False
=20
sortWordCount::WordList->WordList
&nb=
sp; =20
sortWordCount [] =3D []
=20
sortWordCount ((wn,wcn):ws=3DsortWordCount =
[(w,wc|cw,wc)<-ws,ws<=3Dwvn++=20
&nb=
sp; =20
[(wn,wcn)]++sortWordCount =
[(cw,wc)|(w,wc)<-ws,wcs,wcn]
------=_NextPart_000_0086_01C25F30.FEC22340--
From hdaume@ISI.EDU Wed Sep 18 15:34:42 2002
From: hdaume@ISI.EDU (Hal Daume III)
Date: Wed, 18 Sep 2002 07:34:42 -0700 (PDT)
Subject: layout problem
In-Reply-To: <008901c25f17$dd549670$6000000a@dbserver>
Message-ID:
> |(isMemberOf "-f" args) && (isMemberOf "-i" args)
> =printFreq(sortWordCount(parseLcLine textLines))
> |(isMemberOf "-f" args)
these two '|'s should be lined up, as in:
> |(isMemberOf "-f" args) && (isMemberOf "-i" args)
> =printFreq(sortWordCount(parseLcLine textLines))
> |(isMemberOf "-f" args)
as should all successive '|'s
From gkosmidis@epsilon7.gr Thu Sep 19 08:19:57 2002
From: gkosmidis@epsilon7.gr (=?iso-8859-7?B?w+n+8ePv8iDK7/Ps3+Tn8g==?=)
Date: Thu, 19 Sep 2002 10:19:57 +0300
Subject: layout problem
References: <20020918160103.9F2AC4223C1@www.haskell.org>
Message-ID: <001301c25fac$fbdddcb0$6000000a@dbserver>
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]
From Malcolm.Wallace@cs.york.ac.uk Thu Sep 19 13:49:15 2002
From: Malcolm.Wallace@cs.york.ac.uk (Malcolm Wallace)
Date: Thu, 19 Sep 2002 13:49:15 +0100
Subject: layout problem
In-Reply-To: <001301c25fac$fbdddcb0$6000000a@dbserver>
References: <20020918160103.9F2AC4223C1@www.haskell.org>
<001301c25fac$fbdddcb0$6000000a@dbserver>
Message-ID: <20020919134915.5c7190f4.Malcolm.Wallace@cs.york.ac.uk>
"Ãéşñãïò Êïóìßäçò" writes:
> 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
From shiin@gmx.de Thu Sep 19 14:45:51 2002
From: shiin@gmx.de (Dennis Schieferdecker)
Date: Thu, 19 Sep 2002 15:45:51 +0200
Subject: Depth-First search problems
Message-ID: <3D89D50E.CAC2A717@gmx.de>
Hi!
I hope you can help me with this little problem I have:
I'm trying to implement a depth-first search on a binary tree from a
school book but somehow I always get Haskell error messages (more after
the source code).
The source is as follows:
-- Binary Tree structure
data BinTree t = EmptyTree | Bin (BinTree t) t (BinTree t)
left (Bin b1 _ _) = b1
right (Bin _ _ b2) = b2
value (Bin _ v _) = v
empty EmptyTree = True
empty (Bin _ _ _) = False
-- Give the Binary Tree ==
instance Eq a => Eq (BinTree a) where
(Bin b v c) == (Bin d w e) = (v == w) && (b == d) && (c == e)
EmptyTree == EmptyTree = True
EmptyTree == Bin _ _ _ = False
-- Stack structure
data Keller t = CreateStack | Push (Keller t) t
top (Push s x) = x
pop (Push s x) = s
-- Depth-First search
tiefensuche b = fst (until p f ([], Push CreateStack b))
where p(_, k) = empty k
f(erg, k) | (top k) == EmptyTree = (erg, pop k)
| otherwise = ([v] ++ erg, Push( Push( pop k) b2) b1)
where (Bin b1 v b2) = top k
The error message says that p has a wrong types
Haskell thinks it is p :: (b, BinTree c) -> Bool, instead of p :: ([a],
Keller (BinTree a)) -> Bool
I really don't know how I can tell to see the right type. Does anyone
have an idea what I have to change ?
--
ciao
dennis
"I hear and I forget,
I see and I remember,
I do and I understand"
From gkosmidis@epsilon7.gr Thu Sep 19 15:33:24 2002
From: gkosmidis@epsilon7.gr (=?iso-8859-1?Q?G=3F=3F=3F=3F=3F=3F_=3F=3Fs=B5=3Fd=3F=3F?=)
Date: Thu, 19 Sep 2002 17:33:24 +0300
Subject: layout problem
References: <20020918160103.9F2AC4223C1@www.haskell.org><001301c25fac$fbdddcb0$6000000a@dbserver>
<20020919134915.5c7190f4.Malcolm.Wallace@cs.york.ac.uk>
Message-ID: <009901c25fe9$86b08810$6000000a@dbserver>
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
]
From Malcolm.Wallace@cs.york.ac.uk Thu Sep 19 15:33:26 2002
From: Malcolm.Wallace@cs.york.ac.uk (Malcolm Wallace)
Date: Thu, 19 Sep 2002 15:33:26 +0100
Subject: layout problem
In-Reply-To: <009901c25fe9$86b08810$6000000a@dbserver>
References: <20020918160103.9F2AC4223C1@www.haskell.org>
<001301c25fac$fbdddcb0$6000000a@dbserver>
<20020919134915.5c7190f4.Malcolm.Wallace@cs.york.ac.uk>
<009901c25fe9$86b08810$6000000a@dbserver>
Message-ID: <20020919153326.42949bb9.Malcolm.Wallace@cs.york.ac.uk>
> 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
From paul.hudak@yale.edu Thu Sep 19 15:35:21 2002
From: paul.hudak@yale.edu (Paul Hudak)
Date: Thu, 19 Sep 2002 10:35:21 -0400
Subject: Depth-First search problems
References: <3D89D50E.CAC2A717@gmx.de>
Message-ID: <3D89E0A9.128D1B4E@yale.edu>
I'm not sure whether your program is correct, but it's easy to see why
you're getting the type error. You define p(_, k) = empty k, but empty
has type BinTree t -> Bool, so clearly p has type (a, BinTree t) ->
Bool. However, you use p in "until p f ([], Push CreateStack b)".
Since until has type (a -> Bool) -> (a -> a) -> a -> a, this implies
that p must have type ([a], Keller (BinTree t)) -> Bool. So you need to
either fix the definition of p or fix how it is used.
By the way, you are missing the case (Bin _ _ _) == EmptyTree in the
instance decl. Also, note that Keller t is isomorphic to [t], i.e. to
the list data type. Specifically, CreateStack is [], Push is (:), top
is head, and pop is tail.
Hope this helps, -Paul Hudak
> -- Binary Tree structure
> data BinTree t = EmptyTree | Bin (BinTree t) t (BinTree t)
> left (Bin b1 _ _) = b1
> right (Bin _ _ b2) = b2
> value (Bin _ v _) = v
> empty EmptyTree = True
> empty (Bin _ _ _) = False
>
> -- Give the Binary Tree ==
> instance Eq a => Eq (BinTree a) where
> (Bin b v c) == (Bin d w e) = (v == w) && (b == d) && (c == e)
> EmptyTree == EmptyTree = True
> EmptyTree == Bin _ _ _ = False
>
> -- Stack structure
> data Keller t = CreateStack | Push (Keller t) t
> top (Push s x) = x
> pop (Push s x) = s
>
> -- Depth-First search
> tiefensuche b = fst (until p f ([], Push CreateStack b))
> where p(_, k) = empty k
> f(erg, k) | (top k) == EmptyTree = (erg, pop k)
> | otherwise = ([v] ++ erg, Push( Push( pop k) b2) b1)
> where (Bin b1 v b2) = top k
>
> The error message says that p has a wrong types
> Haskell thinks it is p :: (b, BinTree c) -> Bool, instead of p :: ([a],
> Keller (BinTree a)) -> Bool
From shiin@gmx.de Thu Sep 19 18:00:49 2002
From: shiin@gmx.de (Dennis Schieferdecker)
Date: Thu, 19 Sep 2002 19:00:49 +0200
Subject: Depth-First search problems
References: <3D89D50E.CAC2A717@gmx.de> <3D89E0A9.128D1B4E@yale.edu>
Message-ID: <3D8A02C1.BE78C40B@gmx.de>
Paul Hudak wrote:
> I'm not sure whether your program is correct, but it's easy to see why
> you're getting the type error. You define p(_, k) = empty k, but empty
> has type BinTree t -> Bool, so clearly p has type (a, BinTree t) ->
> Bool. However, you use p in "until p f ([], Push CreateStack b)".
> Since until has type (a -> Bool) -> (a -> a) -> a -> a, this implies
> that p must have type ([a], Keller (BinTree t)) -> Bool. So you need to
> either fix the definition of p or fix how it is used.
>
> By the way, you are missing the case (Bin _ _ _) == EmptyTree in the
> instance decl. Also, note that Keller t is isomorphic to [t], i.e. to
> the list data type. Specifically, CreateStack is [], Push is (:), top
> is head, and pop is tail.
>
> Hope this helps, -Paul Hudak
Thanks, that really helped.
My fault was that the depth-search algorithm expected an empty-method for the
stack not for the binary tree.
--
ciao
dennis
"I hear and I forget,
I see and I remember,
I do and I understand"
From nick.name@inwind.it Thu Sep 19 21:06:59 2002
From: nick.name@inwind.it (Nick Name)
Date: Thu, 19 Sep 2002 22:06:59 +0200
Subject: "zipping" two streams in the IO monad
Message-ID: <20020919220659.622e1a77.nick.name@inwind.it>
How could I "zip" two possibily infinite streams obtained by IO
operations, for example to return the infinite list of pairs of values
read both from channel a and from channel b with getChanContents?
In general, how does one implement a function like "getChanContents"
wich returns an infinite list? Tell me just some pointer to information
of course, I don't want an entire functional programming lesson :)
Vincenzo
From duncan@coutts.uklinux.net Thu Sep 19 21:28:31 2002
From: duncan@coutts.uklinux.net (Duncan Coutts)
Date: Thu, 19 Sep 2002 21:28:31 +0100
Subject: "zipping" two streams in the IO monad
In-Reply-To: <20020919220659.622e1a77.nick.name@inwind.it>
References: <20020919220659.622e1a77.nick.name@inwind.it>
Message-ID: <20020919212831.6b85a225.duncan@coutts.uklinux.net>
On Thu, 19 Sep 2002 22:06:59 +0200
Nick Name wrote:
> In general, how does one implement a function like "getChanContents"
> wich returns an infinite list? Tell me just some pointer to information
> of course, I don't want an entire functional programming lesson :)
See unsafeInterleaveIO:
http://www.haskell.org/ghc/docs/latest/html/base/System.IO.Unsafe.html#unsafeInterleaveIO
This is how getContents is implemented so that it reads the file lazily.
It is "unsafe" in that it doesn't guarantee any particuar order of evaluation with respect to other IO operations.
Duncan
From nick.name@inwind.it Thu Sep 19 21:35:25 2002
From: nick.name@inwind.it (Nick Name)
Date: Thu, 19 Sep 2002 22:35:25 +0200
Subject: "zipping" two streams in the IO monad
In-Reply-To: <20020919212831.6b85a225.duncan@coutts.uklinux.net>
References: <20020919220659.622e1a77.nick.name@inwind.it>
<20020919212831.6b85a225.duncan@coutts.uklinux.net>
Message-ID: <20020919223525.7667575b.nick.name@inwind.it>
On Thu, 19 Sep 2002 21:28:31 +0100
Duncan Coutts wrote:
>
> See unsafeInterleaveIO:
Thanks for help, I'm going to look at it.
Vincenzo
From droundy@civet.berkeley.edu Sat Sep 21 12:30:03 2002
From: droundy@civet.berkeley.edu (David Roundy)
Date: Sat, 21 Sep 2002 07:30:03 -0400
Subject: question regarding ordering of function definitions
Message-ID: <20020921112937.GA9057@jdj5.mit.edu>
Hello all!
I've just started learning (and using haskell), and am also using the
literate comment mode (latex style), and just ran into a problem that seems
like it ought to have a simple solution, which is that it seems that
haskell requires you to define all the variations of a function
sequentially, which is raining on my literate programming parade.
Here is what I'd like to do:
\begin{code}
data D = A String | B String
instance Show D where
show = showD
instance Read D where
readsPrec _ = readsD
readD s = (readsA s) ++ (readsB s)
\end{code}
A is formatted like ``A string''.
\begin{code}
showD (A s) = "A " ++ s
readsA s = [(A thestr, r) | ("A", x) <- mylex s,
(thestr, r) <- mylex x]
\end{code}
B is formatted like ``B string''.
\begin{code}
showD (B s) = "B " ++ s
readsB s = [(B thestr, r) | ("B", x) <- mylex s,
(thestr, r) <- mylex x]
\end{code}
The problem I have is that ghc complains because I've split up the
definition of showD with readsA defined in between. This surprised me,
since it seemed that the code should still be unambiguous.
Is there some nice way around this, or do I have to define a separate
function for each constructor, and then have a list in one place (as I do
with the readsD, in that case because pattern matching won't give me what I
want), like:
showD (A s) = showA (A s)
showD (B s) = showB (B s)
Of course, in my actual example, there are more than two constructors, and
the parsing is considerably more complex, which is why I'd like to put the
analagous showing and parsing right next to eachother along with a
description of what the formatting is intended to be.
--
David Roundy
http://civet.berkeley.edu/droundy/
From franka@cs.uu.nl Sat Sep 21 13:55:24 2002
From: franka@cs.uu.nl (Frank Atanassow)
Date: Sat, 21 Sep 2002 14:55:24 +0200
Subject: Show the components of the sum
In-Reply-To: <20020921112937.GA9057@jdj5.mit.edu>
References: <20020921112937.GA9057@jdj5.mit.edu>
Message-ID: <20020921125524.GA8728@cs.uu.nl>
David Roundy wrote (on 21-09-02 07:30 -0400):
> Here is what I'd like to do:
>
> \begin{code}
> data D = A String | B String
> instance Show D where
> show = showD
> instance Read D where
> readsPrec _ = readsD
> readD s = (readsA s) ++ (readsB s)
> \end{code}
>
> A is formatted like ``A string''.
> \begin{code}
> showD (A s) = "A " ++ s
> readsA s = [(A thestr, r) | ("A", x) <- mylex s,
> (thestr, r) <- mylex x]
> \end{code}
.. [ and similarly for B ] ...
>
> The problem I have is that ghc complains because I've split up the
> definition of showD with readsA defined in between. This surprised me,
> since it seemed that the code should still be unambiguous.
>
> Is there some nice way around this,
There's no way to intersperse clauses of top-level declarations, no.
> or do I have to define a separate
> function for each constructor, and then have a list in one place (as I do
> with the readsD, in that case because pattern matching won't give me what I
> want), like:
>
> showD (A s) = showA (A s)
> showD (B s) = showB (B s)
Almost. But then showA and showB are partial. It's better to do this:
showA s = "A " ++ s
and similarly for B, and then:
data D = A String | B String
instance Show D where
show (A s) = showA s
show (B s) = showB s
instance Read D where
readsPrec _ = readsD
readD s = (readsA s) ++ (readsB s)
What you are doing here basically is just assigning names to the branches of a
case-expression:
h sum =
case sum of
Left x -> ... x ...
Right y -> ... y ...
<=
h sum =
case sum of
Left x -> (\x' -> ... x' ...) x
Right y -> (\y' -> ... y' ...) y
<=
h sum =
let f x' = ... x' ...
g y' = ... y' ...
in case sum of
Left x -> f x
Right y -> g y
<=
f x' = ... x' ...
g y' = ... y' ...
h (Left x) = f x
h (Right y) = g y
--
Frank
From roconnor@Math.Berkeley.EDU Sat Sep 21 20:56:13 2002
From: roconnor@Math.Berkeley.EDU (Russell O'Connor)
Date: Sat, 21 Sep 2002 12:56:13 -0700 (PDT)
Subject: Monad Maybe?
Message-ID:
-----BEGIN PGP SIGNED MESSAGE-----
Hash: SHA1
[To: haskell-cafe@haskell.org]
Is there a nicer way of writing the following sort of code?
case (number g) of
Just n -> Just (show n)
Nothing ->
case (fraction g) of
Just n -> Just (show n)
Nothing ->
case (nimber g) of
Just n -> Just ("*"++(show n))
Nothing -> Nothing
- --
Russell O'Connor roconnor@math.berkeley.edu
``Any time you skip a commercial [...] you're actually stealing the
programming'' -- Jamie Kellner, CEO of TBS
-----BEGIN PGP SIGNATURE-----
Version: GnuPG v1.0.6 (SunOS)
Comment: For info see http://www.gnupg.org
iD8DBQE9jM7juZUa0PWVyWQRAjmlAJ9+YDXUEXEhLTtb2huBZKskJ9JvegCgjPb2
iGb/vYYLK7I+UdfijtEePyQ=
=6UZh
-----END PGP SIGNATURE-----
From dpt@math.harvard.edu Sat Sep 21 23:42:12 2002
From: dpt@math.harvard.edu (Dylan Thurston)
Date: Sat, 21 Sep 2002 18:42:12 -0400
Subject: Monad Maybe?
In-Reply-To:
References:
Message-ID: <20020921224212.GB19418@lotus.bostoncoop.net>
--EuxKj2iCbKjpUGkD
Content-Type: text/plain; charset=us-ascii
Content-Disposition: inline
Content-Transfer-Encoding: quoted-printable
On Sat, Sep 21, 2002 at 12:56:13PM -0700, Russell O'Connor wrote:
> -----BEGIN PGP SIGNED MESSAGE-----
> Hash: SHA1
>=20
> [To: haskell-cafe@haskell.org]
>=20
> Is there a nicer way of writing the following sort of code?
>=20
> case (number g) of
> Just n -> Just (show n)
> Nothing ->
> case (fraction g) of
> Just n -> Just (show n)
> Nothing ->
> case (nimber g) of
> Just n -> Just ("*"++(show n))
> Nothing -> Nothing
You could write (using GHC's pattern guards):
show g | Just n =3D number g =3D Just (show n)
| Just n =3D fraction g =3D Just (show n)
| Just n =3D nimber g =3D Just ("*"++show n)
| Nothing =3D Nothing
Do I detect a program for analyzing combinatorial games being written?
--Dylan
--EuxKj2iCbKjpUGkD
Content-Type: application/pgp-signature
Content-Disposition: inline
-----BEGIN PGP SIGNATURE-----
Version: GnuPG v1.0.7 (GNU/Linux)
iD8DBQE9jPXEVeybfhaa3tcRArsPAJ9LSm/YUfL4ohVMMeXYRI7Zkhup6gCdGu2n
y5HgyZSr1X6BW6G76uJZNTw=
=5bPk
-----END PGP SIGNATURE-----
--EuxKj2iCbKjpUGkD--
From pixel@mandrakesoft.com Sat Sep 21 23:40:46 2002
From: pixel@mandrakesoft.com (Pixel)
Date: 22 Sep 2002 00:40:46 +0200
Subject: Monad Maybe?
In-Reply-To:
References:
Message-ID:
"Russell O'Connor" writes:
> [To: haskell-cafe@haskell.org]
>
> Is there a nicer way of writing the following sort of code?
>
> case (number g) of
> Just n -> Just (show n)
> Nothing ->
> case (fraction g) of
> Just n -> Just (show n)
> Nothing ->
> case (nimber g) of
> Just n -> Just ("*"++(show n))
> Nothing -> Nothing
what about?
listToMaybe $ mapMaybe (\ (f, format) -> fmap format (f g)) l
where l = [ (number, show), (fraction, show), (nimber, (\ n -> "*" ++ show n)) ]
or:
if_just (number g) show $
if_just (fraction g) show $
if_just (nimber g) (\ n -> "*" ++ show n) Nothing
using:
if_just (Just e) f _ = Just(f e)
if_just Nothing _ f = f
From ken@digitas.harvard.edu Sat Sep 21 23:37:53 2002
From: ken@digitas.harvard.edu (Ken Shan)
Date: Sat, 21 Sep 2002 18:37:53 -0400
Subject: Monad Maybe?
In-Reply-To:
References:
Message-ID: <20020921223753.GA9857@proper.eecs.harvard.edu>
--45Z9DzgjV8m4Oswq
Content-Type: text/plain; charset=us-ascii
Content-Disposition: inline
Content-Transfer-Encoding: quoted-printable
On 2002-09-21T12:56:13-0700, Russell O'Connor wrote:
> case (number g) of
> Just n -> Just (show n)
> Nothing ->
> case (fraction g) of
> Just n -> Just (show n)
> Nothing ->
> case (nimber g) of
> Just n -> Just ("*"++(show n))
> Nothing -> Nothing
How about something like:
msum [ liftM show (number g)
, liftM show (fraction g)
, liftM (("*"++).show) (nimber g) ]
--=20
Edit this signature at http://www.digitas.harvard.edu/cgi-bin/ken/sig
So the choice which Lomborg presents us with, of whether to save a drowning
Tuvaluan (climate change) or a dying Somalian (water and sanitation) is not=
=20
a choice at all -- in fact we need to do both, and not least because one is
unlikely to be successful without the other. http://www.anti-lomborg.com/
--45Z9DzgjV8m4Oswq
Content-Type: application/pgp-signature
Content-Disposition: inline
-----BEGIN PGP SIGNATURE-----
Version: GnuPG v1.0.7 (GNU/Linux)
iD8DBQE9jPTAzjAc4f+uuBURAurxAKD8SSuUzXx2D3ZsLkYb9ZPY+mZgkgCfUhc0
hVfK4vjO/jQfvgXwyqSvG+o=
=MHO1
-----END PGP SIGNATURE-----
--45Z9DzgjV8m4Oswq--
From hdaume@ISI.EDU Sun Sep 22 00:54:22 2002
From: hdaume@ISI.EDU (Hal Daume III)
Date: Sat, 21 Sep 2002 16:54:22 -0700 (PDT)
Subject: Monad Maybe?
In-Reply-To: <20020921224212.GB19418@lotus.bostoncoop.net>
Message-ID:
> show g | Just n = number g = Just (show n)
> | Just n = fraction g = Just (show n)
> | Just n = nimber g = Just ("*"++show n)
> | Nothing = Nothing
These should be "Just n <- number g", not "="
- Hal
From ajb@spamcop.net Sun Sep 22 04:30:43 2002
From: ajb@spamcop.net (Andrew J Bromage)
Date: Sun, 22 Sep 2002 13:30:43 +1000
Subject: Monad Maybe?
In-Reply-To:
References:
Message-ID: <20020922033043.GA7175@smtp.alicorna.com>
G'day all.
On Sat, Sep 21, 2002 at 12:56:13PM -0700, Russell O'Connor wrote:
> case (number g) of
> Just n -> Just (show n)
> Nothing ->
> case (fraction g) of
> Just n -> Just (show n)
> Nothing ->
> case (nimber g) of
> Just n -> Just ("*"++(show n))
> Nothing -> Nothing
This isn't exactly the most beautiful way of doing it, but...
(number g >>= return . show) `mplus`
(fraction g >>= return . show) `mplus`
(nimber g >>= return . ('*':) . show)
Cheers,
Andrew Bromage
From droundy@jdj5.mit.edu Mon Sep 23 15:06:14 2002
From: droundy@jdj5.mit.edu (David Roundy)
Date: Mon, 23 Sep 2002 10:06:14 -0400
Subject: Show the components of the sum
In-Reply-To: <20020921125524.GA8728@cs.uu.nl>
References: <20020921112937.GA9057@jdj5.mit.edu>
<20020921125524.GA8728@cs.uu.nl>
Message-ID: <20020923140613.GE1500@jdj5.mit.edu>
On Sat, Sep 21, 2002 at 02:55:24PM +0200, Frank Atanassow wrote:
>
> Almost. But then showA and showB are partial. It's better to do this:
>
> showA s = "A " ++ s
>
> and similarly for B, and then:
>
> data D = A String | B String
> instance Show D where
> show (A s) = showA s
> show (B s) = showB s
> instance Read D where
> readsPrec _ = readsD
> readD s = (readsA s) ++ (readsB s)
Thank you for this advice! This solved my quandry quite cleanly.
--
David Roundy
http://civet.berkeley.edu/droundy/
From hdaume@ISI.EDU Mon Sep 23 22:57:45 2002
From: hdaume@ISI.EDU (Hal Daume III)
Date: Mon, 23 Sep 2002 14:57:45 -0700 (PDT)
Subject: Monad Maybe?
In-Reply-To: <20020922033043.GA7175@smtp.alicorna.com>
Message-ID:
I know this has been written about way too much, but I was wondering what
people thought about using 'liftM f' as opposed to '>>= return . f'. I
would probably have written Andrew's code using liftM, but I don't know if
one is necessarily better than the other. Does anyone have strong
thoughts on this?
--
Hal Daume III
"Computer science is no more about computers | hdaume@isi.edu
than astronomy is about telescopes." -Dijkstra | www.isi.edu/~hdaume
On Sun, 22 Sep 2002, Andrew J Bromage wrote:
> G'day all.
>
> On Sat, Sep 21, 2002 at 12:56:13PM -0700, Russell O'Connor wrote:
>
> > case (number g) of
> > Just n -> Just (show n)
> > Nothing ->
> > case (fraction g) of
> > Just n -> Just (show n)
> > Nothing ->
> > case (nimber g) of
> > Just n -> Just ("*"++(show n))
> > Nothing -> Nothing
>
> This isn't exactly the most beautiful way of doing it, but...
>
> (number g >>= return . show) `mplus`
> (fraction g >>= return . show) `mplus`
> (nimber g >>= return . ('*':) . show)
>
> Cheers,
> Andrew Bromage
> _______________________________________________
> Haskell-Cafe mailing list
> Haskell-Cafe@haskell.org
> http://www.haskell.org/mailman/listinfo/haskell-cafe
>
From diatchki@cse.ogi.edu Tue Sep 24 00:30:35 2002
From: diatchki@cse.ogi.edu (Iavor Diatchki)
Date: Mon, 23 Sep 2002 16:30:35 -0700
Subject: Monad Maybe?
In-Reply-To: ;
from hdaume@ISI.EDU on Mon, Sep 23, 2002 at 02:57:45PM -0700
References: <20020922033043.GA7175@smtp.alicorna.com>
Message-ID: <20020923163035.C9409@cse.ogi.edu>
hi,
i personally think that one should use fmap instead. it tells
you exactly how much structure you need. having said that it is
sometimes annoying to get the extra Functor constraint (alas
Functor is not a super class of Moand)... so my preference is:
1. fmap
2. liftM
3. bind with return
bye
iavor
On Mon, Sep 23, 2002 at 02:57:45PM -0700, Hal Daume III wrote:
> I know this has been written about way too much, but I was wondering what
> people thought about using 'liftM f' as opposed to '>>= return . f'. I
> would probably have written Andrew's code using liftM, but I don't know if
> one is necessarily better than the other. Does anyone have strong
> thoughts on this?
>
> --
> Hal Daume III
>
> "Computer science is no more about computers | hdaume@isi.edu
> than astronomy is about telescopes." -Dijkstra | www.isi.edu/~hdaume
>
> On Sun, 22 Sep 2002, Andrew J Bromage wrote:
>
> > G'day all.
> >
> > On Sat, Sep 21, 2002 at 12:56:13PM -0700, Russell O'Connor wrote:
> >
> > > case (number g) of
> > > Just n -> Just (show n)
> > > Nothing ->
> > > case (fraction g) of
> > > Just n -> Just (show n)
> > > Nothing ->
> > > case (nimber g) of
> > > Just n -> Just ("*"++(show n))
> > > Nothing -> Nothing
> >
> > This isn't exactly the most beautiful way of doing it, but...
> >
> > (number g >>= return . show) `mplus`
> > (fraction g >>= return . show) `mplus`
> > (nimber g >>= return . ('*':) . show)
> >
> > Cheers,
> > Andrew Bromage
> > _______________________________________________
> > 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
--
---------------------------------------+----------------------------------------
Iavor S. Diatchki | email: diatchki@cse.ogi.edu
Dept. of Computer Science | web: http://www.cse.ogi.edu/~diatchki
OGI School of Science and Engineering | work phone: 5037481631
OHSU | home phone: 5036434085
---------------------------------------+----------------------------------------
From =?KOI8-R?Q?=F6=C2=C1=CE=CF=D7_=F0=C1=D7=C5=CC_=E7=C5=CE=CE=C1=C4?= Tue Sep 24 12:14:28 2002
From: =?KOI8-R?Q?=F6=C2=C1=CE=CF=D7_=F0=C1=D7=C5=CC_=E7=C5=CE=CE=C1=C4?= (=?KOI8-R?Q?=F6=C2=C1=CE=CF=D7_=F0=C1=D7=C5=CC_=E7=C5=CE=CE=C1=C4?=)
Date: Tue, 24 Sep 2002 15:14:28 +0400
Subject: Problems with IO
Message-ID: <3D904914.9090501@joker.botik.ru>
I'm having a problem with writing a function dealing with I/O. Maybe
it's just a lack of experience or simple Haskell knowledge because I'm
just a beginer. The problem:
I want to write a function that converts an IO String into String
lala :: IO String -> String
Is it possible? If yes, how?
--
öÂÁÎÏ× ğÁ×ÅÌ
From =?ISO-8859-1?Q?=3F=3F=3F=3F=3F=3F_=3F=3F=3F=3F=3F_=3F=3F=3F=3F=3F?= Tue Sep 24 12:46:49 2002
From: =?ISO-8859-1?Q?=3F=3F=3F=3F=3F=3F_=3F=3F=3F=3F=3F_=3F=3F=3F=3F=3F?= (=?ISO-8859-1?Q?=3F=3F=3F=3F=3F=3F_=3F=3F=3F=3F=3F_=3F=3F=3F=3F=3F?=)
Date: Tue, 24 Sep 2002 15:46:49 +0400
Subject: Problems with IO
References:
Message-ID: <3D9050A7.4070001@joker.botik.ru>
Now I understand that it's just a lack of knowledge... Sorry for
interrupring...
By the way, can you recommend a good manual which I can find on the web?
--
Zhbanov Pavel
From glynn.clements@virgin.net Tue Sep 24 12:49:33 2002
From: glynn.clements@virgin.net (Glynn Clements)
Date: Tue, 24 Sep 2002 12:49:33 +0100
Subject: Problems with IO
In-Reply-To: <3D9050A7.4070001@joker.botik.ru>
References:
<3D9050A7.4070001@joker.botik.ru>
Message-ID: <15760.20813.158394.704537@cerise.nosuchdomain.co.uk>
Zhbanov Pavel wrote:
> Now I understand that it's just a lack of knowledge... Sorry for
> interrupring...
>
> By the way, can you recommend a good manual which I can find on the web?
Tutorial:
http://www.haskell.org/tutorial/
Reference Manual:
http://www.haskell.org/definition/
Further Information:
http://www.haskell.org/bookshelf/
--
Glynn Clements
From herrmann@fmi.uni-passau.de Tue Sep 24 12:57:28 2002
From: herrmann@fmi.uni-passau.de (Ch. A. Herrmann)
Date: Tue, 24 Sep 2002 13:57:28 +0200
Subject: Problems with IO
In-Reply-To: <3D9050A7.4070001@joker.botik.ru>
References:
<3D9050A7.4070001@joker.botik.ru>
Message-ID: <15760.21288.977737.108027@debussy.fmi.uni-passau.de>
>>>>> "pavel" == pavel writes:
pavel> Now I understand that it's just a lack of knowledge... Sorry
pavel> for interrupring...
pavel> By the way, can you recommend a good manual which I can find
pavel> on the web?
The best source would be a good book like Simon Thompsons:
"Haskell: The Craft of Functional Programming", published
by Addison-Wesley. I/O is described in Chapter 18 on page 383
which makes clear that I/O is not the first thing you should
try when learning Haskell. Use an interpreter like ghci first
and evaluate expressions in interaction with the interpreter.
You can also find a tutorial on the web at:
http://www.haskell.org/tutorial/
Cheers
--
Christoph Herrmann
From =?ISO-8859-1?Q?=3F=3F=3F=3F=3F=3F_=3F=3F=3F=3F=3F_=3F=3F=3F=3F=3F?= Tue Sep 24 13:59:07 2002
From: =?ISO-8859-1?Q?=3F=3F=3F=3F=3F=3F_=3F=3F=3F=3F=3F_=3F=3F=3F=3F=3F?= (=?ISO-8859-1?Q?=3F=3F=3F=3F=3F=3F_=3F=3F=3F=3F=3F_=3F=3F=3F=3F=3F?=)
Date: Tue, 24 Sep 2002 16:59:07 +0400
Subject: Problems with IO
References:
<3D9050A7.4070001@joker.botik.ru>
<15760.21288.977737.108027@debussy.fmi.uni-passau.de>
Message-ID: <3D906187.7060109@joker.botik.ru>
My task is to write a parser for some language (TSG). I'm using an
UU_Parsing library.
I wrote that parser even tested it by using some example provided, but I
have problems with using my parser.
I wrote a function:
> test :: [Char] -> IO ()
> test inp = do res <- parseIO pTSG inp
> print res
parseIO :: InputState a b => AnaParser a Pair b c -> a b -> IO c
is provided by the library, pTSG is my parser and inp is a String that
I'm parsing.
How can I use that function "test" while using readFile?
Is it something like:
> test1 file = do inp <- readFile file
> test inp
Why should I use that "do" thing? What is so "magical" in it?
PS: Please, don't say that I'm stupid, I just have problem with
understanding IO/Monad part, besides that is just me second week of
Haskell... :)
PS1: "Haskell: The Craft of Functional Programming" didn't make that
part clear to me. That's why I'm writing...
--
Pavel Zhbanov
From herrmann@fmi.uni-passau.de Tue Sep 24 14:15:05 2002
From: herrmann@fmi.uni-passau.de (Ch. A. Herrmann)
Date: Tue, 24 Sep 2002 15:15:05 +0200
Subject: Problems with IO
In-Reply-To: <3D906187.7060109@joker.botik.ru>
References:
<3D9050A7.4070001@joker.botik.ru>
<15760.21288.977737.108027@debussy.fmi.uni-passau.de>
<3D906187.7060109@joker.botik.ru>
Message-ID: <15760.25945.903554.449036@debussy.fmi.uni-passau.de>
Hi Pavel,
>>>>> "pavel" == pavel writes:
pavel> My task is to write a parser for some language (TSG).
pavel> ...
pavel> Why should I use that "do" thing? What is so "magical" in it?
pavel> PS: Please, don't say that I'm stupid, I just have problem
pavel> with understanding IO/Monad part, besides that is just me
pavel> second week of Haskell... :)
I think that your task is not appropriate for a Haskell beginner.
You should go to the person who gave you the task and tell
him/her that you need much more time to learn Haskell, understand
how monads are to be used and, maybe, what type classes are.
Otherwise, you cannot guarantee that your program will
work the way it is supposed to.
Good luck
--
Christoph
From simonmar@microsoft.com Tue Sep 24 14:24:47 2002
From: simonmar@microsoft.com (Simon Marlow)
Date: Tue, 24 Sep 2002 14:24:47 +0100
Subject: Monad Maybe?
Message-ID: <9584A4A864BD8548932F2F88EB30D1C60A69EA83@TVP-MSG-01.europe.corp.microsoft.com>
> I know this has been written about way too much, but I was=20
> wondering what
> people thought about using 'liftM f' as opposed to '>>=3D=20
> return . f'. I
> would probably have written Andrew's code using liftM, but I=20
> don't know if
> one is necessarily better than the other. Does anyone have strong
> thoughts on this?
so, using liftM:
(number g >>=3D return . show)
becomes
(liftM show (number g))
or
(show `liftM` number g)
but it's important not to get too carried away with abstractions - this
example requires a bit of a trawl around the library documentation for
someone not familiar with liftM. Personally, unless I was writing
fragments like this a lot, I'd just write it as
(do r <- number g; return (show r))
Each to his own I suppose.
Cheers,
Simon
From alastair@reid-consulting-uk.ltd.uk Tue Sep 24 17:28:18 2002
From: alastair@reid-consulting-uk.ltd.uk (Alastair Reid)
Date: 24 Sep 2002 17:28:18 +0100
Subject: Monad Maybe?
In-Reply-To:
References:
Message-ID:
Hal Daume writes:
> I know this has been written about way too much, but I was wondering
> what people thought about using 'liftM f' as opposed to '>>= return . f'.
> I would probably have written Andrew's code using liftM, but
> I don't know if one is necessarily better than the other. Does
> anyone have strong thoughts on this?
I tend to use liftM only as part of a pattern of lifting a family of
non-monadic functions up to the monadic level in code like this:
instance (Monad m, Num a) => Num (m a) where
(+) = liftM2 (+)
(-) = liftM2 (-)
negate = liftM1 negate
...
instance (Monad m, Integral a) => Integral (m a) where
...
If it doesn't feel like lifting and/or it isn't part of a pattern like
the above, I tend not to use it.
A
From gkosmidis@epsilon7.gr Wed Sep 25 14:14:06 2002
From: gkosmidis@epsilon7.gr (=?iso-8859-1?Q?G=3F=3F=3F=3F=3F=3F_=3F=3Fs=B5=3Fd=3F=3F?=)
Date: Wed, 25 Sep 2002 16:14:06 +0300
Subject: new to haskell-not working for some reason
References: <20020918160103.9F2AC4223C1@www.haskell.org><001301c25fac$fbdddcb0$6000000a@dbserver><20020919134915.5c7190f4.Malcolm.Wallace@cs.york.ac.uk><009901c25fe9$86b08810$6000000a@dbserver>
<20020919153326.42949bb9.Malcolm.Wallace@cs.york.ac.uk>
Message-ID: <001801c26495$6e40cb40$6000000a@dbserver>
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)
From hdaume@ISI.EDU Wed Sep 25 15:44:33 2002
From: hdaume@ISI.EDU (Hal Daume III)
Date: Wed, 25 Sep 2002 07:44:33 -0700 (PDT)
Subject: new to haskell-not working for some reason
In-Reply-To: <001801c26495$6e40cb40$6000000a@dbserver>
Message-ID:
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
From carctol@yahoo.com Wed Sep 25 22:13:09 2002
From: carctol@yahoo.com (carctol@yahoo.com)
Date: Wed, 25 Sep 2002 17:13:09 -0400 (EDT)
Subject: Kanser tedavisi
Message-ID: <20020925211309.19D24422078@www.haskell.org>
charset="US-ASCII";
charset="US-ASCII";
charset="US-ASCII";
charset="US-ASCII"
Reply-To: carctol@yahoo.com
Date: Thu, 26 Sep 2002 00:12:08 +0300
X-Priority: 3
X-Library: Indy 9.00.10
X-Mailer: Foxmail
Kemoterapinin yan etkileri nedeniyle yorgun ve bitkin düsmüs bir yakininiz mi var? Yanitiniz evetse vakit kaybetmeyin ve CARCTOL'u denemesini saglayin. Genelde ancak klasik tedavinin ise yaramadiginin anlasilmasi, insanlari baska seçenekler aramaya itmektedir, ancak o durumda maalesef yapacak fazla birsey kalmamaktadir. Ayni hatanin yapilmasina izin vermeyin ve hiçbir yan etkisi olmayan, Himalaya Dagi bitkilerinden üretilen Carctol'u denemesini saglayin. CARCTOL, birkaç bin yillik, alternatif Hint Tibbinin (Ayuverda'nin) insanliga sundugu bir umut isigidir. Önceleri vücudu takviye edici tonik olarak kullanilan bu ürün simdi yeni formülüyle kansere karsi etkili bir ilaçtir
Lütfen asagidaki siteye ugrayin ve Carctol'u yakindan taniyin.
http://www.kanser-tedavisi.com esenlikler dileriz..
Listeden adinizin silinmesini istiyorsaniz a_cengiz2002@yahoo.com a bos e posta yollayin. Tesekkürler
From liyang@nerv.cx Thu Sep 26 00:06:36 2002
From: liyang@nerv.cx (Liyang Hu)
Date: Thu, 26 Sep 2002 00:06:36 +0100
Subject: Dealing with configuration data
Message-ID: <20020925230636.GA30622@sakura.local.nerv.cx>
--mYCpIKhGyMATD0i+
Content-Type: text/plain; charset=us-ascii
Content-Disposition: inline
Content-Transfer-Encoding: quoted-printable
Evening,
I'm trying to write a utility that reads in some user preferences from
a pre-determined file, does some work, and exits. Sounds simple enough.
The problem I'm having is with the preferences: How do I make it
available throughout the entire program? (FWIW, most of the work is
effectively done inside the IO monad.) I could explicitly pass the
record around everywhere, but that seems a trifle inelegant.
My current solution is to use a global ('scuse my terminology, I'm not
sure that's the right word to use here) variable of type IORef Config
obtained through unsafePerformIO. It works, but strikes me as a rather
barbaric solution to a seemingly tame enough problem...
Intuition tells me I should be able to `embed', if you will, the config
record somehow within or alongside the IO state, and retrieve it at
will. (Is this what MonadState is for?) However it also tells me that
this will /probably/ involve lots of needless lifting and rewriting of
the existing code, which makes it even less enticing than passing
everything around explicitly.
Any opinions or suggestions?
Cheers,
/Liyang
--=20
=2E--{ Liyang HU }--{ http://nerv.cx/ }--{ Caius@Cam }--{ ICQ: 39391385 }--.
| :: zettai unmei mokusiroku :::: absolute destined apocalypse ::::::::: |
--mYCpIKhGyMATD0i+
Content-Type: application/pgp-signature
Content-Disposition: inline
-----BEGIN PGP SIGNATURE-----
Version: GnuPG v1.0.6 (GNU/Linux)
Comment: moo! (ID: 7B632CB8)
iEYEARECAAYFAj2SQXwACgkQ1QR4EHtjLLjwHwCg7cZF+od6Ow+2xmBDVdN5W5K7
HaUAnjeTfReSxXfw02eat0sF0hgQStAi
=Oxsh
-----END PGP SIGNATURE-----
--mYCpIKhGyMATD0i+--
From hdaume@ISI.EDU Thu Sep 26 00:06:29 2002
From: hdaume@ISI.EDU (Hal Daume III)
Date: Wed, 25 Sep 2002 16:06:29 -0700 (PDT)
Subject: Dealing with configuration data
In-Reply-To: <20020925230636.GA30622@sakura.local.nerv.cx>
Message-ID:
AFAIK, the global variable (so-called), passing around, and lifting the IO
monad are your only options. I almost always use the global variable
method since I know that in this case the unsafePerformIO is actually
safe, since writing to the variable will always occur before the call to
upIO and that it will only be written once. I don't feel bad about doing
this because GHC does this itself for its own configuration :).
--
Hal Daume III
"Computer science is no more about computers | hdaume@isi.edu
than astronomy is about telescopes." -Dijkstra | www.isi.edu/~hdaume
On Thu, 26 Sep 2002, Liyang Hu wrote:
> Evening,
>
> I'm trying to write a utility that reads in some user preferences from
> a pre-determined file, does some work, and exits. Sounds simple enough.
>
> The problem I'm having is with the preferences: How do I make it
> available throughout the entire program? (FWIW, most of the work is
> effectively done inside the IO monad.) I could explicitly pass the
> record around everywhere, but that seems a trifle inelegant.
>
> My current solution is to use a global ('scuse my terminology, I'm not
> sure that's the right word to use here) variable of type IORef Config
> obtained through unsafePerformIO. It works, but strikes me as a rather
> barbaric solution to a seemingly tame enough problem...
>
> Intuition tells me I should be able to `embed', if you will, the config
> record somehow within or alongside the IO state, and retrieve it at
> will. (Is this what MonadState is for?) However it also tells me that
> this will /probably/ involve lots of needless lifting and rewriting of
> the existing code, which makes it even less enticing than passing
> everything around explicitly.
>
> Any opinions or suggestions?
>
> Cheers,
> /Liyang
> --
> .--{ Liyang HU }--{ http://nerv.cx/ }--{ Caius@Cam }--{ ICQ: 39391385 }--.
> | :: zettai unmei mokusiroku :::: absolute destined apocalypse ::::::::: |
>
From hdaume@ISI.EDU Thu Sep 26 00:09:24 2002
From: hdaume@ISI.EDU (Hal Daume III)
Date: Wed, 25 Sep 2002 16:09:24 -0700 (PDT)
Subject: Dealing with configuration data
In-Reply-To:
Message-ID:
Sorry, I should also mention implicit parameters, if you're willing to use
that extension. I don't like them, though, and my impression from SPJ is
that it's very unclear whether they will get into Haskell 2 or not...
--
Hal Daume III
"Computer science is no more about computers | hdaume@isi.edu
than astronomy is about telescopes." -Dijkstra | www.isi.edu/~hdaume
On Wed, 25 Sep 2002, Hal Daume III wrote:
> AFAIK, the global variable (so-called), passing around, and lifting the IO
> monad are your only options. I almost always use the global variable
> method since I know that in this case the unsafePerformIO is actually
> safe, since writing to the variable will always occur before the call to
> upIO and that it will only be written once. I don't feel bad about doing
> this because GHC does this itself for its own configuration :).
>
> --
> Hal Daume III
>
> "Computer science is no more about computers | hdaume@isi.edu
> than astronomy is about telescopes." -Dijkstra | www.isi.edu/~hdaume
>
> On Thu, 26 Sep 2002, Liyang Hu wrote:
>
> > Evening,
> >
> > I'm trying to write a utility that reads in some user preferences from
> > a pre-determined file, does some work, and exits. Sounds simple enough.
> >
> > The problem I'm having is with the preferences: How do I make it
> > available throughout the entire program? (FWIW, most of the work is
> > effectively done inside the IO monad.) I could explicitly pass the
> > record around everywhere, but that seems a trifle inelegant.
> >
> > My current solution is to use a global ('scuse my terminology, I'm not
> > sure that's the right word to use here) variable of type IORef Config
> > obtained through unsafePerformIO. It works, but strikes me as a rather
> > barbaric solution to a seemingly tame enough problem...
> >
> > Intuition tells me I should be able to `embed', if you will, the config
> > record somehow within or alongside the IO state, and retrieve it at
> > will. (Is this what MonadState is for?) However it also tells me that
> > this will /probably/ involve lots of needless lifting and rewriting of
> > the existing code, which makes it even less enticing than passing
> > everything around explicitly.
> >
> > Any opinions or suggestions?
> >
> > Cheers,
> > /Liyang
> > --
> > .--{ Liyang HU }--{ http://nerv.cx/ }--{ Caius@Cam }--{ ICQ: 39391385 }--.
> > | :: zettai unmei mokusiroku :::: absolute destined apocalypse ::::::::: |
> >
>
> _______________________________________________
> Haskell-Cafe mailing list
> Haskell-Cafe@haskell.org
> http://www.haskell.org/mailman/listinfo/haskell-cafe
>
From nick.name@inwind.it Thu Sep 26 00:33:14 2002
From: nick.name@inwind.it (Nick Name)
Date: Thu, 26 Sep 2002 01:33:14 +0200
Subject: Dealing with configuration data
In-Reply-To:
References: <20020925230636.GA30622@sakura.local.nerv.cx>
Message-ID: <20020926013314.5da489b7.nick.name@inwind.it>
On Wed, 25 Sep 2002 16:06:29 -0700 (PDT)
Hal Daume III wrote:
> I don't feel bad about doing
> this because GHC does this itself for its own configuration :).
I am going to show you that using unsafePerformIO where there really are
side effects leads to unpredictable results, and is generally wrong in a
lazy language. Don't hate me for this :)
Consider this example (supposing that a Config is represented by an
Int):
storeConfig :: Int -> ()
readConfig :: Int
They both are obtained through the use of "unsafePerformIO".
Now, say I got this code:
(storeConfig 0,storeConfig 1,readConfig,storeConfig 0,readConfig)
What is this 5-uple supposed to evaluate to?
First of all, this depends on order of evaluation. We can't say that all
the elements of the tuple will be evaluated, so we can't tell if the
fifth readConfig will evaluate to 0 or 1 (if the third storeConfig is
never evaluated, readConfig will evaluate to 0, else to 1) This is one
of the causes of the use of monads: ensuring correct order of
evaluation.
Second, suppose we were able to force order of evaluation (which
shouldn't be allowed, in a lazy language). We still can't say what the
last "readConfig" would evaluate to, since we don't know if the compiler
is substituting equals for equals (I am expecting a lazy functional
language to do this).
If the compiler does, the last readConfig is equal to the first (in
fact, by the use of unsafePerformIO, you have told the compiler that
both the functions storeConfig and readConfig are pure, which is not
true) and will evaluate to 1, else it will evaluate to 0. And, besides,
the compiler should also substitute the second "storeConfig 0" with the
result of the first occurrence, so it would not evaluate the second
"storeConfig" at all.
This is another example of the need for monads: allowing program
transformations, first of all substituting equals for equals.
This is why (even if, by enough knoweledge of the implementation, we
could), by only relying on the semantics of a lazy language, we can not
have functions with side effects.
If it wasn't so, they would not have invented monads, believe me.
I apologize, as always, for my terrible english, and hope I have been
clear.
Vincenzo Ciancia
From jadrian@mat.uc.pt Thu Sep 26 00:31:00 2002
From: jadrian@mat.uc.pt (Jorge Adriano)
Date: Thu, 26 Sep 2002 00:31:00 +0100
Subject: Dealing with configuration data
In-Reply-To: <20020925230636.GA30622@sakura.local.nerv.cx>
References: <20020925230636.GA30622@sakura.local.nerv.cx>
Message-ID: <200209260030.12960.jadrian@mat.uc.pt>
> Evening,
>
> I'm trying to write a utility that reads in some user preferences from
> a pre-determined file, does some work, and exits. Sounds simple enough.
>
> The problem I'm having is with the preferences: How do I make it
> available throughout the entire program? (FWIW, most of the work is
> effectively done inside the IO monad.) I could explicitly pass the
> record around everywhere, but that seems a trifle inelegant.
>
> My current solution is to use a global ('scuse my terminology, I'm not
> sure that's the right word to use here) variable of type IORef Config
> obtained through unsafePerformIO. It works, but strikes me as a rather
> barbaric solution to a seemingly tame enough problem...
>
> Intuition tells me I should be able to `embed', if you will, the config
> record somehow within or alongside the IO state, and retrieve it at
> will. (Is this what MonadState is for?) However it also tells me that
> this will /probably/ involve lots of needless lifting and rewriting of
> the existing code, which makes it even less enticing than passing
> everything around explicitly.
This is how I usually do it:
http://www.mail-archive.com/haskell@haskell.org/msg10565.html
(ignore the last part of the post...)
J.A.
From hdaume@ISI.EDU Thu Sep 26 00:34:02 2002
From: hdaume@ISI.EDU (Hal Daume III)
Date: Wed, 25 Sep 2002 16:34:02 -0700 (PDT)
Subject: Dealing with configuration data
In-Reply-To: <20020926013314.5da489b7.nick.name@inwind.it>
Message-ID:
I don't mean to troll, but this isn't what I meant. Suppose we have:
data Configuration = ... -- config data
globalConfig :: IORef Configuration
globalConfig = unsafePerformIO (newIORef undefined)
Now, we define an unsafe function to read the configuration:
getConfig :: Configuration
getConfig = unsafePerformIO $ readIORef globalConfig
Okay, this is "bad" but I claim it's okay, iff it is used as in:
main = do
...read configuration from file...no calls to getConfig...
writeIORef globalConfig configuration
doStuff
return ()
now, we have doStuff :: IO a. doStuff is allowed (even in its pure
methods) to use getConfig. I claim that this is safe. I could be
wrong; this is only a hand-waiving argument. Why?
The first reference in the program to globalConfig is through a
writeIORef. This means that at this point globalConfig gets evaluated and
thus a ref is created. Immediately we put a value in it.
Now, when doStuff runs, since it is an action run *after* the call to
writeIORef, provided that it doesn't also write to 'globalConfig' (which I
mentioned in my original message), any call to getConfig is deterministic.
I could be wrong...please correct me if I am.
--
Hal Daume III
"Computer science is no more about computers | hdaume@isi.edu
than astronomy is about telescopes." -Dijkstra | www.isi.edu/~hdaume
On Thu, 26 Sep 2002, Nick Name wrote:
> On Wed, 25 Sep 2002 16:06:29 -0700 (PDT)
> Hal Daume III wrote:
>
> > I don't feel bad about doing
> > this because GHC does this itself for its own configuration :).
>
> I am going to show you that using unsafePerformIO where there really are
> side effects leads to unpredictable results, and is generally wrong in a
> lazy language. Don't hate me for this :)
>
> Consider this example (supposing that a Config is represented by an
> Int):
>
> storeConfig :: Int -> ()
> readConfig :: Int
>
> They both are obtained through the use of "unsafePerformIO".
>
> Now, say I got this code:
>
> (storeConfig 0,storeConfig 1,readConfig,storeConfig 0,readConfig)
>
> What is this 5-uple supposed to evaluate to?
>
> First of all, this depends on order of evaluation. We can't say that all
> the elements of the tuple will be evaluated, so we can't tell if the
> fifth readConfig will evaluate to 0 or 1 (if the third storeConfig is
> never evaluated, readConfig will evaluate to 0, else to 1) This is one
> of the causes of the use of monads: ensuring correct order of
> evaluation.
>
> Second, suppose we were able to force order of evaluation (which
> shouldn't be allowed, in a lazy language). We still can't say what the
> last "readConfig" would evaluate to, since we don't know if the compiler
> is substituting equals for equals (I am expecting a lazy functional
> language to do this).
>
> If the compiler does, the last readConfig is equal to the first (in
> fact, by the use of unsafePerformIO, you have told the compiler that
> both the functions storeConfig and readConfig are pure, which is not
> true) and will evaluate to 1, else it will evaluate to 0. And, besides,
> the compiler should also substitute the second "storeConfig 0" with the
> result of the first occurrence, so it would not evaluate the second
> "storeConfig" at all.
>
> This is another example of the need for monads: allowing program
> transformations, first of all substituting equals for equals.
>
> This is why (even if, by enough knoweledge of the implementation, we
> could), by only relying on the semantics of a lazy language, we can not
> have functions with side effects.
>
> If it wasn't so, they would not have invented monads, believe me.
>
> I apologize, as always, for my terrible english, and hope I have been
> clear.
>
> Vincenzo Ciancia
> _______________________________________________
> Haskell-Cafe mailing list
> Haskell-Cafe@haskell.org
> http://www.haskell.org/mailman/listinfo/haskell-cafe
>
From sales@smokersassociation.co.uk Wed Sep 25 23:36:43 2002
From: sales@smokersassociation.co.uk (Sales Department)
Date: Thu, 26 Sep 2002 00:36:43 +0200
Subject: Low Price Fags
Message-ID: <20020926003656.B0F554223AC@www.haskell.org>
Dear Sir or Madam
In the past you have requested information on discounted products. We hope that you find this of interest. If you are not a smoker, and find this email offensive, we sincerely apologise! We will be only too happy to take you off our mailing list.
If you are a smoker, however, and are fed up with paying high prices for your cigarettes and tobacco, take a look at what we have to offer by clicking on this link.
http://www.smokersassociation.co.uk/?S=15&ID=2
We can send you, legally, by registered air mail, direct to your door, 4 cartons of cigarettes or 40 pouches of rolling tobacco (all brands are available) from only 170 Euros - about 105 pounds - fully inclusive of postage and packing. Why pay more?
To remove yourself from our mailing list, please click below
mailto:unsubscribe@smokersassociation.co.uk
Yours faithfully.
Smokers Association
http://www.smokersassociation.co.uk/?S=15&ID=2
xay5402731y
From ajb@spamcop.net Thu Sep 26 02:09:18 2002
From: ajb@spamcop.net (Andrew J Bromage)
Date: Thu, 26 Sep 2002 11:09:18 +1000
Subject: Dealing with configuration data
In-Reply-To: <20020925230636.GA30622@sakura.local.nerv.cx>
References: <20020925230636.GA30622@sakura.local.nerv.cx>
Message-ID: <20020926010918.GA16066@smtp.alicorna.com>
G'day all.
On Thu, Sep 26, 2002 at 12:06:36AM +0100, Liyang Hu wrote:
> The problem I'm having is with the preferences: How do I make it
> available throughout the entire program? (FWIW, most of the work is
> effectively done inside the IO monad.) I could explicitly pass the
> record around everywhere, but that seems a trifle inelegant.
>
> My current solution is to use a global ('scuse my terminology, I'm not
> sure that's the right word to use here) variable of type IORef Config
> obtained through unsafePerformIO. It works, but strikes me as a rather
> barbaric solution to a seemingly tame enough problem...
One solution is to do precisely as you suggested, using a state
monad to wrap the IORef. For example:
import Control.Monad.Reader
import Data.IORef
type MyIO a = ReaderT (IORef Config) IO a
main
= do config <- readConfigurationStuff
configref <- newIORef config
runReaderT configref main'
getConfig :: MyIO Config
getConfig
= do configref <- ask
liftIO (readIORef configref)
-- Same as above, but you can supply a projection function.
getsConfig :: (Config -> a) -> MyIO a
getsConfig f
= do config <- getConfig
return (f config)
-- ...and this is where the code REALLY starts.
main' :: MyIO ()
main'
= do config <- getConfig
liftIO (putStrLn (show config)) -- etc
You can wrap whole slabs of existing code in liftIO if it uses
IO but does not need to read the configuration.
There's also a much uglier solution which I occasionally use if I
need an "ad hoc" global variable. Rather than using IORefs, I use
Strings as keys. The code is here:
http://cvs.sourceforge.net/cgi-bin/viewcvs.cgi/hfl/hfl/ioext/
Example of use:
import IOGlobal
main :: IO ()
main
= do writeIOGlobalM "foo" "Foo data"
writeIOGlobalM "bar" ("Bar", ["data"])
foo <- readIOGlobalM "foo"
putStrLn foo
bar <- readIOGlobalM "bar"
putStrLn (show (bar :: (String, [String])))
Cheers,
Andrew Bromage
From koen@cs.chalmers.se Thu Sep 26 07:47:56 2002
From: koen@cs.chalmers.se (Koen Claessen)
Date: Thu, 26 Sep 2002 08:47:56 +0200 (MET DST)
Subject: Dealing with configuration data
In-Reply-To:
Message-ID:
Hal Daume III suggested:
| data Configuration = ... -- config data
|
| globalConfig :: IORef Configuration
| globalConfig = unsafePerformIO (newIORef undefined)
:
| getConfig :: Configuration
| getConfig = unsafePerformIO $ readIORef globalConfig
:
| main = do
| ...read configuration from file...no calls to getConfig...
| writeIORef globalConfig configuration
| doStuff
| return ()
In this case, there is no need to use unsafePerformIO more
than once, nor does one need IORefs. Here is how:
data Configuration = ... -- config data
getConfig :: Configuration
getConfig = unsafePerformIO $
do ...read configuration from file...
return configuration
main =
do doStuff
We know getConfig will only be evaluated once (because of
sharing) (*)
Don't use the dirty stuff when you do not have to! :-)
I think GHC even supports a function getArgs which is not in
the IO monad since the arguments to a program do not change
during a program. If getConfig only depends on the
arguments, no unsafePerformIO is necessary at all.
Gofer, and even early versions of Hugs, had a function
openFile :: FilePath -> String. Thge rationale was (I
guess) that the contents of a file would not change during
the evaluation of a Gofer program.
Regards,
/Koen.
(*) Actually, a Haskell compiler is free to inline these
kind of expressions, so really one has to give a
NOINLINE pragma to the compiler as well.
--
Koen Claessen
http://www.cs.chalmers.se/~koen
Chalmers University, Gothenburg, Sweden.
From koen@cs.chalmers.se Thu Sep 26 08:07:57 2002
From: koen@cs.chalmers.se (Koen Claessen)
Date: Thu, 26 Sep 2002 09:07:57 +0200 (MET DST)
Subject: Pure File Reading (was: Dealing with configuration data)
In-Reply-To:
Message-ID:
Dear all,
At the moment, a discussion on haskell-cafe is going on
about how to neatly program the fact that an entire program
depends on a number of parameters that are read in once at
the beginning of a program.
The suggestion that many people came up with was using
unsafePerformIO in the beginning to read the file. Here is
my version of that:
| data Configuration = ... -- config data
|
| getConfig :: Configuration
| getConfig = unsafePerformIO $
| do ...read configuration from file...
| return configuration
|
| main =
| do doStuff
It is quite disturbing that there is no other easy way to do
this than using unsafePerformIO (except for using implicit
parameters perhaps, but there are other reasons for not
using those).
I have been thinking a little bit more about this and here
is what I found.
Remember the Gofer days, when Gofer had a "function":
openFile :: FilePath -> String
This was of course a cheap and dirty way of implementing
things like the getConfig above, but it is impure. However,
one could imagine a functional version of this function:
readFileOnce :: FilePath -> Maybe String
This function will read the contents of the file (and return
Nothing if something went wrong), but it is memoized, so
that the second time you use this function you get the same
result.
So, it is a pure function. (Admittedly, it is somewhat
unpredictable, but you will always get the same result for
the same arguments.) It is no more strange than GHC's pure
version of the getArgs function (I forgot what it was/is
called).
How about space behavior, you say? Reading a file, and
memoizing the result means storing the whole contents of the
file in memory!
The point is that the use of this function will typically
happen at the beginning of a program, when reading the
configuration file(s). When all this has happened, the
function readFileOnce, and its memo table, will be garabage
collected. (Of course there is no guarantee that all calls
to readFileOnce will be evaluated at the beginning of a
program, and it is not required, but when you do, there are
no space problems.)
There could of course be pure "-Once" versions of other IO
operations. Here is a list of possibilities:
- reading a file
- getting arguments
- getting environment variables
- downloading a webpage
- ...
What do you think?
Regards,
/Koen.
--
Koen Claessen
http://www.cs.chalmers.se/~koen
Chalmers University, Gothenburg, Sweden.
From simonpj@microsoft.com Thu Sep 26 08:37:59 2002
From: simonpj@microsoft.com (Simon Peyton-Jones)
Date: Thu, 26 Sep 2002 08:37:59 +0100
Subject: Dealing with configuration data
Message-ID:
| Sorry, I should also mention implicit parameters, if you're willing to
use
| that extension. I don't like them, though, and my impression from SPJ
is
| that it's very unclear whether they will get into Haskell 2 or not...
It's *linear* implicit parameters that are a weird beast. Ordinary
implicit parameters are quite well behaved. =20
Having said that, there is no Haskell 2 process at the moment...
Simon
From Yoann.Padioleau@irisa.fr Thu Sep 26 14:09:13 2002
From: Yoann.Padioleau@irisa.fr (Yoann Padioleau)
Date: 26 Sep 2002 15:09:13 +0200
Subject: Pure File Reading (was: Dealing with configuration data)
In-Reply-To: Koen Claessen's message of
"Thu, 26 Sep 2002 09:07:57 +0200 (MET DST)"
References:
Message-ID:
Koen Claessen writes:
i find your idea very good.
indeed for the library GetOpt, the argument of a program never change so it
make sense to make this library without using IO monad, same for argv and for the enviroment.
for openFile it seems harder, it would require to have a lock on the file
to be sure that no one modify the file, same for a webpage.
> Dear all,
>
> At the moment, a discussion on haskell-cafe is going on
> about how to neatly program the fact that an entire program
> depends on a number of parameters that are read in once at
> the beginning of a program.
>
> The suggestion that many people came up with was using
> unsafePerformIO in the beginning to read the file. Here is
> my version of that:
>
> | data Configuration = ... -- config data
> |
> | getConfig :: Configuration
> | getConfig = unsafePerformIO $
> | do ...read configuration from file...
> | return configuration
> |
> | main =
> | do doStuff
>
> It is quite disturbing that there is no other easy way to do
> this than using unsafePerformIO (except for using implicit
> parameters perhaps, but there are other reasons for not
> using those).
>
> I have been thinking a little bit more about this and here
> is what I found.
>
> Remember the Gofer days, when Gofer had a "function":
>
> openFile :: FilePath -> String
>
> This was of course a cheap and dirty way of implementing
> things like the getConfig above, but it is impure. However,
> one could imagine a functional version of this function:
>
> readFileOnce :: FilePath -> Maybe String
>
> This function will read the contents of the file (and return
> Nothing if something went wrong), but it is memoized, so
> that the second time you use this function you get the same
> result.
>
> So, it is a pure function. (Admittedly, it is somewhat
> unpredictable, but you will always get the same result for
> the same arguments.) It is no more strange than GHC's pure
> version of the getArgs function (I forgot what it was/is
> called).
>
> How about space behavior, you say? Reading a file, and
> memoizing the result means storing the whole contents of the
> file in memory!
>
> The point is that the use of this function will typically
> happen at the beginning of a program, when reading the
> configuration file(s). When all this has happened, the
> function readFileOnce, and its memo table, will be garabage
> collected. (Of course there is no guarantee that all calls
> to readFileOnce will be evaluated at the beginning of a
> program, and it is not required, but when you do, there are
> no space problems.)
>
> There could of course be pure "-Once" versions of other IO
> operations. Here is a list of possibilities:
>
> - reading a file
> - getting arguments
> - getting environment variables
> - downloading a webpage
> - ...
>
> What do you think?
>
> Regards,
> /Koen.
>
> --
> Koen Claessen
> http://www.cs.chalmers.se/~koen
> Chalmers University, Gothenburg, Sweden.
>
> _______________________________________________
> Haskell-Cafe mailing list
> Haskell-Cafe@haskell.org
> http://www.haskell.org/mailman/listinfo/haskell-cafe
>
--
Yoann Padioleau, INSA de Rennes, France,
Opinions expressed here are only mine. Je n'écris qu'à titre personnel.
**____ Get Free. Be Smart. Simply use Linux and Free Software. ____**
From nick.name@inwind.it Thu Sep 26 14:36:35 2002
From: nick.name@inwind.it (Nick Name)
Date: Thu, 26 Sep 2002 15:36:35 +0200
Subject: Dealing with configuration data
In-Reply-To:
References: <20020926013314.5da489b7.nick.name@inwind.it>
Message-ID: <20020926153635.1bd6ab30.nick.name@inwind.it>
I just wrote a long and clear answer, but my e-mail client has crashed.
I am going to change it (or to rewrite one in Haskell, grrr) but the
answer will be shorter, I apologize.
On Wed, 25 Sep 2002 16:34:02 -0700 (PDT)
Hal Daume III wrote:
> I don't mean to troll, but this isn't what I meant.
You aren't. I misunderstood you, of course.
> now, we have doStuff :: IO a. doStuff is allowed (even in its pure
> methods) to use getConfig. I claim that this is safe. I could be
> wrong; this is only a hand-waiving argument. Why?
>
> The first reference in the program to globalConfig is through a
> writeIORef. This means that at this point globalConfig gets evaluated
> and thus a ref is created. Immediately we put a value in it.
>
> Now, when doStuff runs, since it is an action run *after* the call to
> writeIORef, provided that it doesn't also write to 'globalConfig'
> (which I mentioned in my original message), any call to getConfig is
> deterministic.
Even this appears correct, and I feel that it's a technique widely used
in the haskell community, nothing prevents a global optimizer to
evaluate all pure functions wich do not depend on a value obtained by IO
*before the "main" function*.
This is also stated in the GHC documentation, about "unsafePerformIO":
"If the I/O computation wrapped in unsafePerformIO performs side
effects, then the relative order in which those side effects take place
(relative to the main I/O trunk, or other calls to unsafePerformIO) is
indeterminate."
If getConfig is evaluated before the main function (nothing prevents it)
and if all equal pure expressions are evaluated only once, readConfig
will always lead to "undefined" (yes, it will always be evaluated after
"globalConfig").
The first idea from Koen Claessen (getConfig operates directly on the
file with unsafePerformIO) appears to work, but this time we are
*relying* on the fact that the function will be evaluated once, since
the file could change and multiple evaluations of readConfig wouldn't
lead to the same result. This is not good anyway.
Vincenzo
From d95lars@dtek.chalmers.se Thu Sep 26 14:39:04 2002
From: d95lars@dtek.chalmers.se (Lars Lundgren)
Date: Thu, 26 Sep 2002 15:39:04 +0200 (MEST)
Subject: Pure File Reading (was: Dealing with configuration data)
In-Reply-To:
Message-ID:
On 26 Sep 2002, Yoann Padioleau wrote:
> Koen Claessen writes:
>
> i find your idea very good.
> indeed for the library GetOpt, the argument of a program never change so it
> make sense to make this library without using IO monad, same for argv and for the enviroment.
> for openFile it seems harder, it would require to have a lock on the file
> to be sure that no one modify the file, same for a webpage.
>
No, not at all. All that is required is to make sure all calls to openFile
f returns the same string, i.e the contents of the file when it was read
the first time.
/Lars L
From Yoann.Padioleau@irisa.fr Thu Sep 26 14:52:47 2002
From: Yoann.Padioleau@irisa.fr (Yoann Padioleau)
Date: 26 Sep 2002 15:52:47 +0200
Subject: Pure File Reading (was: Dealing with configuration data)
In-Reply-To: Lars Lundgren's message of
"Thu, 26 Sep 2002 15:39:04 +0200 (MEST)"
References:
Message-ID:
Lars Lundgren writes:
> On 26 Sep 2002, Yoann Padioleau wrote:
>
> > Koen Claessen writes:
> >
> > i find your idea very good.
> > indeed for the library GetOpt, the argument of a program never change so it
> > make sense to make this library without using IO monad, same for argv and for the enviroment.
>
> > for openFile it seems harder, it would require to have a lock on the file
> > to be sure that no one modify the file, same for a webpage.
> >
>
> No, not at all. All that is required is to make sure all calls to openFile
> f returns the same string, i.e the contents of the file when it was read
> the first time.
yes you are right. but it requires to change
the name of the function to have Once appended to it.
so in the Prelude, we should have 2 version of the same kind of fonction,
one pure such as readFileOnce with a cool type, and one such as readFile with
an Io type.
Sounds good idea to me, cos many programs require just to read
a file one time.
i dont know if practically it is useful. after all we can do
all the IO stuff in the main, and then continue in a pure world.
dont know if it is useful to read a file in the middle of a pure function.
>
> /Lars L
>
>
>
--
Yoann Padioleau, INSA de Rennes, France,
Opinions expressed here are only mine. Je n'écris qu'à titre personnel.
**____ Get Free. Be Smart. Simply use Linux and Free Software. ____**
From koen@cs.chalmers.se Thu Sep 26 15:02:01 2002
From: koen@cs.chalmers.se (Koen Claessen)
Date: Thu, 26 Sep 2002 16:02:01 +0200 (MET DST)
Subject: Dealing with configuration data
In-Reply-To: <20020926153635.1bd6ab30.nick.name@inwind.it>
Message-ID:
Nick Name wrote:
| The first idea from Koen Claessen (getConfig operates
| directly on the file with unsafePerformIO) appears to
| work, but this time we are *relying* on the fact that
| the function will be evaluated once, since the file
| could change and multiple evaluations of readConfig
| wouldn't lead to the same result. This is not good
| anyway.
But Hal Daume III's suggestion has that same problem:
| data Configuration = ... -- config data
|
| globalConfig :: IORef Configuration
| globalConfig = unsafePerformIO (newIORef undefined)
:
| getConfig :: Configuration
| getConfig = unsafePerformIO $ readIORef globalConfig
:
| main = do
| ...read configuration from file...no calls to getConfig...
| writeIORef globalConfig configuration
| doStuff
| return ()
Imagine "globalConfig" being evaluated twice! This means
there will be *two* IORefs in your program; one might be
initialized, and not the other. This is even more
disastrous.
(To see what could happen: just inline the definition of
globalConfig into the two places where it is used.)
This is why one has to be EXTREMELY careful when using these
kinds of constructs. Really, only use unsafePerformIO when
you know what you are doing, and otherwise, leave it to
someone else who can wrap it up into a nice, pure library.
In general, when using unsafePerformIO in this way, one
wants to tell the compiler that it is not allowed to inline
the expression. This can be done in most compilers by giving
compiler pragma's.
/Koen.
--
Koen Claessen
http://www.cs.chalmers.se/~koen
Chalmers University, Gothenburg, Sweden.
From nick.name@inwind.it Thu Sep 26 15:40:32 2002
From: nick.name@inwind.it (Nick Name)
Date: Thu, 26 Sep 2002 16:40:32 +0200
Subject: Dealing with configuration data
In-Reply-To:
References: <20020926153635.1bd6ab30.nick.name@inwind.it>
Message-ID: <20020926164032.1863e2da.nick.name@inwind.it>
On Thu, 26 Sep 2002 16:02:01 +0200 (MET DST)
Koen Claessen wrote:
> In general, when using unsafePerformIO in this way, one
> wants to tell the compiler that it is not allowed to inline
> the expression. This can be done in most compilers by giving
> compiler pragma's.
In the need of a mutable configuration, I prefer to use the IO monad
anyway, because one of the reasons I am studying haskell is to stop
having to bother with "inline" and/or order of evaluation.
Vincenzo
--
Fedeli alla linea, anche quando non c'è
Quando l'imperatore è malato, quando muore,o è dubbioso, o è perplesso.
Fedeli alla linea la linea non c'è.
[CCCP]
From hdaume@ISI.EDU Thu Sep 26 15:46:51 2002
From: hdaume@ISI.EDU (Hal Daume III)
Date: Thu, 26 Sep 2002 07:46:51 -0700 (PDT)
Subject: Dealing with configuration data
In-Reply-To:
Message-ID:
Koen,
> getConfig :: Configuration
> getConfig = unsafePerformIO $
> do ...read configuration from file...
> return configuration
>
> (*) Actually, a Haskell compiler is free to inline these
> kind of expressions, so really one has to give a
> NOINLINE pragma to the compiler as well.
I'd always avoided this type of thing precisely because of the inline
issue, which I don't think my version is in danger of. That's just me,
though :).
From rjmh@cs.chalmers.se Thu Sep 26 19:26:17 2002
From: rjmh@cs.chalmers.se (John Hughes)
Date: Thu, 26 Sep 2002 20:26:17 +0200 (MET DST)
Subject: Dealing with configuration data
In-Reply-To:
Message-ID:
On Thu, 26 Sep 2002, Simon Peyton-Jones wrote:
> | Sorry, I should also mention implicit parameters, if you're willing to
> use
> | that extension. I don't like them, though, and my impression from SPJ
> is
> | that it's very unclear whether they will get into Haskell 2 or not...
>
I wrote a short paper on this very topic, comparing alternative solutions.
I ended up favouring implicit parameters. If you want to read it, it's at
http://www.cs.chalmers.se/~rjmh/Globals.ps
John
From oleg@pobox.com Fri Sep 27 00:28:03 2002
From: oleg@pobox.com (oleg@pobox.com)
Date: Thu, 26 Sep 2002 16:28:03 -0700 (PDT)
Subject: Pure File Reading (was: Dealing with configuration data)
References:
Message-ID: <200209262328.QAA11313@adric.fnmoc.navy.mil>
There is another solution to the problem of configurational
parameters. The main part of the solution is portable, does not depend
on any pragmas, does not use unsafe operations, does not use implicit
parameters, and does not require any modifications to the user code. I
must warn that it is also potentially vomit-inducing.
It seems that the problem at hand naturally splits into two phases:
building the configuration environment, and executing some code in
that environment. The phases are executed sequentially. The facts
suggest the use of a SupedMonad. SuperMonad is very well known and
often used, even by people who never heard of simpler monads.
The following code is an illustration. Suppose file '/tmp/a.hs'
contains the following user code, which is to run within the
configuration environment provided by the module Config. For
simplicity, our configuration is made of one Int datum, config_item:
>>> File "/tmp/a.hs"
> import Config (config_item)
>
> foo = "foo shows: " ++ (show config_item)
>
> bar = "bar shows: " ++ (show config_item)
>
> main = do
> print foo
> print bar
> print foo
We specifically illustrate the reading of the config item several
times.
The following code runs the first phase: reads the configuration,
build the SuperMonad and runs the SuperMonad.
> import System (system, ExitCode(ExitSuccess))
>
> myconfig_file = "/tmp/config"
>
> phaseII_var = "/tmp/Config.hs"
> phaseII_const = "/tmp/a.hs"
>
> nl = "\n"
>
> writeConfig :: Int -> IO ()
> writeConfig num =
> do
> writeFile phaseII_var $
> concat
> ["module Config (config_item) where", nl,
> "config_item =", show num, nl]
>
>
> runSuperIO () = system ("echo main | hugs " ++ phaseII_const)
> >>= \ExitSuccess -> print "Phase II done"
>
> main = readFile myconfig_file >>= writeConfig . read >>= runSuperIO
I did warn you, didn't I?
I have a hunch this solution will work with GHC even better than it
works with Hugs. Perhaps we can even play with some dynamic linking
tricks (like shared object initializers, etc). BTW, the solution above
is similar in spirit to the following trick in C++:
Config config;
int main() { /* pure functional C++ code here -- yes, it exists*/}
the constructor for 'config' is guaranteed to run before main().
Perhaps someone will implement Staged Haskell one day?
From liyang@nerv.cx Fri Sep 27 04:16:20 2002
From: liyang@nerv.cx (Liyang Hu)
Date: Fri, 27 Sep 2002 04:16:20 +0100
Subject: Dealing with configuration data
In-Reply-To:
References: <20020926013314.5da489b7.nick.name@inwind.it>
Message-ID: <20020927031620.GA13747@sakura.local.nerv.cx>
--oJ71EGRlYNjSvfq7
Content-Type: multipart/mixed; boundary="wq9mPyueHGvFACwf"
Content-Disposition: inline
--wq9mPyueHGvFACwf
Content-Type: text/plain; charset=us-ascii
Content-Disposition: inline
Content-Transfer-Encoding: quoted-printable
Evening all,
Thanks for all the replies and suggestions! They've been extremely
helpful.
On Wed, Sep 25, 2002 at 04:34:02PM -0700, Hal Daume III wrote:
> Okay, this is "bad" but I claim it's okay, iff it is used as in:
In the end, I opted for the global IORef through unsafePerformIO scheme;
implicit parameters seemed too `bleedin' edge' for me... (that and I had
in mind to also retro-fit the idea on top of WASH-CGI[0]; I don't want
to make more changes than I absolutely have to.)
(I haven't yet read John Hughes' paper on the topic though; that should
be quite fun.)
One thing to watch out for though: hGetContents is *not* your friend. At
least it isn't if you're going to let it defer its work until you're
inside modifyIORef... see the attached prefs.hs, line 28 onwards. Just
for reference, I'm using GHC 5.02.2.
I must have went almost insane trying to figure out why I was still
getting the default settings, when every single line of the code seemed
to state the contrary; I had already written up prefs.hs to post to the
list to ask for help, when I noticed that if I put in the line ``mapM_
putStrLn kvs'' before I update the IORef, I get my new settings. If
I leave it out, I get the defaults. Then it hit me -- hGetContents was
lazily deferring its reads. A quickie alternative hGetLines seems to
have fixed the problem.
But I'm still not sure *why* that was a problem in the first place...
Can anyone explain? (Looking at the library source didn't help.) Surely
modifyIORef would have reduced kvs to head normal form (correct termino-
logy?) just like putStrLn did?
*sigh* This can't be good for my mental health.
Thanks everyone,
/Liyang
BTW: I'm on both the main and -cafe lists; you don't have to CC me. ^_-
[0] http://www.informatik.uni-freiburg.de/~thiemann/WASH/
--=20
=2E--{ Liyang HU }--{ http://nerv.cx/ }--{ Caius@Cam }--{ ICQ: 39391385 }--.
| ``Computer games don't affect kids, I mean if Pac Man affected us as |
| kids, we'd all be running around in darkened rooms, munching pills and |
| listening to repetitive music.'' |
--wq9mPyueHGvFACwf
Content-Type: text/plain; charset=us-ascii
Content-Disposition: attachment; filename="prefs.hs"
module Main where
import Prelude
import Char ( isSpace, toLower )
import IO
import IOExts ( IORef, modifyIORef, newIORef, readIORef, unsafePerformIO )
-- Bung everything inside a record, to save us multiple IORefs
data Config = Config
{ cfgSomeSetting :: String }
configRef = unsafePerformIO $ newIORef $ Config
{ cfgSomeSetting = "this is the default setting" }
config = unsafePerformIO $ readIORef configRef
-- as a shortcut / compatibility with existing code
someSetting = cfgSomeSetting config
-- returns lines in reverse order, I know, but it's irrelevant
hGetLines h = get [] where
get ls = (hGetLine h >>= get . (: ls)) `catch` (const $ return ls)
-- *should* be called first thing in main (if at all);
-- otherwise madness ensues...
loadConfig :: FilePath -> IO ()
loadConfig conf = bracket (openFile conf ReadMode) hClose $ \ h -> do
kvs <- fmap (map keyVal . filter isNotComment . lines) (hGetContents h)
--kvs <- fmap (map keyVal . filter isNotComment) (hGetLines h)
--mapM_ putStrLn kvs
modifyIORef configRef (\ c -> foldl cfgLine c kvs) where
keyVal s = (map toLower key, dropWhile isSpace rest)
where (key, rest) = break isSpace s
isNotComment ('#':_) = False
isNotComment [] = False
isNotComment _ = True
cfgLine c ("setting", v) = c { cfgSomeSetting = v }
cfgLine c _ = c -- ignore everything else
main = do
loadConfig "prefs.conf"
local <- readIORef configRef
mapM_ putStrLn [ cfgSomeSetting local, cfgSomeSetting config, someSetting ]
--wq9mPyueHGvFACwf
Content-Type: text/plain; charset=us-ascii
Content-Disposition: attachment; filename="prefs.conf"
# ignored
setting overridden
--wq9mPyueHGvFACwf
Content-Type: text/plain; charset=us-ascii
Content-Disposition: attachment; filename=Makefile
GHC=ghc -O2
PACKAGES=-package lang
SRC=prefs.hs
all: $(SRC:.hs=)
%: %.hs
@$(GHC) --make $(@) -o $@ $(PACKAGES) $<
clean:
rm -f *.hi *.o $(SRC:.hs=)
.PHONY: clean ghci
--wq9mPyueHGvFACwf--
--oJ71EGRlYNjSvfq7
Content-Type: application/pgp-signature
Content-Disposition: inline
-----BEGIN PGP SIGNATURE-----
Version: GnuPG v1.0.6 (GNU/Linux)
Comment: moo! (ID: 7B632CB8)
iEYEARECAAYFAj2TzYQACgkQ1QR4EHtjLLg3JgCgwhm+pMumR6XdWTxz66/F2rya
NrcAoI75ViSlKhwng0DsJBOBqsdSiC7f
=IGrg
-----END PGP SIGNATURE-----
--oJ71EGRlYNjSvfq7--
From heringto@cs.unc.edu Fri Sep 27 17:56:38 2002
From: heringto@cs.unc.edu (Dean Herington)
Date: Fri, 27 Sep 2002 12:56:38 -0400
Subject: Dealing with configuration data
References: <20020925230636.GA30622@sakura.local.nerv.cx>
<20020926010918.GA16066@smtp.alicorna.com>
Message-ID: <3D948DC6.D3222A1D@cs.unc.edu>
Andrew J Bromage wrote:
> There's also a much uglier solution which I occasionally use if I
> need an "ad hoc" global variable. Rather than using IORefs, I use
> Strings as keys. The code is here:
>
> http://cvs.sourceforge.net/cgi-bin/viewcvs.cgi/hfl/hfl/ioext/
I'm not sure why you consider the code you refer to above so ugly. In any
case, I have a question and a comment on it.
Question:
Why do you use `seq` on `globalTableRef`?
Comment:
You use `addToFM` to replace entries in your table. Without additional
logic to increase strictness, I think you unnecessarily risk stack
overflow. Consider the case where `writeIOGlobal` is used many times on a
global between uses of `readIOGlobal` on that global.
The above issue raises a general question: How should strictness best be
achieved with `addToFM`?
-- Dean
From ajb@spamcop.net Sun Sep 29 02:00:28 2002
From: ajb@spamcop.net (Andrew J Bromage)
Date: Sun, 29 Sep 2002 11:00:28 +1000
Subject: Dealing with configuration data
In-Reply-To: <3D948DC6.D3222A1D@cs.unc.edu>
References: <20020925230636.GA30622@sakura.local.nerv.cx>
<20020926010918.GA16066@smtp.alicorna.com> <3D948DC6.D3222A1D@cs.unc.edu>
Message-ID: <20020929010028.GA13399@smtp.alicorna.com>
G'day all.
On Fri, Sep 27, 2002 at 12:56:38PM -0400, Dean Herington wrote:
> I'm not sure why you consider the code you refer to above so ugly.
Anything which relies on unsafePerformIO (or seq, for that matter)
is ugly. Personal opinion, of course. :-)
> Question:
> Why do you use `seq` on `globalTableRef`?
Good question. It's actually a form of documentation. I wasn't 100%
sure how concurrency and CAFs interact at the time (and I'm still
not), so I left that in as a sort of note to myself to check this out.
Admittedly a comment would have been clearer. :-)
> You use `addToFM` to replace entries in your table. Without additional
> logic to increase strictness, I think you unnecessarily risk stack
> overflow.
That's true, although the case of many writes followed by a single
read I would expect to be rare in practice. Besides, IOGlobal is not
designed for performance. It's designed for quick hacks.
Cheers,
Andrew Bromage
From cdreklam@daldal.com Mon Sep 30 17:52:58 2002
From: cdreklam@daldal.com (Hayri DALDAL)
Date: Mon, 30 Sep 2002 19:52:58 +0300
Subject: E-MaiL Bankası
Message-ID: <20020930165556.1C7ED421F56@www.haskell.org>
=3Chtml=3E
=3Chead=3E
=3Ctitle=3ET=FCrk E-Mail Bank=3C=2Ftitle=3E
=3Cmeta http-equiv=3D=22Content-Type=22 content=3D=22text=2Fhtml=3B charset=3Diso-8859-9=22=3E
=3Cmeta http-equiv=3D=22Content-Type=22 content=3D=22text=2Fhtml=3B charset=3Dwindows-1254=22=3E
=3C=2Fhead=3E
=3Cbody bgcolor=3D=22#FFFFFF=22 text=3D=22#000000=22 leftmargin=3D=220=22 topmargin=3D=220=22 marginwidth=3D=220=22 marginheight=3D=220=22=3E
=3Ctable width=3D=22630=22 border=3D=220=22 cellspacing=3D=220=22 cellpadding=3D=220=22 align=3D=22center=22 background=3D=22http=3A=2F=2Fcdreklam=2Edaldal=2Ecom=2Fbackchip2=2Ejpg=22=3E
=3Ctr=3E
=3Ctd valign=3D=22middle=22=3E
=3Cblockquote=3E
=3Cdiv align=3D=22right=22=3E=3C=2Fdiv=3E
=3Cp align=3D=22right=22=3E=3Cfont face=3D=22Verdana=22 size=3D=222=22=3E=3Cb=3E=3Cfont color=3D=22#000099=22=3ET=FCrk
E-Mail Bank =AE patentli=2C =22E-Mail Adres Rehberleri=22miz g=FCncellenmi=FEtir=3C=2Ffont=3E=3Cfont color=3D=22#FFCC00=22=3E=2E=3C=2Ffont=3E=3C=2Fb=3E=3C=2Ffont=3E=3C=2Fp=3E
=3Cp align=3D=22right=22=3E=3Cfont face=3D=22Verdana=22 size=3D=222=22=3E Sekt=F6rler=2C iller=2C kurum
ve kurulu=FElar=2C e=F0ilim ve ilgiler baz=FDnda kategorize edilmi=FE E-Mail Adres
Rehberleri'mizle 5 Milyon yerli Internet kullan=FDc=FDs=FDna "=3B=3Cstrong=3Ebir
anda=3C=2Fstrong=3E"=3B ula=FEabilir=3B=3Cbr=3E
reklam=2C tan=FDt=FDm=2C duyuru=2C ilan ve her t=FCrl=FC kampanyalar=FDn=FDz=FD g=F6nderebilirsiniz=2E=3Cbr=3E
=3C=2Ffont=3E=3C=2Fp=3E
=3Cp align=3D=22center=22=3E=3Cfont face=3D=22Times New Roman=22=3E=3Cb=3E=3Cfont size=3D=225=22=3E5=2E000=2E000
YERLi E-MAIL REHBERi=3Cbr=3E
=3Cfont color=3D=22#000000=22 size=3D=227=22=3E150 $=3C=2Ffont=3E=3C=2Ffont=3E=3Cfont size=3D=224=22=3E=3Cbr=3E
=3Cfont size=3D=222=22 color=3D=22#FF0000=22=3ESaatte 80=2E000 mail yollayabilen Group
Mail program=FD hediyeli=3C=2Ffont=3E=3C=2Ffont=3E=3C=2Fb=3E=3C=2Ffont=3E=3C=2Fp=3E
=3Cp align=3D=22center=22=3E=3Cfont color=3D=22#003366=22 size=3D=223=22 face=3D=22Arial=22=3E=3Cstrong=3EGazete=2C
Radyo ve Tv'lerin Traj ve Reatingiyle=3Cbr=3E
Reklam Fiyatlar=FDyla Kar=FE=FDla=FEt=FDr=FDn Hangisi Karl=FD !=3C=2Fstrong=3E=3C=2Ffont=3E=3C=2Fp=3E
=3Cp align=3D=22center=22=3E=3Cfont face=3D=22Verdana=22 size=3D=222=22=3E=3Cstrong=3EWeb=3A =3Ca href=3D=22http=3A=2F=2Fcdreklam=2Edaldal=2Ecom=22 target=3D=22=5Fblank=22=3Ecdreklam=2Edaldal=2Ecom=3C=2Fa=3E=3C=2Fstrong=3E=3C=2Ffont=3E=3C=2Fp=3E
=3Cp align=3D=22right=22=3E=3Cfont face=3D=22Verdana=22 size=3D=222=22=3E Daha farkl=FD soru=2C g=F6r=FC=FE=2C
teklif ve sipari=FEleriniz i=E7in bize ula=FEabilirsiniz=2E=3C=2Ffont=3E=3C=2Fp=3E
=3Cp align=3D=22right=22=3E=3Cfont face=3D=22Verdana=22 size=3D=222=22=3EWeb Tasar=FDm=FD=2C Domain tescili
ve Hosting fiyatlar=FDm=FDz=FD mutlaka sorun=2E=3C=2Ffont=3E=3C=2Fp=3E
=3Cp align=3D=22right=22=3E=3Cfont face=3D=22Verdana=22 size=3D=222=22=3E=3Cb=3E=3Cfont color=3D=22#0000FF=22=3E"=3BKaaN
Ajans Organizasyon=AE"=3B=3Cbr=3E
Hayri DALDAL =28Koordinator=29 =3B=3C=2Ffont=3E=3C=2Fb=3E=3C=2Ffont=3E=3C=2Fp=3E
=3Cp align=3D=22right=22=3E=3Cfont face=3D=22Verdana=22 size=3D=222=22=3E=3Cb=3ETEL=3A 0312 440 78 65=28PBX=29=3C=2Fb=3E=3C=2Ffont=3E=3Cfont face=3D=22Verdana=22 size=3D=222=22=3E=3Cb=3E=3Cbr=3E
E-MaiL=3A =3Ca href=3D=22mailto=3Ahayri=40daldal=2Ecom=22=3Ehayri=40daldal=2Ecom=3C=2Fa=3E=3C=2Fb=3E=3C=2Ffont=3E=3C=2Fp=3E
=3Cp align=3D=22right=22=3E=3Cfont face=3D=22Verdana=22 size=3D=222=22=3EBu ileti 5 Milyon Turk
Internet kullan=FDc=FDs=FDn=FDn e-mail adresine g=F6nderilmi=FEtir=2E=3Cbr=3E
=3C=2Ffont=3E=3C=2Fp=3E
=3C=2Fblockquote=3E
=3C=2Ftd=3E
=3C=2Ftr=3E
=3C=2Ftable=3E
=3C=2Fbody=3E
=3C=2Fhtml=3E