Skip to content
Closed
Show file tree
Hide file tree
Changes from all commits
Commits
File filter

Filter by extension

Filter by extension

Conversations
Failed to load comments.
Loading
Jump to
Jump to file
Failed to load files.
Loading
Diff view
Diff view
6 changes: 4 additions & 2 deletions Data/JSString.hs
Original file line number Diff line number Diff line change
Expand Up @@ -167,8 +167,8 @@ import Data.Semigroup (Semigroup(..))

import Unsafe.Coerce

import GHCJS.Prim (JSVal)
import qualified GHCJS.Prim as Prim
import GHC.JS.Prim (JSVal)
import qualified GHC.JS.Prim as Prim

import Data.JSString.Internal.Type
import Data.JSString.Internal.Fusion (stream, unstream)
Expand Down Expand Up @@ -300,11 +300,13 @@ unpackCString# addr# = unstream (S.streamCString# addr#)
unstream (S.map safe (S.streamList [a]))
= singleton a #-}

#ifdef MIN_VERSION_ghcjs_prim
#if MIN_VERSION_ghcjs_prim(0,1,1)
{-# RULES "JSSTRING literal prim" [0] forall a.
unpackCString# a = JSString (Prim.unsafeUnpackJSStringUtf8# a)
#-}
#endif
#endif

-- | /O(1)/ Convert a character into a 'JSString'. Subject to fusion.
-- Performs replacement on invalid scalar values.
Expand Down
42 changes: 19 additions & 23 deletions Data/JSString/Int.hs
Original file line number Diff line number Diff line change
Expand Up @@ -16,14 +16,10 @@ import Data.Monoid

import GHC.Int
import GHC.Word
import GHC.Exts ( ByteArray#
, Int(..), Int#, Int64#
, Word(..), Word#, Word64#
, (<#), (<=#), isTrue# )

import GHC.Integer.GMP.Internals
import GHC.Exts hiding (Any)
import GHC.Num.Integer
import Unsafe.Coerce
import GHCJS.Prim
import GHC.JS.Prim

decimal :: Integral a => a -> JSString
decimal i = decimal' i
Expand Down Expand Up @@ -56,31 +52,31 @@ decimalI (I# x) = js_decI x
{-# INLINE decimalI #-}

decimalI8 :: Int8 -> JSString
decimalI8 (I8# x) = js_decI x
decimalI8 (I8# x) = js_decI (int8ToInt# x)
{-# INLINE decimalI8 #-}

decimalI16 :: Int16 -> JSString
decimalI16 (I16# x) = js_decI x
decimalI16 (I16# x) = js_decI (int16ToInt# x)
{-# INLINE decimalI16 #-}

decimalI32 :: Int32 -> JSString
decimalI32 (I32# x) = js_decI x
decimalI32 (I32# x) = js_decI (int32ToInt# x)
{-# INLINE decimalI32 #-}

decimalI64 :: Int64 -> JSString
decimalI64 (I64# x) = js_decI64 x
{-# INLINE decimalI64 #-}

decimalW8 :: Word8 -> JSString
decimalW8 (W8# x) = js_decW x
decimalW8 (W8# x) = js_decW (word8ToWord# x)
{-# INLINE decimalW8 #-}

decimalW16 :: Word16 -> JSString
decimalW16 (W16# x) = js_decW x
decimalW16 (W16# x) = js_decW (word16ToWord# x)
{-# INLINE decimalW16 #-}

decimalW32 :: Word32 -> JSString
decimalW32 (W32# x) = js_decW32 x
decimalW32 (W32# x) = js_decW32 (word32ToWord# x)
{-# INLINE decimalW32 #-}

decimalW64 :: Word64 -> JSString
Expand Down Expand Up @@ -163,23 +159,23 @@ hexI (I# x) = if isTrue# (x <# 0#)

hexI8 :: Int8 -> JSString
hexI8 (I8# x) =
if isTrue# (x <# 0#)
if isTrue# (int8ToInt# x <# 0#)
then error hexErrMsg
else js_hexI x
else js_hexI (int8ToInt# x)
{-# INLINE hexI8 #-}

hexI16 :: Int16 -> JSString
hexI16 (I16# x) =
if isTrue# (x <# 0#)
if isTrue# (int16ToInt# x <# 0#)
then error hexErrMsg
else js_hexI x
else js_hexI (int16ToInt# x)
{-# INLINE hexI16 #-}

hexI32 :: Int32 -> JSString
hexI32 (I32# x) =
if isTrue# (x <# 0#)
if isTrue# (int32ToInt# x <# 0#)
then error hexErrMsg
else js_hexI x
else js_hexI (int32ToInt# x)
{-# INLINE hexI32 #-}

hexI64 :: Int64 -> JSString
Expand All @@ -190,15 +186,15 @@ hexI64 i@(I64# x) =
{-# INLINE hexI64 #-}

hexW :: Word -> JSString
hexW (W# x) = js_hexW32 x
hexW (W# x) = js_hexW x
{-# INLINE hexW #-}

hexW8 :: Word8 -> JSString
hexW8 (W8# x) = js_hexW x
hexW8 (W8# x) = js_hexW (word8ToWord# x)
{-# INLINE hexW8 #-}

hexW16 :: Word16 -> JSString
hexW16 (W16# x) = js_hexW x
hexW16 (W16# x) = js_hexW (word16ToWord# x)
{-# INLINE hexW16 #-}

hexW32 :: Word32 -> JSString
Expand Down Expand Up @@ -246,7 +242,7 @@ foreign import javascript unsafe
js_hexW :: Word# -> JSString
foreign import javascript unsafe
"(($1>=0)?$1:($1+4294967296)).toString(16)"
js_hexW32 :: Word# -> JSString
js_hexW32 :: Word32# -> JSString
foreign import javascript unsafe
"h$jsstringHexW64($1_1, $1_2)"
js_hexW64 :: Word64# -> JSString
Expand Down
2 changes: 1 addition & 1 deletion Data/JSString/Internal/Fusion.hs
Original file line number Diff line number Diff line change
Expand Up @@ -43,7 +43,7 @@ import qualified Data.JSString.Internal.Fusion.Common as S

import System.IO.Unsafe

import GHCJS.Prim
import GHC.JS.Prim

default (Int)

Expand Down
2 changes: 1 addition & 1 deletion Data/JSString/Internal/Type.hs
Original file line number Diff line number Diff line change
Expand Up @@ -36,7 +36,7 @@ import Data.Int (Int32, Int64)
import Data.Typeable (Typeable)
import GHC.Exts (Char(..), ord#, andI#, (/=#), isTrue#)

import GHCJS.Prim (JSVal)
import GHC.JS.Prim (JSVal)

import GHCJS.Internal.Types

Expand Down
2 changes: 1 addition & 1 deletion Data/JSString/Raw.hs
Original file line number Diff line number Diff line change
Expand Up @@ -25,7 +25,7 @@ import GHC.Exts
, (+#), (-#), (>=#), (<#)
, isTrue#, chr#)
import qualified GHC.Exts as Exts
import GHCJS.Prim (JSVal)
import GHC.JS.Prim (JSVal)

import Unsafe.Coerce

Expand Down
2 changes: 1 addition & 1 deletion Data/JSString/RegExp.hs
Original file line number Diff line number Diff line change
Expand Up @@ -18,7 +18,7 @@ module Data.JSString.RegExp ( RegExp
, execNext
) where

import GHCJS.Prim
import GHC.JS.Prim
import GHC.Exts (Any, Int#, Int(..))

import Unsafe.Coerce (unsafeCoerce)
Expand Down
8 changes: 4 additions & 4 deletions Data/JSString/Text.hs
Original file line number Diff line number Diff line change
Expand Up @@ -15,7 +15,7 @@ module Data.JSString.Text
, lazyTextFromJSVal
) where

import GHCJS.Prim
import GHC.JS.Prim

import GHC.Exts (ByteArray#, Int(..), Int#, Any)

Expand All @@ -31,15 +31,15 @@ import Data.JSString.Internal.Type
import Unsafe.Coerce

textToJSString :: T.Text -> JSString
textToJSString (T.Text (A.Array ba) (I# offset) (I# length)) =
textToJSString (T.Text (A.ByteArray ba) (I# offset) (I# length)) =
js_toString ba offset length
{-# INLINE textToJSString #-}

textFromJSString :: JSString -> T.Text
textFromJSString j =
case js_fromString j of
(# _ , 0# #) -> T.empty
(# ba, length #) -> T.Text (A.Array ba) 0 (I# length)
(# ba, length #) -> T.Text (A.ByteArray ba) 0 (I# length)
{-# INLINE textFromJSString #-}

lazyTextToJSString :: TL.Text -> JSString
Expand All @@ -54,7 +54,7 @@ lazyTextFromJSString = TL.fromStrict . textFromJSString
textFromJSVal :: JSVal -> T.Text
textFromJSVal j = case js_fromString' j of
(# _, 0# #) -> T.empty
(# ba, length #) -> T.Text (A.Array ba) 0 (I# length)
(# ba, length #) -> T.Text (A.ByteArray ba) 0 (I# length)
{-# INLINE textFromJSVal #-}

-- | returns the empty Text if not a string
Expand Down
2 changes: 1 addition & 1 deletion GHCJS/Buffer.hs
Original file line number Diff line number Diff line change
Expand Up @@ -41,7 +41,7 @@ module GHCJS.Buffer
import GHC.Exts (ByteArray#, MutableByteArray#, Addr#, Ptr(..), Any)

import GHCJS.Buffer.Types
import GHCJS.Prim
import GHC.JS.Prim
import GHCJS.Internal.Types

import Data.Int
Expand Down
2 changes: 1 addition & 1 deletion GHCJS/Concurrent.hs
Original file line number Diff line number Diff line change
Expand Up @@ -33,7 +33,7 @@ module GHCJS.Concurrent ( isThreadSynchronous
, synchronously
) where

import GHCJS.Prim
import GHC.JS.Prim

import Control.Applicative
import Control.Concurrent
Expand Down
2 changes: 1 addition & 1 deletion GHCJS/Foreign/Callback.hs
Original file line number Diff line number Diff line change
Expand Up @@ -25,7 +25,7 @@ import GHCJS.Concurrent
import GHCJS.Marshal
import GHCJS.Marshal.Pure
import GHCJS.Foreign.Callback.Internal
import GHCJS.Prim
import GHC.JS.Prim
import GHCJS.Types

import qualified GHC.Exts as Exts
Expand Down
2 changes: 1 addition & 1 deletion GHCJS/Foreign/Export.hs
Original file line number Diff line number Diff line change
Expand Up @@ -27,7 +27,7 @@ import Data.Word
import Unsafe.Coerce
import qualified GHC.Exts as Exts

import GHCJS.Prim
import GHC.JS.Prim
import GHCJS.Types

newtype Export a = Export JSVal
Expand Down
2 changes: 1 addition & 1 deletion GHCJS/Foreign/Internal.hs
Original file line number Diff line number Diff line change
Expand Up @@ -80,7 +80,7 @@ module GHCJS.Foreign.Internal ( JSType(..)
) where

import GHCJS.Types
import qualified GHCJS.Prim as Prim
import qualified GHC.JS.Prim as Prim

import GHC.Prim
import GHC.Exts
Expand Down
2 changes: 1 addition & 1 deletion GHCJS/Internal/Types.hs
Original file line number Diff line number Diff line change
Expand Up @@ -13,7 +13,7 @@ import Unsafe.Coerce

import Control.DeepSeq

import GHCJS.Prim (JSVal)
import GHC.JS.Prim (JSVal)

instance NFData JSVal where
rnf x = x `seq` ()
Expand Down
2 changes: 1 addition & 1 deletion GHCJS/Marshal/Internal.hs
Original file line number Diff line number Diff line change
Expand Up @@ -23,7 +23,7 @@ import Data.Typeable

import GHC.Generics

import qualified GHCJS.Prim as Prim
import qualified GHC.JS.Prim as Prim
import qualified GHCJS.Foreign as F
import GHCJS.Types

Expand Down
28 changes: 15 additions & 13 deletions GHCJS/Marshal/Pure.hs
Original file line number Diff line number Diff line change
Expand Up @@ -42,7 +42,7 @@ import GHC.Float
import GHC.Prim

import GHCJS.Types
import qualified GHCJS.Prim as Prim
import qualified GHC.JS.Prim as Prim
import GHCJS.Foreign.Internal
import GHCJS.Marshal.Internal

Expand Down Expand Up @@ -77,15 +77,15 @@ instance PFromJSVal Int8 where pFromJSVal x = I8# (jsvalToInt8 x)
{-# INLINE pFromJSVal #-}
instance PFromJSVal Int16 where pFromJSVal x = I16# (jsvalToInt16 x)
{-# INLINE pFromJSVal #-}
instance PFromJSVal Int32 where pFromJSVal x = I32# (jsvalToInt x)
instance PFromJSVal Int32 where pFromJSVal x = I32# (jsvalToInt32 x)
{-# INLINE pFromJSVal #-}
instance PFromJSVal Word where pFromJSVal x = W# (jsvalToWord x)
{-# INLINE pFromJSVal #-}
instance PFromJSVal Word8 where pFromJSVal x = W8# (jsvalToWord8 x)
{-# INLINE pFromJSVal #-}
instance PFromJSVal Word16 where pFromJSVal x = W16# (jsvalToWord16 x)
{-# INLINE pFromJSVal #-}
instance PFromJSVal Word32 where pFromJSVal x = W32# (jsvalToWord x)
instance PFromJSVal Word32 where pFromJSVal x = W32# (jsvalToWord32 x)
{-# INLINE pFromJSVal #-}
instance PFromJSVal Float where pFromJSVal x = F# (jsvalToFloat x)
{-# INLINE pFromJSVal #-}
Expand All @@ -112,19 +112,19 @@ instance PToJSVal Bool where pToJSVal True = jsTrue
{-# INLINE pToJSVal #-}
instance PToJSVal Int where pToJSVal (I# x) = intToJSVal x
{-# INLINE pToJSVal #-}
instance PToJSVal Int8 where pToJSVal (I8# x) = intToJSVal x
instance PToJSVal Int8 where pToJSVal (I8# x) = intToJSVal (int8ToInt# x)
{-# INLINE pToJSVal #-}
instance PToJSVal Int16 where pToJSVal (I16# x) = intToJSVal x
instance PToJSVal Int16 where pToJSVal (I16# x) = intToJSVal (int16ToInt# x)
{-# INLINE pToJSVal #-}
instance PToJSVal Int32 where pToJSVal (I32# x) = intToJSVal x
instance PToJSVal Int32 where pToJSVal (I32# x) = intToJSVal (int32ToInt# x)
{-# INLINE pToJSVal #-}
instance PToJSVal Word where pToJSVal (W# x) = wordToJSVal x
{-# INLINE pToJSVal #-}
instance PToJSVal Word8 where pToJSVal (W8# x) = wordToJSVal x
instance PToJSVal Word8 where pToJSVal (W8# x) = wordToJSVal (word8ToWord# x)
{-# INLINE pToJSVal #-}
instance PToJSVal Word16 where pToJSVal (W16# x) = wordToJSVal x
instance PToJSVal Word16 where pToJSVal (W16# x) = wordToJSVal (word16ToWord# x)
{-# INLINE pToJSVal #-}
instance PToJSVal Word32 where pToJSVal (W32# x) = wordToJSVal x
instance PToJSVal Word32 where pToJSVal (W32# x) = wordToJSVal (word32ToWord# x)
{-# INLINE pToJSVal #-}
instance PToJSVal Float where pToJSVal (F# x) = floatToJSVal x
{-# INLINE pToJSVal #-}
Expand All @@ -137,11 +137,13 @@ instance PToJSVal a => PToJSVal (Maybe a) where
{-# INLINE pToJSVal #-}

foreign import javascript unsafe "$r = $1|0;" jsvalToWord :: JSVal -> Word#
foreign import javascript unsafe "$r = $1&0xff;" jsvalToWord8 :: JSVal -> Word#
foreign import javascript unsafe "$r = $1&0xffff;" jsvalToWord16 :: JSVal -> Word#
foreign import javascript unsafe "$r = $1&0xff;" jsvalToWord8 :: JSVal -> Word8#
foreign import javascript unsafe "$r = $1&0xffff;" jsvalToWord16 :: JSVal -> Word16#
foreign import javascript unsafe "$r = $1|0;" jsvalToWord32 :: JSVal -> Word32#
foreign import javascript unsafe "$r = $1|0;" jsvalToInt :: JSVal -> Int#
foreign import javascript unsafe "$r = $1<<24>>24;" jsvalToInt8 :: JSVal -> Int#
foreign import javascript unsafe "$r = $1<<16>>16;" jsvalToInt16 :: JSVal -> Int#
foreign import javascript unsafe "$r = $1<<24>>24;" jsvalToInt8 :: JSVal -> Int8#
foreign import javascript unsafe "$r = $1<<16>>16;" jsvalToInt16 :: JSVal -> Int16#
foreign import javascript unsafe "$r = $1|0;" jsvalToInt32 :: JSVal -> Int32#
foreign import javascript unsafe "$r = +$1;" jsvalToFloat :: JSVal -> Float#
foreign import javascript unsafe "$r = +$1;" jsvalToDouble :: JSVal -> Double#
foreign import javascript unsafe "$r = $1&0x7fffffff;" jsvalToChar :: JSVal -> Char#
Expand Down
2 changes: 1 addition & 1 deletion GHCJS/Nullable.hs
Original file line number Diff line number Diff line change
Expand Up @@ -3,7 +3,7 @@ module GHCJS.Nullable ( Nullable(..)
, maybeToNullable
) where

import GHCJS.Prim (JSVal(..))
import GHC.JS.Prim (JSVal(..))
import GHCJS.Marshal.Pure (PToJSVal(..), PFromJSVal(..))

newtype Nullable a = Nullable JSVal
Expand Down
2 changes: 1 addition & 1 deletion GHCJS/Types.hs
Original file line number Diff line number Diff line change
Expand Up @@ -24,7 +24,7 @@ module GHCJS.Types ( JSVal
import Data.JSString.Internal.Type (JSString)
import GHCJS.Internal.Types

import GHCJS.Prim
import GHC.JS.Prim

import GHC.Int
import GHC.Types
Expand Down
2 changes: 1 addition & 1 deletion JavaScript/Array.hs
Original file line number Diff line number Diff line change
Expand Up @@ -33,7 +33,7 @@ module JavaScript.Array

import Prelude hiding (length, drop, read, take, reverse, null)

import qualified GHCJS.Prim as Prim
import qualified GHC.JS.Prim as Prim
import GHCJS.Types

import JavaScript.Array.Internal (JSArray(..))
Expand Down
2 changes: 1 addition & 1 deletion JavaScript/Array/Internal.hs
Original file line number Diff line number Diff line change
Expand Up @@ -16,7 +16,7 @@ import qualified GHC.Exts as Exts
import GHC.Exts (State#)

import GHCJS.Internal.Types
import qualified GHCJS.Prim as Prim
import qualified GHC.JS.Prim as Prim
import GHCJS.Types

newtype SomeJSArray (m :: MutabilityType s) = SomeJSArray JSVal
Expand Down
2 changes: 1 addition & 1 deletion JavaScript/Cast.hs
Original file line number Diff line number Diff line change
Expand Up @@ -5,7 +5,7 @@ module JavaScript.Cast ( Cast(..)
, unsafeCast
) where

import GHCJS.Prim
import GHC.JS.Prim

cast :: forall a. Cast a => JSVal -> Maybe a
cast x | js_checkCast x (instanceRef (undefined :: a)) = Just (unsafeWrap x)
Expand Down
2 changes: 1 addition & 1 deletion JavaScript/JSON/Types/Generic.hs
Original file line number Diff line number Diff line change
Expand Up @@ -28,7 +28,7 @@ import qualified Data.JSString as JSS
import qualified JavaScript.JSON.Types.Internal as I
import qualified JavaScript.Array as JSA
import qualified JavaScript.Array.ST as JSAST
import Data.Bits
import Data.Bits hiding (And)

import Data.DList (DList, toList, empty)

Expand Down
Loading