Safe Haskell | Safe |
---|---|
Language | Haskell2010 |
Synopsis
- newtype SourceT m a = SourceT {}
- mapStepT :: (StepT m a -> StepT m b) -> SourceT m a -> SourceT m b
- data StepT m a
- fromStepT :: StepT m a -> SourceT m a
- source :: [a] -> SourceT m a
- runSourceT :: Monad m => SourceT m a -> ExceptT String m [a]
- runStepT :: Monad m => StepT m a -> ExceptT String m [a]
- mapMaybe :: Functor m => (a -> Maybe b) -> SourceT m a -> SourceT m b
- mapMaybeStep :: Functor m => (a -> Maybe b) -> StepT m a -> StepT m b
- foreach :: Monad m => (String -> m ()) -> (a -> m ()) -> SourceT m a -> m ()
- foreachStep :: Monad m => (String -> m ()) -> (a -> m ()) -> StepT m a -> m ()
- fromAction :: Functor m => (a -> Bool) -> m a -> SourceT m a
- fromActionStep :: Functor m => (a -> Bool) -> m a -> StepT m a
- readFile :: FilePath -> SourceT IO ByteString
- transformWithAtto :: Monad m => Parser a -> SourceT m ByteString -> SourceT m a
- transformStepWithAtto :: forall a m. Monad m => Parser a -> StepT m ByteString -> StepT m a
Documentation
>>>
:set -XOverloadedStrings
>>>
import Control.Monad.Except (runExcept)
>>>
import Data.Foldable (toList)
>>>
import qualified Data.Attoparsec.ByteString.Char8 as A8
This is CPSised ListT.
Since: 0.15
Instances
MonadIO m => FromSourceIO a (SourceT m a) Source # | |
Defined in Servant.API.Stream fromSourceIO :: SourceIO a -> SourceT m a Source # | |
SourceToSourceIO m => ToSourceIO chunk (SourceT m chunk) Source # | Relax to use auxiliary class, have m |
Defined in Servant.API.Stream toSourceIO :: SourceT m chunk -> SourceIO chunk Source # | |
Functor m => Functor (SourceT m) Source # | |
Identity ~ m => Foldable (SourceT m) Source # |
|
Defined in Servant.Types.SourceT fold :: Monoid m0 => SourceT m m0 -> m0 # foldMap :: Monoid m0 => (a -> m0) -> SourceT m a -> m0 # foldr :: (a -> b -> b) -> b -> SourceT m a -> b # foldr' :: (a -> b -> b) -> b -> SourceT m a -> b # foldl :: (b -> a -> b) -> b -> SourceT m a -> b # foldl' :: (b -> a -> b) -> b -> SourceT m a -> b # foldr1 :: (a -> a -> a) -> SourceT m a -> a # foldl1 :: (a -> a -> a) -> SourceT m a -> a # toList :: SourceT m a -> [a] # length :: SourceT m a -> Int # elem :: Eq a => a -> SourceT m a -> Bool # maximum :: Ord a => SourceT m a -> a # minimum :: Ord a => SourceT m a -> a # | |
(Applicative m, Show1 m) => Show1 (SourceT m) Source # | |
MFunctor SourceT Source # |
|
(Applicative m, Show1 m, Show a) => Show (SourceT m a) Source # | |
(Arbitrary a, Monad m) => Arbitrary (SourceT m a) Source # | Doesn't generate |
ListT
with additional constructors.
Since: 0.15
Instances
MonadTrans StepT Source # |
|
Defined in Servant.Types.SourceT | |
Functor m => Functor (StepT m) Source # | |
Identity ~ m => Foldable (StepT m) Source # | |
Defined in Servant.Types.SourceT fold :: Monoid m0 => StepT m m0 -> m0 # foldMap :: Monoid m0 => (a -> m0) -> StepT m a -> m0 # foldr :: (a -> b -> b) -> b -> StepT m a -> b # foldr' :: (a -> b -> b) -> b -> StepT m a -> b # foldl :: (b -> a -> b) -> b -> StepT m a -> b # foldl' :: (b -> a -> b) -> b -> StepT m a -> b # foldr1 :: (a -> a -> a) -> StepT m a -> a # foldl1 :: (a -> a -> a) -> StepT m a -> a # elem :: Eq a => a -> StepT m a -> Bool # maximum :: Ord a => StepT m a -> a # minimum :: Ord a => StepT m a -> a # | |
(Applicative m, Show1 m) => Show1 (StepT m) Source # | |
MFunctor StepT Source # | |
(Applicative m, Show1 m, Show a) => Show (StepT m a) Source # | |
(Arbitrary a, Monad m) => Arbitrary (StepT m a) Source # | Doesn't generate |
source :: [a] -> SourceT m a Source #
Create pure SourceT
.
>>>
source "foo" :: SourceT Identity Char
fromStepT (Effect (Identity (Yield 'f' (Yield 'o' (Yield 'o' Stop)))))
runSourceT :: Monad m => SourceT m a -> ExceptT String m [a] Source #
Get the answers.
>>>
runSourceT (source "foo" :: SourceT Identity Char)
ExceptT (Identity (Right "foo"))
>>>
runSourceT (source "foo" :: SourceT [] Char)
ExceptT [Right "foo"]
mapMaybe :: Functor m => (a -> Maybe b) -> SourceT m a -> SourceT m b Source #
Filter values.
>>>
toList $ mapMaybe (\x -> if odd x then Just x else Nothing) (source [0..10]) :: [Int]
[1,3,5,7,9]
>>>
mapMaybe (\x -> if odd x then Just x else Nothing) (source [0..2]) :: SourceT Identity Int
fromStepT (Effect (Identity (Skip (Yield 1 (Skip Stop)))))
Illustrates why we need Skip
.
Run action for each value in the SourceT
.
>>>
foreach fail print (source "abc")
'a' 'b' 'c'
See foreach
.
readFile :: FilePath -> SourceT IO ByteString Source #
Read file.
>>>
foreach fail BS.putStr (readFile "servant.cabal")
cabal-version: >=1.10 name: servant ...
transformWithAtto :: Monad m => Parser a -> SourceT m ByteString -> SourceT m a Source #
Transform using attoparsec
parser.
Note: parser
should not accept empty input!
>>>
let parser = A.skipWhile A8.isSpace_w8 >> A.takeWhile1 A8.isDigit_w8
>>>
runExcept $ runSourceT $ transformWithAtto parser (source ["1 2 3"])
Right ["1","2","3"]
>>>
runExcept $ runSourceT $ transformWithAtto parser (source ["1", "2", "3"])
Right ["123"]
>>>
runExcept $ runSourceT $ transformWithAtto parser (source ["1", "2 3", "4"])
Right ["12","34"]
>>>
runExcept $ runSourceT $ transformWithAtto parser (source ["foobar"])
Left "Failed reading: takeWhile1"
transformStepWithAtto :: forall a m. Monad m => Parser a -> StepT m ByteString -> StepT m a Source #