| Copyright | (c) 2022 Composewell Technologies |
|---|---|
| License | BSD-3-Clause |
| Maintainer | streamly@composewell.com |
| Stability | released |
| Portability | GHC |
| Safe Haskell | None |
| Language | Haskell2010 |
Streamly.Data.Stream.MkType
Description
Template Haskell macros to create custom newtype wrappers for the Stream
type. See the examples below to create the standard stream types that were
available in streamly versions before 0.9.0.
To use this module, the following extensions must be enabled:
>>>:set -XStandaloneDeriving>>>:set -XTemplateHaskell>>>:set -XTypeFamilies>>>:set -XUndecidableInstances
Import this module unqualified to bring everything needed in scope without
having to import several other modules. Also, Streamly.Data.Stream or
Streamly.Data.Stream.Prelude must be imported as Stream.
>>>import Streamly.Data.Stream.MkType>>>import qualified Streamly.Data.Stream.Prelude as Stream
We are describing below many useful types that can be created using macros in this module and the behavior of those types. These could be useful if you like to program using the monad "do notation" instead of using concatMap like operations.
Parallel
An unordered concurrent version of the serial Nested type. Runs multiple
iterations of the nested loops concurrently, iterations may execute out of
order. More outer iterations are started only if the existing inner
iterations are not saturating the resources.
>>>:{bind = flip (Stream.parConcatMap id) $(mkCrossType "Parallel" "bind" True) :}
This is a bounded concurrent, unordered list-transformer (ListT) monad.
WARNING! By design, monad bind of this type is not associative, because of concurrency order of effects as well as results may be unpredictable.
Same as the deprecated AsyncT type.
FairParallel
Like Parallel but strikes a balance between going deeper into existing iterations of the loop and starting new iterations.
>>>:{bind = flip (Stream.parConcatMap (Stream.interleaved True)) $(mkCrossType "FairParallel" "bind" True) :}
This is a bounded concurrent, fair logic programming (LogicT) monad.
WARNING! By design, monad bind of this type is not associative, because of concurrency order of effects as well as results may be unpredictable.
Same as the deprecated WAsyncT type.
EagerParallel
Like Parallel, but executes as many actions concurrently as possible. This is useful if you want all actions to be scheduled at the same time so that something does not get starved due to others.
>>>:{parBind = flip (Stream.parConcatMap (Stream.eager True)) $(mkCrossType "EagerParallel" "parBind" True) :}
This is an unbounded concurrent, unordered list transformer (ListT) monad.
WARNING! By design, monad bind of this type is not associative, because of concurrency order of effects as well as results may be unpredictable.
Same as the deprecated ParallelT type.
OrderedParallel
Like Parallel, runs many iterations concurrently, but stages the results such that the results of iterations are presented in the same order as specified in the code. This is closest to the serial Nested type in behavior among all the concurrent types.
>>>:{bind = flip (Stream.parConcatMap (Stream.ordered True)) $(mkCrossType "OrderedParallel" "bind" True) :}
This is a bounded concurrent, ordered list transformer (ListT) monad.
WARNING! Monad bind of this type is associative for values, but because of concurrency, order of effects may be unpredictable.
Same as the deprecated AheadT type.
Zip
An applicative type to zip two streams.
>>>:{zipApply = Stream.zipWith ($) $(mkZipType "Zip" "zipApply" False) :}
Same as the deprcated ZipSerialM type.
ParZip
Like Zip but evaluates the two streams concurrently.
>>>:{parCrossApply = Stream.parCrossApply id $(mkZipType "ParZip" "parCrossApply" True) :}
Same as the deprecated ZipAsync type.
Avoiding Template Haskell
Instead of using these macros directly you could copy and paste the generated code as well. Use these macros in ghci to generate the required code and paste it in your package, you can customize the code as desired. See the docs of the macros below for examples about how to view the generated code. For example:
>>>bind = flip (Stream.parConcatMap id)>>>expr <- runQ (mkCrossType "AsyncT" "bind" True)
> putStrLn $ pprint expr
Synopsis
- mkZipType :: String -> String -> Bool -> Q [Dec]
- mkCrossType :: String -> String -> Bool -> Q [Dec]
- class Read a where
- class Monad m => MonadIO (m :: Type -> Type) where
- class Monad m => MonadThrow (m :: Type -> Type) where
- throwM :: (HasCallStack, Exception e) => e -> m a
- class Monad m => MonadReader r (m :: Type -> Type) | m -> r where
- class (forall (m :: Type -> Type). Monad m => Monad (t m)) => MonadTrans (t :: (Type -> Type) -> Type -> Type) where
- data Identity a
- class IsList l
- class IsString a
- ap :: Monad m => m (a -> b) -> m a -> m b
Imports for Examples
>>>:m>>>import Language.Haskell.TH>>>import qualified Streamly.Data.Stream.Prelude as Stream>>>import Streamly.Data.Stream.MkType
Template Haskell Macros
Arguments
| :: String | Name of the type |
| -> String | Function to use for (<*>) |
| -> Bool |
|
| -> Q [Dec] |
Create a type with a zip-like applicative.
>>>expr <- runQ (mkZipType "ZipStream" "zipApply" False)>>>putStrLn $ pprint exprnewtype ZipStream m a = ZipStream (Stream.Stream m a) deriving Foldable mkZipStream :: Stream.Stream m a -> ZipStream m a mkZipStream = ZipStream unZipStream :: ZipStream m a -> Stream.Stream m a unZipStream (ZipStream strm) = strm deriving instance IsList (ZipStream Identity a) deriving instance a ~ GHC.Types.Char => IsString (ZipStream Identity a) deriving instance GHC.Classes.Eq a => Eq (ZipStream Identity a) deriving instance GHC.Classes.Ord a => Ord (ZipStream Identity a) instance Show a => Show (ZipStream Identity a) where {{-# INLINE show #-}; show (ZipStream strm) = show strm} instance Read a => Read (ZipStream Identity a) where {{-# INLINE readPrec #-}; readPrec = fmap ZipStream readPrec} instance Monad m => Functor (ZipStream m) where {{-# INLINE fmap #-}; fmap f (ZipStream strm) = ZipStream (fmap f strm)} instance Monad m => Applicative (ZipStream m) where {{-# INLINE pure #-}; pure = ZipStream . Stream.repeat; {-# INLINE (<*>) #-}; (<*>) (ZipStream strm1) (ZipStream strm2) = ZipStream (zipApply strm1 strm2)}
Arguments
| :: String | Name of the type |
| -> String | Function to use for (>>=) |
| -> Bool |
|
| -> Q [Dec] |
Create a type with specific stream combination properties.
>>>expr <- runQ (mkCrossType "Parallel" "parBind" True)>>>putStrLn $ pprint exprnewtype Parallel m a = Parallel (Stream.Stream m a) mkParallel :: Stream.Stream m a -> Parallel m a mkParallel = Parallel unParallel :: Parallel m a -> Stream.Stream m a unParallel (Parallel strm) = strm instance Monad m => Functor (Parallel m) where {{-# INLINE fmap #-}; fmap f (Parallel strm) = Parallel (fmap f strm)} instance Stream.MonadAsync m => Monad (Parallel m) where {{-# INLINE (>>=) #-}; (>>=) (Parallel strm1) f = let f1 a = unParallel (f a) in Parallel (parBind strm1 f1)} instance Stream.MonadAsync m => Applicative (Parallel m) where {{-# INLINE pure #-}; pure = Parallel . Stream.fromPure; {-# INLINE (<*>) #-}; (<*>) = ap} instance (Monad (Parallel m), MonadIO m) => MonadIO (Parallel m) where {{-# INLINE liftIO #-}; liftIO = Parallel . (Stream.fromEffect . liftIO)} instance (Monad (Parallel m), MonadThrow m) => MonadThrow (Parallel m) where {{-# INLINE throwM #-}; throwM = Parallel . (Stream.fromEffect . throwM)}
Re-exports
Parsing of Strings, producing values.
Derived instances of Read make the following assumptions, which
derived instances of Show obey:
- If the constructor is defined to be an infix operator, then the
derived
Readinstance will parse only infix applications of the constructor (not the prefix form). - Associativity is not used to reduce the occurrence of parentheses, although precedence may be.
- If the constructor is defined using record syntax, the derived
Readwill parse only the record-syntax form, and furthermore, the fields must be given in the same order as the original declaration. - The derived
Readinstance allows arbitrary Haskell whitespace between tokens of the input string. Extra parentheses are also allowed.
For example, given the declarations
infixr 5 :^: data Tree a = Leaf a | Tree a :^: Tree a
the derived instance of Read in Haskell 2010 is equivalent to
instance (Read a) => Read (Tree a) where
readsPrec d r = readParen (d > app_prec)
(\r -> [(Leaf m,t) |
("Leaf",s) <- lex r,
(m,t) <- readsPrec (app_prec+1) s]) r
++ readParen (d > up_prec)
(\r -> [(u:^:v,w) |
(u,s) <- readsPrec (up_prec+1) r,
(":^:",t) <- lex s,
(v,w) <- readsPrec (up_prec+1) t]) r
where app_prec = 10
up_prec = 5Note that right-associativity of :^: is unused.
The derived instance in GHC is equivalent to
instance (Read a) => Read (Tree a) where
readPrec = parens $ (prec app_prec $ do
Ident "Leaf" <- lexP
m <- step readPrec
return (Leaf m))
+++ (prec up_prec $ do
u <- step readPrec
Symbol ":^:" <- lexP
v <- step readPrec
return (u :^: v))
where app_prec = 10
up_prec = 5
readListPrec = readListPrecDefaultWhy do both readsPrec and readPrec exist, and why does GHC opt to
implement readPrec in derived Read instances instead of readsPrec?
The reason is that readsPrec is based on the ReadS type, and although
ReadS is mentioned in the Haskell 2010 Report, it is not a very efficient
parser data structure.
readPrec, on the other hand, is based on a much more efficient ReadPrec
datatype (a.k.a "new-style parsers"), but its definition relies on the use
of the RankNTypes language extension. Therefore, readPrec (and its
cousin, readListPrec) are marked as GHC-only. Nevertheless, it is
recommended to use readPrec instead of readsPrec whenever possible
for the efficiency improvements it brings.
As mentioned above, derived Read instances in GHC will implement
readPrec instead of readsPrec. The default implementations of
readsPrec (and its cousin, readList) will simply use readPrec under
the hood. If you are writing a Read instance by hand, it is recommended
to write it like so:
instanceReadT wherereadPrec= ...readListPrec=readListPrecDefault
Methods
Arguments
| :: Int | the operator precedence of the enclosing
context (a number from |
| -> ReadS a |
attempts to parse a value from the front of the string, returning a list of (parsed value, remaining string) pairs. If there is no successful parse, the returned list is empty.
Derived instances of Read and Show satisfy the following:
That is, readsPrec parses the string produced by
showsPrec, and delivers the value that
showsPrec started with.
The method readList is provided to allow the programmer to
give a specialised way of parsing lists of values.
For example, this is used by the predefined Read instance of
the Char type, where values of type String are expected to
use double quotes, rather than square brackets.
Proposed replacement for readsPrec using new-style parsers (GHC only).
readListPrec :: ReadPrec [a] #
Proposed replacement for readList using new-style parsers (GHC only).
The default definition uses readList. Instances that define readPrec
should also define readListPrec as readListPrecDefault.
Instances
class Monad m => MonadIO (m :: Type -> Type) where #
Monads in which IO computations may be embedded.
Any monad built by applying a sequence of monad transformers to the
IO monad will be an instance of this class.
Instances should satisfy the following laws, which state that liftIO
is a transformer of monads:
Methods
Lift a computation from the IO monad.
This allows us to run IO computations in any monadic stack, so long as it supports these kinds of operations
(i.e. IO is the base monad for the stack).
Example
import Control.Monad.Trans.State -- from the "transformers" library printState :: Show s => StateT s IO () printState = do state <- get liftIO $ print state
Had we omitted , we would have ended up with this error:liftIO
• Couldn't match type ‘IO’ with ‘StateT s IO’ Expected type: StateT s IO () Actual type: IO ()
The important part here is the mismatch between StateT s IO () and .IO ()
Luckily, we know of a function that takes an and returns an IO a(m a): ,
enabling us to run the program and see the expected results:liftIO
> evalStateT printState "hello" "hello" > evalStateT printState 3 3
Instances
class Monad m => MonadThrow (m :: Type -> Type) where #
A class for monads in which exceptions may be thrown.
Instances should obey the following law:
throwM e >> x = throwM e
In other words, throwing an exception short-circuits the rest of the monadic computation.
Methods
throwM :: (HasCallStack, Exception e) => e -> m a #
Throw an exception. Note that this throws when this action is run in
the monad m, not when it is applied. It is a generalization of
Control.Exception's throwIO.
Should satisfy the law:
throwM e >> f = throwM e
Instances
class Monad m => MonadReader r (m :: Type -> Type) | m -> r where #
See examples in Control.Monad.Reader.
Note, the partially applied function type (->) r is a simple reader monad.
See the instance declaration below.
Methods
Retrieves the monad environment.
Arguments
| :: (r -> r) | The function to modify the environment. |
| -> m a |
|
| -> m a |
Executes a computation in a modified environment.
Arguments
| :: (r -> a) | The selector function to apply to the environment. |
| -> m a |
Retrieves a function of the current environment.
Instances
class (forall (m :: Type -> Type). Monad m => Monad (t m)) => MonadTrans (t :: (Type -> Type) -> Type -> Type) where #
The class of monad transformers.
For any monad m, the result t m should also be a monad,
and lift should be a monad transformation from m to t m,
i.e. it should satisfy the following laws:
Since 0.6.0.0 and for GHC 8.6 and later, the requirement that t m
be a Monad is enforced by the implication constraint
forall m. enabled by the
Monad m => Monad (t m)QuantifiedConstraints extension.
Ambiguity error with GHC 9.0 to 9.2.2
These versions of GHC have a bug (https://gitlab.haskell.org/ghc/ghc/-/issues/20582) which causes constraints like
(MonadTrans t, forall m. Monad m => Monad (t m)) => ...
to be reported as ambiguous. For transformers 0.6 and later, this can be fixed by removing the second constraint, which is implied by the first.
Methods
lift :: Monad m => m a -> t m a #
Lift a computation from the argument monad to the constructed monad.
Instances
Identity functor and monad. (a non-strict monad)
Since: base-4.8.0.0
Instances
The IsList class and its methods are intended to be used in
conjunction with the OverloadedLists extension.
Since: base-4.7.0.0
Instances
| IsList ByteArray | Since: base-4.17.0.0 | ||||
| IsList Version | Since: base-4.8.0.0 | ||||
| IsList CallStack | Be aware that 'fromList . toList = id' only for unfrozen Since: base-4.9.0.0 | ||||
| IsList ByteString | Since: bytestring-0.10.12.0 | ||||
Defined in Data.ByteString.Internal.Type Associated Types
Methods fromList :: [Item ByteString] -> ByteString # fromListN :: Int -> [Item ByteString] -> ByteString # toList :: ByteString -> [Item ByteString] # | |||||
| IsList ByteString | Since: bytestring-0.10.12.0 | ||||
Defined in Data.ByteString.Lazy.Internal Associated Types
Methods fromList :: [Item ByteString] -> ByteString # fromListN :: Int -> [Item ByteString] -> ByteString # toList :: ByteString -> [Item ByteString] # | |||||
| IsList ShortByteString | Since: bytestring-0.10.12.0 | ||||
Defined in Data.ByteString.Short.Internal Associated Types
Methods fromList :: [Item ShortByteString] -> ShortByteString # fromListN :: Int -> [Item ShortByteString] -> ShortByteString # toList :: ShortByteString -> [Item ShortByteString] # | |||||
| IsList IntSet | Since: containers-0.5.6.2 | ||||
| IsList (ZipList a) | Since: base-4.15.0.0 | ||||
| IsList (NonEmpty a) | Since: base-4.9.0.0 | ||||
| IsList (IntMap a) | Since: containers-0.5.6.2 | ||||
| IsList (Seq a) | |||||
| Ord a => IsList (Set a) | Since: containers-0.5.6.2 | ||||
| IsList (Array a) | |||||
| Unbox a => IsList (Array a) | |||||
| (Eq a, Hashable a) => IsList (HashSet a) | |||||
| IsList [a] | Since: base-4.7.0.0 | ||||
| Ord k => IsList (Map k v) | Since: containers-0.5.6.2 | ||||
| IsList (SerialT Identity a) Source # | |||||
Defined in Streamly.Internal.Data.Stream.Serial Associated Types
| |||||
| IsList (WSerialT Identity a) Source # | |||||
Defined in Streamly.Internal.Data.Stream.Serial Associated Types
| |||||
| IsList (ZipSerialM Identity a) Source # | |||||
Defined in Streamly.Internal.Data.Stream.Zip Associated Types
Methods fromList :: [Item (ZipSerialM Identity a)] -> ZipSerialM Identity a # fromListN :: Int -> [Item (ZipSerialM Identity a)] -> ZipSerialM Identity a # toList :: ZipSerialM Identity a -> [Item (ZipSerialM Identity a)] # | |||||
| IsList (Nested Identity a) | |||||
Defined in Streamly.Internal.Data.Stream.Type | |||||
| IsList (Stream Identity a) | |||||
Defined in Streamly.Internal.Data.Stream.Type Associated Types
| |||||
| IsList (FairNested Identity a) | |||||
Defined in Streamly.Internal.Data.StreamK.Type Associated Types
Methods fromList :: [Item (FairNested Identity a)] -> FairNested Identity a # fromListN :: Int -> [Item (FairNested Identity a)] -> FairNested Identity a # toList :: FairNested Identity a -> [Item (FairNested Identity a)] # | |||||
| IsList (Nested Identity a) | |||||
Defined in Streamly.Internal.Data.StreamK.Type | |||||
| IsList (StreamK Identity a) | |||||
Defined in Streamly.Internal.Data.StreamK.Type Associated Types
| |||||
| (Eq k, Hashable k) => IsList (HashMap k v) | |||||
Defined in Data.HashMap.Internal Associated Types
| |||||
IsString is used in combination with the -XOverloadedStrings
language extension to convert the literals to different string types.
For example, if you use the text package, you can say
{-# LANGUAGE OverloadedStrings #-}
myText = "hello world" :: Text
Internally, the extension will convert this to the equivalent of
myText = fromString @Text ("hello world" :: String)
Note: You can use fromString in normal code as well,
but the usual performance/memory efficiency problems with String apply.
Minimal complete definition
Instances
| IsString ByteString | Beware: |
Defined in Data.ByteString.Internal.Type Methods fromString :: String -> ByteString # | |
| IsString ByteString | Beware: |
Defined in Data.ByteString.Lazy.Internal Methods fromString :: String -> ByteString # | |
| IsString ShortByteString | Beware: |
Defined in Data.ByteString.Short.Internal Methods fromString :: String -> ShortByteString # | |
| IsString Doc | |
Defined in Text.PrettyPrint.HughesPJ Methods fromString :: String -> Doc # | |
| IsString a => IsString (Identity a) | Since: base-4.9.0.0 |
Defined in Data.String Methods fromString :: String -> Identity a # | |
| a ~ Char => IsString (Seq a) | Since: containers-0.5.7 |
Defined in Data.Sequence.Internal Methods fromString :: String -> Seq a # | |
| (IsString a, Hashable a) => IsString (Hashed a) | |
Defined in Data.Hashable.Class Methods fromString :: String -> Hashed a # | |
| IsString (Doc a) | |
Defined in Text.PrettyPrint.Annotated.HughesPJ Methods fromString :: String -> Doc a # | |
| a ~ Char => IsString (Array a) | |
Defined in Streamly.Internal.Data.Array.Type Methods fromString :: String -> Array a # | |
| a ~ Char => IsString [a] |
Since: base-2.1 |
Defined in Data.String Methods fromString :: String -> [a] # | |
| a ~ Char => IsString (SerialT Identity a) Source # | |
Defined in Streamly.Internal.Data.Stream.Serial Methods fromString :: String -> SerialT Identity a # | |
| a ~ Char => IsString (WSerialT Identity a) Source # | |
Defined in Streamly.Internal.Data.Stream.Serial Methods fromString :: String -> WSerialT Identity a # | |
| a ~ Char => IsString (ZipSerialM Identity a) Source # | |
Defined in Streamly.Internal.Data.Stream.Zip Methods fromString :: String -> ZipSerialM Identity a # | |
| a ~ Char => IsString (Nested Identity a) | |
Defined in Streamly.Internal.Data.Stream.Type Methods fromString :: String -> Nested Identity a # | |
| a ~ Char => IsString (Stream Identity a) | |
Defined in Streamly.Internal.Data.Stream.Type Methods fromString :: String -> Stream Identity a # | |
| a ~ Char => IsString (FairNested Identity a) | |
Defined in Streamly.Internal.Data.StreamK.Type Methods fromString :: String -> FairNested Identity a # | |
| a ~ Char => IsString (Nested Identity a) | |
Defined in Streamly.Internal.Data.StreamK.Type Methods fromString :: String -> Nested Identity a # | |
| a ~ Char => IsString (StreamK Identity a) | |
Defined in Streamly.Internal.Data.StreamK.Type Methods fromString :: String -> StreamK Identity a # | |
| IsString a => IsString (Const a b) | Since: base-4.9.0.0 |
Defined in Data.String Methods fromString :: String -> Const a b # | |