On Tue, Mar 15, 2005 at 10:44:28AM +, Ross Paterson wrote:
>
> You can select binary I/O using the openBinaryFile and hSetBinaryMode
> functions from System.IO. After that, the Chars you get from that Handle
> are actually bytes.
What about the ones sent to it?
Are all the following results
Benjamin Pierce wrote:
Other people seem to rely on Haddock to generate interfaces as
documentation. This is nicer in many ways (e.g., it solves the above
problem because Haddock elides the right-hand side of a "data" or "newtype"
declaration if the constructors are not exported by the module), bu
Benjamin Pierce wrote:
> For someone coming to Haskell from an OCaml background, one of the hardest
> things to get used to is the somewhat more bare bones module system that
> Haskell provides.
> ...
> This works fine as long as what you're exporting is just values, but it's
> awkward for types,
For someone coming to Haskell from an OCaml background, one of the hardest
things to get used to is the somewhat more bare bones module system that
Haskell provides. Naturally, as I've gotten into the Haskell groove I've
discovered (or learned from reading other people's code) nice ways of doing
*
Bryce Bockman wrote:
> How would you guys memoize the following code.
>
> simpleCalc :: (Int,Int) -> (Int,Int)
> simpleCalc (1,l) = (1,l+1)
> simpleCalc (x,l) | (odd x) = simpleCalc (((3*x) + 1), 1 + l)
> | otherwise = simpleCalc ((x `div` 2), 1 + l)
>
> sCalc x = simpleCalc (x,
If I have,
newtype Floating a => Vector a = Vector [a]
if I want to make it an instance of Functor (with the obvious meaning),
how do I write that?
Thanks,
Mark
--
Haskell vacancies in Columbus, Ohio, USA: see http://www.aetion.com/jobs.html
John Meacham <[EMAIL PROTECTED]> writes:
> In any case, we need tools to be able to conform to the common cases
> of ascii-only (withCAStrirg) and current locale (withCString).
>
> withUTF8String would be a nice addition, but is much less important to
> come standard as it can easily be written by
On Wed, Mar 16, 2005 at 05:13:25PM +, Glynn Clements wrote:
>
> Marcin 'Qrczak' Kowalczyk wrote:
>
> > >> It doesn't affect functions added by the hierarchical libraries,
> > >> i.e. those functions are safe only with the ASCII subset. (There is
> > >> a vague plan to make Foreign.C.String co
G'day.
Quoting Bryce Bockman <[EMAIL PROTECTED]>:
> How would you guys memoize the following code.
Take a look here:
http://haskell.org/hawiki/MemoisingCafs
Cheers,
Andrew Bromage
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www
How would you guys memoize the following code.
simpleCalc :: (Int,Int) -> (Int,Int)
simpleCalc (1,l) = (1,l+1)
simpleCalc (x,l) | (odd x) = simpleCalc (((3*x) + 1), 1 + l)
| otherwise = simpleCalc ((x `div` 2), 1 + l)
sCalc x = simpleCalc (x,0)
sCalcListRange a b = map sCalc [a..b
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.
What encoding should a binding to readline or curses use?
Curses in C comes in two flavors: the traditio
Marcin 'Qrczak' Kowalczyk wrote:
> >> It doesn't affect functions added by the hierarchical libraries,
> >> i.e. those functions are safe only with the ASCII subset. (There is
> >> a vague plan to make Foreign.C.String conform to the FFI spec,
> >> which mandates locale-based encoding, and thus w
Duncan Coutts <[EMAIL PROTECTED]> writes:
>> It doesn't affect functions added by the hierarchical libraries,
>> i.e. those functions are safe only with the ASCII subset. (There is
>> a vague plan to make Foreign.C.String conform to the FFI spec,
>> which mandates locale-based encoding, and thus w
On Wed, 2005-03-16 at 13:09 +, Duncan Coutts wrote:
> On Wed, 2005-03-16 at 11:55 +, Ross Paterson wrote:
> > It doesn't affect functions added by the hierarchical libraries, i.e.
> > those functions are safe only with the ASCII subset. (There is a vague
> > plan to make Foreign.C.String
On Wed, 2005-03-16 at 11:55 +, Ross Paterson wrote:
> On Wed, Mar 16, 2005 at 03:54:19AM +, Ian Lynagh wrote:
> > Do you have a list of functions which behave differently in the new
> > release to how they did in the previous release?
> > (I'm not interested in changes that will affect only
On Wed, Mar 16, 2005 at 03:54:19AM +, Ian Lynagh wrote:
> Do you have a list of functions which behave differently in the new
> release to how they did in the previous release?
> (I'm not interested in changes that will affect only whether something
> compiles, not how it behaves given it compi
On Sun, Feb 13, 2005 at 11:25:07PM +0100, Remi Turk wrote:
> > > (as the paper claims that e.g. mergeIO :: [IO a] -> IO a is
> > > unimplementable in anything built on mutexes and condition
> > > variables.)
> >
> > My STM monad is not IO, it has the same restrictions as STM in the
> > paper. The
On 16 March 2005 03:54, Ian Lynagh wrote:
> On Tue, Mar 15, 2005 at 10:44:28AM +, Ross Paterson wrote:
>> On Mon, Mar 14, 2005 at 07:38:09PM -0600, John Goerzen wrote:
>>> I've got some gzip (and Ian Lynagh's Inflate) code that breaks
>>> under the new hugs with:
>>>
>>> : IO.getContents: p
18 matches
Mail list logo