parsing strings

2003-07-30 Thread Iavor Diatchki
hello, there seems to be a problem when parsing multi-line strings: in the first string there is no space after the \, while in the second there is. i tried this on linux, with the july version of hugs. > probelm = "hello \ > \world" > noproblem = "hello \ > \world" the erro

type synonym or fun dep problem

2003-09-16 Thread Iavor Diatchki
apologies if this gets to the list twice. --- hello, there seems to be something wrong with the implementation of functional dependencies, or perhaps the expansion of type synonyms. i am using hugs (september 2003). the program: > module Test where > > class C a b | a -> b where > mk :: IO a >

type synonyms/fun deps

2003-09-17 Thread Iavor Diatchki
hello, there seems to be something wrong with the implementation of functional dependencies, or perhaps the expansion of type synonyms. i am using hugs from july 2003. the program: > module Test where > > class C a b | a -> b where > mk :: IO a > eq :: a -> a -> IO Bool > > type F = IO > > inst

Re: illegal export of lone data constructor

2003-09-17 Thread Iavor Diatchki
hello, Andrew Frank wrote: (minor point: my report says that the prelude module is always available as qualified import (p. 71) the hugs now (2002) seem to require an explicite import qualified (after a import Prelude hiding (stuff)) the latest report is availabel online at haskell.org, and also a

defining unix

2003-10-02 Thread Iavor Diatchki
hello, hugs crashes if one tries to define unix: > unix = undefined INTERNAL ERROR: compileGlobalFunction another interesting thing occurs if the following is added: > f = test' unix > test' = undefined then one gets an undefined variable: ERROR "test.lhs":11 - Undefined variable "unix" how

Re: defining unix

2003-10-03 Thread Iavor Diatchki
hello, Ross Paterson wrote: On Thu, Oct 02, 2003 at 06:35:10PM -0700, Iavor Diatchki wrote: hugs crashes if one tries to define unix: unix = undefined INTERNAL ERROR: compileGlobalFunction I presume you have -F set to run the C preprocessor on source files aha, this is true indeed (i&#

module system problem

2003-10-06 Thread Iavor Diatchki
hello, there seems to be a bug in the module system implementation: > module Test where > import Prelude hiding (negate) > negate = not > test= negate ERROR "Test.lhs":7 - Ambiguous variable occurrence "negate" *** Could refer to: Test.negate Hugs.Prelude.negate bye iavor -- ==

INTERNAL ERROR: parseInput

2003-10-07 Thread Iavor Diatchki
hello, appologies for the many bug-posts. hugs crahes with an internal error when it encounters an unfinished pattern like this: > test ( INTERNAL ERROR: parseInput bye iavor -- == | Iavor S. Diatchki, Ph.D. student | | Department of Co

IO problems

2003-10-10 Thread Iavor Diatchki
hello, while looking at the program henk posted a few days ago, i run into a rather weird bug in hugs, where it seems to be mixing IO handles. the problem seems to happen with versions of hugs as early as Nov 2002. it occurs on linux (Mandrake 9.1 and Redhat 9.0). this is how one can reproduce the

Re: None

2003-10-16 Thread Iavor Diatchki
hello, Ross Paterson wrote: On Thu, Oct 16, 2003 at 03:54:51PM -0400, Doug McIlroy wrote: In Hugs 1.4, ++ was an operator of class Monad; in Hugs 98 it is an operator on lists. I've looked in the Hugs documentation and haven't found anything about the change (probably a failing of mine, not the

[Hugs-bugs] Installing Hugs

2005-02-16 Thread Iavor Diatchki
Hello, I seem to be having trouble installing Hugs from CVS. I checked out a fresh copy from CVS, and typed 'make' as the instructions on the web-page suggest. The actual Hugs builds fine, but something goes wrong with the libraries. I am using a Mandrake 10.1 distribuition of linux, and I suspect

[Hugs-bugs] Bug with fun-deps

2005-02-18 Thread Iavor Diatchki
Hello, I seem to have run into a problem involving functional dependencies. Below is an excerpt of a program I was writing that illustrates the bug. > data N0 > newtype Succ n= Succ n > class Plus a b c | a b -> c > instance Plus N0 n n > instance Plus a b c => Plus (Succ a) b (Succ c) > (

[Hugs-bugs] Internal error

2006-03-07 Thread Iavor Diatchki
Hello, the following (erroneous) program generates an internal error, in hugs (20060307), when started with flag -98. > f m :: IO a -> IO a > = m Output: INTERNAL ERROR: findBtyvsInt Please report this Hugs bug to hugs-bugs@haskell.org -Iavor ___ Hugs

[Hugs-bugs] Module system bug

2006-03-07 Thread Iavor Diatchki
Hello, the two modules bellow illustrate a bug in the implementation of the module system (20060307). The problem appears to be that record labels are not treated as "belonging" to a type. > module A(get) where > import B hiding (T(..)) > data T = C { get :: Char } > module B where > data T = C

[Hugs-bugs] parser internal error

2006-03-28 Thread Iavor Diatchki
Hello, The following program fragment causes INTERNAL ERROR: parseInput > import Prelude > f ( Hugs Version: 20060328 -Iavor ___ Hugs-Bugs mailing list Hugs-Bugs@haskell.org http://www.haskell.org/mailman/listinfo/hugs-bugs

[Hugs-bugs] unsafeSTToIO

2006-03-28 Thread Iavor Diatchki
Hello, loading "Control.Monad.ST" causes an error, because it exports an undefined name: unsafeSTToIO -- :: ST s a -> IO a If I comment out the export, things appear to work. -Iavor ___ Hugs-Bugs mailing list Hugs-Bugs@haskell.org http://www.haske

module system bug

2007-01-21 Thread Iavor Diatchki
Hello, There appears to be a problem when combinig "hiding" and "qualified" imports. Here is an example: module A where x = True module Main(main) where import qualified A hiding () main = print A.x When loading the second module (Main) Hugs (September 2006) complains that A.x is not in scope

Scoping bug in module system implementation

2007-02-11 Thread Iavor Diatchki
Hello, Consider the following two modules: module A where x = True module B where import A x = 'a' test = let x = "" in x Upon loading "B", Hugs (Sept 2006) erroneously reports: Ambiguous variable occurrence "x" *** Could refer to: B.x A.x The variable "x" in the definition of "test" refer

Re: smelly code in input.c

2021-06-14 Thread Iavor Diatchki
Hi, I don't not know that code either, but looking at the comments and the surrounding code, my guess is that the 2nd `c0` should be `c1`, and it is checking for something like `.` followed by either a lower case or upper case or symbol operator. -Iavor On Mon, Jun 14, 2021 at 3:48 AM Anthony