{-# LANGUAGE MagicHash, BangPatterns, UnboxedTuples, TypeFamilies,
ForeignFunctionInterface, JavaScriptFFI, UnliftedFFITypes,
GHCForeignImportPrim, CPP
#-}
module Data.JSString ( JSString
, pack
, unpack, unpack'
, singleton
, empty
, cons
, snoc
, append
, uncons
, unsnoc
, head
, last
, tail
, init
, null
, length
, compareLength
, map
, intercalate
, intersperse
, transpose
, reverse
, replace
, toCaseFold
, toLower
, toUpper
, toTitle
, justifyLeft
, justifyRight
, center
, foldl
, foldl'
, foldl1
, foldl1'
, foldr
, foldr1
, concat
, concatMap
, any
, all
, maximum
, minimum
, scanl
, scanl1
, scanr
, scanr1
, mapAccumL
, mapAccumR
, replicate
, unfoldr
, unfoldrN
, take
, takeEnd
, drop
, dropEnd
, takeWhile
, takeWhileEnd
, dropWhile
, dropWhileEnd
, dropAround
, strip
, stripStart
, stripEnd
, splitAt
, breakOn
, breakOnEnd
, break
, span
, group
, group'
, groupBy
, inits
, tails
, splitOn, splitOn'
, split
, chunksOf, chunksOf'
, lines, lines'
, words, words'
, unlines
, unwords
, isPrefixOf
, isSuffixOf
, isInfixOf
, stripPrefix
, stripSuffix
, commonPrefixes
, filter
, breakOnAll, breakOnAll'
, find
, partition
, index
, findIndex
, count
, zip
, zipWith
) where
import Prelude
( Char, Bool(..), Int, Maybe(..), String, Eq(..), Ord(..), Ordering(..), (++)
, Read(..), Show(..), (&&), (||), (+), (-), (.), ($), ($!), (>>)
, not, seq, return, otherwise, quot)
import qualified Prelude as P
import Control.DeepSeq (NFData(..))
import Data.Binary (Binary(..))
import Data.Char (isSpace)
import qualified Data.List as L
import Data.Data
import GHC.Exts
( Int#, (+#), (-#), (>=#), (>#), isTrue#, chr#, Char(..)
, Int(..), Addr#, tagToEnum#)
import qualified GHC.Exts as Exts
import qualified GHC.CString as GHC
import qualified GHC.Base as GHC
#if MIN_VERSION_base(4,9,0)
import Data.Semigroup (Semigroup(..))
#endif
import Unsafe.Coerce
import GHCJS.Prim (JSVal)
import qualified GHCJS.Prim as Prim
import Data.JSString.Internal.Type
import Data.JSString.Internal.Fusion (stream, unstream)
import qualified Data.JSString.Internal.Fusion as S
import qualified Data.JSString.Internal.Fusion.Common as S
import Text.Printf (PrintfArg(..), formatString)
getJSVal :: JSString -> JSVal
getJSVal (JSString x) = x
{-# INLINE getJSVal #-}
instance Exts.IsString JSString where
fromString = pack
instance Exts.IsList JSString where
type Item JSString = Char
fromList = pack
toList = unpack
#if MIN_VERSION_base(4,9,0)
instance Semigroup JSString where
(<>) = append
#endif
instance P.Monoid JSString where
mempty = empty
#if MIN_VERSION_base(4,9,0)
mappend = (<>)
#else
mappend = append
#endif
mconcat = concat
instance Eq JSString where
x == y = js_eq x y
#if MIN_VERSION_base(4,7,0)
instance PrintfArg JSString where
formatArg txt = formatString $ unpack txt
#endif
instance Ord JSString where
compare x y = compareStrings x y
equals :: JSString -> JSString -> Bool
equals x y = js_eq x y
{-# INLINE equals #-}
compareStrings :: JSString -> JSString -> Ordering
compareStrings x y = tagToEnum# (js_compare x y +# 1#)
{-# INLINE compareStrings #-}
instance Data JSString where
gfoldl f z txt = z pack `f` (unpack txt)
toConstr _ = packConstr
gunfold k z c = case constrIndex c of
1 -> k (z pack)
_ -> P.error "gunfold"
dataTypeOf _ = jsstringDataType
packConstr :: Constr
packConstr = mkConstr jsstringDataType "pack" [] Prefix
jsstringDataType :: DataType
jsstringDataType = mkDataType "Data.JSString.JSString" [packConstr]
instance Show JSString where
showsPrec p ps r = showsPrec p (unpack ps) r
instance Read JSString where
readsPrec p str = [(pack x,y) | (x,y) <- readsPrec p str]
pack :: String -> JSString
pack x = rnf x `seq` js_pack (unsafeCoerce x)
{-# INLINE [1] pack #-}
{-# RULES
"JSSTRING pack -> fused" [~1] forall x.
pack x = unstream (S.map safe (S.streamList x))
"JSSTRING pack -> unfused" [1] forall x.
unstream (S.map safe (S.streamList x)) = pack x
#-}
unpack :: JSString -> String
unpack = S.unstreamList . stream
{-# INLINE [1] unpack #-}
unpack' :: JSString -> String
unpack' x = unsafeCoerce (js_unpack x)
{-# INLINE unpack' #-}
unpackCString# :: Addr# -> JSString
unpackCString# addr# = unstream (S.streamCString# addr#)
{-# NOINLINE unpackCString# #-}
{-# RULES "JSSTRING literal" forall a.
unstream (S.map safe (S.streamList (GHC.unpackCString# a)))
= unpackCString# a #-}
{-# RULES "JSSTRING literal UTF8" forall a.
unstream (S.map safe (S.streamList (GHC.unpackCStringUtf8# a)))
= unpackCString# a #-}
{-# RULES "JSSTRING empty literal"
unstream (S.map safe (S.streamList []))
= empty_ #-}
{-# RULES "JSSTRING singleton literal" forall a.
unstream (S.map safe (S.streamList [a]))
= singleton a #-}
#if MIN_VERSION_ghcjs_prim(0,1,1)
{-# RULES "JSSTRING literal prim" [0] forall a.
unpackCString# a = JSString (Prim.unsafeUnpackJSStringUtf8# a)
#-}
#endif
singleton :: Char -> JSString
singleton c = js_singleton c
{-# INLINE [1] singleton #-}
{-# RULES
"JSSTRING singleton -> fused" [~1] forall a.
singleton a = unstream (S.singleton (safe a))
"JSSTRING singleton -> unfused" [1] forall a.
unstream (S.singleton (safe a)) = singleton a
#-}
cons :: Char -> JSString -> JSString
cons c x = js_cons c x
{-# INLINE [1] cons #-}
{-# RULES
"JSSTRING cons -> fused" [~1] forall c x.
cons c x = unstream (S.cons (safe c) (stream x))
"JSSTRING cons -> unfused" [1] forall c x.
unstream (S.cons (safe c) (stream x)) = cons c x
#-}
infixr 5 `cons`
snoc :: JSString -> Char -> JSString
snoc x c = js_snoc x c
{-# INLINE [1] snoc #-}
{-# RULES
"JSSTRING snoc -> fused" [~1] forall x c.
snoc x c = unstream (S.snoc (stream x) (safe c))
"JSSTRING snoc -> unfused" [1] forall x c.
unstream (S.snoc (stream x) (safe c)) = snoc x c
#-}
append :: JSString -> JSString -> JSString
append x y = js_append x y
{-# INLINE [1] append #-}
{-# RULES
"JSSTRING append -> fused" [~1] forall x1 x2.
append x1 x2 = unstream (S.append (stream x1) (stream x2))
"JSSTRING append -> unfused" [1] forall x1 x2.
unstream (S.append (stream x1) (stream x2)) = append x1 x2
#-}
head :: JSString -> Char
head x = case js_head x of
-1# -> emptyError "head"
ch -> C# (chr# ch)
{-# INLINE [1] head #-}
{-# RULES
"JSSTRING head -> fused" [~1] forall x.
head x = S.head (stream x)
"JSSTRING head -> unfused" [1] forall x.
S.head (stream x) = head x
#-}
uncons :: JSString -> Maybe (Char, JSString)
uncons x = case js_uncons x of
(# -1#, _ #) -> Nothing
(# cp, t #) -> Just (C# (chr# cp), t)
{-# INLINE [1] uncons #-}
unsnoc :: JSString -> Maybe (JSString, Char)
unsnoc x = case js_unsnoc x of
(# -1#, _ #) -> Nothing
(# cp, t #) -> Just (t, C# (chr# cp))
{-# INLINE [1] unsnoc #-}
second :: (b -> c) -> (a,b) -> (a,c)
second f (a, b) = (a, f b)
last :: JSString -> Char
last x = case js_last x of
-1# -> emptyError "last"
c -> (C# (chr# c))
{-# INLINE [1] last #-}
{-# RULES
"JSSTRING last -> fused" [~1] forall x.
last x = S.last (stream x)
"JSSTRING last -> unfused" [1] forall x.
S.last (stream x) = last x
#-}
tail :: JSString -> JSString
tail x =
let r = js_tail x
in if js_isNull r
then emptyError "tail"
else JSString r
{-# INLINE [1] tail #-}
{-# RULES
"JSSTRING tail -> fused" [~1] forall x.
tail x = unstream (S.tail (stream x))
"JSSTRING tail -> unfused" [1] forall x.
unstream (S.tail (stream x)) = tail x
#-}
init :: JSString -> JSString
init x =
let r = js_init x
in if js_isNull r
then emptyError "init"
else JSString r
{-# INLINE [1] init #-}
{-# RULES
"JSSTRING init -> fused" [~1] forall t.
init t = unstream (S.init (stream t))
"JSSTRING init -> unfused" [1] forall t.
unstream (S.init (stream t)) = init t
#-}
null :: JSString -> Bool
null x = js_null x
{-# INLINE [1] null #-}
{-# RULES
"JSSTRING null -> fused" [~1] forall t.
null t = S.null (stream t)
"JSSTRING null -> unfused" [1] forall t.
S.null (stream t) = null t
#-}
isSingleton :: JSString -> Bool
isSingleton x = js_isSingleton x
{-# INLINE [1] isSingleton #-}
{-# RULES
"JSSTRING isSingleton -> fused" [~1] forall x.
isSingleton x = S.isSingleton (stream x)
"JSSTRING isSingleton -> unfused" [1] forall x.
S.isSingleton (stream x) = isSingleton x
#-}
length :: JSString -> Int
length x = S.length (stream x)
{-# INLINE [0] length #-}
compareLength :: JSString -> Int -> Ordering
compareLength t n = S.compareLengthI (stream t) n
{-# INLINE [1] compareLength #-}
{-# RULES
"JSSTRING compareN/length -> compareLength" [~1] forall t n.
compare (length t) n = compareLength t n
#-}
{-# RULES
"JSSTRING ==N/length -> compareLength/==EQ" [~1] forall t n.
GHC.eqInt (length t) n = compareLength t n == EQ
#-}
{-# RULES
"JSSTRING /=N/length -> compareLength//=EQ" [~1] forall t n.
GHC.neInt (length t) n = compareLength t n /= EQ
#-}
{-# RULES
"JSSTRING <N/length -> compareLength/==LT" [~1] forall t n.
GHC.ltInt (length t) n = compareLength t n == LT
#-}
{-# RULES
"JSSTRING <=N/length -> compareLength//=GT" [~1] forall t n.
GHC.leInt (length t) n = compareLength t n /= GT
#-}
{-# RULES
"JSSTRING >N/length -> compareLength/==GT" [~1] forall t n.
GHC.gtInt (length t) n = compareLength t n == GT
#-}
{-# RULES
"JSSTRING >=N/length -> compareLength//=LT" [~1] forall t n.
GHC.geInt (length t) n = compareLength t n /= LT
#-}
map :: (Char -> Char) -> JSString -> JSString
map f t = unstream (S.map (safe . f) (stream t))
{-# INLINE [1] map #-}
intercalate :: JSString -> [JSString] -> JSString
intercalate i xs = rnf xs `seq` js_intercalate i (unsafeCoerce xs)
{-# INLINE [1] intercalate #-}
intersperse :: Char -> JSString -> JSString
intersperse c x = js_intersperse c x
{-# INLINE [1] intersperse #-}
{-# RULES
"JSSTRING intersperse -> fused" [~1] forall c x.
intersperse c x = unstream (S.intersperse (safe c) (stream x))
"JSSTRING intersperse -> unfused" [1] forall c x.
unstream (S.intersperse (safe c) (stream x)) = intersperse c x
#-}
reverse :: JSString -> JSString
reverse x = js_reverse x
{-# INLINE [1] reverse #-}
{-# RULES
"JSSTRING reverse -> fused" [~1] forall x.
reverse x = S.reverse (stream x)
"JSSTRING reverse -> unfused" [1] forall x.
S.reverse (stream x) = reverse x
#-}
replace :: JSString
-> JSString
-> JSString
-> JSString
replace needle replacement haystack
| js_null needle = emptyError "replace"
| otherwise = js_replace needle replacement haystack
{-# INLINE replace #-}
toCaseFold :: JSString -> JSString
toCaseFold t = unstream (S.toCaseFold (stream t))
{-# INLINE toCaseFold #-}
toLower :: JSString -> JSString
toLower x = js_toLower x
{-# INLINE [1] toLower #-}
{-# RULES
"JSSTRING toLower -> fused" [~1] forall x.
toLower x = unstream (S.toLower (stream x))
"JSSTRING toLower -> unfused" [1] forall x.
unstream (S.toLower (stream x)) = toLower x
#-}
toUpper :: JSString -> JSString
toUpper x = js_toUpper x
{-# INLINE [1] toUpper #-}
{-# RULES
"JSSTRING toUpper -> fused" [~1] forall x.
toUpper x = unstream (S.toUpper(stream x))
"JSSTRING toUpper -> unfused" [1] forall x.
unstream (S.toUpper (stream x)) = toUpper x
#-}
toTitle :: JSString -> JSString
toTitle t = unstream (S.toTitle (stream t))
{-# INLINE toTitle #-}
justifyLeft :: Int -> Char -> JSString -> JSString
justifyLeft k c t
| len >= k = t
| otherwise = t `append` replicateChar (k-len) c
where len = length t
{-# INLINE [1] justifyLeft #-}
{-# RULES
"JSSTRING justifyLeft -> fused" [~1] forall k c t.
justifyLeft k c t = unstream (S.justifyLeftI k c (stream t))
"JSSTRING justifyLeft -> unfused" [1] forall k c t.
unstream (S.justifyLeftI k c (stream t)) = justifyLeft k c t
#-}
justifyRight :: Int -> Char -> JSString -> JSString
justifyRight k c t
| len >= k = t
| otherwise = replicateChar (k-len) c `append` t
where len = length t
{-# INLINE justifyRight #-}
center :: Int -> Char -> JSString -> JSString
center k c t
| len >= k = t
| otherwise = replicateChar l c `append` t `append` replicateChar r c
where len = length t
d = k - len
r = d `quot` 2
l = d - r
{-# INLINE center #-}
transpose :: [JSString] -> [JSString]
transpose ts = P.map pack (L.transpose (P.map unpack ts))
foldl :: (a -> Char -> a) -> a -> JSString -> a
foldl f z t = S.foldl f z (stream t)
{-# INLINE foldl #-}
foldl' :: (a -> Char -> a) -> a -> JSString -> a
foldl' f z t = S.foldl' f z (stream t)
{-# INLINE foldl' #-}
foldl1 :: (Char -> Char -> Char) -> JSString -> Char
foldl1 f t = S.foldl1 f (stream t)
{-# INLINE foldl1 #-}
foldl1' :: (Char -> Char -> Char) -> JSString -> Char
foldl1' f t = S.foldl1' f (stream t)
{-# INLINE foldl1' #-}
foldr :: (Char -> a -> a) -> a -> JSString -> a
foldr f z t = S.foldr f z (stream t)
{-# INLINE foldr #-}
foldr1 :: (Char -> Char -> Char) -> JSString -> Char
foldr1 f t = S.foldr1 f (stream t)
{-# INLINE foldr1 #-}
concat :: [JSString] -> JSString
concat xs = rnf xs `seq` js_concat (unsafeCoerce xs)
concatMap :: (Char -> JSString) -> JSString -> JSString
concatMap f = concat . foldr ((:) . f) []
{-# INLINE concatMap #-}
any :: (Char -> Bool) -> JSString -> Bool
any p t = S.any p (stream t)
{-# INLINE any #-}
all :: (Char -> Bool) -> JSString -> Bool
all p t = S.all p (stream t)
{-# INLINE all #-}
maximum :: JSString -> Char
maximum t = S.maximum (stream t)
{-# INLINE maximum #-}
minimum :: JSString -> Char
minimum t = S.minimum (stream t)
{-# INLINE minimum #-}
scanl :: (Char -> Char -> Char) -> Char -> JSString -> JSString
scanl f z t = unstream (S.scanl g z (stream t))
where g a b = safe (f a b)
{-# INLINE scanl #-}
scanl1 :: (Char -> Char -> Char) -> JSString -> JSString
scanl1 f x = case uncons x of
Just (h, t) -> scanl f h t
Nothing -> empty
{-# INLINE scanl1 #-}
scanr :: (Char -> Char -> Char) -> Char -> JSString -> JSString
scanr f z = S.reverse . S.reverseScanr g z . S.reverseStream
where g a b = safe (f a b)
{-# INLINE scanr #-}
scanr1 :: (Char -> Char -> Char) -> JSString -> JSString
scanr1 f t | null t = empty
| otherwise = scanr f (last t) (init t)
{-# INLINE scanr1 #-}
mapAccumL :: (a -> Char -> (a,Char)) -> a -> JSString -> (a, JSString)
mapAccumL f z0 = S.mapAccumL g z0 . stream
where g a b = second safe (f a b)
{-# INLINE mapAccumL #-}
mapAccumR :: (a -> Char -> (a,Char)) -> a -> JSString -> (a, JSString)
mapAccumR f z0 = second reverse . S.mapAccumL g z0 . S.reverseStream
where g a b = second safe (f a b)
{-# INLINE mapAccumR #-}
replicate :: Int -> JSString -> JSString
replicate (I# n) t = js_replicate n t
{-# INLINE [1] replicate #-}
{-# RULES
"JSSTRING replicate/singleton -> replicateChar" [~1] forall n c.
replicate n (singleton c) = replicateChar n c
#-}
replicateChar :: Int -> Char -> JSString
replicateChar n c = js_replicateChar n c
{-# INLINE [1] replicateChar #-}
{-# RULES
"JSSTRING replicateChar -> fused" [~1] forall n c.
replicateChar n c = unstream (S.replicateCharI n (safe c))
"JSSTRING replicateChar -> unfused" [1] forall n c.
unstream (S.replicateCharI n (safe c)) = replicateChar n c
#-}
unfoldr :: (a -> Maybe (Char,a)) -> a -> JSString
unfoldr f s = unstream (S.unfoldr (firstf safe . f) s)
{-# INLINE unfoldr #-}
unfoldrN :: Int -> (a -> Maybe (Char,a)) -> a -> JSString
unfoldrN n f s = unstream (S.unfoldrN n (firstf safe . f) s)
{-# INLINE unfoldrN #-}
take :: Int -> JSString -> JSString
take (I# n) t = js_take n t
{-# INLINE [1] take #-}
{-# RULES
"JSSTRING take -> fused" [~1] forall n t.
take n t = unstream (S.take n (stream t))
"JSSTRING take -> unfused" [1] forall n t.
unstream (S.take n (stream t)) = take n t
#-}
takeEnd :: Int -> JSString -> JSString
takeEnd (I# n) x = js_takeEnd n x
drop :: Int -> JSString -> JSString
drop (I# n) x = js_drop n x
{-# INLINE [1] drop #-}
{-# RULES
"JSSTRING drop -> fused" [~1] forall n t.
drop n t = unstream (S.drop n (stream t))
"JSSTRING drop -> unfused" [1] forall n t.
unstream (S.drop n (stream t)) = drop n t
#-}
dropEnd :: Int -> JSString -> JSString
dropEnd n x = js_dropEnd n x
takeWhile :: (Char -> Bool) -> JSString -> JSString
takeWhile p x = loop 0# (js_length x)
where loop i l | isTrue# (i >=# l) = x
| otherwise =
case js_index i x of
c | p (C# (chr# c)) -> loop (i +# charWidth c) l
_ -> js_substr 0# i x
{-# INLINE [1] takeWhile #-}
{-# RULES
"TEXT takeWhile -> fused" [~1] forall p t.
takeWhile p t = unstream (S.takeWhile p (stream t))
"TEXT takeWhile -> unfused" [1] forall p t.
unstream (S.takeWhile p (stream t)) = takeWhile p t
#-}
takeWhileEnd :: (Char -> Bool) -> JSString -> JSString
takeWhileEnd p x = loop (js_length x -# 1#)
where loop -1# = empty
loop i = case js_uncheckedIndexR i x of
c | p (C# (chr# c)) -> loop (i -# charWidth c)
_ -> js_substr1 (i +# 1#) x
{-# INLINE takeWhileEnd #-}
dropWhile :: (Char -> Bool) -> JSString -> JSString
dropWhile p x = loop 0# (js_length x)
where loop i l | isTrue# (i >=# l) = empty
| otherwise =
case js_uncheckedIndex i x of
c | p (C# (chr# c)) -> loop (i +# charWidth c) l
_ -> js_substr1 i x
{-# INLINE [1] dropWhile #-}
{-# RULES
"TEXT dropWhile -> fused" [~1] forall p t.
dropWhile p t = unstream (S.dropWhile p (stream t))
"TEXT dropWhile -> unfused" [1] forall p t.
unstream (S.dropWhile p (stream t)) = dropWhile p t
#-}
dropWhileEnd :: (Char -> Bool) -> JSString -> JSString
dropWhileEnd p x = loop (js_length x -# 1#)
where loop -1# = empty
loop i = case js_uncheckedIndexR i x of
c | p (C# (chr# c)) -> loop (i -# charWidth c)
_ -> js_substr 0# (i +# 1#) x
{-# INLINE [1] dropWhileEnd #-}
{-# RULES
"TEXT dropWhileEnd -> fused" [~1] forall p t.
dropWhileEnd p t = S.reverse (S.dropWhile p (S.reverseStream t))
"TEXT dropWhileEnd -> unfused" [1] forall p t.
S.reverse (S.dropWhile p (S.reverseStream t)) = dropWhileEnd p t
#-}
dropAround :: (Char -> Bool) -> JSString -> JSString
dropAround p = dropWhile p . dropWhileEnd p
{-# INLINE [1] dropAround #-}
stripStart :: JSString -> JSString
stripStart = dropWhile isSpace
{-# INLINE [1] stripStart #-}
stripEnd :: JSString -> JSString
stripEnd = dropWhileEnd isSpace
{-# INLINE [1] stripEnd #-}
strip :: JSString -> JSString
strip = dropAround isSpace
{-# INLINE [1] strip #-}
splitAt :: Int -> JSString -> (JSString, JSString)
splitAt (I# n) x = case js_splitAt n x of (# y, z #) -> (y, z)
{-# INLINE splitAt #-}
span :: (Char -> Bool) -> JSString -> (JSString, JSString)
span p x = case js_length x of
0# -> (empty, empty)
l -> let c0 = js_uncheckedIndex 0# x
in if p (C# (chr# c0)) then loop 0# l else (empty, x)
where
loop i l
| isTrue# (i >=# l) = (x, empty)
| otherwise =
let c = js_uncheckedIndex i x
in if p (C# (chr# c))
then loop (i +# charWidth c) l
else (js_substr 0# i x, js_substr1 i x)
{-# INLINE span #-}
break :: (Char -> Bool) -> JSString -> (JSString, JSString)
break p = span (not . p)
{-# INLINE break #-}
groupBy :: (Char -> Char -> Bool) -> JSString -> [JSString]
groupBy p x =
case js_length x of
0# -> []
l -> let c0 = js_uncheckedIndex 0# x
in loop (C# (chr# c0)) 0# (charWidth c0) l
where
loop b s i l
| isTrue# (i >=# l) =
if isTrue# (i ># s) then [js_substr1 s x] else []
| otherwise =
let c = js_uncheckedIndex i x
c' = C# (chr# c)
i' = i +# charWidth c
in if p b c'
then loop b s i' l
else js_substring s i x : loop c' i i' l
group :: JSString -> [JSString]
group x = group' x
{-# INLINE group #-}
group' :: JSString -> [JSString]
group' x = unsafeCoerce (js_group x)
{-# INLINE group' #-}
inits :: JSString -> [JSString]
inits x = empty : case js_length x of
0# -> []
l -> loop (js_charWidthAt 0# x) l
where
loop i l
| isTrue# (i >=# l) = [x]
| otherwise =
js_substr 0# i x : loop (i +# js_charWidthAt i x) l
tails :: JSString -> [JSString]
tails x =
case js_length x of
0# -> [empty]
l -> loop 0# l
where
loop i l
| isTrue# (i >=# l) = [empty]
| otherwise =
js_substr1 i x : loop (i +# js_charWidthAt i x) l
splitOn :: JSString
-> JSString
-> [JSString]
splitOn = splitOn'
{-# INLINE [1] splitOn #-}
splitOn' :: JSString
-> JSString
-> [JSString]
splitOn' pat src
| null pat = emptyError "splitOn'"
| otherwise = unsafeCoerce (js_splitOn pat src)
{-# NOINLINE splitOn' #-}
split :: (Char -> Bool) -> JSString -> [JSString]
split p x = case js_length x of
0# -> [empty]
l -> loop 0# 0# l
where
loop s i l
| isTrue# (i >=# l) = [js_substr s i x]
| otherwise =
let ch = js_uncheckedIndex i x
i' = i +# charWidth ch
in if p (C# (chr# ch))
then js_substr s (i -# s) x : loop i' i' l
else loop s i' l
{-# INLINE split #-}
chunksOf :: Int -> JSString -> [JSString]
chunksOf (I# k) p = go 0#
where
go i = case js_chunksOf1 k i p of
(# n, c #) -> case n of
-1# -> []
_ -> c : go n
{-# INLINE chunksOf #-}
chunksOf' :: Int -> JSString -> [JSString]
chunksOf' (I# k) p = unsafeCoerce (js_chunksOf k p)
{-# INLINE chunksOf' #-}
find :: (Char -> Bool) -> JSString -> Maybe Char
find p t = S.findBy p (stream t)
{-# INLINE find #-}
partition :: (Char -> Bool) -> JSString -> (JSString, JSString)
partition p t = (filter p t, filter (not . p) t)
{-# INLINE partition #-}
filter :: (Char -> Bool) -> JSString -> JSString
filter p t = unstream (S.filter p (stream t))
{-# INLINE filter #-}
breakOn :: JSString -> JSString -> (JSString, JSString)
breakOn pat src
| null pat = emptyError "breakOn"
| otherwise = case js_breakOn pat src of (# y, z #) -> (y, z)
{-# INLINE breakOn #-}
breakOnEnd :: JSString -> JSString -> (JSString, JSString)
breakOnEnd pat src
| null pat = emptyError "breakOnEnd"
| otherwise = case js_breakOnEnd pat src of (# y, z #) -> (y, z)
{-# INLINE breakOnEnd #-}
breakOnAll :: JSString
-> JSString
-> [(JSString, JSString)]
breakOnAll pat src
| null pat = emptyError "breakOnAll"
| otherwise = go 0#
where
go i = case js_breakOnAll1 i pat src of
(# n, x, y #) -> case n of
-1# -> []
_ -> (x,y) : go n
{-# INLINE breakOnAll #-}
breakOnAll' :: JSString
-> JSString
-> [(JSString, JSString)]
breakOnAll' pat src
| null pat = emptyError "breakOnAll'"
| otherwise = unsafeCoerce (js_breakOnAll pat src)
{-# INLINE breakOnAll' #-}
index :: JSString -> Int -> Char
index t n = S.index (stream t) n
{-# INLINE index #-}
findIndex :: (Char -> Bool) -> JSString -> Maybe Int
findIndex p t = S.findIndex p (stream t)
{-# INLINE findIndex #-}
count :: JSString -> JSString -> Int
count pat src
| null pat = emptyError "count"
| otherwise = I# (js_count pat src)
{-# INLINE [1] count #-}
countChar :: Char -> JSString -> Int
countChar c t = S.countChar c (stream t)
{-# INLINE countChar #-}
zip :: JSString -> JSString -> [(Char,Char)]
zip a b = S.unstreamList $ S.zipWith (,) (stream a) (stream b)
{-# INLINE zip #-}
zipWith :: (Char -> Char -> Char) -> JSString -> JSString -> JSString
zipWith f t1 t2 = unstream (S.zipWith g (stream t1) (stream t2))
where g a b = safe (f a b)
{-# INLINE zipWith #-}
words :: JSString -> [JSString]
words x = loop 0#
where
loop i = case js_words1 i x of
(# n, w #) -> case n of
-1# -> []
_ -> w : loop n
{-# INLINE words #-}
words' :: JSString -> [JSString]
words' x = unsafeCoerce (js_words x)
{-# INLINE words' #-}
lines :: JSString -> [JSString]
lines ps = loop 0#
where
loop i = case js_lines1 i ps of
(# n, l #) -> case n of
-1# -> []
_ -> l : loop n
{-# INLINE lines #-}
lines' :: JSString -> [JSString]
lines' ps = unsafeCoerce (js_lines ps)
{-# INLINE lines' #-}
unlines :: [JSString] -> JSString
unlines xs = rnf xs `seq` js_unlines (unsafeCoerce xs)
{-# INLINE unlines #-}
unwords :: [JSString] -> JSString
unwords xs = rnf xs `seq` js_unwords (unsafeCoerce xs)
{-# INLINE unwords #-}
isPrefixOf :: JSString -> JSString -> Bool
isPrefixOf x y = js_isPrefixOf x y
{-# INLINE [1] isPrefixOf #-}
{-# RULES
"JSSTRING isPrefixOf -> fused" [~1] forall x y.
isPrefixOf x y = S.isPrefixOf (stream x) (stream y)
"JSSTRING isPrefixOf -> unfused" [1] forall x y.
S.isPrefixOf (stream x) (stream y) = isPrefixOf x y
#-}
isSuffixOf :: JSString -> JSString -> Bool
isSuffixOf x y = js_isSuffixOf x y
{-# INLINE isSuffixOf #-}
isInfixOf :: JSString -> JSString -> Bool
isInfixOf needle haystack = js_isInfixOf needle haystack
{-# INLINE [1] isInfixOf #-}
{-# RULES
"JSSTRING isInfixOf/singleton -> S.elem/S.stream" [~1] forall n h.
isInfixOf (singleton n) h = S.elem n (S.stream h)
#-}
stripPrefix :: JSString -> JSString -> Maybe JSString
stripPrefix x y = unsafeCoerce (js_stripPrefix x y)
{-# INLINE stripPrefix #-}
commonPrefixes :: JSString -> JSString -> Maybe (JSString,JSString,JSString)
commonPrefixes x y = unsafeCoerce (js_commonPrefixes x y)
{-# INLINE commonPrefixes #-}
stripSuffix :: JSString -> JSString -> Maybe JSString
stripSuffix x y = unsafeCoerce (js_stripSuffix x y)
{-# INLINE stripSuffix #-}
sumP :: String -> [Int] -> Int
sumP fun = go 0
where go !a (x:xs)
| ax >= 0 = go ax xs
| otherwise = overflowError fun
where ax = a + x
go a _ = a
emptyError :: String -> a
emptyError fun = P.error $ "Data.JSString." ++ fun ++ ": empty input"
overflowError :: String -> a
overflowError fun = P.error $ "Data.JSString." ++ fun ++ ": size overflow"
charWidth :: Int# -> Int#
charWidth cp | isTrue# (cp >=# 0x10000#) = 2#
| otherwise = 1#
{-# INLINE charWidth #-}
foreign import javascript unsafe
"h$jsstringPack($1)" js_pack :: Exts.Any -> JSString
foreign import javascript unsafe
"$1===''" js_null :: JSString -> Bool
foreign import javascript unsafe
"$1===null" js_isNull :: JSVal -> Bool
foreign import javascript unsafe
"$1===$2" js_eq :: JSString -> JSString -> Bool
foreign import javascript unsafe
"$1+$2" js_append :: JSString -> JSString -> JSString
foreign import javascript unsafe
"h$jsstringCompare" js_compare :: JSString -> JSString -> Int#
foreign import javascript unsafe
"h$jsstringSingleton" js_singleton :: Char -> JSString
foreign import javascript unsafe
"h$jsstringUnpack" js_unpack :: JSString -> Exts.Any
foreign import javascript unsafe
"h$jsstringCons" js_cons :: Char -> JSString -> JSString
foreign import javascript unsafe
"h$jsstringSnoc" js_snoc :: JSString -> Char -> JSString
foreign import javascript unsafe
"h$jsstringUncons" js_uncons :: JSString -> (# Int#, JSString #)
foreign import javascript unsafe
"h$jsstringUnsnoc" js_unsnoc :: JSString -> (# Int#, JSString #)
foreign import javascript unsafe
"$3.substr($1,$2)" js_substr :: Int# -> Int# -> JSString -> JSString
foreign import javascript unsafe
"$2.substr($1)" js_substr1 :: Int# -> JSString -> JSString
foreign import javascript unsafe
"$3.substring($1,$2)" js_substring :: Int# -> Int# -> JSString -> JSString
foreign import javascript unsafe
"$1.length" js_length :: JSString -> Int#
foreign import javascript unsafe
"(($2.charCodeAt($1)|1023)===0xDBFF)?2:1" js_charWidthAt
:: Int# -> JSString -> Int#
foreign import javascript unsafe
"h$jsstringIndex" js_index :: Int# -> JSString -> Int#
foreign import javascript unsafe
"h$jsstringIndexR" js_indexR :: Int# -> JSString -> Int#
foreign import javascript unsafe
"h$jsstringUncheckedIndex" js_uncheckedIndex :: Int# -> JSString -> Int#
foreign import javascript unsafe
"h$jsstringIndexR" js_uncheckedIndexR :: Int# -> JSString -> Int#
foreign import javascript unsafe
"h$jsstringHead" js_head :: JSString -> Int#
foreign import javascript unsafe
"h$jsstringLast" js_last :: JSString -> Int#
foreign import javascript unsafe
"h$jsstringInit" js_init :: JSString -> JSVal
foreign import javascript unsafe
"h$jsstringTail" js_tail :: JSString -> JSVal
foreign import javascript unsafe
"h$jsstringReverse" js_reverse :: JSString -> JSString
foreign import javascript unsafe
"h$jsstringGroup" js_group :: JSString -> Exts.Any
foreign import javascript unsafe
"h$jsstringConcat" js_concat :: Exts.Any -> JSString
foreign import javascript unsafe
"h$jsstringReplace" js_replace :: JSString -> JSString -> JSString -> JSString
foreign import javascript unsafe
"h$jsstringCount" js_count :: JSString -> JSString -> Int#
foreign import javascript unsafe
"h$jsstringWords1" js_words1 :: Int# -> JSString -> (# Int#, JSString #)
foreign import javascript unsafe
"h$jsstringWords" js_words :: JSString -> Exts.Any
foreign import javascript unsafe
"h$jsstringLines1" js_lines1 :: Int# -> JSString -> (# Int#, JSString #)
foreign import javascript unsafe
"h$jsstringLines" js_lines :: JSString -> Exts.Any
foreign import javascript unsafe
"h$jsstringUnlines" js_unlines :: Exts.Any -> JSString
foreign import javascript unsafe
"h$jsstringUnwords" js_unwords :: Exts.Any -> JSString
foreign import javascript unsafe
"h$jsstringIsPrefixOf" js_isPrefixOf :: JSString -> JSString -> Bool
foreign import javascript unsafe
"h$jsstringIsSuffixOf" js_isSuffixOf :: JSString -> JSString -> Bool
foreign import javascript unsafe
"h$jsstringIsInfixOf" js_isInfixOf :: JSString -> JSString -> Bool
foreign import javascript unsafe
"h$jsstringStripPrefix" js_stripPrefix
:: JSString -> JSString -> Exts.Any
foreign import javascript unsafe
"h$jsstringStripSuffix" js_stripSuffix
:: JSString -> JSString -> Exts.Any
foreign import javascript unsafe
"h$jsstringCommonPrefixes" js_commonPrefixes
:: JSString -> JSString -> Exts.Any
foreign import javascript unsafe
"h$jsstringChunksOf" js_chunksOf
:: Int# -> JSString -> Exts.Any
foreign import javascript unsafe
"h$jsstringChunksOf1" js_chunksOf1
:: Int# -> Int# -> JSString -> (# Int#, JSString #)
foreign import javascript unsafe
"h$jsstringSplitAt" js_splitAt
:: Int# -> JSString -> (# JSString, JSString #)
foreign import javascript unsafe
"h$jsstringSplitOn" js_splitOn
:: JSString -> JSString -> Exts.Any
foreign import javascript unsafe
"h$jsstringSplitOn1" js_splitOn1
:: Int# -> JSString -> JSString -> (# Int#, JSString #)
foreign import javascript unsafe
"h$jsstringBreakOn" js_breakOn
:: JSString -> JSString -> (# JSString, JSString #)
foreign import javascript unsafe
"h$jsstringBreakOnEnd" js_breakOnEnd
:: JSString -> JSString -> (# JSString, JSString #)
foreign import javascript unsafe
"h$jsstringBreakOnAll" js_breakOnAll
:: JSString -> JSString -> Exts.Any
foreign import javascript unsafe
"h$jsstringBreakOnAll1" js_breakOnAll1
:: Int# -> JSString -> JSString -> (# Int#, JSString, JSString #)
foreign import javascript unsafe
"h$jsstringDrop" js_drop :: Int# -> JSString -> JSString
foreign import javascript unsafe
"h$jsstringDropEnd" js_dropEnd :: Int -> JSString -> JSString
foreign import javascript unsafe
"h$jsstringTake" js_take :: Int# -> JSString -> JSString
foreign import javascript unsafe
"h$jsstringTakeEnd" js_takeEnd :: Int# -> JSString -> JSString
foreign import javascript unsafe
"h$jsstringReplicate" js_replicate :: Int# -> JSString -> JSString
foreign import javascript unsafe
"h$jsstringReplicateChar" js_replicateChar :: Int -> Char -> JSString
foreign import javascript unsafe
"var l=$1.length; $r=l==1||(l==2&&($1.charCodeAt(0)|1023)==0xDFFF);"
js_isSingleton :: JSString -> Bool
foreign import javascript unsafe
"h$jsstringIntersperse"
js_intersperse :: Char -> JSString -> JSString
foreign import javascript unsafe
"h$jsstringIntercalate"
js_intercalate :: JSString -> Exts.Any -> JSString
foreign import javascript unsafe
"$1.toUpperCase()" js_toUpper :: JSString -> JSString
foreign import javascript unsafe
"$1.toLowerCase()" js_toLower :: JSString -> JSString