#! 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