Skip to content

Commit 4b8ad4e

Browse files
committed
Merge pull request #36 from mgsloan/jsref-to-jsval
Rename JSRef to JSVal
2 parents 8ee0812 + b3cb786 commit 4b8ad4e

Some content is hidden

Large Commits have some content hidden by default. Use the searchbox below for content that may be hidden.

52 files changed

+832
-825
lines changed

Data/JSString.hs

Lines changed: 7 additions & 7 deletions
Original file line numberDiff line numberDiff line change
@@ -159,16 +159,16 @@ import qualified GHC.CString as GHC
159159

160160
import Unsafe.Coerce
161161

162-
import GHCJS.Prim (JSRef)
162+
import GHCJS.Prim (JSVal)
163163

164164
import Data.JSString.Internal.Type
165165
import Data.JSString.Internal.Fusion (stream, unstream)
166166
import qualified Data.JSString.Internal.Fusion as S
167167
import qualified Data.JSString.Internal.Fusion.Common as S
168168

169-
getJSRef :: JSString -> JSRef
170-
getJSRef (JSString x) = x
171-
{-# INLINE getJSRef #-}
169+
getJSVal :: JSString -> JSVal
170+
getJSVal (JSString x) = x
171+
{-# INLINE getJSVal #-}
172172

173173
instance Exts.IsString JSString where
174174
fromString = pack
@@ -1687,7 +1687,7 @@ foreign import javascript unsafe
16871687
foreign import javascript unsafe
16881688
"$1===''" js_null :: JSString -> Bool
16891689
foreign import javascript unsafe
1690-
"$1===null" js_isNull :: JSRef -> Bool
1690+
"$1===null" js_isNull :: JSVal -> Bool
16911691
foreign import javascript unsafe
16921692
"$1===$2" js_eq :: JSString -> JSString -> Bool
16931693
foreign import javascript unsafe
@@ -1731,9 +1731,9 @@ foreign import javascript unsafe
17311731
"h$jsstringLast" js_last :: JSString -> Int#
17321732

17331733
foreign import javascript unsafe
1734-
"h$jsstringInit" js_init :: JSString -> JSRef -- null for empty string
1734+
"h$jsstringInit" js_init :: JSString -> JSVal -- null for empty string
17351735
foreign import javascript unsafe
1736-
"h$jsstringTail" js_tail :: JSString -> JSRef -- null for empty string
1736+
"h$jsstringTail" js_tail :: JSString -> JSVal -- null for empty string
17371737
foreign import javascript unsafe
17381738
"h$jsstringReverse" js_reverse :: JSString -> JSString
17391739
foreign import javascript unsafe

Data/JSString/Internal.hs

Lines changed: 2 additions & 2 deletions
Original file line numberDiff line numberDiff line change
@@ -12,9 +12,9 @@ import Control.DeepSeq (NFData(..))
1212
import qualified GHC.Exts as Exts
1313
1414
import Unsafe.Coerce
15-
import GHCJS.Prim (JSRef)
15+
import GHCJS.Prim (JSVal)
1616
17-
newtype JSString = JSString (JSRef ())
17+
newtype JSString = JSString (JSVal ())
1818
1919
instance Monoid JSString where
2020
mempty = empty

Data/JSString/Internal/Fusion.hs

Lines changed: 4 additions & 4 deletions
Original file line numberDiff line numberDiff line change
@@ -185,10 +185,10 @@ foreign import javascript unsafe
185185
foreign import javascript unsafe
186186
"$1.length" js_length :: JSString -> Int#
187187
foreign import javascript unsafe
188-
"$r = [$1];" js_newSingletonArray :: Char -> IO JSRef
188+
"$r = [$1];" js_newSingletonArray :: Char -> IO JSVal
189189
foreign import javascript unsafe
190-
"$3[$2] = $1;" js_writeArray :: Char -> Int -> JSRef -> IO ()
190+
"$3[$2] = $1;" js_writeArray :: Char -> Int -> JSVal -> IO ()
191191
foreign import javascript unsafe
192-
"h$jsstringPackArray" js_packString :: JSRef -> IO JSString
192+
"h$jsstringPackArray" js_packString :: JSVal -> IO JSString
193193
foreign import javascript unsafe
194-
"h$jsstringPackArrayReverse" js_packReverse :: JSRef -> IO JSString
194+
"h$jsstringPackArrayReverse" js_packReverse :: JSVal -> IO JSString

Data/JSString/Internal/Type.hs

Lines changed: 3 additions & 3 deletions
Original file line numberDiff line numberDiff line change
@@ -36,13 +36,13 @@ import Data.Int (Int32, Int64)
3636
import Data.Typeable (Typeable)
3737
import GHC.Exts (Char(..), ord#, andI#, (/=#), isTrue#)
3838

39-
import GHCJS.Prim (JSRef)
39+
import GHCJS.Prim (JSVal)
4040

4141
import GHCJS.Internal.Types
4242

4343
-- | A wrapper around a JavaScript string
44-
newtype JSString = JSString JSRef
45-
instance IsJSRef JSString
44+
newtype JSString = JSString JSVal
45+
instance IsJSVal JSString
4646

4747
instance NFData JSString where rnf !x = ()
4848

Data/JSString/Read.hs

Lines changed: 7 additions & 7 deletions
Original file line numberDiff line numberDiff line change
@@ -136,7 +136,7 @@ readIntegerMaybe j = convertNullMaybe js_readInteger j
136136

137137
-- ----------------------------------------------------------------------------
138138

139-
convertNullMaybe :: (JSString -> JSRef) -> JSString -> Maybe a
139+
convertNullMaybe :: (JSString -> JSVal) -> JSString -> Maybe a
140140
convertNullMaybe f j
141141
| js_isNull r = Nothing
142142
| otherwise = Just (unsafeCoerce (js_toHeapObject r))
@@ -150,21 +150,21 @@ readError xs = error ("Data.JSString.Read." ++ xs)
150150
-- ----------------------------------------------------------------------------
151151

152152
foreign import javascript unsafe
153-
"$r = $1===null;" js_isNull :: JSRef -> Bool
153+
"$r = $1===null;" js_isNull :: JSVal -> Bool
154154
foreign import javascript unsafe
155-
"$r=$1;" js_toHeapObject :: JSRef -> Any
155+
"$r=$1;" js_toHeapObject :: JSVal -> Any
156156
foreign import javascript unsafe
157-
"h$jsstringReadInteger" js_readInteger :: JSString -> JSRef
157+
"h$jsstringReadInteger" js_readInteger :: JSString -> JSVal
158158
foreign import javascript unsafe
159-
"h$jsstringReadInt" js_readInt :: JSString -> JSRef
159+
"h$jsstringReadInt" js_readInt :: JSString -> JSVal
160160
foreign import javascript unsafe
161-
"h$jsstringLenientReadInt" js_lenientReadInt :: JSString -> JSRef
161+
"h$jsstringLenientReadInt" js_lenientReadInt :: JSString -> JSVal
162162
foreign import javascript unsafe
163163
"h$jsstringReadInt64" js_readInt64 :: JSString -> (# Int#, Int64# #)
164164
foreign import javascript unsafe
165165
"h$jsstringReadWord64" js_readWord64 :: JSString -> (# Int#, Word64# #)
166166
foreign import javascript unsafe
167-
"h$jsstringReadDouble" js_readDouble :: JSString -> JSRef
167+
"h$jsstringReadDouble" js_readDouble :: JSString -> JSVal
168168
foreign import javascript unsafe
169169
"h$jsstringIsInteger" js_isInteger :: JSString -> Bool
170170
foreign import javascript unsafe

Data/JSString/RegExp.hs

Lines changed: 1 addition & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -25,7 +25,7 @@ import Unsafe.Coerce (unsafeCoerce)
2525
import Data.JSString
2626
import Data.Typeable
2727

28-
newtype RegExp = RegExp JSRef deriving Typeable
28+
newtype RegExp = RegExp JSVal deriving Typeable
2929

3030
data REFlags = REFlags { multiline :: !Bool
3131
, ignoreCase :: !Bool

Data/JSString/Text.hs

Lines changed: 9 additions & 9 deletions
Original file line numberDiff line numberDiff line change
@@ -11,8 +11,8 @@ module Data.JSString.Text
1111
, textFromJSString
1212
, lazyTextToJSString
1313
, lazyTextFromJSString
14-
, textFromJSRef
15-
, lazyTextFromJSRef
14+
, textFromJSVal
15+
, lazyTextFromJSVal
1616
) where
1717

1818
import GHCJS.Prim
@@ -51,16 +51,16 @@ lazyTextFromJSString = TL.fromStrict . textFromJSString
5151
{-# INLINE lazyTextFromJSString #-}
5252

5353
-- | returns the empty Text if not a string
54-
textFromJSRef :: JSRef -> T.Text
55-
textFromJSRef j = case js_fromString' j of
54+
textFromJSVal :: JSVal -> T.Text
55+
textFromJSVal j = case js_fromString' j of
5656
(# _, 0# #) -> T.empty
5757
(# ba, length #) -> T.Text (A.Array ba) 0 (I# length)
58-
{-# INLINE textFromJSRef #-}
58+
{-# INLINE textFromJSVal #-}
5959

6060
-- | returns the empty Text if not a string
61-
lazyTextFromJSRef :: JSRef -> TL.Text
62-
lazyTextFromJSRef = TL.fromStrict . textFromJSRef
63-
{-# INLINE lazyTextFromJSRef #-}
61+
lazyTextFromJSVal :: JSVal -> TL.Text
62+
lazyTextFromJSVal = TL.fromStrict . textFromJSVal
63+
{-# INLINE lazyTextFromJSVal #-}
6464

6565
-- ----------------------------------------------------------------------------
6666

@@ -72,7 +72,7 @@ foreign import javascript unsafe
7272
js_fromString :: JSString -> (# ByteArray#, Int# #)
7373
foreign import javascript unsafe
7474
"h$textFromString"
75-
js_fromString' :: JSRef -> (# ByteArray#, Int# #)
75+
js_fromString' :: JSVal -> (# ByteArray#, Int# #)
7676
foreign import javascript unsafe
7777
"h$lazyTextToString"
7878
js_lazyTextToString :: Any -> JSString

GHCJS/Buffer.hs

Lines changed: 3 additions & 3 deletions
Original file line numberDiff line numberDiff line change
@@ -217,11 +217,11 @@ foreign import javascript unsafe
217217
foreign import javascript unsafe
218218
"$r = $1;" js_toByteArray :: SomeBuffer any -> ByteArray#
219219
foreign import javascript unsafe
220-
"$r = $1;" js_fromByteArray :: ByteArray# -> JSRef
220+
"$r = $1;" js_fromByteArray :: ByteArray# -> JSVal
221221
foreign import javascript unsafe
222-
"$r = $1;" js_fromMutableByteArray :: MutableByteArray# s -> JSRef
222+
"$r = $1;" js_fromMutableByteArray :: MutableByteArray# s -> JSVal
223223
foreign import javascript unsafe
224-
"$r = $1;" js_toMutableByteArray :: JSRef -> MutableByteArray# s
224+
"$r = $1;" js_toMutableByteArray :: JSVal -> MutableByteArray# s
225225
foreign import javascript unsafe
226226
"$r1 = $1; $r2 = 0;" js_toAddr :: SomeBuffer any -> Addr#
227227
foreign import javascript unsafe

GHCJS/Buffer/Types.hs

Lines changed: 1 addition & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -5,7 +5,7 @@ module GHCJS.Buffer.Types where
55
import GHCJS.Types
66
import GHCJS.Internal.Types
77

8-
newtype SomeBuffer (a :: MutabilityType s) = SomeBuffer JSRef
8+
newtype SomeBuffer (a :: MutabilityType s) = SomeBuffer JSVal
99

1010
type Buffer = SomeBuffer Immutable
1111
type MutableBuffer = SomeBuffer Mutable

GHCJS/Foreign.hs

Lines changed: 21 additions & 21 deletions
Original file line numberDiff line numberDiff line change
@@ -3,18 +3,18 @@
33
{-# LANGUAGE DefaultSignatures #-}
44
{- | Basic interop between Haskell and JavaScript.
55
6-
The principal type here is 'JSRef', which is a lifted type that contains
7-
a JavaScript reference. The 'JSRef' type is parameterized with one phantom
6+
The principal type here is 'JSVal', which is a lifted type that contains
7+
a JavaScript reference. The 'JSVal' type is parameterized with one phantom
88
type, and GHCJS.Types defines several type synonyms for specific variants.
99
10-
The code in this module makes no assumptions about 'JSRef a' types.
10+
The code in this module makes no assumptions about 'JSVal a' types.
1111
Operations that can result in a JS exception that can kill a Haskell thread
12-
are marked unsafe (for example if the 'JSRef' contains a null or undefined
12+
are marked unsafe (for example if the 'JSVal' contains a null or undefined
1313
value). There are safe variants where the JS exception is propagated as
1414
a Haskell exception, so that it can be handled on the Haskell side.
1515
1616
For more specific types, like 'JSArray' or 'JSBool', the code assumes that
17-
the contents of the 'JSRef' actually is a JavaScript array or bool value.
17+
the contents of the 'JSVal' actually is a JavaScript array or bool value.
1818
If it contains an unexpected value, the code can result in exceptions that
1919
kill the Haskell thread, even for functions not marked unsafe.
2020
@@ -70,7 +70,7 @@ module GHCJS.Foreign ( jsTrue
7070
, jsTypeOf, JSType(..)
7171
, jsonTypeOf, JSONType(..)
7272
{- , wrapBuffer, wrapMutableBuffer
73-
, byteArrayJSRef, mutableByteArrayJSRef
73+
, byteArrayJSVal, mutableByteArrayJSVal
7474
, bufferByteString, byteArrayByteString
7575
, unsafeMutableByteArrayByteString -}
7676
) where
@@ -88,14 +88,14 @@ import qualified Data.Text as T
8888
class ToJSString a where
8989
toJSString :: a -> JSString
9090

91-
-- toJSString = ptoJSRef
91+
-- toJSString = ptoJSVal
9292

9393

9494
class FromJSString a where
9595
fromJSString :: JSString -> a
9696

97-
-- default PFromJSRef
98-
-- fromJSString = pfromJSRef
97+
-- default PFromJSVal
98+
-- fromJSString = pfromJSVal
9999
-- {-# INLINE fromJSString #-}
100100
{-
101101
instance ToJSString [Char]
@@ -114,26 +114,26 @@ instance FromJSString JSString
114114
o is not a JS object or the property cannot be accessed
115115
-}
116116
getProp :: ToJSString a => a -- ^ the property name
117-
-> JSRef b -- ^ the object
118-
-> IO (JSRef c) -- ^ the property value
117+
-> JSVal b -- ^ the object
118+
-> IO (JSVal c) -- ^ the property value
119119
getProp p o = js_getProp (toJSString p) o
120120
{-# INLINE getProp #-}
121121
122122
{- | Read a property from a JS object. Kills the Haskell thread
123123
if o is not a JS object or the property cannot be accessed
124124
-}
125125
unsafeGetProp :: ToJSString a => a -- ^ the property name
126-
-> JSRef b -- ^ the object
127-
-> IO (JSRef c) -- ^ the property value, Nothing if the object doesn't have a property with the given name
126+
-> JSVal b -- ^ the object
127+
-> IO (JSVal c) -- ^ the property value, Nothing if the object doesn't have a property with the given name
128128
unsafeGetProp p o = js_unsafeGetProp (toJSString p) o
129129
{-# INLINE unsafeGetProp #-}
130130
131131
{- | Read a property from a JS object. Throws a JSException if
132132
o is not a JS object or the property cannot be accessed
133133
-}
134134
getPropMaybe :: ToJSString a => a -- ^ the property name
135-
-> JSRef b -- ^ the object
136-
-> IO (Maybe (JSRef c)) -- ^ the property value, Nothing if the object doesn't have a property with the given name
135+
-> JSVal b -- ^ the object
136+
-> IO (Maybe (JSVal c)) -- ^ the property value, Nothing if the object doesn't have a property with the given name
137137
getPropMaybe p o = do
138138
p' <- js_getProp (toJSString p) o
139139
if isUndefined p' then return Nothing else return (Just p')
@@ -143,8 +143,8 @@ getPropMaybe p o = do
143143
if o is not a JS object or the property cannot be accessed
144144
-}
145145
unsafeGetPropMaybe :: ToJSString a => a -- ^ the property name
146-
-> JSRef b -- ^ the object
147-
-> IO (Maybe (JSRef c)) -- ^ the property value, Nothing if the object doesn't have a property with the given name
146+
-> JSVal b -- ^ the object
147+
-> IO (Maybe (JSVal c)) -- ^ the property value, Nothing if the object doesn't have a property with the given name
148148
unsafeGetPropMaybe p o = do
149149
p' <- js_unsafeGetProp (toJSString p) o
150150
if isUndefined p' then return Nothing else return (Just p')
@@ -155,8 +155,8 @@ unsafeGetPropMaybe p o = do
155155
be set
156156
-}
157157
setProp :: ToJSString a => a -- ^ the property name
158-
-> JSRef b -- ^ the value
159-
-> JSRef c -- ^ the object
158+
-> JSVal b -- ^ the value
159+
-> JSVal c -- ^ the object
160160
-> IO ()
161161
setProp p v o = js_setProp (toJSString p) v o
162162
{-# INLINE setProp #-}
@@ -165,8 +165,8 @@ setProp p v o = js_setProp (toJSString p) v o
165165
if the property cannot be set.
166166
-}
167167
unsafeSetProp :: ToJSString a => a -- ^ the property name
168-
-> JSRef b -- ^ the value
169-
-> JSRef c -- ^ the object
168+
-> JSVal b -- ^ the value
169+
-> JSVal c -- ^ the object
170170
-> IO ()
171171
unsafeSetProp p v o = js_unsafeSetProp (toJSString p) v o
172172

0 commit comments

Comments
 (0)