Marcin 'Qrczak' Kowalczyk wrote:
> stToIO looks better for me. What about declaring that lowercasing
> the first letter of an abbreviation consisting of only capital
> letters is realized by lowercasing the whole word? [...]
OK, this makes sense and the rule is not much more complicated.
> > e.g
I *knew* people couldn't resist talking about names! :-) OK, I've
invited you to do this, but more than a dozen mails solely about the
first item of section 1.1.1 were a little bit surprising...
To be more serious: Perhaps I wasn't clear enough about the purpose of
these conventions. What they're
After some discussions in the GHC developer mailing lists a small
bunch of conventions around library design emerged. Currently things
mainly concentrate on naming issues (everybody's delight :-), but it
is only meant as a starting point:
http://www.informatik.uni-muenchen.de/~Sven.Panne/hslib
Is the following behaviour of GHC allowed by the H98 report?
-- Foo.hs
main :: IO ()
main = print (0.1234567891234567891 :: Float,
0.1234567891234567891 :: Double)
--
panne@jeanluc:~ > ghc Foo.h
red with constructors, field accessors and
> variables. [ example deleted ]
But this is really a matter of taste. I'm a real friend of
variable-free definitions, but from time to time (e.g. in this
example) it's IMHO much easier to see what's going on *with*
explicit variables
Mike Jones wrote:
> Yes, I do derive Show for MyData. I was surprised it did not work.
Deriving works, but GHC currently only contains instance declarations
for tuples up to 5 elements, so you have to write you own boring
instances for larger ones. *yawn*
Cheers,
Sven
--
Sven Pa
tions are not an instance of Show, so you have to supply
instance Show (a -> b) where
showsPrec _ _ = showString ""
or add `import ShowFunctions' (in the upcoming GHC 4.07's package lang).
Cheers,
Sven
--
Sven PanneTel.: +
cess >>= writeFile "xxx"
-- hack for hyperstrictness
hyper txt | length txt >= 0 = return txt
| otherwise = error "never happens"
And using hGetBuf{,BA}Full from GHC's upcoming IOExts module would be
a completely different way.
--
Sven Panne
mand (I'm a little bit reluctant to write the word
"subs...be" here, because I have seen versions of Majormdomo which
tried to interpret commands in *every* mail).
Cheers,
Sven
--
Sven PanneTel.: +49/89/2178-2235
LMU, Institut fuer Informatik
it apart from the usual unsafePerformIO-plus-noInline-trickery at
the top level.
Cheers,
Sven
--
Sven PanneTel.: +49/89/2178-2235
LMU, Institut fuer Informatik FAX : +49/89/2178-2211
LFE Programmier- und Modellierungssprachen
ng.
* Interfaces.C.Pointers is similar to module FFI.
So what remains is basically the first item. Could somebody make a
detailed proposal how the FFI should handle this character/string
stuff?
Cheers,
Sven
--
Sven PanneTel.: +49/89/2178-223
er, but this is a
different story, we are discussing Haskell's primitive FFI and a lib
for handwritten (and automatically generated) bindings, not H/Direct.
Cheers,
Sven
--
Sven PanneTel.: +49/89/2178-2235
LMU, Institut fuer Informatik
te between
StablePtr (a, Maybe b)
StablePtr (a, Maybe a)
StablePtr (a, MyOwnModule.Maybe b)
...
This is certainly doable, but is this really worth the trouble? I'm not
sure and would definitely like to hear some opinions on this topic.
Cheers,
Sven
--
S
nciples of Ethics and Code of Professional Conduct)
:-)
Apart from that, I'll have a look at the "real" ADA stuff.
Cheers,
Sven
--
Sven PanneTel.: +49/89/2178-2235
LMU, Institut fuer Informatik FAX : +49/89/2178-2211
LFE
ode that relies on
> byte ordering. I don't see any reason for the Haskell FFI to
> encourage this.
It's not a matter of encouragement, but a matter of necessity: There
are a lot of binary file formats out in the real world, and you really
need to know if some swapping is needed or
dian -- are there more esoteric ones?
byteOrder :: ByteOrder
Comments/suggestions/flames?
Cheers,
Sven
--
Sven PanneTel.: +49/89/2178-2235
LMU, Institut fuer Informatik FAX : +49/89/2178-2211
LFE Programmier- und Modellierungssp
is hyperstrict (at least according to my definition :-) :
len :: Eq a => [a] -> Int
len [] = 0
len (x:xs) | x == x = 1 + len xs
This 'x == x' is folklore for getting rid of some space leaks,
AFAIK.
Cheers,
Sven
--
Sven PanneT
/GLUT support under
Cygwin/Mingw32 can be found at
http://www.informatik.uni-muenchen.de/~Sven.Panne/cygwin/opengl_glut.html
HOpenGL should work on Sparc-based platforms, too, but this has not
been thoroughly tested yet.
Have fun!
Sven
--
Sven Panne
could complain to the
SuSE support, I wasn't very successful with my attempts... :-(
Cheers,
Sven
--
Sven PanneTel.: +49/89/2178-2235
LMU, Institut fuer Informatik FAX : +49/89/2178-2211
LFE Programmier- und Modellieru
#x27;re currently working
> on fixing them.
A workaround is not using -O for modules using FFI or readXXXOffAddr.
Cheers,
Sven
--
Sven PanneTel.: +49/89/2178-2235
LMU, Institut fuer Informatik FAX : +49/89/2178-2211
LFE Programmier- und Mo
hat.
Sigbjorn: I think it's time to release a new version...
Cheers,
Sven
--
Sven PanneTel.: +49/89/2178-2235
LMU, Institut fuer Informatik FAX : +49/89/2178-2211
LFE Programmier- und Modellierungssprachen Oettingenstr.
s,
Sven
--
Sven PanneTel.: +49/89/2178-2235
LMU, Institut fuer Informatik FAX : +49/89/2178-2211
LFE Programmier- und Modellierungssprachen Oettingenstr. 67
mailto:[EMAIL PROTECTED]D-80538 Muenchen
http://www.info
Sven Panne wrote:
> Tom Pledger wrote:
> > How about using qualified imports of modules?
> > [...]
> > module Test where
> > import qualified QL1
> > import QL2
> > [...]
>
> You don't even have to use a qualified import for QL1, prefixi
e module QL1
where most names don't clash). This "lazy" disambiguation is one of
the few things of Haskell's module system I really like.
Cheers,
Sven
--
Sven PanneTel.: +49/89/2178-2235
LMU, Institut fuer Informatik
myself... :-}
What about a grand unified EMACS HTML/XML library?
(Erik's, Malcolm's, Andy's, Colin's, and Sven's HTML/XML library)
Ooops, forgot Peter, but he would spoil the acronym... :-)
Cheers,
Sven
--
Sven Panne
ngs like vectors, matrices,
etc. which contain elements of a polymorphic numeric type.
When no good reason for this restriction exists, it should be removed
IMHO. This only extends the set of programs which can be compiled, and
existing programs don't change their meaning.
heers,
Santa
P.S.: Some day the Wish List will move to haskell.org, but at the
moment my connection to it reminds me of those good old 300baud-days...
--
Sven PanneTel.: +49/89/2178-2235
LMU, Institut fuer Informatik FAX : +4
rograms this box fiddling should better be hidden in
some GUI abstraction (URLs have already been given in this thread).
Cheers,
Sven
--
Sven PanneTel.: +49/89/2178-2235
LMU, Institut fuer Informatik FAX : +49/89/2178-22
t from the Haskell community, so head over to
the above URL and see how *you* can contribute and improve the
Haskell-experience! :-)
Cheers,
Sven
--
Sven PanneTel.: +49/89/2178-2235
LMU, Institut fuer Informatik FAX : +
cs.gla.ac.uk/mail-www/glasgow-haskell-bugs/msg01147.html
Cheers,
Sven
--
Sven PanneTel.: +49/89/2178-2235
LMU, Institut fuer Informatik FAX : +49/89/2178-2211
LFE Programmier- und Modellierungssprachen Oettingenstr. 67
ma
real fan of it, and I know that in academia you earn *nothing* for
implementing hSeek and friends, but on the other hand, it shouldn't be
*that* hard and time-consuming...
Cheers,
Sven
--
Sven PanneTel.: +49/89/2178-2235
LMU, Institut fuer Informat
ollected in a clever
way (describe in SPJ's book, I think), e.g. if there is only one
reference into the "middle" of a CAF left, only that part is kept alive.
and not the wohle CAF. Comments from Mr. GC? :-)
Cheers,
Sven
--
Sven PanneTe
nual conversion of .h files
into .idl files, which of the dozens of ihc's command line options you
need for this simple interfacing to C, etc. Without this, I guess, most
*nix people will stick to Green Card and/or the FFI.
Cheers,
Sven
--
Sven Panne
he CR/LF vs LF is a non-issue here. Lseek's
manual pages tell me something about a *byte* offset, not a
*character* offset.
Related points would be: What does hGetChar exactly mean in the
presence of Unicode/UTF-8/... and random access?
Cheers,
Sven
--
Sven Panne
cky point is dealing correctly with infix ops in the
presence of the module system. Any *easy* suggestions for this?
Perhaps if I have some spare time... (Hmmm, not very probable at the
moment, the weather in Munich is too nice... :-) But I wouldn't mind
if somebody else volunteered.
Cheers
tion: What's the rationale of throwing
different namespaces together in the hiding clause?
Cheers,
Sven
--
Sven PanneTel.: +49/89/2178-2235
LMU, Institut fuer Informatik FAX : +49/89/2178-2211
LFE Programmier- und Modellierungsspra
g = MakeDing 123
in Bar (the exact opposite of an abstract type? :-).
Another question: What is visible in Bar when the name of MakeDing is
changed to Ding, too?
Cheers,
Sven
--
Sven PanneTel.: +49/89/2178-2235
LMU, Institut fuer Informat
ng in scope (as
expected), while Hugs is completely happy with this.
Can somebody elaborate on this?
Cheers,
Sven
--
Sven PanneTel.: +49/89/2178-2235
LMU, Institut fuer Informatik FAX : +49/89/2178-2211
LFE Programmier- und Modelli
extremely
ugly. And another suggestion: Standardize the Socket library in some
way, all sensible operating systems have sockets by now (or the OS
will vanish soon, anyway, due to the omnipresent internetworking).
Hava a look at Java: Even Joe Programmer can write networki
w-bandwidth
connections, everybody on the Haskell mailing list can easily
reconstruct the original name. Patent pending...
"Everything counts in large amounts" (Depeche Mode)
:-)
Cheers,
Sven
--
Sven PanneTel.: +49/89/2178
heers,
Sven
P.S.: The only response was from Ferguson, pointing out possible
problems with CR/LF vs LF, but I take Java's point of view:
"A newline is a newline is a newline."
--
Sven PanneTel.: +49/89/2178-2235
LMU, Institut fuer Informati
ct that arithmetic is possible
on file positions, see e.g. http://www.wotsit.org/. Merging a file
position with a handle is even worse, because this keeps the file
open even when only the position is needed later.
Opinions?
Cheers,
Sven
--
Sven Panne
iscussion if I had written the more general
(.|) :: Functor f => f a -> (a -> b) -> f b
(.|) = flip fmap
instead...:-}
Cheers,
Sven
--
Sven PanneTel.: +49/89/2178-2235
LMU, Institut fuer Informatik FAX :
Sven
--
Sven PanneTel.: +49/89/2178-2235
LMU, Institut fuer Informatik FAX : +49/89/2178-2211
LFE Programmier- und Modellierungssprachen Oettingenstr. 67
mailto:[EMAIL PROTECTED]D-80538 Muenchen
ength .| (>lenlim)) .| zip
[1..] .| map (\(n,l) -> shows n ") " ++ l) .| unlines .| putStr
[ This mail is optimised for 1280x1024 in landscape mode... ]
Cheers,
Sven
--
Sven PanneTel.: +49/89/2178-2235
LMU, Institut fuer Informatik
fn lenlim = readFile fn >>= lines .| filter (length .| (>lenlim)) .|
unlines .| putStr
Whether this is more or less readable than Hannah's version is largely
a matter of personal taste.
Cheers,
Sven
--
Sven PanneTel.: +49/89/2178-2235
L
rately
> preprocessor directives. [...]
Hmmm, defining symbols is obfuscating...?
\end{sarcasm}
Cheers,
Sven
--
Sven PanneTel.: +49/89/2178-2235
LMU, Institut fuer Informatik FAX : +49/89/2178-2211
LFE Programmier-
a case of typing
> 'ghcmake' in a directory that contains at least Main.hs.
... and 'ghcmake MyMain1.hs', 'ghcmake MyMain2.hs', ... should be
possible, too. I'd really love to have this for teaching.
Cheers,
Sven
--
Sven Panne
by isAlphaNum. "Keep the common case simple".
As an additional tool it could be nice.
Cheers,
Sven
--
Sven PanneTel.: +49/89/2178-2235
LMU, Institut fuer Informatik FAX : +49/89/2178-2211
LFE Programmier- und Modellierungsspr
cripts, Hugs fails with a "Program line next to comment". I stumbled
over this when trying a different version of the above program).
With a big *sigh*,
Sven
--
Sven PanneTel.: +49/89/2178-2235
LMU, Institut fuer Informatik FA
;= (\xs -> return (filter (\(x:_) -> x /= '.') xs))
or to impress your friends with your higher-order programming skills:
;-)
liftM (filter $ (/= '.') . head) $ getDirectoryContents "."
The funny Pfail in the error message stems from the fa
print . head $ ys
where (xs,ys) = splitStream (repeat 1)
This gives you space usage linear in n... :-(
Cheers,
Sven
--
Sven PanneTel.: +49/89/2178-2235
LMU, Institut fuer Informatik FAX : +49/89/2178-2211
LF
Fergus Henderson wrote:
> On 05-Nov-1998, Sven Panne <[EMAIL PROTECTED]> wrote:
> > [...] Please automatically prefix the subjects with
> > something like [haskell], [ghc-bugs], [ghc-users].
>
> BTW, this is easily done using majordomo -- you just set the
> &q
reliable.
Cheers,
Sven
P.S.: No, I'm not affiliated with Great Circle Associates! :-)
--
Sven PanneTel.: +49/89/2178-2235
LMU, Institut fuer Informatik FAX : +49/89/2178-2211
LFE Programmier- und Modellie
rary contains some layout
errors.
Waiting for enlightment,
Sven "Nitpick" Panne
--
Sven PanneTel.: +49/89/2178-2235
LMU, Institut fuer Informatik FAX : +49/89/2178-2211
LFE Programmier- und Modellierungssprachen
= k (s . showChar '\n')
format :: ((ShowS -> ShowS) -> ShowS -> a) -> a
format c = c id id
Example:
format (l_ "Foo" . p_ . s_ . p_ . n_) (2+2) "y" True ""
=> "Fo
should *really* end up in Haskell's standard libs.
Admittedly, these are all things having very little to do with the
merry world of the lambda calculus, they are of crucial importance if
Haskell should be accepted as a non-toy language.
--
Sven Panne
Nothing very
concrete, just to get a feeling for what is changing. This has nothing
to do with Green Card per se, but both things are needed for some
planned/running projects here and I suspect this combination will not
be uncommon when existing APIs are ported to Haskell.
--
Sven Panne
inear manner.
GHC's behaviour is even worse: In addition to a large heap, the compiled
program needs *lots* of stack space, too. Comments (or excuses :-) from
Glasgow?
Space leaks like this are lurking in a lot of places in the standard
prelude, so it's quite funny that Hugs
oteric examples from category theory.
--
Sven PanneTel.: +49/89/2178-2235
LMU, Institut fuer Informatik FAX : +49/89/2178-2211
LFE Programmier- und Modellierungssprachen Oettingenstr. 67
mailto:[EMAIL PROTECTED]D
source-to-source transformations.
Don't hesitate, contribute!
--
Sven PanneTel.: +49/89/2178-2235
LMU, Institut fuer Informatik FAX : +49/89/2178-2211
LFE Programmier- und Modellierungssprachen Oettingenstr. 67
mai
and returning a "b"
and a list of "a"s,
yield an IO action returning a list of "b"s.
Here, both "a" and "b" are String.
P.S.: Closing the files with hClose would be a good idea...
--
Sven Panne
http://www.pms.informatik.uni-muenchen.de/mitarbeiter/panne/happy-0.99.tar.gz
It should work fine with recent Versions of GHC and Hugs. It's basically
Happy 0.9a with massaged imports/exports, replacement of a home-made
monad with the standard IO monad, and better command line handling.
--
ecific to this
kind of problem?
[Help is desperately needed. Otherwise the Prolog menace is waiting for
me again... :-( ]
--
Sven PanneTel.: +49/89/2178-2235
LMU, Institut fuer Informatik FAX : +49/89/2178-2211
LFE Programmier- und Model
baz :: Collection a Char => a Char -> a Char
baz c = bar c 'a'
addRange :: (Enum a, Collection col a) => a -> a -> col a -> col a
addRange start end c = foldr add c [start..end]
test :: SList Char
test = addRange 'a' 'z
101 - 165 of 165 matches
Mail list logo