hubris 0.0.3 → 0.0.4

This diff represents the content of publicly available package versions that have been released to one of the supported registries. The information contained in this diff is provided for informational purposes only and reflects changes between package versions as they appear in their respective public registries.
Files changed (49) hide show
  1. data/.gitignore +31 -0
  2. data/.rvmrc +2 -0
  3. data/Gemfile +11 -0
  4. data/Haskell/Hubrify.hs +69 -0
  5. data/Haskell/LICENSE +22 -0
  6. data/Haskell/Language/Ruby/Foo.hs +20 -0
  7. data/Haskell/Language/Ruby/Hubris/Binding.hsc +214 -0
  8. data/Haskell/Language/Ruby/Hubris/GHCBuild.hs +46 -0
  9. data/Haskell/Language/Ruby/Hubris/Hash.hs +27 -0
  10. data/Haskell/Language/Ruby/Hubris/Interpolator.hs +22 -0
  11. data/Haskell/Language/Ruby/Hubris/LibraryBuilder.hs +181 -0
  12. data/Haskell/Language/Ruby/Hubris/ZCode.hs +68 -0
  13. data/Haskell/Language/Ruby/Hubris.hs +254 -0
  14. data/Haskell/Language/Ruby/Wrappers.hs +32 -0
  15. data/Haskell/Language/Ruby/testLib.hs +9 -0
  16. data/Haskell/Setup.hs +31 -0
  17. data/Haskell/cbits/rshim.c +46 -0
  18. data/Haskell/cbits/rshim.h +50 -0
  19. data/Haskell/hubris.cabal +53 -0
  20. data/INSTALL +21 -0
  21. data/Manifest.txt +22 -0
  22. data/PostInstall.txt +1 -0
  23. data/README.markdown +107 -0
  24. data/Rakefile +46 -43
  25. data/VERSION +1 -0
  26. data/doc/CommonErrors.txt +18 -0
  27. data/doc/CommonErrors.txt~HEAD +18 -0
  28. data/doc/don_feedback.txt +25 -0
  29. data/doc/haskell-hubris.tex +242 -0
  30. data/doc/new_interface.rb +74 -0
  31. data/doc/ruby-hubris.tex +176 -0
  32. data/doc/wisdom_of_ancients.txt +55 -0
  33. data/ext/hubris.rb +4 -0
  34. data/ext/stub/extconf.rb +5 -0
  35. data/ext/{HubrisStubLoader.c → stub/stub.c} +1 -1
  36. data/hubris.gemspec +31 -0
  37. data/lib/Makefile +181 -0
  38. data/lib/hubris/version.rb +3 -0
  39. data/lib/hubris.rb +16 -13
  40. data/rspec.rake +21 -0
  41. data/sample/Fibonacci.hs +2 -2
  42. data/sample/config.ru +3 -1
  43. data/script/ci.sh +25 -0
  44. data/script/console +10 -0
  45. data/spec/hubris_spec.rb +173 -47
  46. data/tasks/extconf/stub.rake +43 -0
  47. data/tasks/extconf.rake +13 -0
  48. metadata +118 -27
  49. data/ext/extconf.rb +0 -5
@@ -0,0 +1,68 @@
1
+ {-# LANGUAGE PatternGuards #-}
2
+
3
+ module Language.Ruby.Hubris.ZCode (zenc,zdec,Zname(..)) where
4
+
5
+ import Data.Char
6
+ import Data.Ix
7
+ import qualified Data.Map as M
8
+ import Numeric
9
+
10
+ zemap :: M.Map Char String
11
+ zemap = M.fromList $
12
+ [ ('(', "ZL")
13
+ , (')', "ZR")
14
+ , ('[', "ZM")
15
+ , (']', "ZN")
16
+ , (':', "ZC")
17
+ , ('Z', "ZZ")
18
+
19
+ , ('z', "zz")
20
+ , ('&', "za")
21
+ , ('|', "zb")
22
+ , ('^', "zc")
23
+ , ('$', "zd")
24
+ , ('=', "ze")
25
+ , ('>', "zg")
26
+ , ('#', "zh")
27
+ , ('.', "zi")
28
+ , ('<', "zl")
29
+ , ('-', "zm")
30
+ , ('!', "zn")
31
+ , ('+', "zp")
32
+ , ('\'', "zq")
33
+ , ('\\', "zr")
34
+ , ('/', "zs")
35
+ , ('*', "zt")
36
+ , ('_', "zu")
37
+ , ('%', "zv")
38
+ ]
39
+
40
+ zdmap :: M.Map String Char
41
+ zdmap = M.fromList . map (\(a, b) -> (b, a)) . M.toList $ zemap
42
+
43
+ newtype Zname = Zname String
44
+ zenc :: String -> Zname
45
+ zenc s = Zname $ concatMap (\c -> M.findWithDefault (z c) c zemap) s
46
+ where
47
+ z c
48
+ | any (($ c) . inRange) [('a', 'y'), ('A', 'Z'), ('0', '9')] =
49
+ [c]
50
+ | otherwise =
51
+ let
52
+ s = showHex (ord c) "U"
53
+ p = if inRange ('0', '9') (head s) then id else ('0' :)
54
+ in
55
+ 'z' : p s
56
+
57
+ zdec :: String -> String
58
+ zdec "" = ""
59
+ zdec [c] = [c]
60
+ zdec (c : cs@(c' : cs'))
61
+ | c `elem` "zZ"
62
+ , Just x <- M.lookup [c, c'] zdmap
63
+ = x : zdec cs'
64
+ | c == 'z'
65
+ , (h@(_ : _), 'U' : t) <- span isHexDigit cs
66
+ , [(n, "")] <- readHex h
67
+ = chr n : zdec t
68
+ | otherwise = c : zdec cs
@@ -0,0 +1,254 @@
1
+ {-# LANGUAGE DeriveDataTypeable, ScopedTypeVariables, TypeSynonymInstances, FlexibleInstances, OverlappingInstances, UndecidableInstances#-}
2
+ module Language.Ruby.Hubris where
3
+
4
+ --import Data.Word
5
+ import Data.Map as Map
6
+ -- import Language.Ruby.Hubris.Binding
7
+ -- import System.IO.Unsafe (unsafePerformIO)
8
+ --import Foreign.C.Types
9
+ import Language.Ruby.Hubris.Binding
10
+ --import Control.Monad (forM)
11
+ import Control.Applicative
12
+ import qualified Debug.Trace as T
13
+ import Foreign.C.String
14
+ import qualified Data.ByteString as S
15
+ import qualified Data.ByteString.Lazy as L
16
+ import Data.ByteString.Internal(w2c,c2w)
17
+ -- type Value = CULong
18
+ import System.IO.Unsafe
19
+ import Data.Array.IArray
20
+ import Data.Maybe
21
+ import Control.Exception
22
+ import Prelude hiding(catch)
23
+ import Monad hiding (when)
24
+ import Data.Typeable
25
+
26
+ class Callable a where
27
+ arity :: a -> Int
28
+
29
+ instance (Callable b, Haskellable a) => Callable (a -> b) where
30
+ arity x = 1 + arity (undefined :: b)
31
+
32
+ instance Rubyable a => Callable a where
33
+ arity x = 0
34
+
35
+ -- with thanks to copumpkin on #haskell and twitter
36
+
37
+ -- wrap :: (Haskellable a, Rubyable b) => (a->b) -> (Value -> Value)
38
+ -- wrap func v= unsafePerformIO $ do r <- try (evaluate $ toRuby . func $ toHaskell v)
39
+ -- case r of
40
+ -- Left (e::SomeException) -> createException (show e) `traces` "died in haskell"
41
+ -- Right a -> return a
42
+ -- -- wrapIO too? Is there a more generic way of doin
43
+ -- g this? would need a = a', b = IO c, so Rubyable b => Rubyable (IO c). (Throw away Show constraint, not necessary)
44
+
45
+ data HubrisException = HubrisException String
46
+ deriving(Show, Typeable)
47
+
48
+
49
+ instance Exception HubrisException
50
+
51
+ -- utility stuff:
52
+ sshow :: S.ByteString -> [Char]
53
+ sshow s = Prelude.map w2c $S.unpack s
54
+ lshow :: L.ByteString -> [Char]
55
+ lshow s = Prelude.map w2c $L.unpack s
56
+
57
+ -- debugging only
58
+ trace a b = b
59
+ traces :: b -> String -> b
60
+ traces = flip trace
61
+
62
+ when :: Value -> RubyType -> a -> a
63
+ when v b c = if (rubyType v == b)
64
+ then c
65
+ else trace (show (rubyType v,b)) $ throw (HubrisException "failed in when")
66
+
67
+ class Haskellable a where
68
+ toHaskell :: Value -> a
69
+
70
+ class Rubyable a where
71
+ toRuby :: a -> Value
72
+
73
+ instance Haskellable Int where
74
+ toHaskell v = when v RT_FIXNUM $ fix2int v
75
+
76
+ -- this is ugly, maybe we can use template haskell to remove the boilerplate?
77
+ instance (Rubyable a, Rubyable b) => Rubyable (a,b) where
78
+ toRuby (a,b) = unsafePerformIO $ do ary <- rb_ary_new2 2
79
+ rb_ary_push ary (toRuby a)
80
+ rb_ary_push ary (toRuby b)
81
+ return ary
82
+
83
+ instance (Rubyable a, Rubyable b, Rubyable c) => Rubyable (a,b,c) where
84
+ toRuby (a,b,c) = unsafePerformIO $ do ary <- rb_ary_new2 3
85
+ rb_ary_push ary (toRuby a)
86
+ rb_ary_push ary (toRuby b)
87
+ rb_ary_push ary (toRuby c)
88
+ return ary
89
+
90
+ instance (Haskellable a, Haskellable b) => Haskellable (a,b) where
91
+ toHaskell v = when v RT_ARRAY $ unsafePerformIO $
92
+ do a <- toHaskell <$> rb_ary_entry v 0
93
+ b <- toHaskell <$> rb_ary_entry v 1
94
+ return (a,b)
95
+
96
+ instance (Haskellable a, Haskellable b, Haskellable c) => Haskellable (a,b,c) where
97
+ toHaskell v = when v RT_ARRAY $ unsafePerformIO $
98
+ do a <- toHaskell <$> rb_ary_entry v 0
99
+ b <- toHaskell <$> rb_ary_entry v 1
100
+ c <- toHaskell <$> rb_ary_entry v 2
101
+ return (a,b,c)
102
+
103
+
104
+
105
+ instance Rubyable Int where
106
+ toRuby i = int2fix i
107
+
108
+ instance Rubyable a => Rubyable (IO a) where
109
+ toRuby a = unsafePerformIO (a >>= return . toRuby)
110
+ instance Haskellable Integer where
111
+ toHaskell v = case rubyType v of
112
+ RT_BIGNUM -> trace ("got a big") $ read $ unsafePerformIO (rb_big2str v 10 >>= str2cstr >>= peekCString)
113
+ RT_FIXNUM -> trace("got a fix") $ fromIntegral $ fix2int v
114
+ _ -> throw (HubrisException "Integer") -- wonder if it's kosher to just let the pattern match fail...
115
+
116
+ instance Rubyable Integer where
117
+ toRuby i = trace ("integer to ruby") $ rb_str_to_inum (unsafePerformIO $ (newCAString $ show i) >>= rb_str_new2) 10 1
118
+
119
+ instance Haskellable Bool where
120
+ toHaskell v = case rubyType v of
121
+ RT_TRUE -> True
122
+ RT_FALSE -> False
123
+ _ -> throw (HubrisException "Bool")
124
+
125
+ instance Rubyable Bool where
126
+ toRuby True = constToRuby RUBY_Qtrue
127
+ toRuby False = constToRuby RUBY_Qfalse
128
+
129
+ instance Rubyable Double where
130
+ toRuby d = rb_float_new d
131
+
132
+ instance Haskellable Double where
133
+ toHaskell v = case rubyType v of
134
+ RT_FLOAT -> num2dbl v
135
+ RT_FIXNUM -> fromIntegral $ fix2int v
136
+ _ -> throw (HubrisException "Double")
137
+
138
+ instance Rubyable Value where
139
+ toRuby v = v
140
+
141
+ instance Haskellable Value where
142
+ toHaskell v = v
143
+
144
+
145
+ instance Haskellable S.ByteString where
146
+ toHaskell v = when v RT_STRING $ unsafePerformIO $
147
+ str2cstr v >>= S.packCString >>= \a -> return a `traces` ("strict to Haskell: " ++ sshow a)
148
+
149
+ instance Rubyable S.ByteString where
150
+ toRuby s = unsafePerformIO $ S.useAsCStringLen s rb_str_new
151
+ -- \(cs,len) -> rb_str_new (cs,len) --`traces` ("sstrict back to ruby:" ++ (show $ S.unpack s))
152
+
153
+
154
+ instance Rubyable () where
155
+ toRuby () = toRuby True -- ???
156
+
157
+ instance Haskellable L.ByteString where
158
+ toHaskell v = L.fromChunks [toHaskell v]
159
+
160
+ instance Rubyable L.ByteString where
161
+ toRuby s = let res = S.concat $ L.toChunks s
162
+ in trace ("lazy back to ruby: " ++ show (S.unpack res)) (toRuby res)
163
+
164
+ instance Haskellable a => Haskellable [a] where
165
+ toHaskell v = when v RT_ARRAY $ Prelude.map toHaskell $ unsafePerformIO $ mapM (rb_ary_entry v . fromIntegral) [0..(rb_ary_len v) - 1]
166
+
167
+
168
+
169
+ instance Rubyable a => Rubyable [a] where
170
+ toRuby l = unsafePerformIO $ do ary <- rb_ary_new2 $ fromIntegral $ Prelude.length l
171
+ mapM_ (\x -> rb_ary_push ary (toRuby x)) l
172
+ return ary
173
+
174
+ -- this one is probably horribly inefficient.
175
+ instance (Integral a, Ix a, Haskellable b) => Haskellable (Array a b) where
176
+ toHaskell v = let x = toHaskell v in (listArray (0, fromIntegral $ Prelude.length x) x)
177
+
178
+ -- could be more efficient, perhaps, but it's space-efficient still thanks to laziness
179
+ instance (Rubyable b, Ix a) => Rubyable (Array a b) where
180
+ toRuby a = toRuby $ Data.Array.IArray.elems a
181
+
182
+ instance Haskellable RubyHash where
183
+ toHaskell v = when v RT_HASH $ RubyHash v
184
+
185
+ instance Rubyable RubyHash where
186
+ toRuby (RubyHash v) = v
187
+
188
+
189
+ -- Nil maps to Nothing - all the other falsey values map to real haskell values.
190
+ instance Haskellable a => Haskellable (Maybe a) where
191
+ toHaskell v = case rubyType v of
192
+ RT_NIL -> Nothing `traces` "Haskell got nothing"
193
+ _ -> Just (toHaskell v) `traces` "Haskell got a value"
194
+
195
+ instance Rubyable a => Rubyable (Maybe a) where
196
+ toRuby Nothing = constToRuby RUBY_Qnil `traces` "Sending ruby a nil"
197
+ toRuby (Just a) = toRuby a `traces` "Sending a value back"
198
+
199
+ newtype RubyHash = RubyHash Value -- don't export constructor
200
+
201
+ instance (Ord a, Eq a, Rubyable a, Rubyable b) => Rubyable (Map.Map a b) where
202
+ toRuby s = unsafePerformIO $
203
+ do hash <- rb_hash_new
204
+ mapM_ (\(k,v) -> rb_hash_aset hash (toRuby k) (toRuby v)) (toList s)
205
+ return hash
206
+
207
+ instance (Ord a, Eq a, Haskellable b, Haskellable a) => Haskellable (Map.Map a b) where
208
+ toHaskell hash = when hash RT_HASH $ unsafePerformIO $
209
+ -- fromJust is legit, rb_keys will always return list
210
+ do -- putStrLn "Bringing hash over"
211
+ keys <- rb_keys hash
212
+ -- putStrLn ("got the keys: " ++ show keys)
213
+ l :: [Value] <- toHaskell <$> rb_keys hash
214
+
215
+ r <- foldM (\m k -> do -- putStrLn $ "Key is " ++ show k
216
+ val <- rb_hash_aref hash k
217
+ -- putStrLn $ "Val is " ++ show val
218
+ return $ Map.insert (toHaskell k)
219
+ (toHaskell val)
220
+ m)
221
+ Map.empty l
222
+ return r
223
+
224
+
225
+
226
+ -- This is a tricky case.
227
+ -- The ruby FFI wants us to pass a C callback which it can apply to each key-value pair
228
+ -- of the hash, so Haskell cannot be fully in control of the process - this makes building
229
+ -- up a Data.Map object in the natural way a bit tricky.
230
+
231
+ -- current thoughts:
232
+ -- 1. write a direct binding to the ruby API, include a C level function for getting the keys.
233
+ -- just eat the cost of transferring through a keys call + looping over the elements.
234
+ -- One big benefit - while iteration is expensive, using it as a hash table should be cheap
235
+ -- (although probably needs to stay in the IO monad, which is less convenient.)
236
+ --
237
+ -- 2. write a binding to the Judy library that creates a Judy object directly. If we can convince
238
+ -- HsJudy to accept that, then we're golden - we still have to copy over, but keys operations
239
+ -- should be cheap (and hopefully lazy, but test to make sure).
240
+ --
241
+ -- These are of course not mutually exclusive.
242
+ --
243
+ -- The first should probably be a part of the base package. The second needs access to internals,
244
+ -- but should probably be an optional package. This means that in Hubris.Internals, we should expose
245
+
246
+ -- > rb_foreach :: Value {- HASH -} -> (CFunction ((Key,Value,a) -> a)) -> a -> IO a
247
+ --
248
+ --
249
+
250
+ -- instance Haskellable (Map.Map a b ) where
251
+ -- toHaskell (T_HASH s) = unsafePerformIO $
252
+ -- get_each
253
+
254
+ -- toHaskell _ = Nothing
@@ -0,0 +1,32 @@
1
+ module Wrappers where
2
+ import Hubris
3
+ data RValue = T_FIXNUM Int
4
+ | T_STRING String
5
+ | T_NIL
6
+ | T_BIGNUM Integer
7
+ deriving (Eq, Show,Ord)
8
+
9
+ wrap :: (Haskellable a, Rubyable b) => (a->b) -> (RValue -> RValue)
10
+ wrap func ar = case (toHaskell ar) of
11
+ Just a -> toRuby $ func a
12
+ Nothing -> T_NIL
13
+
14
+ class Haskellable a where
15
+ toHaskell :: RValue -> Maybe a
16
+
17
+ class Rubyable a where
18
+ toRuby :: a -> RValue
19
+
20
+ instance Haskellable Int where
21
+ toHaskell (T_FIXNUM i) = Just i
22
+ toHaskell _ = Nothing
23
+
24
+ instance Rubyable Int where
25
+ toRuby i = T_FIXNUM i
26
+
27
+ instance Haskellable Integer where
28
+ toHaskell (T_BIGNUM i) = Just i
29
+ toHaskell _ = Nothing
30
+
31
+ instance Rubyable Integer where
32
+ toRuby i = T_BIGNUM i
@@ -0,0 +1,9 @@
1
+ import Language.Ruby.Hubris.LibraryBuilder
2
+
3
+ main = do
4
+ -- Hubris.hs ought to be installed on the system, really.
5
+ source <- generateSource ["Language/Ruby/Hubris.hs","Language/Ruby/Foo.hs"] "Foo"
6
+ case source of
7
+ Left err -> error $ show err
8
+ Right Nothing -> error "shouldn't happen" -- maybe throw an error in the interpreter monad instead
9
+ Right (Just a) -> putStrLn a
data/Haskell/Setup.hs ADDED
@@ -0,0 +1,31 @@
1
+ {-# LANGUAGE NamedFieldPuns #-}
2
+ import Distribution.Simple
3
+ import Distribution.Simple.Setup
4
+ import Distribution.Simple.LocalBuildInfo
5
+ import Distribution.Simple.Utils
6
+ import qualified Distribution.PackageDescription as D
7
+ import Distribution.Verbosity
8
+ import System.Directory
9
+ import System.Process
10
+ import Maybe
11
+ import qualified Distribution.ModuleName as Modname
12
+ main = do
13
+ includeDir <- readProcess "ruby" ["-rrbconfig", "-e", "print RbConfig::CONFIG['rubyhdrdir']"] ""
14
+ archDir <- readProcess "ruby" ["-rrbconfig", "-e", "print RbConfig::CONFIG['archdir'].gsub(/\\/lib\\//, '/include/').gsub(/\\/include\\/ruby\\//, '/include/ruby-')"] ""
15
+ defaultMainWithHooks (hooks includeDir archDir)
16
+
17
+ hooks includeDir archDir = simpleUserHooks
18
+ {
19
+ preConf = \arg flags -> do
20
+ -- probably a nicer way of getting that directory...
21
+ createDirectoryIfMissing True "dist/build/autogen"
22
+ -- FILTHY HACK
23
+ writeFile "dist/build/autogen/Includes.hs" ("module Includes where\nextraIncludeDirs=[\"" ++ includeDir++"\",\"" ++ archDir ++ "\"]") -- show (configExtraIncludeDirs flags))
24
+ return D.emptyHookedBuildInfo,
25
+ confHook = \ info flags -> (confHook simpleUserHooks) info (flags { configSharedLib = Flag True, configExtraIncludeDirs = [includeDir] }),
26
+ sDistHook = \ pkg lbi hooks flags -> let lib = fromJust $ D.library pkg
27
+ modules = filter (/= Modname.fromString "Includes") $ D.exposedModules lib
28
+ pkg' = pkg { D.library = Just $ lib { D.exposedModules = modules } }
29
+ in sDistHook simpleUserHooks pkg' lbi hooks flags
30
+
31
+ }
@@ -0,0 +1,46 @@
1
+
2
+ #include "rshim.h"
3
+
4
+ #include <ruby.h>
5
+ #include <stdio.h>
6
+
7
+ /* void Init_rshim() { */
8
+ /* printf("loaded, bitches\n"); */
9
+ /* } */
10
+
11
+ // did this really have to be a macro? BAD MATZ
12
+ unsigned int rtype(VALUE obj) {
13
+ return TYPE(obj);
14
+ }
15
+
16
+ VALUE int2fix(long x) {
17
+ // printf("long2fix called\n");
18
+ return LONG2FIX(x);
19
+ }
20
+
21
+ long fix2int(VALUE x) {
22
+ // printf("fix2long called\n");
23
+ // return rb_num2int(x);
24
+ return FIX2LONG(x);
25
+ //return FIX2INT(x);
26
+ }
27
+
28
+ double num2dbl(VALUE x) {
29
+ // printf("num2dbl called\n");
30
+ return NUM2DBL(x);
31
+ }
32
+
33
+ unsigned int rb_ary_len(VALUE x) {
34
+ return RARRAY_LEN(x);
35
+ }
36
+
37
+ VALUE keys(VALUE hash) {
38
+ rb_funcall(hash, rb_intern("keys"), 0);
39
+ }
40
+
41
+ VALUE buildException(char * message) {
42
+ VALUE errclass = rb_eval_string("HaskellError");
43
+ VALUE errobj = rb_exc_new2(errclass, message);
44
+ return errobj;
45
+ }
46
+
@@ -0,0 +1,50 @@
1
+ #ifndef __FOOSHIM__
2
+ #define __FOOSHIM__ 1
3
+ #define HAVE_STRUCT_TIMESPEC 1
4
+ #include <ruby.h>
5
+
6
+ // did this really have to be a macro? BAD MATZ
7
+ unsigned int rtype(VALUE obj);
8
+ VALUE int2fix(long i);
9
+ long fix2int(VALUE x);
10
+ double num2dbl(VALUE x);
11
+ unsigned int rb_ary_len(VALUE x);
12
+ VALUE keys(VALUE hash);
13
+ VALUE buildException(char *);
14
+ // argh, and again
15
+ enum RubyType {
16
+ RT_NONE = T_NONE,
17
+
18
+ RT_NIL = T_NIL ,
19
+ RT_OBJECT = T_OBJECT ,
20
+ RT_CLASS = T_CLASS ,
21
+ RT_ICLASS = T_ICLASS ,
22
+ RT_MODULE = T_MODULE ,
23
+ RT_FLOAT = T_FLOAT ,
24
+ RT_STRING = T_STRING ,
25
+ RT_REGEXP = T_REGEXP ,
26
+ RT_ARRAY = T_ARRAY ,
27
+ RT_FIXNUM = T_FIXNUM ,
28
+ RT_HASH = T_HASH ,
29
+ RT_STRUCT = T_STRUCT ,
30
+ RT_BIGNUM = T_BIGNUM ,
31
+ RT_FILE = T_FILE ,
32
+
33
+ RT_TRUE = T_TRUE ,
34
+ RT_FALSE = T_FALSE ,
35
+ RT_DATA = T_DATA ,
36
+ RT_MATCH = T_MATCH ,
37
+ RT_SYMBOL = T_SYMBOL ,
38
+
39
+ // t_BLKTAG = T_BLKTAG , // this one is broken in ruby 1.9
40
+
41
+ RT_UNDEF = T_UNDEF ,
42
+ // t_VARMAP = T_VARMAP , // this one is broken in ruby 1.9
43
+ // t_SCOPE = T_SCOPE , // this one is broken in ruby 1.9
44
+ RT_NODE = T_NODE ,
45
+
46
+ RT_MASK = T_MASK ,
47
+ };
48
+ #endif
49
+
50
+
@@ -0,0 +1,53 @@
1
+ Name: hubris
2
+ Version: 0.0.4
3
+ Author: Mark Wotton
4
+ Maintainer: mwotton@gmail.com
5
+ Build-Type: Simple
6
+ Cabal-Version: >=1.2
7
+ License: OtherLicense
8
+ License-File: LICENSE
9
+ Build-Type: Simple
10
+ Author: Mark Wotton <mwotton@gmail.com>
11
+ Maintainer: Mark Wotton <mwotton@gmail.com>
12
+ bug-reports: http://github.com/mwotton/Hubris-Haskell/issues
13
+ Category: Language
14
+ Stability: Experimental
15
+ extra-source-files:
16
+ Synopsis: Support library for Hubris, the Ruby <=> Haskell bridge
17
+ Description: Support library for Hubris, the Ruby to Haskell bridge
18
+ more info at <http://github.com/mwotton/Hubris-Haskell>
19
+ .
20
+ Anyway, this version strips the boilerplate that used to be necessary, and is intended to be used in conjunction with <http://github.com/mwotton/Hubris>.
21
+
22
+ Library
23
+ -- the ordering is critical, because Cabal doesn't do dependency analysis.
24
+ Exposed-Modules: Language.Ruby.Hubris.Binding, Language.Ruby.Hubris, Language.Ruby.Hubris.LibraryBuilder, Language.Ruby.Hubris.ZCode, Language.Ruby.Hubris.GHCBuild,Language.Ruby.Hubris.Includes
25
+ -- , Language.Ruby.Hubris.Includes
26
+ c-sources: cbits/rshim.c
27
+ -- includes: cbits/rshim.h
28
+ install-includes: cbits/rshim.h
29
+ include-dirs: cbits
30
+ cc-options: -U__BLOCKS__ -DHAVE_SNPRINTF
31
+ extra-libraries: ruby
32
+ -- a proper fix for this would involve autoconf and I'm not feeling up to it.
33
+ -- best to pass the args on the command line.
34
+ --extra-include-dirs=/opt/local/include/ruby-1.9.1/
35
+ --extra-lib-dirs: /opt/local/lib
36
+ extra-libraries: ruby
37
+ build-depends: ghc, Cabal>=1.7.4 && < 2.0, base, haskell98, containers, bytestring, array, mtl, old-time, ghc-paths, hint >= 0.3.3.2, HUnit
38
+
39
+ Executable Hubrify
40
+ Main-is: Hubrify.hs
41
+ Build-Depends: base >= 3 && < 5, Cabal>=1.7.4 && < 2.0, base, haskell98, containers, bytestring, array, mtl, old-time, ghc-paths, hint, process,ghc
42
+ Other-Modules: Language.Ruby.Hubris.Binding
43
+ c-sources: cbits/rshim.c
44
+ include-dirs: cbits
45
+ cc-options: -U__BLOCKS__ -DHAVE_SNPRINTF
46
+ extra-libraries: ruby
47
+ -- extra-libraries: ruby1.9
48
+ -- This is bad form, apparently, and if i include it, ./Setup dist cries big fat tears,
49
+ -- but you _really_ want a dynamic lib with Hubrify, or you'll get a truly
50
+ -- huge binary (may not even link, I had problems with the iconv dependency from HSbase)
51
+ -- anyway, pass "--ghc-options=-dynamic" to ./Setup configure, and you should be apples.
52
+ ghc-options: -dynamic
53
+
data/INSTALL ADDED
@@ -0,0 +1,21 @@
1
+ This is a bit involved at the moment, because you need to have a development version of GHC,
2
+ as well as having a bootstrapping version of GHC to build it with.
3
+
4
+ So, on Ubuntu,
5
+
6
+ sudo apt-get install ruby ruby-dev ghc libopenssl-ruby
7
+ sudo gem install rake open4 rspec hoe
8
+ cabal install c2hs
9
+ wget http://www.haskell.org/ghc/dist/current/dist/ghc-6.11.20090907-src.tar.bz2
10
+ tar -jxvf ghc-6.11.20090907-src.tar.bz2
11
+ cd ghc-6.11.20090907
12
+ # adjust the argument to -j to your number of cores, and the prefix if you need to install somewhere else
13
+ sh boot && ./configure --enable-shared --prefix=/usr/local && make -j 4 && sudo make install
14
+ cd ..
15
+ git clone git://github.com/mwotton/Hubris.git
16
+ cd Hubris
17
+ rake
18
+ # here's where you'll see a whole lot of successes, if you're very lucky
19
+ # There's a good chance you won't. Tell me what went wrong and i'll fix the docs.
20
+ spec spec/*_spec.rb
21
+
data/Manifest.txt ADDED
@@ -0,0 +1,22 @@
1
+ CommonErrors.txt
2
+ HISTORY.markdown
3
+ History.txt
4
+ HubrisStubLoader.so
5
+ Manifest.txt
6
+ PostInstall.txt
7
+ README.markdown
8
+ Rakefile
9
+ examples/simple_inline/clean_and_run.sh
10
+ examples/simple_inline/haskell_math.rb
11
+ examples/simple_rack_app/Test.hs
12
+ examples/simple_rack_app/config.ru
13
+ examples/simple_rack_app/hsload.rb
14
+ hubris.gemspec
15
+ lib/Makefile
16
+ lib/hubris.rb
17
+ rspec.rake
18
+ sample/Fibonacci.hs
19
+ sample/config.ru
20
+ spec/hubris_spec.rb
21
+ spec/spec.opts
22
+ spec/spec_helper.rb
data/PostInstall.txt ADDED
@@ -0,0 +1 @@
1
+ For more information on Hubris, see http://github.com/mwotton/Hubris/tree/master