zifter-0.0.1.4: zifter

Safe HaskellNone
LanguageHaskell2010

Zifter.Zift.Types

Synopsis

Documentation

data ZiftOutput Source #

Constructors

ZiftOutput 

Instances

Eq ZiftOutput Source # 
Show ZiftOutput Source # 
Generic ZiftOutput Source # 

Associated Types

type Rep ZiftOutput :: * -> * #

type Rep ZiftOutput Source # 
type Rep ZiftOutput = D1 * (MetaData "ZiftOutput" "Zifter.Zift.Types" "zifter-0.0.1.4-1pfWuwSPjO7GIdotoq9LHy" False) (C1 * (MetaCons "ZiftOutput" PrefixI True) ((:*:) * (S1 * (MetaSel (Just Symbol "outputColors") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * [SGR])) (S1 * (MetaSel (Just Symbol "outputMessage") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * String))))

data LMR Source #

Constructors

L 
M 
R 

Instances

Eq LMR Source # 

Methods

(==) :: LMR -> LMR -> Bool #

(/=) :: LMR -> LMR -> Bool #

Show LMR Source # 

Methods

showsPrec :: Int -> LMR -> ShowS #

show :: LMR -> String #

showList :: [LMR] -> ShowS #

Generic LMR Source # 

Associated Types

type Rep LMR :: * -> * #

Methods

from :: LMR -> Rep LMR x #

to :: Rep LMR x -> LMR #

type Rep LMR Source # 
type Rep LMR = D1 * (MetaData "LMR" "Zifter.Zift.Types" "zifter-0.0.1.4-1pfWuwSPjO7GIdotoq9LHy" False) ((:+:) * (C1 * (MetaCons "L" PrefixI False) (U1 *)) ((:+:) * (C1 * (MetaCons "M" PrefixI False) (U1 *)) (C1 * (MetaCons "R" PrefixI False) (U1 *))))

newtype ZiftState Source #

Constructors

ZiftState 

Instances

Eq ZiftState Source # 
Show ZiftState Source # 
Generic ZiftState Source # 

Associated Types

type Rep ZiftState :: * -> * #

Monoid ZiftState Source # 
type Rep ZiftState Source # 
type Rep ZiftState = D1 * (MetaData "ZiftState" "Zifter.Zift.Types" "zifter-0.0.1.4-1pfWuwSPjO7GIdotoq9LHy" True) (C1 * (MetaCons "ZiftState" PrefixI True) (S1 * (MetaSel (Just Symbol "bufferedOutput") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * [ZiftOutput])))

newtype Zift a Source #

Constructors

Zift 

Instances

Monad Zift Source #

Zift actions can be composed.

Methods

(>>=) :: Zift a -> (a -> Zift b) -> Zift b #

(>>) :: Zift a -> Zift b -> Zift b #

return :: a -> Zift a #

fail :: String -> Zift a #

Functor Zift Source # 

Methods

fmap :: (a -> b) -> Zift a -> Zift b #

(<$) :: a -> Zift b -> Zift a #

MonadFail Zift Source #

A Zift action can fail.

To make a Zift action fail, you can use the fail :: String -> Zift a function.

The implementation uses the given string as the message that is shown at the very end of the run.

Methods

fail :: String -> Zift a #

Applicative Zift Source #

Zift actions can be sequenced.

The implementation automatically parallelises the arguments of the (*) function. If any of the actions fails, the other is cancelled and the result fails.

Methods

pure :: a -> Zift a #

(<*>) :: Zift (a -> b) -> Zift a -> Zift b #

liftA2 :: (a -> b -> c) -> Zift a -> Zift b -> Zift c #

(*>) :: Zift a -> Zift b -> Zift b #

(<*) :: Zift a -> Zift b -> Zift a #

MonadIO Zift Source #

Any IO action can be part of a Zift action.

This is the most important instance for the end user.

liftIO :: IO a -> Zift a

allows embedding arbitrary IO actions inside a Zift action.

The implementation also ensures that exceptions are caught.

Methods

liftIO :: IO a -> Zift a #

MonadThrow Zift Source # 

Methods

throwM :: Exception e => e -> Zift a #

Generic (Zift a) Source # 

Associated Types

type Rep (Zift a) :: * -> * #

Methods

from :: Zift a -> Rep (Zift a) x #

to :: Rep (Zift a) x -> Zift a #

Monoid a => Monoid (Zift a) Source # 

Methods

mempty :: Zift a #

mappend :: Zift a -> Zift a -> Zift a #

mconcat :: [Zift a] -> Zift a #

type Rep (Zift a) Source # 
type Rep (Zift a) = D1 * (MetaData "Zift" "Zifter.Zift.Types" "zifter-0.0.1.4-1pfWuwSPjO7GIdotoq9LHy" True) (C1 * (MetaCons "Zift" PrefixI True) (S1 * (MetaSel (Just Symbol "zift") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (ZiftContext -> ZiftState -> IO (ZiftResult a, ZiftState)))))

data ZiftResult a Source #

Constructors

ZiftSuccess a 
ZiftFailed String 

Instances

Monad ZiftResult Source # 

Methods

(>>=) :: ZiftResult a -> (a -> ZiftResult b) -> ZiftResult b #

(>>) :: ZiftResult a -> ZiftResult b -> ZiftResult b #

return :: a -> ZiftResult a #

fail :: String -> ZiftResult a #

Functor ZiftResult Source # 

Methods

fmap :: (a -> b) -> ZiftResult a -> ZiftResult b #

(<$) :: a -> ZiftResult b -> ZiftResult a #

MonadFail ZiftResult Source # 

Methods

fail :: String -> ZiftResult a #

Applicative ZiftResult Source # 

Methods

pure :: a -> ZiftResult a #

(<*>) :: ZiftResult (a -> b) -> ZiftResult a -> ZiftResult b #

liftA2 :: (a -> b -> c) -> ZiftResult a -> ZiftResult b -> ZiftResult c #

(*>) :: ZiftResult a -> ZiftResult b -> ZiftResult b #

(<*) :: ZiftResult a -> ZiftResult b -> ZiftResult a #

Eq a => Eq (ZiftResult a) Source # 

Methods

(==) :: ZiftResult a -> ZiftResult a -> Bool #

(/=) :: ZiftResult a -> ZiftResult a -> Bool #

Show a => Show (ZiftResult a) Source # 
Generic (ZiftResult a) Source # 

Associated Types

type Rep (ZiftResult a) :: * -> * #

Methods

from :: ZiftResult a -> Rep (ZiftResult a) x #

to :: Rep (ZiftResult a) x -> ZiftResult a #

Monoid a => Monoid (ZiftResult a) Source # 
Validity a => Validity (ZiftResult a) Source # 
type Rep (ZiftResult a) Source # 
type Rep (ZiftResult a) = D1 * (MetaData "ZiftResult" "Zifter.Zift.Types" "zifter-0.0.1.4-1pfWuwSPjO7GIdotoq9LHy" False) ((:+:) * (C1 * (MetaCons "ZiftSuccess" PrefixI False) (S1 * (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * a))) (C1 * (MetaCons "ZiftFailed" PrefixI False) (S1 * (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * String))))

tryFlushZiftBuffer :: ZiftContext -> ZiftState -> IO ZiftState Source #

Internal: do not use yourself.