op-0.2.0.0: Common operators encouraging large-scale easy reading

Safe HaskellSafe
LanguageHaskell2010

Control.Op

Description

Op provides operators for writing easier-to-read Haskell. It provides new operators with a consistent "look and feel" including fixity direction and precedence, resulting in easier- and quicker-to-read code especially when used on long chains of expressions.

All right-facing operators are defined with infixl 1 which is the same as >>=, so you can chain all of these together without using parentheses.

All left-facing operators are defined with infixr 1 which is the same as =<<, so you can chain all of these together also without using parentheses.

Unlike Flow and FunctorMonadic we do not restrict ourselves to functions and functors respectively, but we try to cover as many operators as possible.

This means we conflict with some non-Prelude base operators (search "redefined" below), but that is the trade-off we chose. They are used less commonly than the ones we retain compatibility with, IOO their inconsistency is part of the reason why they are used less commonly, and this package tries to fix that.

Examples

>>> :set -XTupleSections
>>> import Control.Op
>>> import Data.Functor
>>> import qualified Data.Map.Strict as M
>>> :{
data InnerMap k v = InnerMap
  { innerMeta :: !()
  , innerMap :: !(M.Map k v)
  }
:}
>>> type MultiMap k v = M.Map Integer (InnerMap k v)

Old way, needs extra parens due to <$>'s fixity:

>>> :{
lookupOldR :: Ord k => MultiMap k v -> (Integer, k) -> Maybe (Integer, v)
lookupOldR m (i, k) = (i,) <$> (M.lookup k . innerMap =<< M.lookup i m)
:}

or, slightly better but the . innerMap still breaks up the LTR flow:

>>> :{
lookupOldL :: Ord k => MultiMap k v -> (Integer, k) -> Maybe (Integer, v)
lookupOldL m (i, k) = M.lookup i m >>= M.lookup k . innerMap <&> (i,)
:}

New way:

>>> :{
lookupNewR :: Ord k => MultiMap k v -> (Integer, k) -> Maybe (Integer, v)
lookupNewR m (i, k) = (i,) <$< M.lookup k =<< innerMap <$< M.lookup i <| m
:}
>>> :{
lookupNewL :: Ord k => MultiMap k v -> (Integer, k) -> Maybe (Integer, v)
lookupNewL m (i, k) = m |> M.lookup i >$> innerMap >>= M.lookup k >$> (i,)
:}
Synopsis
  • (|>) :: a -> (a -> b) -> b
  • (<|) :: (a -> b) -> a -> b
  • (.>) :: (a -> b) -> (b -> c) -> a -> c
  • (<.) :: (b -> c) -> (a -> b) -> a -> c
  • (>>>) :: Category f => f a b -> f b c -> f a c
  • (<<<) :: Category f => f b c -> f a b -> f a c
  • (>$>) :: Functor f => f a -> (a -> b) -> f b
  • (<$<) :: Functor f => (a -> b) -> f a -> f b
  • (>>=) :: Monad m => m a -> (a -> m b) -> m b
  • (=<<) :: Monad m => (a -> m b) -> m a -> m b
  • (>=>) :: Monad m => (a -> m b) -> (b -> m c) -> a -> m c
  • (<=<) :: Monad m => (b -> m c) -> (a -> m b) -> a -> m c

Documentation

(|>) :: a -> (a -> b) -> b infixl 1 Source #

LTR function application.

Same as & with a consistent fixity.

(<|) :: (a -> b) -> a -> b infixr 1 Source #

RTL function application.

Same as $ with a consistent fixity.

(.>) :: (a -> b) -> (b -> c) -> a -> c infixl 1 Source #

LTR function composition.

Same as flip . with a consistent fixity.

(<.) :: (b -> c) -> (a -> b) -> a -> c infixr 1 Source #

RTL function composition.

Same as . with a consistent fixity.

(>>>) :: Category f => f a b -> f b c -> f a c infixl 1 Source #

LTR category composition.

This is >>> but with a redefined consistent fixity.

(<<<) :: Category f => f b c -> f a b -> f a c infixr 1 Source #

RTL category composition.

This is <<<.

(>$>) :: Functor f => f a -> (a -> b) -> f b infixl 1 Source #

LTR functor application.

Same as <&> with a consistent fixity.

(<$<) :: Functor f => (a -> b) -> f a -> f b infixr 1 Source #

RTL functor application.

Same as <$> with a consistent fixity.

(>>=) :: Monad m => m a -> (a -> m b) -> m b #

LTR monad application

This is >>=.

(=<<) :: Monad m => (a -> m b) -> m a -> m b #

RTL monad application

This is =<<.

(>=>) :: Monad m => (a -> m b) -> (b -> m c) -> a -> m c infixl 1 Source #

LTR monad composition.

This is >=> but with a redefined consistent fixity.

(<=<) :: Monad m => (b -> m c) -> (a -> m b) -> a -> m c infixr 1 Source #

RTL monad composition.

This is <=<.