Haskell.org
Sign In Sign Up
Manage this list Sign In Sign Up

Keyboard Shortcuts

Thread View

  • j: Next unread message
  • k: Previous unread message
  • j a: Jump to all threads
  • j l: Jump to MailingList overview
thread

Bug?

Jorge Adriano

16 Apr 2002 16 Apr '02
10:15 p.m.
[1] Bug1?
This declaration:
> A = (,) Int Int
is accepted by ghci. Is this behaveour correct,
1. It kind of shadows (,) is defined in PrelTup meaning that you can no longer 
use (,) prefix to refer to tuples - like (,) 1 2.
2. Seems to me like (,) is not correct syntax for a consym as defined in the 
H98 Report so we shouldn't be able to redefine it.

Note: didn't check any other interpreter/compiler.


[2] Bug2?
- Step 1
Load this in ghci,
-----------------------
module Test where
data C = C ((,) Int Int)

data A = (,) !Int !Int 
h :: A
h =  (,) 1 2

{-
f :: C
f = C ((,) 3 4)
-}
------------------------
- Step 2
Uncomment the f function. (you'll get an error function)

- Step 3
To get rid of the error comment out the 'data A' declaration and function 'h'.

Now you should get this error message:
-------------------------------------------------
    Failed to find interface decl for `Teste.A'
    from module `Teste'
-------------------------------------------------


[3] Strict Pairs question
I really miss them :-)
I know I can do something like

data A a b= A !a !b
But then you can't use zips fst etc etc...
One possible solution would be to add some Class Pair, with default instances 
for these functions. Is this a bad idea for any particular reason?

It would also be nice to be able to generalize the idea syntatic sugar for 
standar tuples and be able to define constructors like, say
(:,:) and (#:, , :#) etc. Is this feasable?


J.A.







0 0
Reply
Sign in to reply online Use email software

Back to the thread

Back to the list

HyperKitty Powered by HyperKitty version 1.3.9.