remove trailing white space

This commit is contained in:
Andrew Martin 2016-07-05 11:32:01 -04:00
parent e17df21a2b
commit 3ae2f973d4
9 changed files with 38 additions and 38 deletions

View File

@ -62,7 +62,7 @@ uncheckedRun dc v = getEitherWrap (go dc)
rcurrent = mapLeft (DecodingCellErrors . Vector.singleton . DecodingCellError content ixed) (decode content)
in rnext <*> (EitherWrap rcurrent)
headlessToIndexed :: forall c a.
headlessToIndexed :: forall c a.
Decoding Headless c a -> Decoding (Indexed Headless) c a
headlessToIndexed = go 0 where
go :: forall b. Int -> Decoding Headless c b -> Decoding (Indexed Headless) c b
@ -71,7 +71,7 @@ headlessToIndexed = go 0 where
DecodingAp (Indexed ix Headless) decode (go (ix + 1) apNext)
length :: forall f c a. Decoding f c a -> Int
length = go 0 where
length = go 0 where
go :: forall b. Int -> Decoding f c b -> Int
go !a (DecodingPure _) = a
go !a (DecodingAp _ _ apNext) = go (a + 1) apNext

View File

@ -21,26 +21,26 @@ headed h f = Encoding (Vector.singleton (OneEncoding (Headed h) f))
-- instead. It may allow more things to get inlined
-- in to a loop.
runRow :: (c1 -> c2) -> Encoding f c1 a -> a -> Vector c2
runRow g (Encoding v) a = flip Vector.map v $
runRow g (Encoding v) a = flip Vector.map v $
\(OneEncoding _ encode) -> g (encode a)
runRowMonadic :: Monad m
=> Encoding f content a
-> (content -> m ())
-> a
runRowMonadic :: Monad m
=> Encoding f content a
-> (content -> m ())
-> a
-> m ()
runRowMonadic (Encoding v) g a = Vector.forM_ v $ \e ->
runRowMonadic (Encoding v) g a = Vector.forM_ v $ \e ->
g (oneEncodingEncode e a)
runHeader :: (c1 -> c2) -> Encoding Headed c1 a -> Vector c2
runHeader g (Encoding v) =
runHeader g (Encoding v) =
Vector.map (g . getHeaded . oneEncodingHead) v
runHeaderMonadic :: Monad m
=> Encoding Headed content a
-> (content -> m ())
runHeaderMonadic :: Monad m
=> Encoding Headed content a
-> (content -> m ())
-> m ()
runHeaderMonadic (Encoding v) g =
runHeaderMonadic (Encoding v) g =
Vector.mapM_ (g . getHeaded . oneEncodingHead) v

View File

@ -107,7 +107,7 @@ instance Contravariant (OneEncoding f content) where
contramap f (OneEncoding h e) = OneEncoding h (e . f)
newtype Encoding f content a = Encoding
{ getEncoding :: Vector (OneEncoding f content a)
{ getEncoding :: Vector (OneEncoding f content a)
} deriving (Monoid)
instance Contravariant (Encoding f content) where

View File

@ -33,7 +33,7 @@ elFromCell :: MonadWidget t m => String -> Cell m -> m ()
elFromCell name (Cell attrs contents) = elAttr name attrs contents
theadBuild :: MonadWidget t m => Encoding Headed (Cell m) a -> m ()
theadBuild encoding = el "thead" . el "tr"
theadBuild encoding = el "thead" . el "tr"
$ Encoding.runHeaderMonadic encoding (elFromCell "th")
dynamic :: (MonadWidget t m, Foldable f)

View File

@ -4,7 +4,7 @@ module Siphon where
-- encode
-- decode :: Pipe (Vector c) a m x
-- encode ::
-- encode ::
-- row :: Vector (Escaped Text) -> Text
-- row = Vector.

View File

@ -1,4 +1,4 @@
module Siphon.Content
module Siphon.Content
( byteStringChar8
) where

View File

@ -17,7 +17,7 @@ import qualified Data.ByteString.Char8 as ByteString
import qualified Data.Attoparsec.Types as Atto
-- unrow :: c1 -> (Vector c2,c1)
--
--
-- row :: _
-- -> Decoding (Indexed f) c a
-- -> Vector c
@ -27,7 +27,7 @@ import qualified Data.Attoparsec.Types as Atto
-- Monad m
-- => Decoding (Indexed f) c a
-- -> Pipe (Vector c) a m ()
-- decodeVectorPipe
-- decodeVectorPipe
mkParseError :: Int -> [String] -> String -> DecodingRowError f content
mkParseError i ctxs msg = id
@ -55,7 +55,7 @@ indexedPipe :: Monad m
-> Decoding (Indexed Headless) c a
-> Pipe c a m (DecodingRowError Headless c)
indexedPipe sd decoding = do
(firstRow, mleftovers) <- consumeGeneral sd mkParseError
(firstRow, mleftovers) <- consumeGeneral sd mkParseError
let req = Decoding.maxIndex decoding
vlen = Vector.length firstRow
if vlen < req
@ -72,28 +72,28 @@ headedPipe :: (Monad m, Eq c)
-> Decoding Headed c a
-> Pipe c a m (DecodingRowError Headed c)
headedPipe sd decoding = do
(headers, mleftovers) <- consumeGeneral sd mkParseError
(headers, mleftovers) <- consumeGeneral sd mkParseError
case Decoding.headedToIndexed headers decoding of
Left headingErrs -> return (DecodingRowError 0 (RowErrorHeading headingErrs))
Right indexedDecoding ->
Right indexedDecoding ->
let requiredLength = Vector.length headers
in uncheckedPipe requiredLength 1 sd indexedDecoding mleftovers
uncheckedPipe :: Monad m
=> Int -- ^ expected length of each row
-> Int -- ^ index of first row, usually zero or one
-> Siphon c
-> Siphon c
-> Decoding (Indexed f) c a
-> Maybe c
-> Pipe c a m (DecodingRowError f c)
uncheckedPipe requiredLength ix sd d mleftovers =
uncheckedPipe requiredLength ix sd d mleftovers =
pipeGeneral ix sd mkParseError checkedRunWithRow mleftovers
where
checkedRunWithRow rowIx v =
checkedRunWithRow rowIx v =
let vlen = Vector.length v in
if vlen /= requiredLength
then Left $ DecodingRowError rowIx
then Left $ DecodingRowError rowIx
$ RowErrorSize requiredLength vlen
else Decoding.uncheckedRunWithRow rowIx d v
@ -110,7 +110,7 @@ pipeGeneral :: Monad m
-> (Int -> Vector c -> Either e a)
-> Maybe c -- ^ leftovers that should be handled first
-> Pipe c a m e
pipeGeneral initIx (Siphon _ _ parse isNull) wrapParseError decodeRow mleftovers =
pipeGeneral initIx (Siphon _ _ parse isNull) wrapParseError decodeRow mleftovers =
case mleftovers of
Nothing -> go1 initIx
Just leftovers -> handleResult initIx (parse leftovers)
@ -138,6 +138,6 @@ awaitSkip :: Monad m
awaitSkip f = go where
go = do
a <- await
if f a then go else return a
if f a then go else return a

View File

@ -7,27 +7,27 @@ import qualified Pipes.Prelude as Pipes
import qualified Colonnade.Encoding as Encoding
row :: Siphon c
-> Encoding f c a
-> a
-> Encoding f c a
-> a
-> c
row (Siphon escape intercalate _ _) e =
intercalate . Encoding.runRow escape e
header :: Siphon c
-> Encoding Headed c a
-> Encoding Headed c a
-> c
header (Siphon escape intercalate _ _) e =
intercalate (Encoding.runHeader escape e)
pipe :: Monad m
pipe :: Monad m
=> Siphon c
-> Encoding f c a
-> Encoding f c a
-> Pipe a c m x
pipe siphon encoding = Pipes.map (row siphon encoding)
headedPipe :: Monad m
=> Siphon c
-> Encoding Headed c a
headedPipe :: Monad m
=> Siphon c
-> Encoding Headed c a
-> Pipe a c m x
headedPipe siphon encoding = do
yield (header siphon encoding)

View File

@ -31,6 +31,6 @@ data SiphonDecoding c1 c2 = SiphonDecoding
-- }
-- data SiphonDecodingError
-- { clarify
-- { clarify
-- }