Move Streamly.Unicode to streamly-core

This commit is contained in:
Ranjeet Kumar Ranjan 2022-09-22 17:30:00 +05:30 committed by Adithya Kumar
parent 5868fc9f85
commit 182edfd74f
9 changed files with 82 additions and 83 deletions

View File

@ -1,7 +1,7 @@
core/src/Streamly/Internal/Data/Stream/StreamK/Type.hs
core/src/Streamly/Internal/Data/Pipe/Type.hs
core/src/Streamly/Internal/Unicode/Stream.hs
src/Streamly/Internal/Data/SmallArray/Type.hs
src/Streamly/Internal/Unicode/Stream.hs
test/Streamly/Test/Data/Array.hs
test/Streamly/Test/Data/Parser.hs
test/Streamly/Test/Data/Parser/ParserD.hs

View File

@ -5,7 +5,7 @@ packages:
source-repository-package
type: git
location: https://github.com/composewell/packdiff.git
tag: 45cdca157e7159b8dd4261b3616fe7fa4200b967
tag: 8b5d35b72b8ba3c9fb34f16e30d9d58f22b78f3e
source-repository-package
type: git

View File

@ -18,9 +18,8 @@ module Streamly.Internal.Unicode.Array.Char
where
import Control.Monad.IO.Class (MonadIO)
import Streamly.Data.Array.Unboxed (Array)
import Streamly.Internal.Data.Stream.IsStream (IsStream)
import Streamly.Prelude (MonadAsync)
import Streamly.Data.Stream (Stream)
import Streamly.Internal.Data.Array.Unboxed (Array)
import qualified Streamly.Data.Array.Unboxed as A
import qualified Streamly.Internal.Unicode.Stream as S
@ -43,7 +42,7 @@ import Prelude hiding (String, lines, words, unlines, unwords)
-- ["lines","this","string","",""]
--
{-# INLINE lines #-}
lines :: (MonadIO m, IsStream t) => t m Char -> t m (Array Char)
lines :: (MonadIO m) => Stream m Char -> Stream m (Array Char)
lines = S.lines A.write
-- | Break a string up into a stream of strings, which were delimited
@ -55,7 +54,7 @@ lines = S.lines A.write
-- ["A","newline","is","considered","white","space?"]
--
{-# INLINE words #-}
words :: (MonadIO m, IsStream t) => t m Char -> t m (Array Char)
words :: (MonadIO m) => Stream m Char -> Stream m (Array Char)
words = S.words A.write
-- | Flattens the stream of @Array Char@, after appending a terminating
@ -72,7 +71,7 @@ words = S.words A.write
--
-- > unlines . lines /= id
{-# INLINE unlines #-}
unlines :: (MonadIO m, IsStream t) => t m (Array Char) -> t m Char
unlines :: (MonadIO m) => Stream m (Array Char) -> Stream m Char
unlines = S.unlines A.read
-- | Flattens the stream of @Array Char@, after appending a separating
@ -89,5 +88,5 @@ unlines = S.unlines A.read
--
-- > unwords . words /= id
{-# INLINE unwords #-}
unwords :: (MonadAsync m, IsStream t) => t m (Array Char) -> t m Char
unwords :: (MonadIO m) => Stream m (Array Char) -> Stream m Char
unwords = S.unwords A.read

View File

@ -103,14 +103,12 @@ import GHC.Exts (Addr#)
import GHC.IO.Encoding.Failure (isSurrogate)
import GHC.Ptr (Ptr (..), plusPtr)
import System.IO.Unsafe (unsafePerformIO)
import Streamly.Internal.Data.Array.Unboxed (Array)
import Streamly.Internal.Data.Array.Unboxed.Type (Array(..))
import Streamly.Internal.Data.Array.Unboxed.Mut.Type (MutableByteArray)
import Streamly.Internal.Data.Fold (Fold)
import Streamly.Internal.Data.Stream.IsStream.Type
(IsStream, fromStreamD, toStreamD, adapt)
import Streamly.Internal.Data.Stream (Stream)
import Streamly.Internal.Data.Stream (Stream, fromStreamD, toStreamD)
import Streamly.Internal.Data.Stream.StreamD (Step (..))
import Streamly.Internal.Data.SVar (adaptState)
import Streamly.Internal.Data.SVar.Type (adaptState)
import Streamly.Internal.Data.Tuple.Strict (Tuple'(..))
import Streamly.Internal.Data.Unboxed (peekWith)
import Streamly.Internal.Data.Unfold.Type (Unfold(..))
@ -118,14 +116,10 @@ import Streamly.Internal.System.IO (unsafeInlineIO)
import qualified Streamly.Data.Fold as Fold
import qualified Streamly.Data.Unfold as Unfold
import qualified Streamly.Internal.Data.Array.Unboxed.Type as Array
import qualified Streamly.Internal.Data.Parser as Parser (Parser)
import qualified Streamly.Internal.Data.Parser.ParserD as ParserD
(Parser(..), Step(..), Initial(..), toParserK, toFold)
import qualified Streamly.Internal.Data.Stream as Stream (fromByteStr#)
import qualified Streamly.Internal.Data.Stream.Serial as Serial
import qualified Streamly.Data.Array.Unboxed as Array
import qualified Streamly.Internal.Data.Array.Unboxed.Type as A (Array (..))
import qualified Streamly.Internal.Data.Stream.IsStream as S
import qualified Streamly.Internal.Data.Stream as Stream
import qualified Streamly.Internal.Data.Stream.StreamD as D
import Prelude hiding (lines, words, unlines, unwords)
@ -150,8 +144,8 @@ import Prelude hiding (lines, words, unlines, unwords)
--
-- @since 0.8.0
{-# INLINE decodeLatin1 #-}
decodeLatin1 :: (IsStream t, Monad m) => t m Word8 -> t m Char
decodeLatin1 = S.map (unsafeChr . fromIntegral)
decodeLatin1 :: (Monad m) => Stream m Word8 -> Stream m Char
decodeLatin1 = fmap (unsafeChr . fromIntegral)
-------------------------------------------------------------------------------
-- Latin1 encoding
@ -163,8 +157,8 @@ decodeLatin1 = S.map (unsafeChr . fromIntegral)
--
-- @since 0.8.0
{-# INLINE encodeLatin1' #-}
encodeLatin1' :: (IsStream t, Monad m) => t m Char -> t m Word8
encodeLatin1' = S.map convert
encodeLatin1' :: (Monad m) => Stream m Char -> Stream m Word8
encodeLatin1' = fmap convert
where
convert c =
let codepoint = ord c
@ -185,21 +179,21 @@ encodeLatin1' = S.map convert
--
-- /Since: 0.8.0 (Lenient Behaviour)/
{-# INLINE encodeLatin1 #-}
encodeLatin1 :: (IsStream t, Monad m) => t m Char -> t m Word8
encodeLatin1 = S.map (fromIntegral . ord)
encodeLatin1 :: (Monad m) => Stream m Char -> Stream m Word8
encodeLatin1 = fmap (fromIntegral . ord)
-- | Like 'encodeLatin1' but drops the input characters beyond 255.
--
-- @since 0.8.0
{-# INLINE encodeLatin1_ #-}
encodeLatin1_ :: (IsStream t, Monad m) => t m Char -> t m Word8
encodeLatin1_ = S.map (fromIntegral . ord) . S.filter (<= chr 255)
encodeLatin1_ :: (Monad m) => Stream m Char -> Stream m Word8
encodeLatin1_ = fmap (fromIntegral . ord) . Stream.filter (<= chr 255)
-- | Same as 'encodeLatin1'
--
{-# DEPRECATED encodeLatin1Lax "Please use 'encodeLatin1' instead" #-}
{-# INLINE encodeLatin1Lax #-}
encodeLatin1Lax :: (IsStream t, Monad m) => t m Char -> t m Word8
encodeLatin1Lax :: (Monad m) => Stream m Char -> Stream m Word8
encodeLatin1Lax = encodeLatin1
-------------------------------------------------------------------------------
@ -430,8 +424,8 @@ decodeUtf8EitherD = resumeDecodeUtf8EitherD 0 0
--
-- /Pre-release/
{-# INLINE decodeUtf8Either #-}
decodeUtf8Either :: (Monad m, IsStream t)
=> t m Word8 -> t m (Either DecodeError Char)
decodeUtf8Either :: (Monad m)
=> Stream m Word8 -> Stream m (Either DecodeError Char)
decodeUtf8Either = fromStreamD . decodeUtf8EitherD . toStreamD
-- |
@ -439,11 +433,11 @@ decodeUtf8Either = fromStreamD . decodeUtf8EitherD . toStreamD
-- /Pre-release/
{-# INLINE resumeDecodeUtf8Either #-}
resumeDecodeUtf8Either
:: (Monad m, IsStream t)
:: (Monad m)
=> DecodeState
-> CodePoint
-> t m Word8
-> t m (Either DecodeError Char)
-> Stream m Word8
-> Stream m (Either DecodeError Char)
resumeDecodeUtf8Either st cp =
fromStreamD . resumeDecodeUtf8EitherD st cp . toStreamD
@ -663,7 +657,7 @@ decodeUtf8D = decodeUtf8WithD TransliterateCodingFailure
--
-- /Since: 0.8.0 (Lenient Behaviour)/
{-# INLINE decodeUtf8 #-}
decodeUtf8 :: (Monad m, IsStream t) => t m Word8 -> t m Char
decodeUtf8 :: (Monad m) => Stream m Word8 -> Stream m Char
decodeUtf8 = fromStreamD . decodeUtf8D . toStreamD
{-# INLINE decodeUtf8D' #-}
@ -675,7 +669,7 @@ decodeUtf8D' = decodeUtf8WithD ErrorOnCodingFailure
--
-- @since 0.8.0
{-# INLINE decodeUtf8' #-}
decodeUtf8' :: (Monad m, IsStream t) => t m Word8 -> t m Char
decodeUtf8' :: (Monad m) => Stream m Word8 -> Stream m Char
decodeUtf8' = fromStreamD . decodeUtf8D' . toStreamD
{-# INLINE decodeUtf8D_ #-}
@ -687,14 +681,14 @@ decodeUtf8D_ = decodeUtf8WithD DropOnCodingFailure
--
-- @since 0.8.0
{-# INLINE decodeUtf8_ #-}
decodeUtf8_ :: (Monad m, IsStream t) => t m Word8 -> t m Char
decodeUtf8_ :: (Monad m) => Stream m Word8 -> Stream m Char
decodeUtf8_ = fromStreamD . decodeUtf8D_ . toStreamD
-- | Same as 'decodeUtf8'
--
{-# DEPRECATED decodeUtf8Lax "Please use 'decodeUtf8' instead" #-}
{-# INLINE decodeUtf8Lax #-}
decodeUtf8Lax :: (IsStream t, Monad m) => t m Word8 -> t m Char
decodeUtf8Lax :: (Monad m) => Stream m Word8 -> Stream m Char
decodeUtf8Lax = decodeUtf8
-------------------------------------------------------------------------------
@ -726,7 +720,7 @@ data FlattenState s a
decodeUtf8ArraysWithD ::
MonadIO m
=> CodingFailureMode
-> D.Stream m (A.Array Word8)
-> D.Stream m (Array Word8)
-> D.Stream m Char
decodeUtf8ArraysWithD cfm (D.Stream step state) =
D.Stream (step' utf8d) (OuterLoop state Nothing)
@ -751,7 +745,7 @@ decodeUtf8ArraysWithD cfm (D.Stream step state) =
r <- step (adaptState gst) st
return $
case r of
Yield A.Array {..} s ->
Yield Array {..} s ->
Skip (InnerLoopDecodeInit s arrContents arrStart arrEnd)
Skip s -> Skip (OuterLoop s Nothing)
Stop -> Skip D
@ -759,7 +753,7 @@ decodeUtf8ArraysWithD cfm (D.Stream step state) =
r <- step (adaptState gst) st
return $
case r of
Yield A.Array {..} s ->
Yield Array {..} s ->
Skip (InnerLoopDecoding s arrContents arrStart arrEnd ds cp)
Skip s -> Skip (OuterLoop s dst)
Stop -> Skip inputUnderflow
@ -828,7 +822,7 @@ decodeUtf8ArraysWithD cfm (D.Stream step state) =
{-# INLINE decodeUtf8ArraysD #-}
decodeUtf8ArraysD ::
MonadIO m
=> D.Stream m (A.Array Word8)
=> D.Stream m (Array Word8)
-> D.Stream m Char
decodeUtf8ArraysD = decodeUtf8ArraysWithD TransliterateCodingFailure
@ -837,14 +831,14 @@ decodeUtf8ArraysD = decodeUtf8ArraysWithD TransliterateCodingFailure
-- /Pre-release/
{-# INLINE decodeUtf8Arrays #-}
decodeUtf8Arrays ::
(MonadIO m, IsStream t) => t m (Array Word8) -> t m Char
(MonadIO m) => Stream m (Array Word8) -> Stream m Char
decodeUtf8Arrays =
fromStreamD . decodeUtf8ArraysD . toStreamD
{-# INLINE decodeUtf8ArraysD' #-}
decodeUtf8ArraysD' ::
MonadIO m
=> D.Stream m (A.Array Word8)
=> D.Stream m (Array Word8)
-> D.Stream m Char
decodeUtf8ArraysD' = decodeUtf8ArraysWithD ErrorOnCodingFailure
@ -852,13 +846,13 @@ decodeUtf8ArraysD' = decodeUtf8ArraysWithD ErrorOnCodingFailure
--
-- /Pre-release/
{-# INLINE decodeUtf8Arrays' #-}
decodeUtf8Arrays' :: (MonadIO m, IsStream t) => t m (Array Word8) -> t m Char
decodeUtf8Arrays' :: (MonadIO m) => Stream m (Array Word8) -> Stream m Char
decodeUtf8Arrays' = fromStreamD . decodeUtf8ArraysD' . toStreamD
{-# INLINE decodeUtf8ArraysD_ #-}
decodeUtf8ArraysD_ ::
MonadIO m
=> D.Stream m (A.Array Word8)
=> D.Stream m (Array Word8)
-> D.Stream m Char
decodeUtf8ArraysD_ = decodeUtf8ArraysWithD DropOnCodingFailure
@ -867,7 +861,7 @@ decodeUtf8ArraysD_ = decodeUtf8ArraysWithD DropOnCodingFailure
-- /Pre-release/
{-# INLINE decodeUtf8Arrays_ #-}
decodeUtf8Arrays_ ::
(MonadIO m, IsStream t) => t m (Array Word8) -> t m Char
(MonadIO m) => Stream m (Array Word8) -> Stream m Char
decodeUtf8Arrays_ =
fromStreamD . decodeUtf8ArraysD_ . toStreamD
@ -943,7 +937,7 @@ encodeUtf8D' = D.unfoldMany readCharUtf8'
--
-- @since 0.8.0
{-# INLINE encodeUtf8' #-}
encodeUtf8' :: (Monad m, IsStream t) => t m Char -> t m Word8
encodeUtf8' :: (Monad m) => Stream m Char -> Stream m Word8
encodeUtf8' = fromStreamD . encodeUtf8D' . toStreamD
{-# INLINE_NORMAL readCharUtf8 #-}
@ -965,7 +959,7 @@ encodeUtf8D = D.unfoldMany readCharUtf8
--
-- /Since: 0.8.0 (Lenient Behaviour)/
{-# INLINE encodeUtf8 #-}
encodeUtf8 :: (Monad m, IsStream t) => t m Char -> t m Word8
encodeUtf8 :: (Monad m) => Stream m Char -> Stream m Word8
encodeUtf8 = fromStreamD . encodeUtf8D . toStreamD
{-# INLINE_NORMAL readCharUtf8_ #-}
@ -981,14 +975,14 @@ encodeUtf8D_ = D.unfoldMany readCharUtf8_
--
-- @since 0.8.0
{-# INLINE encodeUtf8_ #-}
encodeUtf8_ :: (Monad m, IsStream t) => t m Char -> t m Word8
encodeUtf8_ :: (Monad m) => Stream m Char -> Stream m Word8
encodeUtf8_ = fromStreamD . encodeUtf8D_ . toStreamD
-- | Same as 'encodeUtf8'
--
{-# DEPRECATED encodeUtf8Lax "Please use 'encodeUtf8' instead" #-}
{-# INLINE encodeUtf8Lax #-}
encodeUtf8Lax :: (IsStream t, Monad m) => t m Char -> t m Word8
encodeUtf8Lax :: (Monad m) => Stream m Char -> Stream m Word8
encodeUtf8Lax = encodeUtf8
-------------------------------------------------------------------------------
@ -1024,27 +1018,27 @@ encodeObject :: MonadIO m =>
-> Unfold m a Char
-> a
-> m (Array Word8)
encodeObject encode u = S.fold Array.write . encode . S.unfold u
encodeObject encode u = Stream.fold Array.write . encode . Stream.unfold u
-- | Encode a stream of container objects using the supplied encoding scheme.
-- Each object is encoded as an @Array Word8@.
--
-- /Internal/
{-# INLINE encodeObjects #-}
encodeObjects :: (MonadIO m, IsStream t) =>
encodeObjects :: (MonadIO m) =>
(Stream m Char -> Stream m Word8)
-> Unfold m a Char
-> t m a
-> t m (Array Word8)
encodeObjects encode u = adapt . Serial.mapM (encodeObject encode u) . adapt
-> Stream m a
-> Stream m (Array Word8)
encodeObjects encode u = Stream.mapM (encodeObject encode u)
-- | Encode a stream of 'String' using the supplied encoding scheme. Each
-- string is encoded as an @Array Word8@.
--
-- @since 0.8.0
{-# INLINE encodeStrings #-}
encodeStrings :: (MonadIO m, IsStream t) =>
(Stream m Char -> Stream m Word8) -> t m String -> t m (Array Word8)
encodeStrings :: (MonadIO m) =>
(Stream m Char -> Stream m Word8) -> Stream m String -> Stream m (Array Word8)
encodeStrings encode = encodeObjects encode Unfold.fromList
{-
@ -1052,21 +1046,21 @@ encodeStrings encode = encodeObjects encode Unfold.fromList
-- Utility operations on strings
-------------------------------------------------------------------------------
strip :: IsStream t => t m Char -> t m Char
strip :: IsStream t => Stream m Char -> Stream m Char
strip = undefined
stripTail :: IsStream t => t m Char -> t m Char
stripTail :: IsStream t => Stream m Char -> Stream m Char
stripTail = undefined
-}
-- | Remove leading whitespace from a string.
--
-- > stripHead = S.dropWhile isSpace
-- > stripHead = Stream.dropWhile isSpace
--
-- /Pre-release/
{-# INLINE stripHead #-}
stripHead :: (Monad m, IsStream t) => t m Char -> t m Char
stripHead = S.dropWhile isSpace
stripHead :: (Monad m) => Stream m Char -> Stream m Char
stripHead = Stream.dropWhile isSpace
-- | Fold each line of the stream using the supplied 'Fold'
-- and stream the result.
@ -1074,12 +1068,12 @@ stripHead = S.dropWhile isSpace
-- >>> Stream.toList $ lines Fold.toList (Stream.fromList "lines\nthis\nstring\n\n\n")
-- ["lines","this","string","",""]
--
-- > lines = S.splitOnSuffix (== '\n')
-- > lines = Stream.splitOnSuffix (== '\n')
--
-- /Pre-release/
{-# INLINE lines #-}
lines :: (Monad m, IsStream t) => Fold m Char b -> t m Char -> t m b
lines = S.splitOnSuffix (== '\n')
lines :: (Monad m) => Fold m Char b -> Stream m Char -> Stream m b
lines f = Stream.foldMany (Fold.takeEndBy_ (== '\n') f)
#if !MIN_VERSION_base(4,17,0)
foreign import ccall unsafe "u_iswspace"
@ -1105,12 +1099,12 @@ isSpace c
-- >>> Stream.toList $ words Fold.toList (Stream.fromList "fold these words")
-- ["fold","these","words"]
--
-- > words = S.wordsBy isSpace
-- > words = Stream.wordsBy isSpace
--
-- /Pre-release/
{-# INLINE words #-}
words :: (Monad m, IsStream t) => Fold m Char b -> t m Char -> t m b
words = S.wordsBy isSpace
words :: (Monad m) => Fold m Char b -> Stream m Char -> Stream m b
words f m = Stream.fromStreamD $ D.wordsBy isSpace f (Stream.toStreamD m)
-- | Unfold a stream to character streams using the supplied 'Unfold'
-- and concat the results suffixing a newline character @\\n@ to each stream.
@ -1122,8 +1116,8 @@ words = S.wordsBy isSpace
--
-- /Pre-release/
{-# INLINE unlines #-}
unlines :: (MonadIO m, IsStream t) => Unfold m a Char -> t m a -> t m Char
unlines = S.interposeSuffix '\n'
unlines :: (MonadIO m) => Unfold m a Char -> Stream m a -> Stream m Char
unlines = Stream.interposeSuffix '\n'
-- | Unfold the elements of a stream to character streams using the supplied
-- 'Unfold' and concat the results with a whitespace character infixed between
@ -1136,5 +1130,5 @@ unlines = S.interposeSuffix '\n'
--
-- /Pre-release/
{-# INLINE unwords #-}
unwords :: (MonadIO m, IsStream t) => Unfold m a Char -> t m a -> t m Char
unwords = S.interpose ' '
unwords :: (MonadIO m) => Unfold m a Char -> Stream m a -> Stream m Char
unwords = Stream.interpose ' '

View File

@ -44,7 +44,7 @@ import Language.Haskell.TH.Quote
import qualified Streamly.Data.Fold as Fold
import qualified Streamly.Internal.Data.Parser as Parser
(some, many, takeWhile1)
import qualified Streamly.Internal.Data.Stream.IsStream as Stream
import qualified Streamly.Data.Stream as Stream (fromList, parse)
import qualified Streamly.Internal.Unicode.Char.Parser as Parser
-- $setup

View File

@ -326,6 +326,12 @@ library
, Streamly.Internal.Data.Array.Stream.Fold.Foreign
, Streamly.Internal.Data.Array.Stream.Foreign
-- streamly-unicode
, Streamly.Internal.Unicode.Stream
, Streamly.Internal.Unicode.String
, Streamly.Internal.Unicode.Char.Parser
, Streamly.Internal.Unicode.Array.Char
-- Ring Arrays
, Streamly.Internal.Data.Ring.Foreign
@ -344,6 +350,9 @@ library
, Streamly.Data.Array.Unboxed
, Streamly.Data.Array.Unboxed.Mut
-- Text Processing
, Streamly.Unicode.Stream
if flag(dev)
exposed-modules:
Streamly.Internal.Data.Stream.StreamDK
@ -363,6 +372,7 @@ library
, ghc-prim >= 0.2 && < 0.10
, mtl >= 2.2 && < 2.3
, transformers >= 0.4 && < 0.7
, template-haskell >= 2.13 && < 2.20
, fusion-plugin-types >= 0.1 && < 0.2

View File

@ -221,6 +221,11 @@ extra-source-files:
core/src/Streamly/Data/Array/Unboxed/Mut.hs
core/src/Streamly/Internal/Data/Time/Clock/Darwin.c
core/src/Streamly/Internal/Data/Time/Clock/Windows.c
core/src/Streamly/Internal/Unicode/Array/Char.hs
core/src/Streamly/Internal/Unicode/Char/Parser.hs
core/src/Streamly/Internal/Unicode/Stream.hs
core/src/Streamly/Internal/Unicode/String.hs
core/src/Streamly/Unicode/Stream.hs
core/streamly-core.cabal
core/jsbits/clock.js
core/Setup.hs
@ -482,12 +487,8 @@ library
, Streamly.Internal.Data.Binary.Decode
-- streamly-unicode
, Streamly.Internal.Unicode.Stream
, Streamly.Internal.Unicode.String
, Streamly.Internal.Unicode.Utf8
, Streamly.Internal.Unicode.Char
, Streamly.Internal.Unicode.Char.Parser
, Streamly.Internal.Unicode.Array.Char
-- streamly-filesystem
, Streamly.Internal.FileSystem.Handle
@ -504,9 +505,6 @@ library
-- Exposed modules
, Streamly.Prelude
-- Text Processing
, Streamly.Unicode.Stream
-- Filesystem/IO
, Streamly.FileSystem.Handle
, Streamly.Console.Stdio
@ -573,13 +571,11 @@ library
, ghc-prim >= 0.2 && < 0.10
, mtl >= 2.2 && < 2.4
, transformers >= 0.4 && < 0.7
, template-haskell >= 2.13 && < 2.20
, monad-control
-- The core streamly package
, streamly-core == 0.1.0
, fusion-plugin-types >= 0.1 && < 0.2
, hashable >= 1.3 && < 1.5
, unordered-containers >= 0.2 && < 0.3