-- |A data type encoding the result of an incremental parser for process output.
module Polysemy.Process.Data.ProcessOutputParseResult where

-- |An incremental parse result, potentially a partial result containing a continuation function.
data ProcessOutputParseResult a =
  Done { forall a. ProcessOutputParseResult a -> a
value :: a, forall a. ProcessOutputParseResult a -> ByteString
leftover :: ByteString }
  |
  Partial { forall a.
ProcessOutputParseResult a
-> ByteString -> ProcessOutputParseResult a
continue :: ByteString -> ProcessOutputParseResult a }
  |
  Fail { forall a. ProcessOutputParseResult a -> Text
error :: Text }

instance Show a => Show (ProcessOutputParseResult a) where
  showsPrec :: Int -> ProcessOutputParseResult a -> ShowS
showsPrec Int
d = \case
    Done {a
ByteString
$sel:value:Done :: forall a. ProcessOutputParseResult a -> a
$sel:leftover:Done :: forall a. ProcessOutputParseResult a -> ByteString
value :: a
leftover :: ByteString
..} ->
      Bool -> ShowS -> ShowS
showParen (Int
d Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
> Int
10) (String -> ShowS
showString String
"Done { value = " ShowS -> ShowS -> ShowS
forall a. Semigroup a => a -> a -> a
<> Int -> a -> ShowS
forall a. Show a => Int -> a -> ShowS
showsPrec Int
11 a
value ShowS -> ShowS -> ShowS
forall a. Semigroup a => a -> a -> a
<> String -> ShowS
showString String
", leftover = " ShowS -> ShowS -> ShowS
forall a. Semigroup a => a -> a -> a
<> Int -> ByteString -> ShowS
forall a. Show a => Int -> a -> ShowS
showsPrec Int
11 ByteString
leftover ShowS -> ShowS -> ShowS
forall a. Semigroup a => a -> a -> a
<> String -> ShowS
showString String
" }")
    Partial ByteString -> ProcessOutputParseResult a
_ ->
      String -> ShowS
showString String
"Partial"
    Fail Text
e ->
      Bool -> ShowS -> ShowS
showParen (Int
d Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
> Int
10) (String -> ShowS
showString String
"Fail { error = " ShowS -> ShowS -> ShowS
forall a. Semigroup a => a -> a -> a
<> String -> ShowS
showString (Text -> String
forall b a. (Show a, IsString b) => a -> b
show Text
e) ShowS -> ShowS -> ShowS
forall a. Semigroup a => a -> a -> a
<> String -> ShowS
showString String
" }")