putStr is a pure function, but it isn't a "pure function" ;)
OTOH, getLine isn't even a function, just a value.
--
Glynn Clements <[EMAIL PROTECTED]>
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe
n of
Haskell's putStr etc sucks when using NoBuffering (one write() per
character).
C follows the same rules (stdin/stdout use line buffering for
terminals, block buffering otherwise, stderr is always unbuffered),
even though C's puts(), printf() etc behave a lot better with
unbuffered str
an explit hFlush after each putStr rather than
disabling buffering altogether, as disabling buffering will result in
putStr etc calling write() once per character, which is very
inefficient.
--
Glynn Clements <[EMAIL PROTECTED]>
___
Haskell-Cafe mailing
Branimir Maksimovic wrote:
> >Could you give an example of a loop you find awkward in Haskell?
>
> Well I want simple loop for(int i =0;i<10;++i)doSomething(i);
mapM_ doSomething [0..9]
--
Glynn Clements <[EMAIL PROTECTED]>
___
se, you can't actually obtain instances of it within a Haskell
program, and thus there is no equivalent to runR.
Instead, you provide an IO instance (main) to the runtime, which
(conceptually) applies it to the World value representing the state of
the universe at program start, and updat
houtMode atts ProcessInput
setTerminalAttributes (handleToFd stdin) atts' Immediately
This disables all input processing, e.g. line-editing and CR->LF
translation (i.e. pressing the Enter/Return key will result in CR, not
LF).
Remember to set it back before exiting.
--
Glynn Clement
t symbol means nothing
> particularly "swedish". In fact, I have no idea what it means at all
> =)
It's a generic currency symbol (the X11 keysym is XK_currency). It
doesn't exist on a UK keyboard (where Shift-4 is the dollar si
gral)
>
> or
>
> map (toEnum . fromEnum)
For anything else, you will have to either to write a decoder (or use
someone else's; several exist for UTF-8), or interface to iconv()
using the FFI.
--
Glynn Clements <[EMAIL PROTECTED]>
___
Ha
nising phase is unaffected by whether or not
an operator, constructor, identifier etc is defined. A specific
sequence of characters will always produce the same sequence of tokens
regardless of what definitions exist.
--
Glynn Clements <[EMAIL PROTECTED]>
_
orst case, you just write a Lisp
interpreter.
As for convenience: syntax matters. The equivalence of code and data
in Lisp lets you write your own syntactic sugar. You're still bound by
the lexical (token-level) grammar, although reader macros mean that
isn't much of a restriction.
--
(e.g. depending upon the "type" field).
Haskell-style sum types, (of which Maybe is an example) are a much
better solution, as the the fields only exist when they are
meaningful.
--
Glynn Clements <[EMAIL PROTECTED]>
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe
d or replace the
language's syntax and semantics. In particular, being able to do so
locally.
Probably the most useful consequence is the ability to create new
control constructs without being constrained by the existing syntax
and semantics (and without having to write your own monadic ver
inal state if you
change the buffering for a handle which is associated with a terminal,
but I don't remember the specifics).
--
Glynn Clements <[EMAIL PROTECTED]>
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe
tirely the right language for that,
IMHO.
--
Glynn Clements <[EMAIL PROTECTED]>
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe
When you put the "print" in place of the return, you force the data to
be consumed immediately, so the issue doesn't arise.
--
Glynn Clements <[EMAIL PROTECTED]>
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe
Emacs' shell-mode;
you would have to use terminal-emulator instead ("M-x term" instead of
"M-x shell").
--
Glynn Clements <[EMAIL PROTECTED]>
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe
1 0 0
> 0 0 1 0
> dx dy dz 1
>
> So the result of "v+" is this matrix.
No. If the above matrix is M, then:
[x y z w].M = [x+w.dx y+w.dy z+w.dz w]
which isn't a translation.
In the specific case of homogeneous coordinates, where:
except for functions are instances of Show, and
Haskell can automatically derive Show instances for user defined
types, provided that all of the constituent types are instances of
Show.
--
Glynn Clements <[EMAIL PROTECTED]>
___
Haskell-Cafe mailing lis
a -> a) -> [a] -> a
foldl1 f (x:xs) = foldl f x xs
foldr1 :: (a -> a -> a) -> [a] -> a
foldr1 f [x] = x
foldr1 f (x:xs) = f x (foldr1 f xs)
--
Glynn Clements <[EMAIL PROTECTED]>
__
compile any .hs file to produce .o and .hi files
%.o %.hi: %.hs
$(HC) -c $<
# how to build the prng program
prng: RC4.o prng.o
$(HC) -o $@ $+
# note that prng.o depends upon RC4.hi
prng.o: RC4.hi
--
Glynn Clements <[EM
lly converted to pointers. Arrays only ever occur as
lvalues, never as expressions.
2. In a declaration, the x[...] syntax indicates that x is an array,
but in an expression, x must be a pointer (which includes an array
which has been converted to a pointer due to rule 1 above).
3. When declaring fun
d8 Word8
For an RC4 implementation, you should probably be using Word8
throughout rather than Int or Integer.
--
Glynn Clements <[EMAIL PROTECTED]>
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe
conversions should be
performed so much as arguing about *whether* these conversions should
be performed. The conversion issues are only problems because the
conversions are being done at all.
--
Glynn Clements <[EMAIL PROTECTED]>
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe
h, the filename encoding problems
> will become irrelevant and we will live in an ideal world where unicode
> actually works. Maybe next year, maybe only in ten years.
Maybe not even then. If Unicode really solved encoding problems, you'd
expect the CJK
ated
> > encodings and ISO-2022.
>
> ISO-2022 is an insanely complicated brain-damaged mess. I know it's
> being used in some parts of the world, but the sooner it will die,
> the better.
ISO-2022 has advantages and disadvantages relative to UTF-8.
ns in theory (you can add as many redundant switching
sequences as you wish), there are multiple "plausible" equivalent
representations in practice.
--
Glynn Clements <[EMAIL PROTECTED]>
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe
ename "\377.ppm" couldn't be converted to UTF-8. (try
setting the environment variable G_FILENAME_ENCODING): Invalid byte sequence in
conversion input
and the filename is omitted altogether.
> > The "current locale" mechanism is just a way of avoiding the issues
&g
can be represented as Unicode text,
but whether you can convert it to and from Unicode without problems.
To do this, you need to know the encoding, you need to store the
encoding so that you can convert the wide string back to a byte
string, and the encoding needs to be reversible.
--
Glynn Clements <[EMAIL PROTECTED]>
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe
est case would be a system used predominantly by Japanese,
where (apparently) it's common to have a mixture of both EUC-JP and
Shift-JIS filenames (occasionally wrapped in ISO-2022, but usually
raw).
--
Glynn Clements <[EMAIL PROTECTED]>
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe
them correctly.
>
> Haskell can't just pass byte strings around without turning the
> Unicode support into a joke (which it is now).
If you try to pretend that I18N comes down to shoe-horning everything
into Unicode, you will turn the language into a joke.
Haskell's Unicod
into category 3, using one of the "universal"
encodings (typically ISO-2022 in southeast Asia and UTF-8 elsewhere).
E.g. Gtk-2.x uses UTF-8 almost exclusively, although you can force the
use of the locale's encoding for filenames (if you have filenames in
multiple encodings, you lose; filenames using the "wrong" encoding
simply don't appear in file selectors).
--
Glynn Clements <[EMAIL PROTECTED]>
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe
Marcin 'Qrczak' Kowalczyk wrote:
> Glynn Clements <[EMAIL PROTECTED]> writes:
>
> >> It should be possible to specify the encoding explicitly.
> >
> > Conversely, it shouldn't be possible to avoid specifying the
> > encoding explicitly.
>
it
shouldn't be shoe-horned into doing so because a library developer
decided to duck the encoding issues by grabbing whatever encoding was
readily to hand (i.e. the locale's encoding).
--
Glynn Clements <[EMAIL PROTECTED]>
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe
That still won't handle the case where you mount a single remote
filesystem via both NFS and SMB though. I doubt that anything can
achieve that.
There are also issues of definition, e.g. is "/dev/tty" considered
"equivalent" to the specific "/dev/ttyXX" device for th
nctions accept or return Strings but interface to OS
functions which (at least on Unix) deal with arrays of bytes (char*),
and the encoding issues are essentially ignored. If you pass strings
containing anything other than ISO-8859-1, you lose.
--
Glynn Clements <[EMAIL PROTECTED]>
__
9-1.
The only difference between binary and text modes is that text mode
converts between the platform's EOL conventions (i.e. LF on Unix, CRLF
on Windows) and LF.
--
Glynn Clements <[EMAIL PROTECTED]>
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe
ss-control
lists to discover the myriad different names which can be used to
refer to a given file for which the administrator is (unsuccessfully)
trying to restrict access.
--
Glynn Clements <[EMAIL PROTECTED]>
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe
Marcin 'Qrczak' Kowalczyk wrote:
> >> The various UTF encodings do not have this particular problem; if a UTF
> >> string is valid, then it is a unique representation of a unicode string.
> >> However, decoding is still a partial function and can fail.
> >
> > And while it is
unicode string.
Except that there are some ad-hoc extensions, e.g. the UTF-8 variant
used by both Java and Tcl permits NUL characters to be embedded in
NUL-terminated UTF-8 strings by encoding them as a two-byte sequence
(which is invalid in UTF-8 proper).
--
Glynn Clements <[EMAIL PROTECTED]&g
, Windows accepts both slash and backslash equally in most
situations. It's only really command-line parsing (where slash is
normally used to denote switches) where there's an issue.
--
Glynn Clements <[EMAIL PROTECTED]>
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe
> instance would have to copy the pathname every time. And I don't
> understand exactly what pathFromForeign is supposed to do.
I presume that it's meant to be the fundamental un-marshalling
function for the Path class. But it seems Unix-s
) can only ever
be a partial solution, because you still have the issue that "memory"
(i.e. code/data/stack segments) is demand-paged. The only solution
there is multiple threads.
--
Glynn Clements <[EMAIL PROTECTED]>
___
Haskell-Cafe ma
y until you call read?
True, unless calling select() automatically triggered read-ahead
(which isn't an unreasonable idea).
In that regard, select/poll is different from non-blocking and
asynchronous I/O. With the latter, you're explicitly asking for data
to be read.
--
Glynn Clements <[EMAIL PROTECTED]>
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe
a already.
E.g. a program which performs trivial operations on large files may
well be able to consume the data faster than the kernel can obtain it.
--
Glynn Clements <[EMAIL PROTECTED]>
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe
If you want to be able to utilise the CPU while waiting for disk I/O
to occur, you have to use multiple kernel threads, with one thread for
each pending I/O operation, plus another one for computations (or
another one for each CPU if you want to obtain the full benefit of
an SMP system).
Even then, you
locking I/O, slow streams only block if no data is
available. If less data is available than was requested, they will
usually return whatever is available rather than waiting until they
have the requested amount. Non-blocking I/O only affects the case
where no data is available.
--
Glynn Clements <[EMAIL PROTECTED]>
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe
e that it is readable, even if a subsequent
read() would have to read the data from disk.
--
Glynn Clements <[EMAIL PROTECTED]>
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe
ling kernel
thread.
OTOH, if you are implementing multiple user-space threads within a
single kernel thread, if that kernel thread blocks, all of the
user-space threads within it will be blocked.
--
Glynn Clements <[EMAIL PROTECTED]>
___
Haskel
echanisms for dealing with "slow" I/O (i.e.
pipes, FIFOs, character devices, sockets) don't work. This applies
equally to non-blocking I/O (O_NONBLOCK), asynchronous I/O (O_ASYNC),
select(), poll() etc.
In that regard, mmap()ed I/O is no better or worse t
pen() call.
For this reason, hSetBuffering shouldn't be modifying the ICANON flag,
IMHO.
--
Glynn Clements <[EMAIL PROTECTED]>
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe
e identifier. Just think of the potential for delightfully
> baffling type error messages that might result!
There's also the issue that you wouldn't be allowed to use backticks
within such an expression, so you would need additional grammar rules
describing expressions w
?
[Yes, I know that BLAS/LAPACK are written in Fortran, but I don't
think that changes the argument. The resulting object code (which is
what you would actually be using) wouldn't be significantly different
if they were written in C.]
--
Glynn C
ts value matches; a constant matches
itself; and a structure matches another structure if they have the
same number of components and all of their components match.
You could probably use GHC's type inference code, although converting
it for your purposes may be more work
rate (RateN x) = 1 + rate x;
>
> fourHertzFilter :: unaryProcessor (RateN (RateN (RateN (RateN Rate0
> fourHertzFilter = ...
I doubt that this specific example wouldn't work in practice (the type
inference would probably give the compiler a heart attack), but you
could presumab
occurs, the shell from which the process was spawned will
typically write "Killed" to the terminal.
--
Glynn Clements <[EMAIL PROTECTED]>
___
Haskell-Cafe mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell-cafe
how infinity
"Infinity"
Prelude> read (show infinity) :: Double
Infinity
Prelude> Infinity
:1: Data constructor not in scope: `Infinity'
--
Glynn Clements <[EMAIL PROTECTED]>
___
Haskell-Cafe mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell-cafe
can't for the
> life of me see how to do it.
As the result is a BasicSet, the accumulator would need to be a
BasicSet and the operator would need to have type:
BasicSet -> Range -> BasicSet
This can presumably be implemented as a fol
red, a call to fwrite() may simply result in data
being appended to the buffer; it doesn't guarantee a call to write().
--
Glynn Clements <[EMAIL PROTECTED]>
___
Haskell-Cafe mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell-cafe
l through the cracks":
Prelude> 0.61 `elem` [0.6,0.7..0.9]
False
Whilst you could, without too much effort, enumerate a range of
floating-point values such that all intermediate values were included,
the resulting list would be massive. Single precision f
that it
doesn't interfere, ensuring that it doesn't hide "unnecessary" details
which may actually be necessary in more involved programs, etc.
--
Glynn Clements <[EMAIL PROTECTED]>
___
Haskell-Cafe mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell-cafe
e your own operators on it (or hope that
someone else has written such a library). Generating massive lists (or
other structures) then testing for membership won't result in the
lists being optimised away.
--
Glynn Clements <[EMAIL PROTECTED]>
__
John Goerzen wrote:
> Oh also, I would very much appreciate Haskell interfaces to realpath()
> and readlink().
I don't know about realpath() (which is a BSD-ism, and included in GNU
libc, but I'm not sure about other Unices), but readlink() exists as
System.Posix.readSymbolic
ly and
> efficiently.
File descriptors aren't simply a "resource" in the sense that memory
is. Closing a descriptor may have significance beyond the process
which closes it. If it refers to the write end of a pipe or socket,
closing it may cause the
ng instead. If that
were to happen, it would be practically (as well as theoretically)
impossible to perform binary I/O using the Haskell98 API, even on
Unix.
This issue has been beaten to death fairly recently, so I'm not going
to repeat it here. See the thread entitled "Writing binar
anism for binary I/O.
> Or where should I be finding it, and
> how could I have known for myself that those particular ghc functions
> were unsupported elsewhere?
The Haskell98 report can be found at:
http://www.haskell.org/onlinereport/
Anything which isn't listed there is
all that many programs should be doing.
> Bugs range from small annoyances like tabular output which doesn't
> line up, through mangled characters on a graphical display, to
> full-screen interactive programs being unusable on a U
#x27;t need a more complex interface in Haskell!
Are you sure that will work in the general case? Or are you assuming
lazy I/O?
--
Glynn Clements <[EMAIL PROTECTED]>
___
Haskell-Cafe mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell-cafe
, you would probably want
separate decoders for the headers and body, switching between them as
you read the stream. You wouldn't want to have to accumulate the
entire body as a single byte string just so that you could decode it
in one go, and you can't just "push
gether.
E.g. if I create a file whose name contains control characters, most
GUI programs display it incorrectly in the file selection dialog, but
they still manage to open it.
--
Glynn Clements <[EMAIL PROTECTED]>
___
Haskell-Cafe mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell-cafe
g/decoding
> happens between CreateProcess() and what the target process sees in its
> argv[] (can't be bothered to dig through MSDN right now). I suspect
> these should be Strings in Haskell too, with appropriate
> decoding/encoding happening under the hood.
I suspect that Windows will convert them according to the active
codepage, so that OpenFileA(argv[i], ...) works.
--
Glynn Clements <[EMAIL PROTECTED]>
___
Haskell-Cafe mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell-cafe
(e.g. ISO-2022), or to handle
decoding multi-byte encodings (e.g. UTF-8) in chunks. Unfortunately,
the iconv interface doesn't allow the encoder state to be extracted,
so a generic iconv-based converter would have to be in the IO monad.
--
Glynn Clements <[EMAIL PROTECTED]>
___
Looks like
> a clean solution to me.
Sure. But I'm looking for a solution which doesn't involve re-writing
everything, and which won't result in lots of programs suddenly
becoming unreliable if the hardwired default ISO-8859-1 conversion is
changed.
--
Glynn Clements <[EMAIL
e encoding before any data has been
read or written. I'm more concerned about FilePaths, argv, the
environment etc.
--
Glynn Clements <[EMAIL PROTECTED]>
___
Haskell-Cafe mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell-cafe
ng features (i.e. I/O /
> env functions accepting bytes instead of strings).
It's broken. Being able to represent filenames as byte strings is
fundamental. Being able to convert them to or from character strings
is useful but not essential. The only reason why the existing API
doesn
ure, the statefulness adds complexity (which is one of the reasons so
many people prefer to work with UTF-8), but it has the benefit of
providing distinct markers to indicate where the character set is
being switched (that isn't a compelling advantage; you could
reconstruct the markers if you could unique
/O API (which is pretty text-orientated anyway, see
> hPutStrLn, hGetLine, ...).
If you want text, well, tough; what comes out most system calls and
core library functions (not just read()) are bytes. There isn't any
magic wand which will turn them into characters
bly that OCaml insists upon using UTF-8. [I don't know that
this is the case, but the fact that they specifically mention UTF-8
suggests that it might be.]
IOW, this incident seems to oppose, rather than support, the
filenames-as-characters viewpoint.
--
Glynn Clements <[EMAIL PROTECTED]>
___
y ".."
and:
dir <- getCurrentDirectory
setCurrentDirectory $ parentDirectory dir
[where parentDirectory is a pure FilePath -> FilePath function.]
if the last component in the path is a symlink.
If you want to make FilePath an instance of Eq, the situation gets
much m
a (wide) character. However, that isn't the hand we've been dealt.
--
Glynn Clements <[EMAIL PROTECTED]>
___
Haskell-Cafe mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell-cafe
between byte-streams and wide characters.
>
> ctype.h is useless for UTF-8.
Hello? Let's try that again, with emphasis:
> > C has ... WIDE VERSIONS OF string.h and ctype.h
They're called wchar.h and wctype.h.
> There is no capability of attaching automatic recoder
ent to which this can be achieved. E.g.
> > what happens if you set the encoding to UTF-8, then call
> > getDirectoryContents for a directory which contains filenames which
> > aren't valid UTF-8 strings?
>
> Well, then you did something stupid, didn't you?
pearing any time soon, nor is ISO-2022 (UTF-8 has quite
spectacularly failed to make inroads in CJK-land; there are probably
more UTF-8 users in the US than there).
> It would be great if Haskell programs were in the group which can
> support it instead of being forced to be abandoned because of lack
> of Unicode support in the language they are written in.
Haskell should be able to support it, but it shouldn't refuse to
support anything else, it shouldn't make you jump through hoops to
write usable programs, and we shouldn't have to wait until all of the
encoding issues have been sorted out to do things which don't even
deal with encodings.
Look, C has all of the functionality that we're talking about: wide
characters, wide versions of string.h and ctype.h, and conversion
between byte-streams and wide characters.
But it did it without getting in the way of writing programs which
don't care about encodings, without consigning everything which has
gone before to the scrap heap, and without everyone having to wait a
couple of decades to (reliably) do simple things like copying a file
to a socket or enumerating a directory.
--
Glynn Clements <[EMAIL PROTECTED]>
___
Haskell-Cafe mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell-cafe
neath
> everything.
The byte stream is inherent, as that's (usually) what the OS gives
you. Everything else is synthesised.
--
Glynn Clements <[EMAIL PROTECTED]>
___
Haskell-Cafe mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell-cafe
along with
the means to specify which encoding to use for functions which need to
perform encoding or decoding.
> > My main concern is that someone will get sick of waiting and make the
> > wrong "fix", i.e. keep the existing API but default to the locale's
> > enc
ather not have to wait until someone
finally gets around to designing the new, improved,
genuinely-I18N-ised API before we can read/write arbitrary files
without too much effort.
My main concern is that someone will get sick of waiting and make the
wrong "fix", i.e. keep the existing API
sn't require interpreting any
non-ASCII characters), and write out the results. OTOH, if you assume
UTF-8 (e.g. because that happens to be the locale's encoding), the
decoder is likely to abort shortly after the first non-ASCII character
it finds (either that, or it will jus
which I suggested (and which is the only
choice if your Haskell implementation doesn't have h{Get,Put}Buf).
The problems would come if it was decided to change the existing
behaviour, i.e. use something other than Latin1.
--
Glynn Clements <[EMAIL PROTECTED]>
__
e array has to be held
in memory, which could be an issue if the amount of data involved is
large.
--
Glynn Clements <[EMAIL PROTECTED]>
___
Haskell-Cafe mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell-cafe
changing the existing functions to deal with encodings is likely
to break a lot of things (i.e. anything which reads or writes data
which is in neither UTF-8 nor the locale-specified encoding).
--
Glynn Clements <[EMAIL PROTECTED]>
___
Haskell-Cafe mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell-cafe
:: IO ()
main = do
h <- openBinaryFile "out.dat" WriteMode
hPutStr h $ map (octetToChar . bitsToOctet) bits
hClose h
--
Glynn Clements <[EMAIL PROTECTED]>
___
Haskell-Cafe mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell-cafe
rd8
charToOctet = fromIntegral . ord
octetToChar :: Word8 -> Char
octetToChar = chr . fromIntegral
--
Glynn Clements <[EMAIL PROTECTED]>
___
Haskell-Cafe mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell-cafe
hem to create a high-level
interface (which typically isn't as useful as the author assumes),
then only export the high-level interface.
--
Glynn Clements <[EMAIL PROTECTED]>
___
Haskell-Cafe mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell-cafe
each instance of Packet uses a specific
instance of Location. The instance declaration says that, for
TestPacket, source and destination will always have type TestLocation.
--
Glynn Clements <[EMAIL PROTECTED]>
___
Haskell-Cafe mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell-cafe
solution" is relying upon a misfeature of the language;
one which won't work in the general case. Suppose that fac was a
different function, one which couldn't be defined as returning a
non-integral result without using an explicit (and conceptually
incorrect) type conversion.
, and the result will be
automatically cast to any instance of Fractional.
However, in practice you may end up getting a lot of errors due to
ambiguous types for intermediate results, so it might be better to
force the return type to e.g. Double.
--
Glynn Clements <[EMAIL PROTECTED]>
___
Haskell-Cafe mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell-cafe
not say anymore that a libc compiled with this
: option is using NSS. There is no switch anymore. Therefore it is
: *highly* recommended *not* to use --enable-static-nss since this makes
: the behaviour of the programs on the system inconsistent.
IOW, you will probably have to build glibc yourse
on which element of which sublist I am at the moment
> in pullHelper function which starts with values !! ind p xs !!
Note that Haskell has arrays as well as lists. Arrays may be better
suited to your problem.
--
Glynn Clements <[EMAIL PROTECTED]>
__
lid solution).
If you prefer (row, column) pairs, use e.g.:
main = print $ map (zip [1..]) $ queens 10
--
Glynn Clements <[EMAIL PROTECTED]>
___
Haskell-Cafe mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell-cafe
c. randomR can use any of Int, Integer,
Float or Double, but it needs to know which. Adding an explicit type
signature to one of the literals will eliminate the error, e.g.:
m1 = do b <- getStdRandom (randomR (1,10 :: Int))
print b
--
Glynn Clements <[EMAIL PROTECTED
symlink("/etc", "bar");
/* "find" ends up chdir()ing into /etc */
To deal with that situation, calls to chdir() need to be followed up
with a check to ensure that they ended up where they thought they
would, e.g. by comparing the device:inode pair for "." with the values
obtained from the lstat() on the directory entry, or by comparing the
device:inode pair for ".." with those for the previous directory.
--
Glynn Clements <[EMAIL PROTECTED]>
___
Haskell-Cafe mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell-cafe
1 - 100 of 135 matches
Mail list logo