[No response on haskell-cafe; trying haskell]
Does anyone know if I can bring a 64-bit (long long or unsigned long
long) value from C-land into Haskell via hsc2hs? #const on such a
value seems to provide only the low 32 bits, at least in my
environment (Haskell Platform 2009.2.0.2 on Windows)
At 7:31 PM +0100 2/24/06, minh thu wrote:
Hi all,
1/
I'd like to know how can I implement an interactive program (an
editor) in haskell where some "things" have to be updated.
The "things" can be text in a word processor, or a pixel array in a
2d graphics editor, and so on.
Have I to pass the
Title: RE: [Haskell] stack overflow - nonobvious
thunks?
The following version seems to do the trick (and still remain
quite readable). It worked for 1 as well.
import Data.Map as Map
import System.Random
import Data.List (foldl')
table :: (Ord a) => [a] -> [(a,Int)]
table xs = Map.ass
At 10:11 PM -0400 4/18/05, Cale Gibbard wrote:
The action readFile is a bit unsafe in that it does lazily interleaved
IO -- that is, the file is read as you consume the string, and only
the part of the string which you use will be read from the file -- if
the file is 10G, but you only end up needin
Is there any practical way to do client-side web scripting in
Haskell? All the references I have found to HaskellScript seem quite
out of date.
Dean
___
Haskell mailing list
Haskell@haskell.org
http://www.haskell.org/mailman/listinfo/haskell
At 4:05 PM + 12/8/04, Ben Rudiak-Gould wrote:
Dean Herington wrote:
deepSeq :: DeepSeq a => a -> b -> b
I should point out that deepSeq with this type is the composition of
two simpler operations:
deepSeq = seq . eval where eval :: DeepSeq a => a -> a
eval ties a demand f
Here's the latest version of my DeepSeq module.
Dean
DeepSeq.lhs -- deep strict evaluation support
The `DeepSeq` class provides a method `deepSeq` that is similar to
`seq` except that it forces deep evaluation of its first argument
before returning its second argument.
Instances of `DeepSeq` are
Is there a good reason why `exitImmediately` (in System.Posix.Process as
well as other places) shouldn't return `IO a` instead of `IO ()`?
___
Haskell mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell
On Wed, 1 Oct 2003, Keith Wansbrough wrote:
> > Can actually someone supply an implementation of something like interact
> > that does no pipelining for the argument "id"? Simply doing "putStr !$ f
> > !$ s" was not enough!
>
> Yes, of course.
>
> Your code above only forces the evaluation of
Can someone explain why the following doesn't work? Is there some other
way to achieve the same effect (declaring a set of instances for pair-like
types in one go)?
Thanks.
Dean
swan(108)% cat Test1.hs
{-# OPTIONS -fglasgow-exts #-}
class R r where
rId :: r -> String
class (R r) => RT r t
Tom Pledger wrote:
> K. Fritz Ruehr writes:
> :
> | But Jerzy Karczmarczuk enlightened me as to the full generality possible
> | along these lines (revealing the whole truth under the influence of at
> | least one beer, as I recall). Namely, one can define a sequence of
> | functions (let's u
Dylan Thurston wrote:
> On Thu, Jun 19, 2003 at 11:08:35AM -0500, Ed Komp wrote:
> > > | type BaseType = Either Integer ( Either Bool () )
> > > |
> > > | type Value = (Either Double BaseType)
> > > |
> > > | data Foo = forall x. (SubType x BaseType) => MkFoo x
> > > |
> > > | test :: Foo
Niels Reyngoud wrote:
> Hello all,
>
> Thanks for your replies on our previous posts. To avoid the lazy
> behaviour, we tried to write our own IO module "IOExts2" which basically
> redifnes
> readFile, writeFile and appendFile to make sure they use binary-mode and
> strict behaviour. The libary is
On Thu, 12 Jun 2003, Wolfgang Jeltsch wrote:
> On Thursday, 2003-06-12, 18:01, CEST, Filip wrote:
> > Hi,
> >
> > I wrote something like "let t = try (hGetLine h1)" and I would like to check
> > is it EOFError or not. How can I do this ??
> >
> > Thanks
>
> Hello,
>
> the above code assigns the
On Thu, 12 Jun 2003, Niels Reyngoud wrote:
> Hello,
>
> We're two students from the department of computer science at the
> University of Utrecht (the Netherlands), and we're havind some severe
> difficulties in working
> with file handles in Haskell. Consider for example the following program
On Sun, 9 Mar 2003, Hal Daume III wrote:
> well, yes, but if you export:
>
> mkN :: Int -> N
> mkD :: Int -> D
>
> or something like that, then they'll still bea ble to tell the difference,
> right?
Well, yes, but I don't. In fact the type in question is an MVar which my
abstraction ensures is
If a type that could be defined either by `data` or `newtype` (i.e., a
single-constructor type) is exported abstractly (without its constructor),
can the user of the type tell how the type was declared?
Dean
___
Haskell mailing list
[EMAIL PROTECTED]
h
Oops! Small bug. See below.
Dean Herington wrote:
> You can't derive Enum Player automatically, but you can program it. Here's one
> way how, using shorter example names.
>
> -- Dean
>
> data E1 = E1a | E1b | E1c deriving (Enum, Bounded, Show, Read)
> data E2 =
You can't derive Enum Player automatically, but you can program it. Here's one
way how, using shorter example names.
-- Dean
data E1 = E1a | E1b | E1c deriving (Enum, Bounded, Show, Read)
data E2 = E2a | E2b | E2c deriving (Enum, Bounded, Show, Read)
data E = E1 E1 | E2 E2deriving (Show, R
On Fri, 14 Feb 2003, John Meacham wrote:
> This seems to be contrary to how i thought haskell was implemented in
> ghc (and probably other systems). I was under the impression that thunks
> in ghc were opaque except for the code address at the begining of them.
> in order to evaluate something you
uot; wrote:
> Dean Herington <[EMAIL PROTECTED]> writes:
>
> > "Ketil Z. Malde" wrote:
>
> >> -- | add data from a file to the histogram
> >> addFile :: FiniteMap String Int -> String -> IO (FiniteMap String Int)
> >> addFile fm name = do
"Ketil Z. Malde" wrote:
> "Simon Marlow" <[EMAIL PROTECTED]> writes:
>
> > > > -- | add data from a file to the histogram
> > > > addFile :: FiniteMap String Int -> String -> IO (FiniteMap
> > > String Int)
> > > > addFile fm name = do
> > > > x <- readFile name
> > > > ret
y.
>
> --
> Hal Daume III
>
> "Computer science is no more about computers| [EMAIL PROTECTED]
> than astronomy is about telescopes." -Dijkstra | www.isi.edu/~hdaume
>
> On Mon, 27 Jan 2003, Dean Herington wrote:
>
> > Can someone explain why the type declar
Can someone explain why the type declaration for `g` is required in the
following?
class RT r t where rt :: r -> t
data D t = Dt t | forall r. RT r t => Dr r
f :: D t -> D t
f = g
where -- g :: D t -> D t
g (Dr r) = Dt (rt r)
As given above, the program evokes these error messages:
w
On Sun, 26 Jan 2003, Norman Ramsey wrote:
> > > In a fit of madness, I have agreed to deliver a 50-minute lecture
> > > on type classes to an audience of undergraduate students. These
> > > students will have seen some simple typing rules for F2 and will
> > > have some exposure to Hindley-Mi
I was unhappy with the use of `error` in my first solution, so I wrote a
second solution that's more robust. It also demonstrates monadic style.
The new solution is at the bottom.
Dean
On Thu, 23 Jan 2003, Dean Herington wrote:
> On Sun, 19 Jan 2003, Nick Name wrote:
>
> &
On Sun, 19 Jan 2003, Nick Name wrote:
> I got another trouble: I need to build a record type like
>
> Package { name :: String, version :: Int , mantainer :: String ... other
> fields ... }
>
> from a list of string of the form
>
> ["Package: ..." , "Mantainer: ..." , "Version: ..." , ... ]
>
Mark P Jones wrote:
> Moreover,
> in attempting to "optimize" the code, you might instead break it
> and introduce some bugs that will eventually come back and bite.
Indeed! If we take Mark Phillips's original version of penultimax as our
specification, all four alternate versions are incorrect:
On 7 Nov 2002, Alastair Reid wrote:
> > Why not just define your own function, much like `read`, that
> > produces a more suitable error message?
>
> readsPrec (i.e., the class method) doesn't report how far it got when
> it reports failure.
Yes, that's true if no prefix is a valid parse. In th
On Thu, 7 Nov 2002, Johannes Waldmann wrote:
> Dear all, I would welcome some advice
> on getting better error messages
> when using read :: Read a => a
>
> The problem is, `readsPrec' (the class method)
> eats the longest feasible input prefix,
> but when I call `read' (built-in prelude funct
Dean Herington wrote:
> On Tue, 29 Oct 2002, Christian Sievers wrote:
>
> > I guess "equivalent" just means equality without suggesting that the type is
> > an instance of Eq. There are other places where the report uses == in
> > situations where you can'
On Tue, 29 Oct 2002, Christian Sievers wrote:
> I guess "equivalent" just means equality without suggesting that the type is
> an instance of Eq. There are other places where the report uses == in
> situations where you can't really apply it, for example, in D.2 it says
> "we would have
>
On Tue, 29 Oct 2002, Simon Peyton-Jones wrote:
> Some last-ditch H98 stuff. I have the proofs now and have to send them
> back this week. Changes will become impossible (or at least much
> harder) after that. Ah well, I'm sure more errors will come to light.
>
> Simon
>
>
> | > | (3) Section
Simon Peyton-Jones wrote:
> | (1) In the first section, in:
> |
> | instance (cx, cx') => Ci (T u1 ... uk) where { d }
> |
> | the use of "(cs, cs')" is a bit loose (that is, suggestive rather than
> | precise syntax). One can't (according to the report, though GHC seems
> to
> | allow it) ha
It's unfortunate that the exception classifier functions differ between
GHC and Hugs, even where capabilities overlap.
GHC has:
ioErrors :: Exception -> Maybe IOError
arithExceptions :: Exception -> Maybe ArithException
errorCalls :: Exception -> Maybe String
dynExceptions :: Exce
Simon Peyton-Jones wrote:
> Folks
>
> The concrete is setting fast, but Ross points out that the instance for
> Enum (Ratio a) is inconsistent with that for Enum Float and Enum Double.
> (It's strange that these non-integral types are in Enum, but we're stuck
> with that.)
>
> All three use 'numer
Ferenc Wagner wrote:
> "Simon Peyton-Jones" <[EMAIL PROTECTED]> writes:
>
> > So I propose to modify the instance decl for Ratio by
> > adding explicit defns for succ/pred just like those in
> > Float/Double.
>
> I bet you guessed: once at it, what about removing those
> unintuitive 1/2-s, like:
>
Simon Peyton-Jones wrote:
> | In GHC 5.04.1, derived instances of Show mishandle precedence:
> |
> | Prelude> putStrLn (showsPrec 10 (Just 0) "")
> | Just 0
> |
> | The result should be: (Just 0)
>
> I think it's a bug in the Report, not in GHC, actually. The Report says
> (Section D.4)
>
> "
Paulo Sequeira wrote:
> A friend is considering to start a project of building a generator of
> certain particular (pieces of) programs. The code generated is most likely
> to be Java.
>
> Anyone knows of a module that provides data structures and functions for
> representing and manipulating Jav
The type `Dynamic` is an instance of `Show` but not of `Read`. Is there
some reason `Dynamic` could not be made an instance of `Read`? Has
anyone extended `Dynamic` in that way?
Dean Herington
___
Haskell mailing list
[EMAIL PROTECTED]
http
By "true concurrency" I meant "simultaneous execution of multiple threads
by multiple processors". This involves both concepts you define:
"concurrency" (to have multiple threads) and "parallelism" (to have them
execute possibly simultaneously when multiple processors are available).
>From Sim
n GHC. If the
costs are the same, does that rely on there being no true concurrency in
the current implementations? How would the cost change if true
concurrency were provided? Wouldn't thunk evaluation involve mutual
exclusion?
Dean Herington
___
be provision of any normal Int value. It's
been a distinct disappointment for me that Haskell allows such
operations to produce a result without any indication that a
representation fault occurred.
Dean Herington
___
Haskell mailing list
[
to write a graphical
test controller for HUnit?)
Dean Herington
On Fri, 1 Feb 2002, Ashley Yakeley wrote:
> At 2002-02-01 10:45, Dean Herington wrote:
>
> >h1 :: (a -> a -> (a,a)) -> (a -> a -> (a,a)) -> (a -> a -> (a,a))
> >h1 = f1 # g1
>
> I think you mean:
>
> h1 :: (a -> a -> (a,a)) -> (a
GHC accepts the declaration:
(a # b) = a ++ b
but Hugs rejects it, saying:
Syntax error in input (unexpected `=')
Who's right?
--Dean
___
Haskell mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell
)
h1 = f1 # g1
Hugs reports:
ERROR "Composition.hs" (line 52): Cannot justify constraints in explicitly
typed binding
*** Expression : h1
*** Type : (a
-> a -> (a,a)) -> (a -> a -> (a,a)) -> a -> a -> (a,a)
*** Given context : ()
*** Constraints : Compo
/pipermail/haskell/2001-August/001581.html and followup
article.
Dean Herington
Amanda Clare wrote:
> I have some code which is being unnecessarily lazy (and occupying too
> much heap space). The code should read and process several files one by
> one. What's happening is that all f
Andreas Gruenbacher wrote:
> Hello,
>
> I was trying to write an abstraction for bidirectional communication
> between two threads. For some reason, MVars seem to break:
>
> ---
> class Cords c t u where
> newCord :: IO (c t u)
> listen :: c t u
e the heap size (much) above its default 25 cells. It sounds
from the error message, though, that 16000 is simply a limit set in the
Hugs interpreter.
Any ideas on how to make this combination of Happy-generated parser and
Hugs work together?
Thanks in advance.
Dean Herington
[EMAIL PROTECTED]
iance with Haskell 98, etc.) of these tools (and any others that you
consider useful) for such a project.
Thanks in advance.
Dean Herington
Department of Computer Science
University of North Carolina at Chapel Hill
[EMAIL PROTECTED]
51 matches
Mail list logo