aboutsummaryrefslogtreecommitdiffhomepage
diff options
context:
space:
mode:
authormichaelt <what_is_it_to_do_anything@yahoo.com>2014-11-12 00:03:36 -0500
committermichaelt <what_is_it_to_do_anything@yahoo.com>2014-11-12 00:03:36 -0500
commitb091cbebda25acfac35c19748c607d26c01b68ec (patch)
tree0e2766f966f31cc157199c1693560dfe173c5062
parent6c2fffdc8bc84879e103e6838e4f9fc762d50a2d (diff)
downloadtext-pipes-b091cbebda25acfac35c19748c607d26c01b68ec.tar.gz
text-pipes-b091cbebda25acfac35c19748c607d26c01b68ec.tar.zst
text-pipes-b091cbebda25acfac35c19748c607d26c01b68ec.zip
tutorial nonsense
-rw-r--r--Pipes/Text/Encoding.hs10
-rw-r--r--Pipes/Text/IO.hs3
-rw-r--r--Pipes/Text/Tutorial.hs73
3 files changed, 57 insertions, 29 deletions
diff --git a/Pipes/Text/Encoding.hs b/Pipes/Text/Encoding.hs
index f26f168..97a9c23 100644
--- a/Pipes/Text/Encoding.hs
+++ b/Pipes/Text/Encoding.hs
@@ -1,10 +1,9 @@
1{-# LANGUAGE RankNTypes, BangPatterns #-} 1{-# LANGUAGE RankNTypes, BangPatterns #-}
2 2
3-- | This module uses the stream decoding functions from Michael Snoyman's new 3-- | This module uses the stream decoding functions from
4-- <http://hackage.haskell.org/package/text-stream-decode text-stream-decode> 4-- <http://hackage.haskell.org/package/text-stream-decode text-stream-decode>
5-- package to define decoding functions and lenses. The exported names 5-- package to define decoding functions and lenses. The exported names
6-- conflict with names in @Data.Text.Encoding@ but the module can otherwise be 6-- conflict with names in @Data.Text.Encoding@ but not with the @Prelude@
7-- imported unqualified.
8 7
9module Pipes.Text.Encoding 8module Pipes.Text.Encoding
10 ( 9 (
@@ -55,7 +54,7 @@ import qualified Data.Text as T
55import qualified Data.Text.Encoding as TE 54import qualified Data.Text.Encoding as TE
56import qualified Data.Streaming.Text as Stream 55import qualified Data.Streaming.Text as Stream
57import Data.Streaming.Text (DecodeResult(..)) 56import Data.Streaming.Text (DecodeResult(..))
58import Control.Monad (join) 57import Control.Monad (join, liftM)
59import Data.Word (Word8) 58import Data.Word (Word8)
60import Pipes 59import Pipes
61 60
@@ -71,8 +70,7 @@ type Lens' a b = forall f . Functor f => (b -> f b) -> (a -> f a)
71 70
72 is just an alias for a Prelude type. Thus you use any particular codec with 71 is just an alias for a Prelude type. Thus you use any particular codec with
73 the @view@ / @(^.)@ , @zoom@ and @over@ functions from either of those libraries; 72 the @view@ / @(^.)@ , @zoom@ and @over@ functions from either of those libraries;
74 we presuppose neither since we already have access to the types they require. 73 we presuppose neither library since we already have access to the types they require.
75
76 -} 74 -}
77 75
78type Codec 76type Codec
diff --git a/Pipes/Text/IO.hs b/Pipes/Text/IO.hs
index de49c7b..4a092b1 100644
--- a/Pipes/Text/IO.hs
+++ b/Pipes/Text/IO.hs
@@ -169,9 +169,6 @@ toHandle :: MonadIO m => IO.Handle -> Consumer' Text m r
169toHandle h = for cat (liftIO . T.hPutStr h) 169toHandle h = for cat (liftIO . T.hPutStr h)
170{-# INLINABLE toHandle #-} 170{-# INLINABLE toHandle #-}
171 171
172{-# RULES "p >-> toHandle h" forall p h .
173 p >-> toHandle h = for p (\txt -> liftIO (T.hPutStr h txt))
174 #-}
175 172
176 173
177-- | Stream text into a file. Uses @pipes-safe@. 174-- | Stream text into a file. Uses @pipes-safe@.
diff --git a/Pipes/Text/Tutorial.hs b/Pipes/Text/Tutorial.hs
index 25f9e41..b021d73 100644
--- a/Pipes/Text/Tutorial.hs
+++ b/Pipes/Text/Tutorial.hs
@@ -3,12 +3,19 @@
3module Pipes.Text.Tutorial ( 3module Pipes.Text.Tutorial (
4 -- * Effectful Text 4 -- * Effectful Text
5 -- $intro 5 -- $intro
6
6 -- ** @Pipes.Text@ 7 -- ** @Pipes.Text@
7 -- $pipestext 8 -- $pipestext
9
8 -- ** @Pipes.Text.IO@ 10 -- ** @Pipes.Text.IO@
9 -- $pipestextio 11 -- $pipestextio
12
10 -- ** @Pipes.Text.Encoding@ 13 -- ** @Pipes.Text.Encoding@
11 -- $pipestextencoding 14 -- $pipestextencoding
15
16 -- ** Implicit chunking
17 -- $chunks
18
12 -- * Lenses 19 -- * Lenses
13 -- $lenses 20 -- $lenses
14 21
@@ -20,6 +27,9 @@ module Pipes.Text.Tutorial (
20 27
21 -- ** @zoom@ 28 -- ** @zoom@
22 -- $zoom 29 -- $zoom
30
31
32
23 33
24 -- * Special types: @Producer Text m (Producer Text m r)@ and @FreeT (Producer Text m) m r@ 34 -- * Special types: @Producer Text m (Producer Text m r)@ and @FreeT (Producer Text m) m r@
25 -- $special 35 -- $special
@@ -36,7 +46,9 @@ import Pipes.Text.Encoding
36 and thus the @Text@ type we are using is the one from @Data.Text@, not @Data.Text.Lazy@ 46 and thus the @Text@ type we are using is the one from @Data.Text@, not @Data.Text.Lazy@
37 But the type @Producer Text m r@, as we are using it, is a sort of /pipes/ equivalent of 47 But the type @Producer Text m r@, as we are using it, is a sort of /pipes/ equivalent of
38 the lazy @Text@ type. 48 the lazy @Text@ type.
49-}
39 50
51{- $pipestext
40 The main @Pipes.Text@ module provides many functions equivalent 52 The main @Pipes.Text@ module provides many functions equivalent
41 in one way or another to the pure functions in 53 in one way or another to the pure functions in
42 <https://hackage.haskell.org/package/text-1.1.0.0/docs/Data-Text-Lazy.html Data.Text.Lazy> 54 <https://hackage.haskell.org/package/text-1.1.0.0/docs/Data-Text-Lazy.html Data.Text.Lazy>
@@ -44,17 +56,28 @@ import Pipes.Text.Encoding
44 divide, group and fold text streams. Though @Producer Text m r@ 56 divide, group and fold text streams. Though @Producer Text m r@
45 is the type of \'effectful Text\', the functions in @Pipes.Text@ are \'pure\' 57 is the type of \'effectful Text\', the functions in @Pipes.Text@ are \'pure\'
46 in the sense that they are uniformly monad-independent. 58 in the sense that they are uniformly monad-independent.
59-}
60
61{- $pipestextencoding
62 In the @text@ library, @Data.Text.Lazy.Encoding@
63 handles inter-operation with @Data.ByteString.Lazy@. Here, @Pipes.Text.Encoding@
64 provides for interoperation with the \'effectful ByteStrings\' of @Pipes.ByteString@.
65-}
66
67{- $pipestextio
47 Simple /IO/ operations are defined in @Pipes.Text.IO@ - as lazy IO @Text@ 68 Simple /IO/ operations are defined in @Pipes.Text.IO@ - as lazy IO @Text@
48 operations are in @Data.Text.Lazy.IO@. Similarly, as @Data.Text.Lazy.Encoding@ 69 operations are in @Data.Text.Lazy.IO@. It is generally
49 handles inter-operation with @Data.ByteString.Lazy@, @Pipes.Text.Encoding@ provides for 70-}
50 interoperation with the \'effectful ByteStrings\' of @Pipes.ByteString@.
51 71
72
73{- $chunks
52 Remember that the @Text@ type exported by @Data.Text.Lazy@ is basically 74 Remember that the @Text@ type exported by @Data.Text.Lazy@ is basically
53 that of a lazy list of strict @Text@: the implementation is arranged so that 75 that of a lazy list of strict @Text@: the implementation is arranged so that
54 the individual strict 'Text' chunks are kept to a reasonable size; the user 76 the individual strict 'Text' chunks are kept to a reasonable size; the user
55 is not aware of the divisions between the connected 'Text' chunks, but uses 77 is not aware of the divisions between the connected 'Text' chunks, but uses
56 operations akin to those for strict text. 78 operations akin to those for strict text.
57 So also here: the functions in this module are designed to operate on character streams that 79
80 So also here: the operations in @Pipes.Text@ are designed to operate on character streams that
58 in a way that is independent of the boundaries of the underlying @Text@ chunks. 81 in a way that is independent of the boundaries of the underlying @Text@ chunks.
59 This means that they may freely split text into smaller texts and /discard empty texts/. 82 This means that they may freely split text into smaller texts and /discard empty texts/.
60 The objective, though, is that they should not /concatenate texts/ in order to provide strict upper 83 The objective, though, is that they should not /concatenate texts/ in order to provide strict upper
@@ -67,16 +90,20 @@ import Pipes.Text.Encoding
67> import qualified Pipes.Text as Text 90> import qualified Pipes.Text as Text
68> import qualified Pipes.Text.IO as Text 91> import qualified Pipes.Text.IO as Text
69> import Pipes.Group (takes') 92> import Pipes.Group (takes')
70> import Lens.Family (view) 93> import Lens.Family (view, (%~)) -- or, Control.Lens
71> 94>
72> main = runEffect $ takeLines 3 Text.stdin >-> Text.stdout 95> main = runEffect $ takeLines 3 Text.stdin >-> Text.stdout
73> where 96> where
74> takeLines n = view Text.unlines . takes' n . view Text.lines 97> takeLines n = view Text.unlines . takes' n . view Text.lines
98> -- or equivalently: Text.unlines %~ takes' n
75 99
76 This program will never bring more into memory than what @Text.stdin@ considers 100 This program will not bring more into memory than what @Text.stdin@ considers
77 one chunk of text (~ 32 KB), even if individual lines are split across many chunks. 101 one chunk of text (~ 32 KB), even if individual lines are split
102 across many chunks. The division into lines does not join Text fragments.
78 103
79-} 104-}
105
106
80{- $lenses 107{- $lenses
81 As the use of @view@ in this example shows, one superficial difference from @Data.Text.Lazy@ 108 As the use of @view@ in this example shows, one superficial difference from @Data.Text.Lazy@
82 is that many of the operations, like 'lines', are \'lensified\'; this has a 109 is that many of the operations, like 'lines', are \'lensified\'; this has a
@@ -90,7 +117,7 @@ import Pipes.Text.Encoding
90 117
91 > splitAt 17 producer 118 > splitAt 17 producer
92 119
93 as we would with the Prelude or Text functions, we write 120 as we would with the Prelude or Text functions called @splitAt@, we write
94 121
95 > view (splitAt 17) producer 122 > view (splitAt 17) producer
96 123
@@ -110,7 +137,7 @@ import Pipes.Text.Encoding
110 they don't admit all the operations of an ideal lens, but only /getting/ and /focusing/. 137 they don't admit all the operations of an ideal lens, but only /getting/ and /focusing/.
111 Just for this reason, though, the magnificent complexities of the lens libraries 138 Just for this reason, though, the magnificent complexities of the lens libraries
112 are a distraction. The lens combinators to keep in mind, the ones that make sense for 139 are a distraction. The lens combinators to keep in mind, the ones that make sense for
113 our lenses, are @view@ \/ @(^.)@), @over@ \/ @(%~)@ , and @zoom@. 140 our lenses, are @view@, @over@, and @zoom@.
114 141
115 One need only keep in mind that if @l@ is a @Lens' a b@, then: 142 One need only keep in mind that if @l@ is a @Lens' a b@, then:
116 143
@@ -120,7 +147,6 @@ import Pipes.Text.Encoding
120 is the corresponding @b@; as was said above, this function will typically be 147 is the corresponding @b@; as was said above, this function will typically be
121 the pipes equivalent of the function you think it is, given its name. So for example 148 the pipes equivalent of the function you think it is, given its name. So for example
122 149
123 > view (Text.drop)
124 > view (Text.splitAt 300) :: Producer Text m r -> Producer Text (Producer Text m r) 150 > view (Text.splitAt 300) :: Producer Text m r -> Producer Text (Producer Text m r)
125 > Text.stdin ^. splitAt 300 :: Producer Text IO (Producer Text IO r) 151 > Text.stdin ^. splitAt 300 :: Producer Text IO (Producer Text IO r)
126 152
@@ -128,23 +154,29 @@ import Pipes.Text.Encoding
128 Thus to uppercase the first n characters 154 Thus to uppercase the first n characters
129 of a Producer, leaving the rest the same, we could write: 155 of a Producer, leaving the rest the same, we could write:
130 156
131
132 > upper n p = do p' <- p ^. Text.splitAt n >-> Text.toUpper 157 > upper n p = do p' <- p ^. Text.splitAt n >-> Text.toUpper
133 > p' 158 > p'
159
160 or equivalently:
161
162 > upper n p = join (p ^. Text.splitAt n >-> Text.toUpper)
163
134-} 164-}
135{- $over 165{- $over
136 @over l@ is a function @(b -> b) -> a -> a@. Thus, given a function that modifies 166 If @l@ is a @Lens a b@, @over l@ is a function @(b -> b) -> a -> a@.
167 Thus, given a function that modifies
137 @b@s, the lens lets us modify an @a@ by applying @f :: b -> b@ to 168 @b@s, the lens lets us modify an @a@ by applying @f :: b -> b@ to
138 the @b@ that we can \"see\" through the lens. So @over l f :: a -> a@ 169 the @b@ that we \"see\" in the @a@ through the lens.
170 So the type of @over l f@ is @a -> a@ for the concrete type @a@
139 (it can also be written @l %~ f@). 171 (it can also be written @l %~ f@).
140 For any particular @a@, then, @over l f a@ or @(l %~ f) a@ is a revised @a@. 172 For any particular @a@, then, @over l f a@ or @(l %~ f) a@ is a revised @a@.
141 So above we might have written things like these: 173 So above we might have written things like these:
142 174
143 > stripLines = Text.lines %~ maps (>-> Text.stripStart)
144 > stripLines = over Text.lines (maps (>-> Text.stripStart)) 175 > stripLines = over Text.lines (maps (>-> Text.stripStart))
176 > stripLines = Text.lines %~ maps (>-> Text.stripStart)
145 > upper n = Text.splitAt n %~ (>-> Text.toUpper) 177 > upper n = Text.splitAt n %~ (>-> Text.toUpper)
146
147-} 178-}
179
148{- $zoom 180{- $zoom
149 @zoom l@, finally, is a function from a @Parser b m r@ 181 @zoom l@, finally, is a function from a @Parser b m r@
150 to a @Parser a m r@ (or more generally a @StateT (Producer b m x) m r@). 182 to a @Parser a m r@ (or more generally a @StateT (Producer b m x) m r@).
@@ -169,9 +201,9 @@ import Pipes.Text.Encoding
169> p' 201> p'
170 202
171 203
172> >>> let doc = each ["toU","pperTh","is document.\n"] 204> -- > let doc = each ["toU","pperTh","is document.\n"]
173> >>> runEffect $ obey doc >-> Text.stdout 205> -- > runEffect $ obey doc >-> Text.stdout
174> THIS DOCUMENT. 206> -- THIS DOCUMENT.
175 207
176 The purpose of exporting lenses is the mental economy achieved with this three-way 208 The purpose of exporting lenses is the mental economy achieved with this three-way
177 applicability. That one expression, e.g. @lines@ or @splitAt 17@ can have these 209 applicability. That one expression, e.g. @lines@ or @splitAt 17@ can have these
@@ -187,8 +219,9 @@ import Pipes.Text.Encoding
187 and to some extent in the @Pipes.Text.Encoding@ module here. 219 and to some extent in the @Pipes.Text.Encoding@ module here.
188 220
189-} 221-}
222
190{- $special 223{- $special
191 These simple 'lines' examples reveal a more important difference from @Data.Text.Lazy@ . 224 The simple programs using the 'lines' lens reveal a more important difference from @Data.Text.Lazy@ .
192 This is in the types that are most closely associated with our central text type, 225 This is in the types that are most closely associated with our central text type,
193 @Producer Text m r@. In @Data.Text@ and @Data.Text.Lazy@ we find functions like 226 @Producer Text m r@. In @Data.Text@ and @Data.Text.Lazy@ we find functions like
194 227