On Fri, Feb 08, 2013 at 02:28:20PM +, Simon Marlow wrote:
> [..]
> So I think, if anything, there's pressure to have fewer major
> releases of GHC. However, we're doing the opposite: 7.0 to 7.2 was
> 10 months, 7.2 to 7.4 was 6 months, 7.4 to 7.6 was 7 months. We're
> getting too efficient at
This is copying to the list my reply to Simon:
On Thu, Jan 03, 2013 at 12:57:02PM +, Simon Peyton-Jones wrote:
> OK I have tested with today's GHC 7.6.2, which is very slightly later
> than the release candidate.
>
> When I add (EuclideanRing (UPol k)) to the signature for cubicExt, the
> who
On Wed, Jan 02, 2013 at 11:27:15PM +, Simon Peyton-Jones wrote:
> I made a second mistake. I meant (LinSolvRing (UPol k)). Apologies.
>
> | > I don't know why 7.4 accepts it, but I'm not inclined to investigate...
> | > looks like a bug in 7.4.
> |
> | ghc-7.4.1 may use a special trick,
On Wed, Jan 02, 2013 at 08:23:37PM +, Simon Peyton-Jones wrote:
> | > The solution is to add (EuclideanRing k) to the type sig of cubicExt.
> | > Then it compiles all the way up to the top.
> |
> | But the DoCon declares
> |class (EuclideanRing a, FactorizationRing a) => Fi
cubicExt :: (Field k, FactorizationRing (UPol k)) =>
k -> k -> Domains1 k -> (Domains1 (E k), [E k], k -> E k)
So, why the compiler does not `extract' EuclideanRing k from Field k
?
Regards,
--
Sergei
> | -Original Message-
> | From:
On Thu, Oct 18, 2012 at 01:54:45PM -0400, Albert Y. C. Lai wrote:
> On 12-10-18 05:24 AM, Serge D. Mechveliani wrote:
>> And concerning this example: I am not even sure now that it worths to
>> setting $! there.
>> Because I deliberately program qRem as returning a pair (
On Wed, Oct 17, 2012 at 07:00:38PM +0300, Roman Cheplyaka wrote:
> * Serge D. Mechveliani [2012-10-17 19:37:38+0400]
> > But it is generally difficult for me to admit that sometimes it is
> > desirable to use strinctess annotation.
> > I programmed DoCon for 6 years, and it
On Wed, Oct 17, 2012 at 06:17:28PM +0300, Roman Cheplyaka wrote:
> * Serge D. Mechveliani [2012-10-17 19:02:37+0400]
> > People,
> > consider the following contrived program for division with remainder:
> >
> > -
People,
consider the following contrived program for division with remainder:
qRem :: Int -> Int -> (Int, Int)
qRem m n = if m < 0 || n <= 0 then error "\nwrong arguments in qRem.\n"
else qRem' 0 m
Who can tell, please, how read string :: Integer
is implemented in ghc-7.4.1 ?
Is it linked from the GMP (Gnu Multi-Precision) library?
It is suspiciosely fast :-)
In my test on 10^5 strings of length l = 5, 20 it shows the cost order
in l less than 1, as if it was O(log(l)), or O(squ
Dear GHC team,
I have compared for performance on DoCon of
ghc-7.4.1 registerised and unregisterised,
both made from source by ghc-7.4.1
(Debian Linux, GenuineIntel, Intel(R) Core(TM)2 CPU),
DoCon and its test compiled under -O
(-O2 is not better than -O).
Dear GHC team,
For some reason ghc-7.4.1-unregisterised cannot build random-1.0.1.1
-- unlike ghc-7.4.1-default.
This is for ghc-7.4.1 built from source by ghc-7.4.1 on
Debian Linux, i386-uknown.
1. I build ghc-7.4.1 from source under the default flags,
by ghc-7.4.1, under
co
On Mon, Feb 06, 2012 at 02:33:53PM +0100, Karel Gardas wrote:
> [..]
> I would recommend to start here:
> http://hackage.haskell.org/trac/ghc/wiki/Building/Unregisterised
>
Thank you.
Probably, there is something like an error on
http://hackage.haskell.org/trac/ghc/wiki/Building/Unregisteri
People,
Please, where the build guide (.pdf, .html) can be download from?
Does the source GHC distibution include the build guide?
Does the GHC user_guide include the build guide?
If not, then -- why?
How to build unregisterized ghc-7.4.1 from source?
(For many years I read "registerized" in
On Sun, Feb 05, 2012 at 09:09:58PM +0100, Krzysztof Skrz??tnicki wrote:
> GHC code still depends on RTS code (written in C by the way) which has to
> be ported to a specific platform first. Native code generator offers
> 'registered' and 'unregistered' builds. The first are aware of specific
> regi
Dear GHC team,
I cannot understand why do you remove the C stage in GHC.
To my mind: let the result be 3 times slower, but preserve the C code.
Because it works everyhere, and there is no real need to rewrite
the same program separately for all the existing processors
(which number may become, for
Dear GHC team,
I needed to look into the C code made by ghc-7.4.1
(made from source by 7.0.1 on Debian Linux)
for
module TT (dropCWhile) where
dropCWhile :: (Char -> Bool) -> [Char] -> [Char]
dropCWhile p xs = case xs of []-> []
x: ys -> if p x then
Dear GHC team,
I have tested ghc-7.4.0.20120126 on Linux Debian, i-386-like
by the following tests.
1. Making it by ghc-7.4.0.20111219.
2. Making it by itself.
3. Making random-1.0.1.1.
4. Making and running the DoCon-2.12 test.
5. Making and running an example under DoCon-2.12 under -prof
On Fri, Jan 27, 2012 at 11:15:46PM +, Ian Lynagh wrote:
>
> We are pleased to announce the first release candidate for GHC 7.4.1:
>
> http://www.haskell.org/ghc/dist/7.4.1-rc2/
>
The first candidate or the second?
(for the date is Jan 27).
Is ghc-7.4.0.20111219 the first candidate?
To my
>> Dear GHC team,
>> I am testing the IO operations of GHC with the Unix named pipes
>> [..]
Albert Y. C. Lai writes on 19 Jan 2012
> Main.hs does not open fromA at all. (fromA_IO is dead code.) This causes
> fifo2.c to be hung whenever it opens fromA. From the man page of mkfifo(3)
> o
Dear GHC team,
I am testing the IO operations of GHC with the Unix named pipes
(in ghc-7.01 under Debian Linux).
In the below example,
the pipe pair are created by > mkfifo toA
> mkfifo fromA,
`main' in Main.hs opens toAfor writing,
On Fri, Jan 13, 2012 at 12:19:34PM -0800, Donn Cave wrote:
> Quoth "Serge D. Mechveliani" ,
> ...
> > Initially, I did the example by the Foreign Function Interface for C.
> > But then, I thought "But this is unnatural! Use plainly the standard
> > Haskell I
On Fri, Jan 13, 2012 at 04:34:37PM +0100, Chadda?? Fouch?? wrote:
> On Thu, Jan 12, 2012 at 7:53 PM, Serge D. Mechveliani
> wrote:
> > [..]
> > I need to organize a string interface for a Haskell function
> > Main.axiom and a C program
> >
People,
GHC provides some extensions for kinds.
Does this make possible different kinds, for example, for `*' ?
Prelude.Num has * :: a -> a -> a.
And mathematicians also like to denote as `*'
(\cdot in TeX)
a "multiplication of a vector v by a coefficient r". It is expressed by the
declarati
Dear GHC team,
I have tested ghc-7.4.0.20111219 on Debian Linux by
1) making it from source,
2) making it by itself,
3) making DoCon-2.12 and running its test.
It looks all right.
In installing DoCon, there appears a new point of installing the package
Random, because Random has separa
On Sun, Jan 01, 2012 at 07:51:39AM -0500, Ryan Newton wrote:
> I haven't entirely followed this and I see that it's been split over
> multiple threads.
>
> Did "cabal install random" actually fail for you under
> ghc-7.4.0.20111219? If so I'd love to know about it as the maintainer
> of the "rand
People,
I have ghc-7.4.0.20111219 made from source and tested it on the
DoCon-2.12 application -- thanks to people for their help!
It looks all right.
This was -- with skipping the module Random.
Now it remains to add the Random package.
I have taken AC-Random Version 0.1 from hackage.
Its
Dear GHC team,
The archive
http://botik.ru/pub/local/Mechveliani/ghcBugs/ghc741candQuest.zip
contains the source of the docon-2.12 application.
ghc-7.0.1 compiles it and runs the test successfully.
ghc-7.4.0.20111219 cannot compile it.
1. It requires to add Show a to Integral a in a
Sorry, I have forgotten to copy to the List my last note on this subject.
The on-line spec of Haskell-2010 shows
Eq Show
\ /
Num
|
Real
|
Integral
On Thu, Dec 22, 2011 at 09:48:06AM -0800, J. Garrett Morris wrote:
> On Thu, Dec 22, 2011 at 9:44 AM, Serge D. Mechveliani
> wrote:
> > And ghc-7.4.0.20111219 reports
> > DExport.hs:28:8:
> > Could not find module `Random'
> > It is a member of th
Dear GHC team,
ghc-7.4.0.20111219 puts the following problem of build-depends.
docon.cabal of the DoCon project has
build-depends: haskell2010, containers
And ghc-7.4.0.20111219 reports
DExport.hs:28:8:
Could not find module `Random'
It is a member of the hidden package `
Dear GHC developers,
This is on ghc-7.4.0.20111219.
Compiling
---
{-# OPTIONS -fno-warn-duplicate-exports #-}
module DExport
(module DPrelude,module Categs, module SetGroup,
module RingModule, module Z, module DPair,
mod
пDear GHC team,
ghc-7.0.1 assumes that Integral includes Show, and
ghc-7.4.0.20111219 does not assume this.
Which one agrees with Haskell-2010 ?
Regards,
--
Sergei
mech...@botik.ru
___
Glasgow-haskell-users mailing list
Glasgow-hask
People,
is it possible to arrange a connected output and input (with something
like a socket) "in a middle" of the Haskell function?
Consider the example of sorting an integer list:
sortInt :: [Int] -> [Int]
sortInt js =
let callString = "sortForeign( " ++ (show js) ++ ")"
The general idea of my recent instance union proposal is that
for a single polymorphic type T, sometimes it is natural to define
several instances by a single `instances' declaration.
--
Sergei
___
Glasgow-haskell-users mailing list
Glasgow-h
Dear Haskell implementors,
I suggest the following small extension to the instance declaration in
the language. So far -- for Haskell + glasgow-ext.
I think that they are easy to implement.
This is the "instance union" proposal.
It is needed to write shorter several `old' instance declarations
Dear GHC developers,
There is a computer algebra library called DoCon and written in
Haskell (+GHC).
And I am considering the possibility to extend it with many new methods
by joining some open libraries written in C, C++, and in
Gnu Common Lisp (GCL).
1. I have seen somewhere the announcement
Simon,
thank you.
Currently, DoCon works under ghc-7.0.1.
And as I understand, the next release which is going to support DoCon
(with its heavy use of overlapping instances) will be ghc-7.2.
Regards,
Serge Mechveliani, mech...@botik.ru
On Wed, Jun 22, 2011 at 11:01:53AM -, GHC
This is to add to my last letter.
It is curious that this 7.02 candidate stucks at оverlapping instances
only when compiling the test:
T_cubeext.hs:143:9:
Overlapping instances for LinSolvRing (UPol k)
arising from a use of `ct'
...
In earlier versions, if any of them stuck at оver
Dear GHC team,
I am testing the 7.02 candidate of ghc-7.0.1.20110217
-- compiled from source, compiled by itself, on Debian Linux,
i386-family.
On my DoCon program, it reports the following.
1. It requires `-fcontext-stack=_' to increase a certain stack:
...
[67 of 83] Compiling Pfact__
People,
I define, for example,
tuple42(_, y, _, _) = y,
setTuple42 (x, _, z, u) y = (x, y, z, u),
mapTuple42 f (x, y, z, u) = (x, f y, z, u).
But it looks natural to have such functions for tuples in the library.
As Haskell-2010 has zip3, zip4 ..., where are the library functions
tu
In ghc-7.0.1, to import `partition', it is sufficient the line
import List (partition),
but to import `intercalate', it is needed
import Data.List (intercalate).
Does Haskell-2010 differ between List and Data.List imp
Christian H?ner zu Siederdissen wrote:
> The change should not affect working programs, as it just allows you to
> define further places where you say that you want an overlapping
> instance.
>
> Gruss,
> Christian
>
> * Serge D. Mechveliani [16.11.2010 16:47]:
> >
On Tue, Oct 26, 2010 at 09:41:58PM +0200, John Smith wrote:
> In the case of overlapping instance declarations, GHC currently requires
> the less specific instance to be compiled with OverlappingInstances for the
> more specific instance to be usable. This means that, for example, if you
> write
Dear GHC developers,
I am testing this fresh ghc-7.0.0.20101028
on Debian Linux, i386-family.
Making it from source by ghc-6.12.3 is all right.
Then, making it from source by itself reports
(here I abbreviate the messages by inserting `...')
--
People,
what is, in short, the relation between www.haskell.org and
new-www.haskell.org ?
Which one do I need to use for looking for the Haskell materials,
for GHC materials?
Regards,
-
Serge Mechveliani
mech...@botik.ru
___
Gla
Simon P. Jones wrote recently about that ghc-6.12 takes in
account the elliplis in MkT {t1 = x, ..} when reporting about
unused bindings.
Now, here is the example:
module TT where
data T = T {t1, t2 :: Int}
f d = x where
T {t1 = x, ..} = d
ghc-6.12.2 warns about unuse
-users-boun...@haskell.org
> [mailto:glasgow-haskell-users-
> | boun...@haskell.org] On Behalf Of Serge D. Mechveliani
> | Sent: 14 October 2010 11:01
> | To: Antoine Latter
> | Cc: glasgow-haskell-users@haskell.org
> | Subject: Re: un-used record wildcards
> |
> | On Wed,
On Thu, Oct 14, 2010 at 05:27:52PM +0200, Christian Maeder wrote:
> Am 14.10.2010 15:44, schrieb Serge D. Mechveliani:
> > I have the two notes on the GHC library.
> > The docs show that
> > 1. Map has the function for the Map inclusion relation,
> >and Set
I have the two notes on the GHC library.
The docs show that
1. Map has the function for the Map inclusion relation,
and Set does not have such for sets.
2. notMember looks unnecessary, because one can write
not . Map.member k.
Regards,
-
Serge Mechveliani
mech...@botik.
On Wed, Oct 13, 2010 at 01:47:11PM -0500, Antoine Latter wrote:
> On Wed, Oct 13, 2010 at 1:02 PM, Serge D. Mechveliani
> wrote:
> > Dear GHC developers,
> >
> > I use the language extension of RecordWildcards, for example,
> >
Dear GHC developers,
I use the language extension of RecordWildcards, for example,
f (Foo {foo1 = n, foo2 = m, ..}) = ...
But the complier warns about un-used values of foo3, foo4,
probably, due to the extension of
Foo {foo1 = n, foo2 =
Dear GHC developers,
http://botik.ru/pub/local/Mechveliani/ghcBugs/ghc701preBug.zip
contains a bug report on ghc-7.0.0.20100924
tested on Debian Linux, i386-family.
Its essence is as follows. At the fragment of
-
On Thu, Sep 30, 2010 at 02:13:49AM +, Simon Peyton-Jones wrote:
> | (2) ghc-6.12.2 compiles docon-2.11
> | (download it via http://haskell.org/ghc/docon/
> | and follow install.txt
> | )
>
> I get "Not found" when following http://haskell.org/ghc/docon
>
> Simon
>
Sorry
Dear GHC developers,
I have tested ghc-7.0.0.20100924
on Debian Linux, i386-family
on making it by ghc-6.12.3, on the DoCon test,
-- with skipping profiling.
There are visible the following changes in GHC:
(1) Usage of ./Main +RTS .. -RTS needs linking with -rtsopts
Dear people and GHC team,
I have a naive question about the compiler and library of ghc-6.12.3.
Consider the program
import List (genericLength)
main = putStr $ shows (genericLength [1 .. n]) "\n"
where
n = -- 10^6, 10^7, 10^8 ...
(1) When it is compiled under -O,
Dear GHC developers,
I have tested ghc-6.12.3-candidate of 6.12.2.20100521 on
Debian Linux, i386-family
on making it by ghc-6.12.2, on making it by itself
on the DoCon test,on the Dumatel test
-- with skipping profiling.
It looks all right.
-
Serge Mechveli
I am sorry, please withdraw my last letter (about -M, -K):
> For the test compiled under -O, 2300k in "./Main +RTS -K2300k -RTS"
> is the minimal memory option of this kind for the test to finish without
> break.
> [..]
I have confused "-M...k" with "-K...k".
Regards,
-
Ser
Dear GHC developers,
I am trying ghc-6.12.2 on Debian Linux, i386-family,
on the DoCon test.
There is a difference in memory management, with respect to 6.12.1.
For the test compiled under -O, 2300k in "./Main +RTS -K2300k -RTS"
is the minimal memory option of this kind for the test to fini
Dear GHC developers,
I have tested ghc-6.12.1.20100330 on Debian Linux, i386-family,
on the DoCon test, without profilig.
It looks all right.
-
Serge Mechveliani
mech...@botik.ru
___
Glasgow-haskell-users mailing list
Glasgow-haskell-
In my last letter I wrote about the prossibility for the GHC
developers to require a keyword in any pragma, "for future".
I thought that pragma is a matter of the GHC language extension.
But if it is of the Haskell standard, then, again I am sorry!
Regards,
-
Serge Mechveliani
On Sun, Feb 07, 2010 at 02:16:11PM +0100, Daniel Fischer wrote:
> Am Sonntag 07 Februar 2010 14:05:48 schrieb Serge D. Mechveliani:
> > On Sun, Feb 07, 2010 at 01:22:07PM +0100, Daniel Fischer wrote:
> > > Am Sonntag 07 Februar 2010 13:06:14 schrieb Serge D. Mechveliani:
On Sun, Feb 07, 2010 at 01:22:07PM +0100, Daniel Fischer wrote:
> Am Sonntag 07 Februar 2010 13:06:14 schrieb Serge D. Mechveliani:
> > I am sorry,
> > indeed, ghc-6.12.1 warns of Unrecognised pragma on {-# "foo" #-}.
> > I have just missed this warning.
> &
Ian Lynagh wrote:
> On Sun, Feb 07, 2010 at 11:39:31AM +0300, Serge D. Mechveliani wrote:
> > On Sat, Feb 06, 2010 at 08:24:07PM +, Ian Lynagh wrote:
> > > On Sun, Jan 31, 2010 at 10:09:42PM +0300, Serge D. Mechveliani wrote:
> > > > I have a suggestion:
> > >
To my
> > Dear GHC team,
> >
> > It looks like ghc-6.12.1 reports erroneous time profiling --
> > when the Main module of the project is made under -O.
> > [..]
> > This is for ghc-6.12.1 made from source for Debian Linux and
> > i386-like.
> >
> > Main.main calls for Complete.complete, `
Dear GHC team,
It looks like ghc-6.12.1 reports erroneous time profiling --
when the Main module of the project is made under -O.
This is for ghc-6.12.1 made from source for Debian Linux and
i386-like.
Main.main calls for Complete.complete, `complete' calls for
eLoop inside its sourc
I have a suggestion:
is it better for GHC to report an error on the source of kind
{-# "foo" #-}
(entered by a typo instead of {-# SCC "foo" #-}) ?
Currently, GHC makes the program under (-prof) in which, the "foo" center
occurs skipped.
On Thu, Jan 28, 2010 at 02:39:56PM +, Simon Marlow wrote:
> On 28/01/2010 14:27, Serge D. Mechveliani wrote:
> >Dear GHC team,
> >
> >this is on tracing in ghc-6.12.1
> >(made from source on Debian Linux i-386-like machine).
> >
> >I wonder what
Dear GHC team,
this is on tracing in ghc-6.12.1
(made from source on Debian Linux i-386-like machine).
I wonder what is the reason for this tracing message
(starting with `Step1 ...' ):
...
equations calc =
[j < i -> true,
m <= p -> true,
p <= q -> true,
q <= n ->
Dear GHC team,
I have tested ghc-6.12.0.20091121
by
1) installing its binary and making and running the DoCon and Dumatel
programs,
2) making it from source by its binary,
making and running on it the DoCon and Dumatel programs.
It looks all right.
I skipped profiling.
Regards,
--
Dear GHC team,
I tried ghc-6.12.0.20091010-src.tar.bz2
on Linux, Debian, i386-*
And it cannot compile my Dumatel project. It fails at the segment:
module Bug where compose :: [a -> a] -> a -> a
compose = foldr (.) id
class Compose a where compose1
I have downloaded ghc-6.12.0.20091010-src.tar.bz2.
But where to read the release notes?
ANNOUNCE shows ``version 6.10.1'', and lists the old features.
What is the difference of 6.12.1 w.r.to 6.10.4 ?
Regards,
-
Serge Mechveliani
mech...@botik.ru
On Sun, Oct 11, 2009 at 09:41:
People,
I have data DBit = Bit0 | Bit1 deriving (Eq, Ord, Enum)
data BNatural = BNat [DBit] deriving (Eq)
and want to apply things like fmap reverse (bn :: BNatural).
GHC reports an error on this usage of fmap.
It also does not allow
instance Functor BNatural whe
People,
I need to convert Char <-> Int in a possibly _standard_ way for
Haskell -- and also in an efficient way. In particular, it must not
spend 100 comparisons in a look through the listing of Char.
I use ord :: Char -> Int and chr :: Int -> Char.
Is this all right?
Thank you
On Tue, Aug 04, 2009 at 09:12:37AM +0100, Simon Marlow wrote:
> I suggest not using Haskell for your list. Put the data in a file and
> read it at runtime, or put it in a static C array and link it in.
>
> On 03/08/2009 22:09, G?nther Schmidt wrote:
> >Hi Thomas,
> >yes, a source file with a sin
Joshua Haberman writes on 2 Aug 2009
> Hello, I'm quite new to Haskell, but experienced in other languages (C,
> Python, Ruby, SQL, etc). I am interested in Haskell because I've heard
> that the language is capable of lots of optimizations based on laziness,
> and I want to learn more about t
Dear GHC developers,
I have tested ghc-6.10.3.20090628
on Debian Linux, i-386-kind machine.
There were only two tests:
1) making from source by itself
2) making DoCon and running its test (without profiling).
It looks all right.
With kind regards,
-
Serge Mechveliani
mech...
Dear GHC team,
I would like to write
[rl {ruleMode = AlwaysApply} | rl <- rules calc](I)
instead of map (\ rl -> rl {ruleMode = AlwaysApply}) $ rules calc (II)
and instead of
let rs = rules calc in [rl {ruleMode = AlwaysApply} | rl <- rs] (III).
But is this reliable
Dear GHC team,
I have tested ghc-6.10.2.20090430
under Debian Linux,
processor = (GenuineIntel cpu family 6,
Intel(R) Core(TM)2 CPU 6400).
It looks all right.
The test was:
1) making ghc-6.10.2.20090430 from source by ghc-6.10.2,
2) making DoCon and running its tes
Dear GHC team,
I withdraw my last bug report.
It was about processing a long list on a 64 bit machine оn GHC-6.10.2.
First, I cannot reproduce (?) this bug report invitation from GHC on
using +RTS -M4000m
Second, I have found that the process interruption only occurs when
this test program r
I have tested ghc-6.10.1.20090314 on Debian Linux, i386-unknown,
on
making from source by ghc-6.10.1, making itself from source, DoCon.
It looks all right.
-
Serge Mechveliani
mech...@botik.ru
___
Glasgow-haskell-users mailing li
People,
I observe the output difference in running ./Bug
and ./Bug >& log
(under Linux) for the program
import Dumatel
main = do calcInput <- readFile "List0.inp"
(putStr $ parseComputeShow calcInput)
where
parseComputeShow calcInpu
Yesterday, I promised to provide a bug report with
Segmentation fault
on missing some method implementation.
I saved this source copy. Hm ... today I still failed to reproduce
this seg-fault situation!
I am sorry.
Regards,
-
Serge Mechveliani
mech...@botik.ru
___
Dear GHC team,
I `make' my (large) project in ghc-6.10.1, Linux Debian, i386-unknown,
run the executable, and obtain
Segmentation fault.
Then, I noted that in a few places the compiler warned about skipping
some class member implementations in some instances.
I added these implementations,
The GHC team writes
> The (Interactive) Glasgow Haskell Compiler -- version 6.10.1
> [..]
> There have been a number of significant changes since the last
> major release, including:
>
> * Some new language features have been implemented:
> * Record syntax: wild-card patterns, punning, and fiel
Another point in testing ghc-6.10.0.20081007:
I make it from source on Debian Linux.
On 1 Gb - 2 GHz machine, it builds in 1400 sec.
On 512 Mb machine, it seems to overfill RAM, it becomes slow, and
this `make' creates difficulties for other processes (like emacs editor):
they start to hang
This is about testing 6.10.0.20081007.
1. DoCon works with it.
2. The question is how to `install' Backspace and UpArrow in ghci.
I make it from source by 6.10-candidate and also by itself
-- on Debian Linux.
And ghci does not process Backspace and UpArrow.
./configure reported
configure
People,
I need to implement the functions
isTypeId, isValueId :: String -> Bool
which check whether the argument fits respectively the syntax of a
type identifier and of a value identifier -- in the Haskell-98 syntax
for a program.
The argument is produced by lex
On Wed, Sep 24, 2008 at 07:18:28PM +0200, Christian Maeder wrote:
> Serge D. Mechveliani wrote:
> > On Wed, Sep 24, 2008 at 05:32:51PM +0200, Christian Maeder wrote:
> >> Do you have libedit on your linux machine (because I haven't)?
> >>
> >
> > I do
On Wed, Sep 24, 2008 at 05:32:51PM +0200, Christian Maeder wrote:
> Do you have libedit on your linux machine (because I haven't)?
>
I do not know what is libedit and where to find it.
> In order to check this:
> Does "ghc-pkg list" the editline package? (And do your arrow keys and
> backspace
This was on Linux, Debian.
> I have tested ghc-6.10.0.20080921
> on
> * making it by ghc-6.8.2,
> * making it by itself,
> * the DoCon and Dumatel applications.
___
Glasgow-haskell-users mailing list
Glasgow-haskell-users@haskell.org
http://www.haskell.
Dear GHC developers,
I have tested ghc-6.10.0.20080921
on
* making it by ghc-6.8.2,
* making it by itself,
* the DoCon and Dumatel applications.
It looks all right.
Regards,
-
Serge Mechveliani
[EMAIL PROTECTED]
___
Glasgow-haskell-us
I take back my two recent reports about the effect of -O2, -fvia-C.
Because
1) -O is sufficient,
2) there are too many issues that are more important than the behavior
under -O2 and via-C. So, it is a good idea to save effort.
Regards,
-
Serge Mechveliani
[EMAIL PROTECTED]
On Sat, Sep 20, 2008 at 11:25:57AM +0100, Simon Marlow wrote:
> Serge D. Mechveliani wrote:
>
> >5. The same is for -O2. But this does not gain more performance.
> > -O2 -fvia-C also does not gain more performance, but leads to 7 times
> > longer compilation.
>
On Fri, Sep 19, 2008 at 08:17:12PM +0100, Ian Lynagh wrote:
> On Tue, Sep 16, 2008 at 10:44:53AM +0100, Simon Peyton-Jones wrote:
> > |
> > | And still ghc-6.8.3 builds itself from source.
> >
> > I have no idea how -- Happy has been needed for some time. Maybe someone
> > else does.
>
> It's n
Thank you for the explanation.
--
Sergey
On Fri, Sep 19, 2008 at 10:26:01AM +0100, Simon Peyton-Jones wrote:
> | 2. But in several places DoCon has parasitic additions
> |(similar to the below MulSemigroup (Fraction a))
> |to the context for overlapping instances.
> |These place
Simon Peyton-Jones <[EMAIL PROTECTED]> wrote on 15 Sep 2008
about Instances and DoCon
To: "Serge D. Mechveliani" <[EMAIL PROTECTED]>
CC: "[EMAIL PROTECTED]" <[EMAIL PROTECTED]>
> Serge
>
> I take it all back. I've been persuaded that i
On Wed, Sep 17, 2008 at 11:10:17AM +0100, Simon Peyton-Jones wrote:
> Why not grab a binary distribution?
>
> [..]
> | cd ~/happy/happy-1.17/
> | runhaskell Setup.lhs configure -v --ghc
> | --prefix=/home/mechvel/happy/happy-1.17/inst
I thank people who advised me o
Dear team of Happy,
Please, where to find the `make' instruction for Happy-1.17 ?
How to `make' it from source on Linux, i386 ?
I have ghc-6.8.3 installed, and Cabal.
As I see happy.cabal, maybe, Happy can be `made' similarly as I
make (with Cabal and GHC) my programs under GHC (?).
So, I comm
Dear GHC team,
I again have problems with making GHC from source.
Now, this is for making ghc-6.9.20080910-src.tar.bz with ghc-6.8.3.
./configure --prefix=...
reports that Happy is needed.
But earlier, I compiled ghc-6.8.3 with itself,
and it did not required Happy.
Generally, as I rec
1 - 100 of 299 matches
Mail list logo