eval_thunk_selector: strange selectee 29

2004-03-08 Thread Greg Baker
For the Haskell program from hell (it kills ghc-6.01 on OpenBSD 3.4,
hugs on MacOS X and hugs on EPOC)
It's a translation of the (in)famous jpeg.gs script - but I'm yet to
see whether it works or not, and how fast. But it does compile cleanly.
I can send you a sample JPEG that causes the crash, but I think any
image will do.
Good luck, and thanks for making Haskell happen in the real world.
 module Jpeg where
 import Char
 type Table a  =  Int - a

Auxiliary functions:

 infixr 9 `o`
 o :: (c-d) - (a-b-c) - (a-b-d)
 (g `o` f) x y = g (f x y)

 ap :: (a-b) - a - b
 ap f x  = f x
 
 ap':: a - (a-b) - b
 ap' x f = f x


 subst :: Eq a = a - b - (a-b) - (a-b)
 subst i e t j  | i==j  =  e
| otherwise =  t j

 multi  :: Int - [a] - [a]
 multi n = concat . map (replicate n)

 ceilDiv:: Int - Int - Int
 --ceilDiv n d = (n+d-1)/d
 ceilDiv n d = (n+d-1) `div` d-- I think

Matrix manipulation

 type Dim   = (Int,Int)
 type Mat a = [[a]]

 matapply:: Num a  =  Mat a - [a] - [a]
 matapply m v = map (inprod v) m

 inprod :: Num a  =  [a] - [a] - a
 inprod  = sum `o` zipWith (*)

 matmap :: (a-b) - Mat a - Mat b
 matmap  = map . map

 matconcat :: Mat (Mat a) - Mat a
 matconcat  = concat . map (map concat . transpose)

 matzip :: [Mat a] - Mat [a]
 matzip  = map transpose . transpose

 transpose:: [[a]] - [[a]]  -- transpose list of lists
 transpose = foldr
   (\xs xss - zipWith (:) xs (xss ++ repeat []))
   []

 Bit Streams

 type Bits = [Bool]

 byte2bits  :: Int - Bits
 byte2bits x = zipWith (=) (map (rem x) powers) (tail powers)
  where powers = [256,128,64,32,16,8,4,2,1]

 string2bits :: String - Bits
 string2bits  = concat . map (byte2bits.ord)

 byte2nibs  :: Int - (Int,Int)
 --byte2nibs x = (x/16, x`rem`16)
 byte2nibs x = (x `div` 16, x `rem` 16) -- I think; maybe should be divMod?

Binary Trees

 data Tree a  =  Nil
  |  Tip a
  |  Bin (Tree a) (Tree a)


 instance Functor Tree where
 fmap f Nil   =  Nil
 fmap f (Tip a)   =  Tip (f a)
 fmap f (Bin x y) =  Bin (fmap f x) (fmap f y)

State Function (StFun) Monad

 data StFun s r = SF (s - (r,s))
 
 instance Functor (StFun s) where
fmap h (SF f)= SF g 
where g s = (h x,s')
where (x,s') = f s 

 instance Monad (StFun s) where
return x= SF g  
where g s = (x,s)
SF f = sfh = SF g 
where g s = h s'
where (x,s') = f s
  SF h   = sfh x

 st'apply :: StFun a b - a - b
 st'apply (SF f) s   = x 
where (x,_) = f s


--
-- Primitive State Functions
--

 empty  ::  StFun [a] Bool
 empty   =  SF f
 where  f [] = (True,  [])
f xs = (False, xs)

 item   ::  StFun [a] a
 item=  SF f
 where  f (x:xs) = (x,xs)

 peekitem   ::  StFun [a] a
 peekitem=  SF f
 where  f ys@(x:xs) = (x, ys)

 entropy :: StFun String String
 entropy =  SF f
 where  f ys@('\xFF':'\x00':xs)  = let (as,bs) = f xs in ('\xFF':as,bs) 
f ys@('\xFF': _   )  = ([],ys)
f( x   :xs)  = let (as,bs) = f xs in (x:as,bs) 


--
-- Auxiliary State Functions
--


The Gofer version here used monad comprehensions, which I think
aren't legitimate Haskell. I think the result still looks OK.

 byte :: StFun String Int
 byte = do
 c - item
 return (ord c)  

 word :: StFun String Int
 word = do
   a - byte
   b - byte 
   return (a*256+b)

 nibbles :: StFun String (Int,Int)
 nibbles  = do
  a - byte
  return (byte2nibs a)


--
-- State Function Combinators
--

 -- list::[StFun s r] - StFun s [r]
 list   :: Monad m = [m   a] - m   [a]
 list [] = return []
 list (f:fs) = do
 x-f
 xs-list fs
 return (x:xs)

 exactly :: Monad m = Int - m a - m [a]
 exactly 0 f  = return []
 exactly (n+1) f  = do
  x-f
  xs-exactly n f 
  return (x:xs)

 matrix  :: Monad m = Dim - m a - m (Mat a)
 matrix (y,x) = exactly y . exactly x

 -- many   :: Monad (StFun [a]) = StFun [a] b - StFun [a] [b]
 many f  = do  b  - empty
   y  - f
   ys - many f
   return (if b then [] else y:ys)
 
 sf'uncur  :: (b - StFun a (b,c)) - StFun (a,b) c
 sf'uncur f = SF h
   where h (a,b) = (c, (a',b'))
 where SF g = f b
   ((b',c),a')  = g a

 sf'curry   :: StFun (a,b) c - b - StFun a (b,c)
 sf'curry (SF h) = f
   where f b = SF g
 

RE: eval_thunk_selector: strange selectee 29

2004-03-08 Thread Simon Marlow
 
 For the Haskell program from hell (it kills ghc-6.01 on OpenBSD 3.4,
 hugs on MacOS X and hugs on EPOC)
 
 It's a translation of the (in)famous jpeg.gs script - but I'm yet to
 see whether it works or not, and how fast. But it does 
 compile cleanly.
 
 I can send you a sample JPEG that causes the crash, but I think any
 image will do.

I believe this bug was fixed in GHC 6.2.  Could you try that version and
let us know if it helps?

Cheers,
Simon
___
Glasgow-haskell-bugs mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/glasgow-haskell-bugs


RE: ghc 6.2 gets confused about Main.hi reuse

2004-03-08 Thread Simon Marlow
Reviving an old thread:

 When trying to build HaRe with ghc 6.2 (builds fine with ghc 6.0.1),
 we encountered a long list of strange error messages of the kind:
 
 ...
 
 *** Compiling Main:
 compile: input file pfe_client.hs
 *** Checking old interface for Main:
 
 Failed to load interface for `MapDeclMBase':
 Could not find interface file for `MapDeclMBase'
 locations searched:
   /proj/haskell/lib/ghc-6.2/imports/MapDeclMBase.hi
   /proj/haskell/lib/ghc-6.2/hslibs-imports/text/MapDeclMBase.hi
   /proj/haskell/lib/ghc-6.2/hslibs-imports/data/MapDeclMBase.hi
   /proj/haskell/lib/ghc-6.2/hslibs-imports/util/MapDeclMBase.hi
   /proj/haskell/lib/ghc-6.2/hslibs-imports/posix/MapDeclMBase.hi
   
 /proj/haskell/lib/ghc-6.2/hslibs-imports/concurrent/MapDeclMBase.hi
   /proj/haskell/lib/ghc-6.2/hslibs-imports/lang/MapDeclMBase.hi
 
 ...

We've found the reason that 6.2 was failing in this way and fixed it in
6.2.1.  It was indeed a bug.

*However*, this doesn't change the fact that swapping in a new Main
module is a dangerous thing to do: the recompilation system relies on
the date of the source file to determine whether compilation is
required, so if you use a new Main module without touching it first, the
compiler might not recompile as it should.  

There are ways we might try to get around this problem.  Putting an md5
signature of the source file in the .hi file is one way.  Using
different .hi files for different source files is another, but we
couldn't see a good way to do this when using the -hidir flag as in your
example.

Cheers,
Simon
___
Glasgow-haskell-bugs mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/glasgow-haskell-bugs


TH naming problem, different 'newName's clash

2004-03-08 Thread Duncan Coutts

I'm using the new abstract names of TH2 in ghc 6.3 (CVS early March)

I'm generating code that looks like this:

let foo_1 = e1
foo_2 = e2
 in e3

I'm using 
name - newName foo
to generate these names (foo_1, foo_2 etc) however when I splice this
code in ghc complains as if I'd written

let foo = e1
foo = e2
 in e3

ie that I have multiple definitions of the same variable in the same let
block.

So, to be precise:

foo :: ExpQ
foo = do
  foo1 - newName foo
  foo2 - newName foo
  letE [valD (varP foo1) (normalB [| 3 |]) []
   ,valD (varP foo2) (normalB [| 4 |]) []]
   [| 5 |]

If we print this, it looks like what we want:
 do {e - runQ foo; print (pprExp 0 e)}
let foo_0 = 3
foo_1 = 4
 in 5

but if we ask about $(foo), ghc tells us:

Conflicting definitions for `foo'
In the binding group for: foo, foo

It looks like the unique identifiers on the local names are being
forgotten when we splice in.

I can work around this for the moment using something like
mkName (foo_ ++ show somethingUnique)
but it's not nice.

Duncan

___
Glasgow-haskell-bugs mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/glasgow-haskell-bugs


#! for GHC?

2004-03-08 Thread Dean Herington
Can GHC be invoked somehow via the #! mechanism?  Put another way, is 
there a GHC analogue to runhugs?
___
Glasgow-haskell-users mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users


RE: -static

2004-03-08 Thread Simon Marlow
 
 In ghc/compiler/main/DriverFlags.hs machdepCCOpts includes a -static
 flag for some arches. Is this really necessary? I can't see 
 any comments
 as to why, nor any real answers from a quick google.

I can't remember why either.

 It causes this when compiling darcs on these arches:
 
 /usr/lib/ghc-6.2/libHSunix.a(User.o)(.text+0x2a2c): In 
 function `s6T9_ret':
 : warning: Using 'getgrgid_r' in statically linked 
 applications requires at runtime the shared libraries from 
 the glibc version used for linking
 
 which I assume would lead to too strict dependencies on glibc being
 necessary.

What platform?  Does everything work if you remove the -static?

Cheers,
Simon
___
Glasgow-haskell-users mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users


Re: #! for GHC?

2004-03-08 Thread Hampus Ram
On Sat, Mar 06 2004, Dean Herington wrote:
 Can GHC be invoked somehow via the #! mechanism?  Put another way, is 
 there a GHC analogue to runhugs?

Well, ghc now has an -e flag to evaluate stuff directly from the prompt 
(e.g. ghc -e Main.main Main.hs). But you can't execute shell-scripts
from a shell-script with #! so you can't just put it in your Haskell
module. Neither can you use the binary directly since you can only give
one argument to programs executed with #! and you need both -e and -B.

/Hampus

-- 
Homepage: http://www.dtek.chalmers.se/~d00ram
E-mail: [EMAIL PROTECTED]

Det är aldrig försent att ge upp
___
Glasgow-haskell-users mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users


RE: #! for GHC?

2004-03-08 Thread Simon Marlow
 
 Can GHC be invoked somehow via the #! mechanism?  Put another way, is 
 there a GHC analogue to runhugs?

Almost, but not quite.  Since 6.2, GHC has the -e switch for invoking
expressions from the command line, which gets a step closer.  GHC
doesn't ignore the '#!' line yet, but I can add that.  Then, as far as
I'm aware, it should work, albeit a little slowly because it goes
through the ordinary GHCi startup which loads some packages etc.

Cheers,
Simon
___
Glasgow-haskell-users mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users


RE: #! for GHC?

2004-03-08 Thread Simon Marlow
 
 On Sat, Mar 06 2004, Dean Herington wrote:
  Can GHC be invoked somehow via the #! mechanism?  Put 
 another way, is 
  there a GHC analogue to runhugs?
 
 Well, ghc now has an -e flag to evaluate stuff directly from 
 the prompt 
 (e.g. ghc -e Main.main Main.hs). But you can't execute shell-scripts
 from a shell-script with #! so you can't just put it in your Haskell
 module. Neither can you use the binary directly since you can 
 only give
 one argument to programs executed with #! and you need both -e and -B.

Aha!  I knew there was something else.

However, I just tried it on a recent Linux (RedHat 9) and it seems to
accept nested #! scripts.  There's a rather annoying limit on the length
of the #! line, too.

Cheers,
Simon
___
Glasgow-haskell-users mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users


Re: #! for GHC?

2004-03-08 Thread Hampus Ram
On Mon, Mar 08 2004, Simon Marlow wrote:
 However, I just tried it on a recent Linux (RedHat 9) and it seems to
 accept nested #! scripts.

It doesn't work for me though (it tries to run the first script (the
Haskell module) with the interpreter for the second script (bash).
Anyway, one cannot expect it to work for everyone (esp. since shells
differ and OS:es too).

However it should be quite simple to include a program similar to the
attached one to provide runhugs capability.

/Hampus

-- 
Homepage: http://www.dtek.chalmers.se/~d00ram
E-mail: [EMAIL PROTECTED]

Det är aldrig försent att ge upp
#include cstdlib
#include string

int main(int argc, char **argv)
{
if (argc != 3)
std::exit(EXIT_FAILURE);

std::string cmd(argv[1]);

cmd +=  -e Main.main ;
cmd += argv[2];

std::system(cmd.c_str());

return 0;
}
___
Glasgow-haskell-users mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users


RE: -static

2004-03-08 Thread Simon Marlow
 
 On Mon, Mar 08, 2004 at 11:07:07AM -, Simon Marlow wrote:
   
   It causes this when compiling darcs on these arches:
   
   /usr/lib/ghc-6.2/libHSunix.a(User.o)(.text+0x2a2c): In 
   function `s6T9_ret':
   : warning: Using 'getgrgid_r' in statically linked 
   applications requires at runtime the shared libraries from 
   the glibc version used for linking
   
   which I assume would lead to too strict dependencies on 
 glibc being
   necessary.
  
  What platform?  Does everything work if you remove the -static?
 
 alpha, powerpc and hppa so far. I expect the same will happen for mips
 and mipsel.
 
 If, on powerpc, I run the final link command without -static 
 (that's the
 only place it should make a difference, right?) then it links without
 warnings and looks to be working fine. I haven't looked at the others
 yet.

Wolfgang: can -static be removed on powerpc as far as you know?

Cheers,
Simon
___
Glasgow-haskell-users mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users


Polymorphic lists...

2004-03-08 Thread MR K P SCHUPKE
I needed a list which could handle items of different types for the 
database code I am writing. I have written a module implementing such a 
list based on dependant types (from Conor McBride: Faking It; Simulating 
Depandant Types in Haskell). Although McBride does not mention 
lists/vectors with items of differing types, the solution to 
implementing them came from his 'nthFront' function for re-arranging the 
order of arguments to a function.

Any type can be inserted into the list, which supports 
head/tail/init/last, as well as indexed lookup, and a cartesian-product 
(concatenating two lists together). I have included fromTuple/toTuple as 
well.

This seems quite a useful construct, and if there is nothing similar in 
the standard libraries at the moment, do you think this is worth including?

   Regards,
   Keean Schupke.
___
Glasgow-haskell-users mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users


Re: -static

2004-03-08 Thread Ian Lynagh
On Mon, Mar 08, 2004 at 03:25:06PM +, Ian Lynagh wrote:
 On Mon, Mar 08, 2004 at 11:07:07AM -, Simon Marlow wrote:
   
  What platform?  Does everything work if you remove the -static?
 
 alpha, powerpc and hppa so far. I expect the same will happen for mips
 and mipsel.
 
 If, on powerpc, I run the final link command without -static (that's the
 only place it should make a difference, right?) then it links without
 warnings and looks to be working fine. I haven't looked at the others
 yet.

Same on alpha and hppa. I unfortunately don't have access to
mips/mipsel at the moment.


Thanks
Ian

___
Glasgow-haskell-users mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users


Re: Polymorphic lists...

2004-03-08 Thread Ralf Laemmel
I would like to see your code indeed ...
it seems the attachment was missing.
Anyway, I am not sure if it obvious or not,
but heterogenously typed lists can be nicely
modelled with Data.Typeable (!!!) I guess we
should add something like this to the module?
See http://www.cs.vu.nl/boilerplate/testsuite/hlist.hs
or the inlined code below
Regards,
Ralf
-- Heterogeneously typed lists
data HList = HNil
   | forall a. Typeable a = HCons a HList
-- The empty list
initHList :: HList
initHList = HNil
-- Add an entry
addHList :: Typeable a = a - HList - HList
addHList a l = HCons a l
-- Test for an empty list
nullHList :: HList - Bool
nullHList HNil = True
nullHList (HCons _ _) = False
-- Retrieve head by type case
headHList :: Typeable a = HList - Maybe a
headHList HNil = Nothing
headHList (HCons a _) = cast a
-- Retrieve head by type case
tailHList :: HList - HList
tailHList HNil = error tailHList
tailHList (HCons _ l) = l
-- Access per index; starts at 1
nth1HList :: Typeable a = Int - HList - Maybe a
nth1HList i l | i  1 || i == 0  nullHList l = error nth1HList
nth1HList 1 l = headHList l
nth1HList i l = nth1HList (i-1) (tailHList l)


-- A demo list
mylist = addHList (1::Int)   $
 addHList (True::Bool)   $
 addHList (42::String) $
 initHList
-- Main function for testing
main = print   ( show (nth1HList 1 mylist :: Maybe Int)-- shows Maybe 1
 , ( show (nth1HList 1 mylist :: Maybe Bool)   -- shows Nothing
 , ( show (nth1HList 2 mylist :: Maybe Bool)   -- shows
Maybe True
 , ( show (nth1HList 3 mylist :: Maybe String) -- shows
Maybe 42
 
MR K P SCHUPKE wrote:

I needed a list which could handle items of different types for the 
database code I am writing. I have written a module implementing such 
a list based on dependant types (from Conor McBride: Faking It; 
Simulating Depandant Types in Haskell). Although McBride does not 
mention lists/vectors with items of differing types, the solution to 
implementing them came from his 'nthFront' function for re-arranging 
the order of arguments to a function.

Any type can be inserted into the list, which supports 
head/tail/init/last, as well as indexed lookup, and a 
cartesian-product (concatenating two lists together). I have included 
fromTuple/toTuple as well.

This seems quite a useful construct, and if there is nothing similar 
in the standard libraries at the moment, do you think this is worth 
including?

   Regards,
   Keean Schupke.
___
Glasgow-haskell-users mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users




___
Glasgow-haskell-users mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users


Re: Polymorphic lists...

2004-03-08 Thread MR K P SCHUPKE

Didn't know If I should post it straight away... its quite long and I dont do
attachments (well not If I can help it. I am aware Dynamic can model heterogenious 
lists
(thanks for correct terminology) - but I need static typing. Thats the clever thing 
about
this code - the list is heterogenious but statically typed.

So... for your perusal - and If its not up to being included in the libraries I would
value any comments/code review for my own edification.

The module is called Relation as I am modelling Relational Algebra... but if anyone 
can
think of a better name...

First some examples:

putStrLn $ show (rIndex two rel1) -- show the third item in rel1
putStrLn $ show (rHead r)
putStrLn $ show (rTail r)
putStrLn $ show (rLast r)
putStrLn $ show (rInit r)
putStrLn $ show (r `rEnqueue` TEST3) -- insert the string into the last (not head) 
position
putStrLn $ show ((3 :: Int) `RCons` r) -- insert the Int into the head of the list
r = toTuple (( 1.1 :: Double) `RCons` (fromTuple (hello,1,World)))


And the code:

{-# OPTIONS -fglasgow-exts #-}
{-# OPTIONS -fallow-undecidable-instances #-}
{-# OPTIONS -fallow-overlapping-instances #-}

module Lib.DBC.Relation where

--
-- (c) 2004 Keean Schupke, All Rights Reserved.
--

data Zero = Zero deriving Show
data Suc n = Suc n deriving Show

class Nat n
instance Nat Zero
instance Nat n = Nat (Suc n)

zero :: Zero
zero = Zero

one :: Suc Zero
one = Suc zero

two :: Suc (Suc Zero)
two = Suc one

three :: Suc (Suc (Suc Zero))
three = Suc two

four :: Suc (Suc (Suc (Suc Zero)))
four = Suc three

five :: Suc (Suc (Suc (Suc (Suc Zero
five = Suc four

--

infixr 1 `RCons`
data RNil = RNil deriving Show
data RCons a r = a `RCons` r deriving Show

--

class Relation r where
   rHead :: a `RCons` r - a
   rTail :: a `RCons` r - r
   rIsEmpty :: r - Bool
instance Relation RNil where
   rHead (x `RCons` _) = x
   rTail (_ `RCons` _) = RNil
   rIsEmpty RNil = True
instance Relation r = Relation (a `RCons` r) where
   rHead (x `RCons` _) = x
   rTail (_ `RCons` xs) = xs
   rIsEmpty (_ `RCons` _) = False

class RLast r a | r - a where
   rLast :: r - a
instance RLast (a `RCons` RNil) a where
   rLast (x `RCons` RNil) = x
instance RLast r b = RLast (a `RCons` r) b where
   rLast (_ `RCons` xs) = rLast xs

class RInit r1 r2 | r1 - r2 where
   rInit :: r1 - r2
instance RInit (a `RCons` RNil) RNil where
   rInit (_ `RCons` RNil) = RNil
instance RInit (b `RCons` r1) r2 = RInit (a `RCons` b `RCons` r1) (a `RCons` r2) where
   rInit (x `RCons` xs) = x `RCons` rInit xs

class REnqueue r1 r2 a | r1 a - r2 where
   rEnqueue :: r1 - a - r2
instance REnqueue RNil (a `RCons` RNil) a where
   rEnqueue RNil y = y `RCons` RNil
instance REnqueue r1 r2 b = REnqueue (a `RCons` r1) (a `RCons` r2) b where
   rEnqueue (x `RCons` xs) y = x `RCons` rEnqueue xs y

class (Nat n,Relation r) = RIndex n r a | n r - a where
   rIndex :: n - r - a
instance Relation r = RIndex Zero (a `RCons` r) a where
   rIndex Zero (x `RCons` _) = x
instance RIndex n r b = RIndex (Suc n) (a `RCons` r) b where
   rIndex (Suc n) (_ `RCons` xs) = rIndex n xs

infixl 2 `rProduct`
class (Relation r1,Relation r2,Relation r3) = RProduct r1 r2 r3 | r1 r2 - r3 where
   rProduct :: r1 - r2 - r3
instance RProduct RNil RNil RNil where
   rProduct RNil RNil = RNil
instance Relation r = RProduct RNil r r where
   rProduct RNil r = r
instance RProduct r1 r2 r3 = RProduct (a `RCons` r1) r2 (a `RCons` r3) where
   rProduct (x `RCons` xs) y = x `RCons` (xs `rProduct` y)

--

class Relation r = RTuple t r | t - r , r - t where
   fromTuple :: t - r
   toTuple :: r - t

instance RTuple (a,b) (a `RCons` b `RCons` RNil) where
   fromTuple (a,b) = a `RCons` b `RCons` RNil
   toTuple (a `RCons` b `RCons` RNil) = (a,b)

instance RTuple (a,b,c) (a `RCons` b `RCons` c `RCons` RNil) where
   fromTuple (a,b,c) = a `RCons` b `RCons` c `RCons` RNil
   toTuple (a `RCons` b `RCons` c `RCons` RNil) = (a,b,c)

instance RTuple (a,b,c,d) (a `RCons` b `RCons` c `RCons` d `RCons` RNil) where
   fromTuple (a,b,c,d) = a `RCons` b `RCons` c `RCons` d `RCons` RNil
   toTuple (a `RCons` b `RCons` c `RCons` d `RCons` RNil) = (a,b,c,d)

instance RTuple (a,b,c,d,e) (a `RCons` b `RCons` c `RCons` d `RCons` e `RCons` RNil) 
where
   fromTuple (a,b,c,d,e) = a `RCons` b `RCons` c `RCons` d `RCons` e `RCons` RNil
   toTuple (a `RCons` b `RCons` c `RCons` d `RCons` e `RCons` RNil) = (a,b,c,d,e)

instance RTuple (a,b,c,d,e,f) (a `RCons` b `RCons` c `RCons` d `RCons` e `RCons` f 
`RCons` RNil) where
   fromTuple (a,b,c,d,e,f) = a `RCons` b `RCons` c `RCons` d `RCons` e `RCons` f 
`RCons` RNil
   

Re: -static

2004-03-08 Thread Wolfgang Thaller
What platform?  Does everything work if you remove the -static?
alpha, powerpc and hppa so far. I expect the same will happen for mips
and mipsel.
If, on powerpc, I run the final link command without -static
(that's the
only place it should make a difference, right?) then it links without
warnings and looks to be working fine. I haven't looked at the others
yet.
Wolfgang: can -static be removed on powerpc as far as you know?
On powerpc-darwin, GHC has always passed -dynamic to the linker 
(otherwise, nothing would work at all). So I assume this is on 
powerpc-linux? If so, I don't see why the PPC should be any different 
from Intel in this respect. I cant test it now, but maybe I'll get 
around to having a short look at it tomorrow.

Cheers,

Wolfgang

___
Glasgow-haskell-users mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users


[Haskell] RFC: DData in hierarchical libraries

2004-03-08 Thread JP Bernardy
Dear haskellers,

I propose to add a modified version of DData to the
hierachical libraries.

DData is a concrete library of collection types, by
Daan Leijen.
My modifications intend to make DData fit better in
the hierarchical libraries.

The haddock-generated documentation can be found here:

http://users.skynet.be/jyp/DData/doc/index.html

while the source code is at

http://users.skynet.be/jyp/DData/ddata.tar.gz

Any comment is welcome. (Including I support this
proposal :))

Cheers,
JP.

PS.
For those who don't follow the libraries list, the
reasoning leading to this proposal goes as such:

* Data.FiniteMap  Data.Set don't use the module
system
* We need better collection types
* A fully fledged collection framework is difficult to
agree on for integration in standard.
* We should have a concrete types library, leaving the
framework for later.
* DData looks like a good candidate




__
Do you Yahoo!?
Yahoo! Search - Find what you’re looking for faster
http://search.yahoo.com
___
Haskell mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell


Re: [Haskell] GHC EXE Windows

2004-03-08 Thread Axel Simon
 At 08:09 04/03/04 +, Stenio wrote:
 
 
 GHC executable file only works in MS-DOS. I would like run the executable 
 file on Windows. Can someone help me
 Thanks

Did you write a GUI program and each time you double click your program gets 
started out of a DOS window? If that is the case you need to supply the 
-subsystem windows (or similar) to the gcc compiler so it links in the code 
for starting a GUI, not a console, application. If you're using a 
pre-packages GUI library, then that library should specify this linker flag 
in the package description.

Axel.

___
Haskell mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell


Re: [Haskell] RFC: DData in hierarchical libraries

2004-03-08 Thread Tomasz Zielonka
On Mon, Mar 08, 2004 at 12:32:21PM +0100, Christian Maeder wrote:
 Yes, I support this proposal.

So do I.

 Maybe the documentation to the 0rdered lists section can be improved.
 
 Set.toAscList is not really necessary as it is the same as Set.toList. 
 In order to be a proper function, the result of Set.tolist must return a 
 sorted list without duplicates, since equal sets should yield equal 
 lists, if converted by Set.toList.

It is still a proper function this way, you only don't get some nice
axioms.

 Returning a descending list is not necessary, because this can simply
 be achieved by reversing, if needed.

If the descending list is built lazily, you can get M highest elements
of N element Set in O(M log N) time, which is nice. Using reverse, you
would pay O(N log N).

Best regards,
Tom

-- 
.signature: Too many levels of symbolic links
___
Haskell mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell


[Haskell] Parsing Typed Data from a String

2004-03-08 Thread Simon D. Foster
I am currently trying to implement a method of allowing arbitrary record
syntax data-types to be converted to and from an XML representation of
them using the Read and Show class; 

i.e. simply derive either Show and then parse the given String to
extract the name/value pairs which can then be converted to XML, or
using the XML generate a representation of the data entity (e.g.
Person{name=\Fred Smith\, age=47}) and read this back into an actual
value.

However I have one small problem; the order of the incoming parameters
of the XML data-type representations is not guaranteed, but according to
Haskell 98 report;

If the constructor is defined using record syntax...the fields must be
given in the same order as the original declaration.

So my question is, is there any method in GHC which allows you to
extract the order of the constructors in a type or to parse a
type-representation in such a way that the order of the records doesn't
matter (I am looking for ease/simplicity of use)?

Or do I just tell them to put the records in alphabetical order?

-Si.

(Please CC replies to me).
-- 
Simon D. Foster [EMAIL PROTECTED]
Sheffield University

___
Haskell mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell


Re: [Haskell] Parsing Typed Data from a String

2004-03-08 Thread Andres Loeh
 So my question is, is there any method in GHC which allows you to
 extract the order of the constructors in a type or to parse a
 type-representation in such a way that the order of the records doesn't
 matter (I am looking for ease/simplicity of use)?

If you happen to use Parsec for parsing -- it has permutation
parser combinators in Text.ParserCombinators.Parsec.Perm.

So has the UUST parser combinator library, in UU.Parsing.Perms.

Best,
  Andres
___
Haskell mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell


Re: [Haskell] RFC: DData in hierarchical libraries

2004-03-08 Thread Graham Klyne
At 01:41 08/03/04 -0800, JP Bernardy wrote:
I propose to add a modified version of DData to the
hierachical libraries.
I support the proposal in principle, though I don't feel qualified to 
comment on the specific modifications.

#g


Graham Klyne
For email:
http://www.ninebynine.org/#Contact
___
Haskell mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell


Re: [Haskell] regular expression syntax - perl ain't got nothin on haskell

2004-03-08 Thread Ganesh Sittampalam
On Tue, 24 Feb 2004 07:18:58 -0800 (PST), Hal Daume III [EMAIL PROTECTED]
wrote:

just as another sample point...

i write 99% of my code in either haskell or perl.  haskell tends to be for 
the longer programs, perl tends to be for the shorter ones, though the 
decision is primarily made for only one reason:

  - if the overhead to write the string processing code in haskell
is outweighed by the overall length of the program, use haskell.
otherwise, use perl.

i would be very very happy to abandon perl all together, but, for the most 
part, this isn't a niche haskell has been able to fit well in to yet.

Another sample point:

I hacked together a perl script to do a particular task in about 30 minutes,
including fixing algorithmic issues with the problem I wanted to solve.

I then thought I'd try porting it to Haskell; I started out by doing the
really dumb conversion of mutable variables to IORefs, hashes to FiniteMaps,
and Perl regular expressions to Text.Regex (i.e. GNU extended regexps). I'd
forgotten about this thread at the time, otherwise I might have tried one of
the cleverer options.

Some observations:

(1) It took me several hours to get it working. Mostly this was because
debugging was difficult - firstly, I got an unhelpful type error message
from GHC followed by problems with making the code I developed with GHC 5
work with GHC 6 so I could show someone else the problem. Then I had a
syntax error in one of my regular expressions, which led to a run-time error
with no information about which regular expression the error was in or where
the error was. Finally debugging semantic problems with the regular
expressions wasn't very pleasant.

(2) The code ran three times as slowly. Profiling it suggests that the time
is being wasted in the regexp matches; quite possibly the main cost is in
marshalling Haskell strings to C strings. The comments in Text.Regex.Posix
suggest a PackedString interface should be provided; I should try making one
and seeing if things are better.

(3) The code was twice as long. Mostly this was for obvious reasons; the
translation of mutable variables to IORefs leads to some overhead in reading
from them, and perl has nice syntax for manipulating hashes.

I don't really have any point, except that it would be nice if it hadn't
turned out that Perl was clearly the better choice :-/

Ganesh
___
Haskell mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell


Re: [Haskell] Parsing Typed Data from a String

2004-03-08 Thread Ralf Laemmel
Hi,

with the boilerplate style one can build terms while exploring permutations.
This can accommodated as a generic program.
An illustrative code snippet follows.
Let's define a function that builds a datum a while reading constructor
strings via a monad. Hence the function is of the following type:
buildT :: forall a. Data a = ReadT a

The corresponding monad is easily defined for the following type:

newtype ReadT a = ReadT { unReadT :: [String] - Maybe ([String],a) }

The function buildT goes essentially like this:

buildT =
do str - readT -- 1
 con - string2constr str -- 2
 ske - return $ fromConstr con -- 3
 fs  - return $ gmapQ buildT' ske -- 4
 perm [] fs ske --5
In step 1, we read a constructor string from the input.
In step 2, we turn the string into a proper constructor.
In step 3, we compute a skeleton term (with bottoms).
In step 4, we compute a list of specialisations of buildT,
that only attempt to build subterms of the given type of kid.
In step 5, we repeatedly map the list of functions over the
skeleton until all functions have been applied once.
For more details, see [1,2]
There are other kinds of type reflection that come handy
in such a context; we really plan to release [3] very soon :-)
Ralf

[1] The boilerplate site: http://www.cs.vu.nl/boilerplate
[2] The code for this example: 
http://www.cs.vu.nl/boilerplate/testsuite/perm.hs
[3] Scrap more boilerplate by SPJ and Ralf Laemmel, forthcoming.

Simon D. Foster wrote:

I am currently trying to implement a method of allowing arbitrary record
syntax data-types to be converted to and from an XML representation of
them using the Read and Show class; 

i.e. simply derive either Show and then parse the given String to
extract the name/value pairs which can then be converted to XML, or
using the XML generate a representation of the data entity (e.g.
Person{name=\Fred Smith\, age=47}) and read this back into an actual
value.
However I have one small problem; the order of the incoming parameters
of the XML data-type representations is not guaranteed, but according to
Haskell 98 report;
If the constructor is defined using record syntax...the fields must be
given in the same order as the original declaration.
So my question is, is there any method in GHC which allows you to
extract the order of the constructors in a type or to parse a
type-representation in such a way that the order of the records doesn't
matter (I am looking for ease/simplicity of use)?
Or do I just tell them to put the records in alphabetical order?

-Si.

(Please CC replies to me).
 



___
Haskell mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell


[Haskell] Final CFP: GPCE'04 (electronic submission open)

2004-03-08 Thread Eelco Visser

 FINAL CALL FOR PAPERS

--
   Third International Conference on
   Generative Programming and Component Engineering (GPCE'04)

 Vancouver, October 24-28, 2004
co-located with OOPSLA 2004 and ISMM 2004

  http://gpce04.gpce.org
--


Electronic submission is now open


http://gpce.program-transformation.org


Important Dates


Pre-submission: March 12, 2004
Submission: March 19, 2004


Page limit is 20 pages LNCS format



Scope


Generative and component approaches have the potential to revolutionize
software development in a similar way as automation and components
revolutionized manufacturing. Generative Programming (developing
programs that synthesize other programs), Component Engineering (raising
the level of modularization and analysis in application design), and
Domain-Specific Languages (elevating program specifications to compact
domain-specific notations that are easier to write and maintain) are key
technologies for automating program development.

GPCE arose as a joint conference, merging the prior conference on
Generative and Component-Based Software Engineering (GCSE) and the
Workshop on Semantics, Applications, and Implementation of Program
Generation (SAIG). The goal of GPCE is to provide a meeting place for
researchers and practitioners interested in cutting edge approaches to
software development. We aim to foster further cross-fertilization
between the software engineering research community on the one hand, and
the programming languages community on the other, in addition to
supporting the original research goals of both the GCSE and the SAIG
communities. We seek papers both in software engineering and in programming
languages, and especially those that bridge the gap and are accessible to
both communities at the same time.

---
more information at http://gpce04.gpce.org


___
Haskell mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell


[Haskell] Re: [Haskell-cafe] matching constructors

2004-03-08 Thread Brandon Michael Moore
I think the generics approach really is overkill here, but it's nice to
know the generics library.

For option processing Tomasz Ziolonka described a nice technique
in the post I refered to. You can find the post in the archives at
http://www.haskell.org//pipermail/haskell/2004-January/013412.html

The big example at the end of his post seems to have exactly the otpion
structure you want, with input, output, a verbose flag, and a (composable)
selection of filters to use.

The basic idea is to make a record containing the options in their most
useful form and make each options descriptor (I assume you are using
(System.Console.)GetOpt here) return a function that transforms an option
record to reflect that option. Now to handle the list of values you get
back you just apply each transformer in turn to the default options.

It somewhat resmbles building up option values in a collection of mutable
variables, although of course values are rather more flexible in Haskell
than most other languages, and the state is encapsulated and well
behaved.

Brandon

___
Haskell mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell


Re: [Haskell-cafe] matching constructors

2004-03-08 Thread Vadim Zaliva
On Mar 5, 2004, at 15:48, Vadim Zaliva wrote:

OK, I figured it out. For sake of other novices like me here is what 
you need
to do to make it work.

0. Need to import Data.Generics
1. Compile with '-fglasgow-exts' flag
2. When deriving from Data you also need to derive from Typeable.
It slightly bothers me that this solution seems to be using 
non-standard GHC extensions.

Vadim

On Mar 5, 2004, at 12:41, Brandon Michael Moore wrote:

At the lower level of remimplementing your functions I can suggest a 
few
things.
Brandon,

Thanks for great suggestions! Following them, here is how I redone the 
code:

...

import Data.Maybe
import Data.Either
import Data.Typeable
...

data Flag = Verbose |
Input String  |
Output String |
Filter String
deriving Show Data
instance Eq Flag where
x == y = toConstr x == toConstr y
findFlag :: Flag - [Flag] - Flag
findFlag f fs = fromMaybe f (find (==f) fs)
The only problem is my GHC does not seems to find 'Data' class and I 
am getting following errors:

Type constructor or class not in scope: `Data'
Variable not in scope: `toConstr'
Variable not in scope: `toConstr'
Also I have style question: What is the best way to define equality 
test in this example:

1. Via instantiating EQ class
2. via standalone function (I can define sameConstr Flag - Flag - 
Bool)
3. inline lambda expression passed to find

I am leaning towards #2 or #3.

Vadim

--
La perfection est atteinte non quand il ne reste rien a ajouter, mais
quand il ne reste rien a enlever.  (Antoine de Saint-Exupery)
___
Haskell-Cafe mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell-cafe
--
La perfection est atteinte non quand il ne reste rien a ajouter, mais
quand il ne reste rien a enlever.  (Antoine de Saint-Exupery)


smime.p7s
Description: S/MIME cryptographic signature
___
Haskell-Cafe mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] matching constructors

2004-03-08 Thread Sven Panne
Vadim Zaliva wrote:
[...] It slightly bothers me that this solution seems to be using non-standard 
GHC extensions.
Hmmm, using generics seems like massive overkill for option handling. Could you
describe what you are exactly trying to achieve?
Cheers,
   S.
___
Haskell-Cafe mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] matching constructors

2004-03-08 Thread Vadim Zaliva
On Mar 8, 2004, at 11:17, Sven Panne wrote:

Hmmm, using generics seems like massive overkill for option handling. 
Could you
describe what you are exactly trying to achieve?
I am doing command line options parsing. I've defined Flag type with 
constructor
for each possible option:

data Flag = Verbose |
Input String  |
Output String |
Filter String
deriving (Show, Typeable, Data)
getOpt returns me a list of such objects. Now I need to
look things up there by constructor. For example:

doSomething fltflag
where
(Filter fltflag) = findFlag (Filter none) opts
To achieve this I've defined:

instance Eq Flag where
x == y = toConstr x == toConstr y
findFlag :: Flag - [Flag] - Flag
findFlag f fs = fromMaybe f (find (==f) fs)
Sincerely,
Vadim
--
La perfection est atteinte non quand il ne reste rien a ajouter, mais
quand il ne reste rien a enlever.  (Antoine de Saint-Exupery)


smime.p7s
Description: S/MIME cryptographic signature
___
Haskell-Cafe mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] matching constructors

2004-03-08 Thread Ben Rudiak-Gould
On Mon, 8 Mar 2004, Vadim Zaliva wrote:

 I am doing command line options parsing. I've defined Flag type with 
 constructor
 for each possible option:
 
 data Flag = Verbose |
  Input String  |
  Output String |
  Filter String
  deriving (Show, Typeable, Data)
 
 getOpt returns me a list of such objects. Now I need to
 look things up there by constructor. For example:
 
   
   doSomething fltflag
   where
  (Filter fltflag) = findFlag (Filter none) opts

Try this instead:

doSomething $ option none [fltflag | Filter fltflag - opts]

...

option :: a - [a] - a
option def []  = def
option def [x] = x
option def _   = error Only one of each option allowed


-- Ben

___
Haskell-Cafe mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] matching constructors

2004-03-08 Thread Vadim Zaliva
On Mar 8, 2004, at 12:55, Ben Rudiak-Gould wrote:

This would work, but I will have to write [] part for each option.
Generics approach is overkill but looks much neater when used.
But thanks for suggestion anyway, it is always good to learn yet
another way of doing things.
Sincerely,
Vadim
Try this instead:
doSomething $ option none [fltflag | Filter fltflag - opts]
option :: a - [a] - a
option def []  = def
option def [x] = x
option def _   = error Only one of each option allowed
--
La perfection est atteinte non quand il ne reste rien a ajouter, mais
quand il ne reste rien a enlever.  (Antoine de Saint-Exupery)


smime.p7s
Description: S/MIME cryptographic signature
___
Haskell-Cafe mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell-cafe