exotic-list-monads-1.0.0: Non-standard monads on lists and non-empty lists

Copyright(c) Dylan McDermott Maciej Piróg Tarmo Uustalu 2020
LicenseMIT
Maintainermaciej.adam.pirog@gmail.com
Stabilityexperimental
Portabilityportable
Safe HaskellTrustworthy
LanguageHaskell2010

Control.Monad.List.NonEmpty.Exotic

Contents

Description

The usual list monad is only one of infinitely many ways to turn the NonEmpty (list) functor into a monad. This module collects a number of such exotic "non-empty list monads". Most of them have been introduced in the paper Degrading Lists by Dylan McDermott, Maciej Piróg, Tarmo Uustalu (PPDP 2020).

Notes:

  • Types marked with "(?)" have not been formally verified to be monads (yet), though they were thoroughly tested with billions of QuickCheck tests.
  • Monads in this module are presented in terms of join rather than >>=, while return is singleton, unless stated otherwise for a particular monad (e.g., HeadTails, HeadsTail, or IdXList).
  • For readability, code snippets in this documentation assume the OverloadedLists and OverloadedStrings extensions, which allow us to omit some newtype constructors. Example definitions of joins of monads always skip the newtype constructors, that is, assume >>= is always defined as follows for a particular local join.
m >>= f = wrap $ join $ fmap (unwrap . f) $ unwrap m
 where
  join = ...
  • Sometimes it is more readable to define the join in terms of possibly-empty lists. In such a case, we call the local function joinList:
m >>= f = wrap $ fromList $ joinList $ map (toList . unwrap . f) $ toList $ unwrap m
 where
  joinList = ...
  • The definitions of monads are optimized for readability and not run-time performance. This is because the monads in this module don't seem to be of any practical use, they are more of a theoretical curiosity.
Synopsis

Non-empty monads in general

class IsNonEmpty l where Source #

This class collects types that are isomorphic to non-empty lists. It mimics the IsList class.

Associated Types

type ItemNE l Source #

Instances
IsNonEmpty (NonEmpty a) Source # 
Instance details

Defined in Control.Monad.List.NonEmpty.Exotic

Associated Types

type ItemNE (NonEmpty a) :: Type Source #

IsNonEmpty (AlphaOmega a) Source # 
Instance details

Defined in Control.Monad.List.NonEmpty.Exotic

Associated Types

type ItemNE (AlphaOmega a) :: Type Source #

IsNonEmpty (HeadsTail a) Source # 
Instance details

Defined in Control.Monad.List.NonEmpty.Exotic

Associated Types

type ItemNE (HeadsTail a) :: Type Source #

IsNonEmpty (HeadTails a) Source # 
Instance details

Defined in Control.Monad.List.NonEmpty.Exotic

Associated Types

type ItemNE (HeadTails a) :: Type Source #

IsNonEmpty (MazeWalkNE a) Source # 
Instance details

Defined in Control.Monad.List.NonEmpty.Exotic

Associated Types

type ItemNE (MazeWalkNE a) :: Type Source #

IsNonEmpty (OpDiscreteHybridNE a) Source # 
Instance details

Defined in Control.Monad.List.NonEmpty.Exotic

Associated Types

type ItemNE (OpDiscreteHybridNE a) :: Type Source #

IsNonEmpty (DiscreteHybridNE a) Source # 
Instance details

Defined in Control.Monad.List.NonEmpty.Exotic

Associated Types

type ItemNE (DiscreteHybridNE a) :: Type Source #

IsNonEmpty (Keeper a) Source # 
Instance details

Defined in Control.Monad.List.NonEmpty.Exotic

Associated Types

type ItemNE (Keeper a) :: Type Source #

ListMonad m => IsNonEmpty (IdXList m a) Source # 
Instance details

Defined in Control.Monad.List.NonEmpty.Exotic

Associated Types

type ItemNE (IdXList m a) :: Type Source #

KnownNat n => IsNonEmpty (StutterNE n a) Source # 
Instance details

Defined in Control.Monad.List.NonEmpty.Exotic

Associated Types

type ItemNE (StutterNE n a) :: Type Source #

IsNonEmpty (m a) => IsNonEmpty (DualNonEmptyMonad m a) Source # 
Instance details

Defined in Control.Monad.List.NonEmpty.Exotic

Associated Types

type ItemNE (DualNonEmptyMonad m a) :: Type Source #

(IsNonEmpty (m a), KnownNat p) => IsNonEmpty (ShortRear m p a) Source # 
Instance details

Defined in Control.Monad.List.NonEmpty.Exotic

Associated Types

type ItemNE (ShortRear m p a) :: Type Source #

(IsNonEmpty (m a), KnownNat p) => IsNonEmpty (ShortFront m p a) Source # 
Instance details

Defined in Control.Monad.List.NonEmpty.Exotic

Associated Types

type ItemNE (ShortFront m p a) :: Type Source #

class Monad m => NonEmptyMonad m where Source #

In this module, a "non-empty monad" is a monad in which the underlying functor is isomorphic to NonEmpty.

Minimal complete definition

Nothing

Methods

wrap :: NonEmpty a -> m a Source #

wrap :: (IsNonEmpty (m a), ItemNE (m a) ~ a) => NonEmpty a -> m a Source #

unwrap :: m a -> NonEmpty a Source #

unwrap :: (IsNonEmpty (m a), ItemNE (m a) ~ a) => m a -> NonEmpty a Source #

Instances
NonEmptyMonad NonEmpty Source # 
Instance details

Defined in Control.Monad.List.NonEmpty.Exotic

NonEmptyMonad AlphaOmega Source # 
Instance details

Defined in Control.Monad.List.NonEmpty.Exotic

NonEmptyMonad HeadsTail Source # 
Instance details

Defined in Control.Monad.List.NonEmpty.Exotic

NonEmptyMonad HeadTails Source # 
Instance details

Defined in Control.Monad.List.NonEmpty.Exotic

NonEmptyMonad MazeWalkNE Source # 
Instance details

Defined in Control.Monad.List.NonEmpty.Exotic

NonEmptyMonad OpDiscreteHybridNE Source # 
Instance details

Defined in Control.Monad.List.NonEmpty.Exotic

NonEmptyMonad DiscreteHybridNE Source # 
Instance details

Defined in Control.Monad.List.NonEmpty.Exotic

NonEmptyMonad Keeper Source # 
Instance details

Defined in Control.Monad.List.NonEmpty.Exotic

Methods

wrap :: NonEmpty a -> Keeper a Source #

unwrap :: Keeper a -> NonEmpty a Source #

ListMonad m => NonEmptyMonad (IdXList m) Source # 
Instance details

Defined in Control.Monad.List.NonEmpty.Exotic

Methods

wrap :: NonEmpty a -> IdXList m a Source #

unwrap :: IdXList m a -> NonEmpty a Source #

KnownNat n => NonEmptyMonad (StutterNE n) Source # 
Instance details

Defined in Control.Monad.List.NonEmpty.Exotic

Methods

wrap :: NonEmpty a -> StutterNE n a Source #

unwrap :: StutterNE n a -> NonEmpty a Source #

NonEmptyMonad m => NonEmptyMonad (DualNonEmptyMonad m) Source # 
Instance details

Defined in Control.Monad.List.NonEmpty.Exotic

(HasShortRear m, KnownNat p) => NonEmptyMonad (ShortRear m p) Source # 
Instance details

Defined in Control.Monad.List.NonEmpty.Exotic

Methods

wrap :: NonEmpty a -> ShortRear m p a Source #

unwrap :: ShortRear m p a -> NonEmpty a Source #

(HasShortFront m, KnownNat p) => NonEmptyMonad (ShortFront m p) Source # 
Instance details

Defined in Control.Monad.List.NonEmpty.Exotic

Methods

wrap :: NonEmpty a -> ShortFront m p a Source #

unwrap :: ShortFront m p a -> NonEmpty a Source #

More on non-empty lists

isSingle :: NonEmpty a -> Bool Source #

Check if a list is a singleton.

splitSnoc :: NonEmpty a -> ([a], a) Source #

Split a non empty list to reveal the last element.

nonEmptyConcat :: NonEmpty (NonEmpty a) -> NonEmpty a Source #

concat for non-empty lists.

(+++) :: NonEmpty a -> NonEmpty a -> NonEmpty a Source #

++ for non-empty lists.

nonEmptyAll :: (a -> Bool) -> NonEmpty a -> Bool Source #

all for non-empty lists.

nonEmptyAny :: (a -> Bool) -> NonEmpty a -> Bool Source #

any for non-empty lists.

Monads from magmas

This section contains monads that come about from free algebras of theories with one binary operation, that is, subcalsses of Magma with no additional methods, but additional equations.

class Magma a where Source #

A very simple algebraic theory with one binary operations and no equations.

Methods

(<>) :: a -> a -> a Source #

class NonEmptyMonad m => FreeRBM m (c :: * -> Constraint) | m -> c where Source #

The name of the class stands for free right-braketed (subclass of) magma. (compare FreeRBPM for more detailed explanation).

We consider theories c with one equation of the following shape:

(x <> y) <> z  ==  ...

and normal forms of the following shape:

x <> (y <> ( ... (z <> t) ... ))

An instance FreeRBM m c means that the monad m comes about from free algebras of the theory c. For such monads and theories, we can define the following function:

foldRBM f (toNonEmpty -> toList -> xs) = foldr1 (<>) (map f xs)

which is the unique lifting of an interpretation of generators to a homomorphism (between algebras of this theory) from the list monad to any algebra (an instance) of c.

Note that the default definition of foldRBM is always the right one for right-bracketed subclasses of Magma, so it is enough to declare the relationship, for example:

instance FreeRBM NonEmpty Semigroup

Minimal complete definition

Nothing

Methods

foldRBM :: (Magma a, c a) => (x -> a) -> m x -> a Source #

Instances
FreeRBM NonEmpty Semigroup Source # 
Instance details

Defined in Control.Monad.List.NonEmpty.Exotic

Methods

foldRBM :: (Magma a, Semigroup a) => (x -> a) -> NonEmpty x -> a Source #

FreeRBM MazeWalkNE PalindromeMagma Source # 
Instance details

Defined in Control.Monad.List.NonEmpty.Exotic

Methods

foldRBM :: (Magma a, PalindromeMagma a) => (x -> a) -> MazeWalkNE x -> a Source #

FreeRBM OpDiscreteHybridNE XZ Source # 
Instance details

Defined in Control.Monad.List.NonEmpty.Exotic

Methods

foldRBM :: (Magma a, XZ a) => (x -> a) -> OpDiscreteHybridNE x -> a Source #

FreeRBM DiscreteHybridNE YZ Source # 
Instance details

Defined in Control.Monad.List.NonEmpty.Exotic

Methods

foldRBM :: (Magma a, YZ a) => (x -> a) -> DiscreteHybridNE x -> a Source #

FreeRBM Keeper XY Source # 
Instance details

Defined in Control.Monad.List.NonEmpty.Exotic

Methods

foldRBM :: (Magma a, XY a) => (x -> a) -> Keeper x -> a Source #

KnownNat n => FreeRBM (StutterNE n) (StutterMagma n) Source # 
Instance details

Defined in Control.Monad.List.NonEmpty.Exotic

Methods

foldRBM :: (Magma a, StutterMagma n a) => (x -> a) -> StutterNE n x -> a Source #

The Keeper monad

class Magma a => XY a Source #

Instances should satisfy the following equation:

(x <> y) <> z  ==  x <> y
Instances
FreeRBM Keeper XY Source # 
Instance details

Defined in Control.Monad.List.NonEmpty.Exotic

Methods

foldRBM :: (Magma a, XY a) => (x -> a) -> Keeper x -> a Source #

XY (Keeper a) Source # 
Instance details

Defined in Control.Monad.List.NonEmpty.Exotic

newtype Keeper a Source #

The keeper monad arises from free XY magmas. Its join (in terms of joinList) is given as follows:

joinList xss = map head (takeWhile isSingle (init xss))
                ++ head (dropWhile isSingle (init xss) ++ [last xss])

Examples:

>>> toList $ unwrap (join ["a", "b", "c", "hello", "there"] :: Keeper Char)
"abchello"
>>> toList $ unwrap (join ["a", "b", "c", "hello"] :: Keeper Char)
"abchello"

Constructors

Keeper 

Fields

Instances
Monad Keeper Source # 
Instance details

Defined in Control.Monad.List.NonEmpty.Exotic

Methods

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

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

return :: a -> Keeper a #

fail :: String -> Keeper a #

Functor Keeper Source # 
Instance details

Defined in Control.Monad.List.NonEmpty.Exotic

Methods

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

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

Applicative Keeper Source # 
Instance details

Defined in Control.Monad.List.NonEmpty.Exotic

Methods

pure :: a -> Keeper a #

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

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

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

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

HasShortFront Keeper Source #

(?)

Instance details

Defined in Control.Monad.List.NonEmpty.Exotic

NonEmptyMonad Keeper Source # 
Instance details

Defined in Control.Monad.List.NonEmpty.Exotic

Methods

wrap :: NonEmpty a -> Keeper a Source #

unwrap :: Keeper a -> NonEmpty a Source #

FreeRBM Keeper XY Source # 
Instance details

Defined in Control.Monad.List.NonEmpty.Exotic

Methods

foldRBM :: (Magma a, XY a) => (x -> a) -> Keeper x -> a Source #

IsList (Keeper a) Source # 
Instance details

Defined in Control.Monad.List.NonEmpty.Exotic

Associated Types

type Item (Keeper a) :: Type #

Methods

fromList :: [Item (Keeper a)] -> Keeper a #

fromListN :: Int -> [Item (Keeper a)] -> Keeper a #

toList :: Keeper a -> [Item (Keeper a)] #

Eq a => Eq (Keeper a) Source # 
Instance details

Defined in Control.Monad.List.NonEmpty.Exotic

Methods

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

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

Show a => Show (Keeper a) Source # 
Instance details

Defined in Control.Monad.List.NonEmpty.Exotic

Methods

showsPrec :: Int -> Keeper a -> ShowS #

show :: Keeper a -> String #

showList :: [Keeper a] -> ShowS #

IsString (Keeper Char) Source # 
Instance details

Defined in Control.Monad.List.NonEmpty.Exotic

XY (Keeper a) Source # 
Instance details

Defined in Control.Monad.List.NonEmpty.Exotic

Magma (Keeper a) Source # 
Instance details

Defined in Control.Monad.List.NonEmpty.Exotic

Methods

(<>) :: Keeper a -> Keeper a -> Keeper a Source #

IsNonEmpty (Keeper a) Source # 
Instance details

Defined in Control.Monad.List.NonEmpty.Exotic

Associated Types

type ItemNE (Keeper a) :: Type Source #

type Item (Keeper a) Source # 
Instance details

Defined in Control.Monad.List.NonEmpty.Exotic

type Item (Keeper a) = a
type ItemNE (Keeper a) Source # 
Instance details

Defined in Control.Monad.List.NonEmpty.Exotic

type ItemNE (Keeper a) = a

The Non-Empty Discrete Hybrid monad

class Magma a => YZ a Source #

Instances should satisfy the following equation:

(x <> y) <> z  ==  y <> z
Instances
FreeRBM DiscreteHybridNE YZ Source # 
Instance details

Defined in Control.Monad.List.NonEmpty.Exotic

Methods

foldRBM :: (Magma a, YZ a) => (x -> a) -> DiscreteHybridNE x -> a Source #

YZ (DiscreteHybridNE a) Source # 
Instance details

Defined in Control.Monad.List.NonEmpty.Exotic

newtype DiscreteHybridNE a Source #

The non-empty discrete hybrid monad arises from free YZ magmas. Its join (in terms of joinList) can be given as follows:

joinList xss = map last (init xss) ++ last xss

See the possibly-empty version (DiscreteHybrid) for more details.

Constructors

DiscreteHybridNE 
Instances
Monad DiscreteHybridNE Source # 
Instance details

Defined in Control.Monad.List.NonEmpty.Exotic

Functor DiscreteHybridNE Source # 
Instance details

Defined in Control.Monad.List.NonEmpty.Exotic

Methods

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

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

Applicative DiscreteHybridNE Source # 
Instance details

Defined in Control.Monad.List.NonEmpty.Exotic

HasShortRear DiscreteHybridNE Source #

(?)

Instance details

Defined in Control.Monad.List.NonEmpty.Exotic

NonEmptyMonad DiscreteHybridNE Source # 
Instance details

Defined in Control.Monad.List.NonEmpty.Exotic

FreeRBM DiscreteHybridNE YZ Source # 
Instance details

Defined in Control.Monad.List.NonEmpty.Exotic

Methods

foldRBM :: (Magma a, YZ a) => (x -> a) -> DiscreteHybridNE x -> a Source #

Eq a => Eq (DiscreteHybridNE a) Source # 
Instance details

Defined in Control.Monad.List.NonEmpty.Exotic

Show a => Show (DiscreteHybridNE a) Source # 
Instance details

Defined in Control.Monad.List.NonEmpty.Exotic

YZ (DiscreteHybridNE a) Source # 
Instance details

Defined in Control.Monad.List.NonEmpty.Exotic

Magma (DiscreteHybridNE a) Source # 
Instance details

Defined in Control.Monad.List.NonEmpty.Exotic

IsNonEmpty (DiscreteHybridNE a) Source # 
Instance details

Defined in Control.Monad.List.NonEmpty.Exotic

Associated Types

type ItemNE (DiscreteHybridNE a) :: Type Source #

type ItemNE (DiscreteHybridNE a) Source # 
Instance details

Defined in Control.Monad.List.NonEmpty.Exotic

The Non-Empty Discrete Op-Hybrid monad

class Magma a => XZ a Source #

Instances should satisfy the following equation:

(x <> y) <> z  ==  x <> z
Instances
FreeRBM OpDiscreteHybridNE XZ Source # 
Instance details

Defined in Control.Monad.List.NonEmpty.Exotic

Methods

foldRBM :: (Magma a, XZ a) => (x -> a) -> OpDiscreteHybridNE x -> a Source #

XZ (OpDiscreteHybridNE a) Source # 
Instance details

Defined in Control.Monad.List.NonEmpty.Exotic

newtype OpDiscreteHybridNE a Source #

The non-empty discrete op-hybrid monad arises from free XZ magmas. It is dual to the DiscreteHybridNE monad (but in a different dimension than DualNonEmptyMonad). Its join (in terms of joinList) can be given as follows:

joinList xss = map head (init xss) ++ last xss

Examples:

>>> toList $ unwrap (join ["John", "Ronald", "Reuel", "Tolkien"] :: OpDiscreteHybridNE Char)
"JRRTolkien"

Surprisingly, while the DiscreteHybridNE monad has a counterpart for possibly-empty lists (DiscreteHybrid), the would-be counterpart of OpDiscreteHybridNE obtained by taking first elements in the init is not a monad.

Instances
Monad OpDiscreteHybridNE Source # 
Instance details

Defined in Control.Monad.List.NonEmpty.Exotic

Functor OpDiscreteHybridNE Source # 
Instance details

Defined in Control.Monad.List.NonEmpty.Exotic

Applicative OpDiscreteHybridNE Source # 
Instance details

Defined in Control.Monad.List.NonEmpty.Exotic

HasShortFront OpDiscreteHybridNE Source #

(?)

Instance details

Defined in Control.Monad.List.NonEmpty.Exotic

NonEmptyMonad OpDiscreteHybridNE Source # 
Instance details

Defined in Control.Monad.List.NonEmpty.Exotic

FreeRBM OpDiscreteHybridNE XZ Source # 
Instance details

Defined in Control.Monad.List.NonEmpty.Exotic

Methods

foldRBM :: (Magma a, XZ a) => (x -> a) -> OpDiscreteHybridNE x -> a Source #

IsList (OpDiscreteHybridNE a) Source # 
Instance details

Defined in Control.Monad.List.NonEmpty.Exotic

Associated Types

type Item (OpDiscreteHybridNE a) :: Type #

Eq a => Eq (OpDiscreteHybridNE a) Source # 
Instance details

Defined in Control.Monad.List.NonEmpty.Exotic

Show a => Show (OpDiscreteHybridNE a) Source # 
Instance details

Defined in Control.Monad.List.NonEmpty.Exotic

IsString (OpDiscreteHybridNE Char) Source # 
Instance details

Defined in Control.Monad.List.NonEmpty.Exotic

XZ (OpDiscreteHybridNE a) Source # 
Instance details

Defined in Control.Monad.List.NonEmpty.Exotic

Magma (OpDiscreteHybridNE a) Source # 
Instance details

Defined in Control.Monad.List.NonEmpty.Exotic

IsNonEmpty (OpDiscreteHybridNE a) Source # 
Instance details

Defined in Control.Monad.List.NonEmpty.Exotic

Associated Types

type ItemNE (OpDiscreteHybridNE a) :: Type Source #

type Item (OpDiscreteHybridNE a) Source # 
Instance details

Defined in Control.Monad.List.NonEmpty.Exotic

type ItemNE (OpDiscreteHybridNE a) Source # 
Instance details

Defined in Control.Monad.List.NonEmpty.Exotic

The Non-Empty Maze Walk monad

class Magma a => PalindromeMagma a Source #

Instances should satisfy the following equation:

(x <> y) <> z  ==  x <> (y <> (x <> z))
Instances
FreeRBM MazeWalkNE PalindromeMagma Source # 
Instance details

Defined in Control.Monad.List.NonEmpty.Exotic

Methods

foldRBM :: (Magma a, PalindromeMagma a) => (x -> a) -> MazeWalkNE x -> a Source #

PalindromeMagma (MazeWalkNE a) Source # 
Instance details

Defined in Control.Monad.List.NonEmpty.Exotic

newtype MazeWalkNE a Source #

The non-empty maze walk monad arises from free PalindromeMagma-s. Its join (in terms of joinList) can be given as follows:

joinList xss = map palindromize (init xss) ++ last xss

See the possibly-empty version (MazeWalk) for more details.

Constructors

MazeWalkNE 

Fields

Instances
Monad MazeWalkNE Source # 
Instance details

Defined in Control.Monad.List.NonEmpty.Exotic

Methods

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

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

return :: a -> MazeWalkNE a #

fail :: String -> MazeWalkNE a #

Functor MazeWalkNE Source # 
Instance details

Defined in Control.Monad.List.NonEmpty.Exotic

Methods

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

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

Applicative MazeWalkNE Source # 
Instance details

Defined in Control.Monad.List.NonEmpty.Exotic

Methods

pure :: a -> MazeWalkNE a #

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

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

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

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

HasShortFront MazeWalkNE Source #

(?)

Instance details

Defined in Control.Monad.List.NonEmpty.Exotic

NonEmptyMonad MazeWalkNE Source # 
Instance details

Defined in Control.Monad.List.NonEmpty.Exotic

FreeRBM MazeWalkNE PalindromeMagma Source # 
Instance details

Defined in Control.Monad.List.NonEmpty.Exotic

Methods

foldRBM :: (Magma a, PalindromeMagma a) => (x -> a) -> MazeWalkNE x -> a Source #

Eq a => Eq (MazeWalkNE a) Source # 
Instance details

Defined in Control.Monad.List.NonEmpty.Exotic

Methods

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

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

Show a => Show (MazeWalkNE a) Source # 
Instance details

Defined in Control.Monad.List.NonEmpty.Exotic

PalindromeMagma (MazeWalkNE a) Source # 
Instance details

Defined in Control.Monad.List.NonEmpty.Exotic

Magma (MazeWalkNE a) Source # 
Instance details

Defined in Control.Monad.List.NonEmpty.Exotic

IsNonEmpty (MazeWalkNE a) Source # 
Instance details

Defined in Control.Monad.List.NonEmpty.Exotic

Associated Types

type ItemNE (MazeWalkNE a) :: Type Source #

type ItemNE (MazeWalkNE a) Source # 
Instance details

Defined in Control.Monad.List.NonEmpty.Exotic

type ItemNE (MazeWalkNE a) = a

The Non-Empty Stutter monad

class (KnownNat n, Magma a) => StutterMagma n a Source #

Instances should satisfy the following equation:

(x <> y) <> z  ==  foldr1 (<>) (replicate (n + 2) x)
Instances
KnownNat n => StutterMagma n (StutterNE n a) Source # 
Instance details

Defined in Control.Monad.List.NonEmpty.Exotic

KnownNat n => FreeRBM (StutterNE n) (StutterMagma n) Source # 
Instance details

Defined in Control.Monad.List.NonEmpty.Exotic

Methods

foldRBM :: (Magma a, StutterMagma n a) => (x -> a) -> StutterNE n x -> a Source #

newtype StutterNE (n :: Nat) a Source #

The non-empty stutter monad arises from free StutterMagma-s. Its join (in terms of joinList) can be given as follows:

joinList xss | any (not . isSingle) (init xss)
             = map head (takeWhile isSingle (init xss))
                ++ replicate (n + 2) (head (head (dropWhile isSingle (init xss))))
             | otherwise
             = map head (init xss) ++ last xss

Examples:

>>> toList $ unwrap (join ["a", "b", "c", "hello", "there"] :: StutterNE 5 Char)
"abchhhhhhh"
>>> toList $ unwrap (join ["a", "b", "c", "hello"] :: StutterNE 5 Char)
"abchello"

Constructors

StutterNE 

Fields

Instances
KnownNat n => StutterMagma n (StutterNE n a) Source # 
Instance details

Defined in Control.Monad.List.NonEmpty.Exotic

KnownNat n => Monad (StutterNE n) Source # 
Instance details

Defined in Control.Monad.List.NonEmpty.Exotic

Methods

(>>=) :: StutterNE n a -> (a -> StutterNE n b) -> StutterNE n b #

(>>) :: StutterNE n a -> StutterNE n b -> StutterNE n b #

return :: a -> StutterNE n a #

fail :: String -> StutterNE n a #

Functor (StutterNE n) Source # 
Instance details

Defined in Control.Monad.List.NonEmpty.Exotic

Methods

fmap :: (a -> b) -> StutterNE n a -> StutterNE n b #

(<$) :: a -> StutterNE n b -> StutterNE n a #

KnownNat n => Applicative (StutterNE n) Source # 
Instance details

Defined in Control.Monad.List.NonEmpty.Exotic

Methods

pure :: a -> StutterNE n a #

(<*>) :: StutterNE n (a -> b) -> StutterNE n a -> StutterNE n b #

liftA2 :: (a -> b -> c) -> StutterNE n a -> StutterNE n b -> StutterNE n c #

(*>) :: StutterNE n a -> StutterNE n b -> StutterNE n b #

(<*) :: StutterNE n a -> StutterNE n b -> StutterNE n a #

KnownNat n => HasShortFront (StutterNE n) Source #

(?)

Instance details

Defined in Control.Monad.List.NonEmpty.Exotic

KnownNat n => NonEmptyMonad (StutterNE n) Source # 
Instance details

Defined in Control.Monad.List.NonEmpty.Exotic

Methods

wrap :: NonEmpty a -> StutterNE n a Source #

unwrap :: StutterNE n a -> NonEmpty a Source #

KnownNat n => FreeRBM (StutterNE n) (StutterMagma n) Source # 
Instance details

Defined in Control.Monad.List.NonEmpty.Exotic

Methods

foldRBM :: (Magma a, StutterMagma n a) => (x -> a) -> StutterNE n x -> a Source #

KnownNat n => IsList (StutterNE n a) Source # 
Instance details

Defined in Control.Monad.List.NonEmpty.Exotic

Associated Types

type Item (StutterNE n a) :: Type #

Methods

fromList :: [Item (StutterNE n a)] -> StutterNE n a #

fromListN :: Int -> [Item (StutterNE n a)] -> StutterNE n a #

toList :: StutterNE n a -> [Item (StutterNE n a)] #

Eq a => Eq (StutterNE n a) Source # 
Instance details

Defined in Control.Monad.List.NonEmpty.Exotic

Methods

(==) :: StutterNE n a -> StutterNE n a -> Bool #

(/=) :: StutterNE n a -> StutterNE n a -> Bool #

Show a => Show (StutterNE n a) Source # 
Instance details

Defined in Control.Monad.List.NonEmpty.Exotic

Methods

showsPrec :: Int -> StutterNE n a -> ShowS #

show :: StutterNE n a -> String #

showList :: [StutterNE n a] -> ShowS #

KnownNat n => IsString (StutterNE n Char) Source # 
Instance details

Defined in Control.Monad.List.NonEmpty.Exotic

KnownNat n => Magma (StutterNE n a) Source # 
Instance details

Defined in Control.Monad.List.NonEmpty.Exotic

Methods

(<>) :: StutterNE n a -> StutterNE n a -> StutterNE n a Source #

KnownNat n => IsNonEmpty (StutterNE n a) Source # 
Instance details

Defined in Control.Monad.List.NonEmpty.Exotic

Associated Types

type ItemNE (StutterNE n a) :: Type Source #

type Item (StutterNE n a) Source # 
Instance details

Defined in Control.Monad.List.NonEmpty.Exotic

type Item (StutterNE n a) = a
type ItemNE (StutterNE n a) Source # 
Instance details

Defined in Control.Monad.List.NonEmpty.Exotic

type ItemNE (StutterNE n a) = a

Other monads with finite presentation

In contrast to the possibly-empty-list case, there are known non-empty monads that arise from algebraic theories, but ones that cannot be presented with one binary operations (as in monads that come about from subclasses of Magma).

The Head-Tails monad

class HeadTailTail a where Source #

The head-tail-tail algebra has two operations: unary hd (intuitively, it produces a singleton list with the head of the argument as the element) and ternary htt (intuitively, it produces the concat of the head of the first argument and tails of the other two arguments).

Instances should satisfy the following equations:

x                         ==  htt x x (hd x)
hd (hd x)                 ==  hd x
hd (htt x y z)            ==  hd x
htt x y (hd z)            ==  htt x y (hd y)
htt x y (htt z v w)       ==  htt x y (htt y v w)
htt x (hd y) (hd z)       ==  hd x
htt x (hd y) (htt z v w)  ==  htt x v w
htt x (htt y z v) w       ==  htt x z (htt z v w)
htt (hd x) y z            ==  htt x y z
htt (htt x y z) v w       ==  htt x v w

Moreover, when read left-to-right they form a terminating and confluent rewriting system with normal forms of the following shape:

htt x y $ htt y z $ htt z v $ ... $ htt w t (hd t)

Methods

hd :: a -> a Source #

htt :: a -> a -> a -> a Source #

Instances
HeadTailTail (HeadTails a) Source # 
Instance details

Defined in Control.Monad.List.NonEmpty.Exotic

newtype HeadTails a Source #

The Head-Tails monad arises from free head-tail-tail algebras. Its unit is a dubleton, that is:

return x = HeadTails (x :| [x])

Its join is defined as:

join ((x :| _) :| xss) = x :| concatMap NonEmpty.tail xss

For example:

>>> toList $ unwrap (join ["John", "Paul", "George", "Ringo"] :: HeadTails Char)
"Jauleorgeingo"

Constructors

HeadTails 

Fields

Instances
Monad HeadTails Source # 
Instance details

Defined in Control.Monad.List.NonEmpty.Exotic

Methods

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

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

return :: a -> HeadTails a #

fail :: String -> HeadTails a #

Functor HeadTails Source # 
Instance details

Defined in Control.Monad.List.NonEmpty.Exotic

Methods

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

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

Applicative HeadTails Source # 
Instance details

Defined in Control.Monad.List.NonEmpty.Exotic

Methods

pure :: a -> HeadTails a #

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

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

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

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

NonEmptyMonad HeadTails Source # 
Instance details

Defined in Control.Monad.List.NonEmpty.Exotic

IsList (HeadTails a) Source # 
Instance details

Defined in Control.Monad.List.NonEmpty.Exotic

Associated Types

type Item (HeadTails a) :: Type #

Methods

fromList :: [Item (HeadTails a)] -> HeadTails a #

fromListN :: Int -> [Item (HeadTails a)] -> HeadTails a #

toList :: HeadTails a -> [Item (HeadTails a)] #

Eq a => Eq (HeadTails a) Source # 
Instance details

Defined in Control.Monad.List.NonEmpty.Exotic

Methods

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

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

Show a => Show (HeadTails a) Source # 
Instance details

Defined in Control.Monad.List.NonEmpty.Exotic

IsString (HeadTails Char) Source # 
Instance details

Defined in Control.Monad.List.NonEmpty.Exotic

HeadTailTail (HeadTails a) Source # 
Instance details

Defined in Control.Monad.List.NonEmpty.Exotic

IsNonEmpty (HeadTails a) Source # 
Instance details

Defined in Control.Monad.List.NonEmpty.Exotic

Associated Types

type ItemNE (HeadTails a) :: Type Source #

type Item (HeadTails a) Source # 
Instance details

Defined in Control.Monad.List.NonEmpty.Exotic

type Item (HeadTails a) = a
type ItemNE (HeadTails a) Source # 
Instance details

Defined in Control.Monad.List.NonEmpty.Exotic

type ItemNE (HeadTails a) = a

foldHeadTails :: HeadTailTail a => (g -> a) -> HeadTails g -> a Source #

The HeadTails monad arises from free head-tail-tail algebras, so an interpretation of generators g to a head-tail-tail algebra a can be (uniquely) lifted to a homomorphism between head-tail-tail algebras.

The Heads-Tail monad

class HeadHeadTail a where Source #

Instances should satisfy the following equations:

x                    ==  ht x x
hd' (hd' x)          ==  hd' x
hd' (ht x y)         ==  hd' x
hd' (hht x y z)      ==  hd' x
ht x (hd' y)         ==  hd' x
ht x (ht y z)        ==  ht x z
ht x (hht y z v)     ==  hht x z v
ht (hd' x) y         ==  ht x y
ht (ht x y) z        ==  ht x z
ht (hht x y z) v     ==  ht x v
hht x y (hd' z)      ==  hd' x
hht x y (ht z v)     ==  hht x y v
hht x y (hht z v w)  ==  hht x y (hht y v w)
hht x (hd' y) z      ==  hht x y z
hht x (ht y z) v     ==  hht x y v
hht x (hht y z v) w  ==  hht x y w
hht (hd' x) y z      ==  hht x y z
hht (ht x y) z v     ==  hht x z v
hht (hht x y z) v w  ==  hht x v w

Moreover, when read left-to-right they form a terminating and confluent rewriting system with normal forms of the following shape:

hd' x
ht x y
hht x y $ hht y z $ hht z v $ ... $ hht w t u

Methods

hd' :: a -> a Source #

ht :: a -> a -> a Source #

hht :: a -> a -> a -> a Source #

newtype HeadsTail a Source #

The Heads-Tail monad arises from free head-head-tail algebras. Its unit is a dubleton, that is:

return x = HeadsTail (x :| [x])

Its join is defined as:

join xss@(splitSnoc -> (xss', xs@(_:|ys)))
  | isSingle xss || isSingle xs
  = (NonEmpty.head $ NonEmpty.head xss) :| []
  | otherwise
  = fromList $ map NonEmpty.head xss' ++ ys

For example:

>>> toList $ unwrap (join ["John", "Paul", "George", "Ringo"] :: HeadsTail Char)
"JPGingo"

Constructors

HeadsTail 

Fields

Instances
Monad HeadsTail Source # 
Instance details

Defined in Control.Monad.List.NonEmpty.Exotic

Methods

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

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

return :: a -> HeadsTail a #

fail :: String -> HeadsTail a #

Functor HeadsTail Source # 
Instance details

Defined in Control.Monad.List.NonEmpty.Exotic

Methods

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

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

Applicative HeadsTail Source # 
Instance details

Defined in Control.Monad.List.NonEmpty.Exotic

Methods

pure :: a -> HeadsTail a #

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

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

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

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

NonEmptyMonad HeadsTail Source # 
Instance details

Defined in Control.Monad.List.NonEmpty.Exotic

IsList (HeadsTail a) Source # 
Instance details

Defined in Control.Monad.List.NonEmpty.Exotic

Associated Types

type Item (HeadsTail a) :: Type #

Methods

fromList :: [Item (HeadsTail a)] -> HeadsTail a #

fromListN :: Int -> [Item (HeadsTail a)] -> HeadsTail a #

toList :: HeadsTail a -> [Item (HeadsTail a)] #

Eq a => Eq (HeadsTail a) Source # 
Instance details

Defined in Control.Monad.List.NonEmpty.Exotic

Methods

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

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

Show a => Show (HeadsTail a) Source # 
Instance details

Defined in Control.Monad.List.NonEmpty.Exotic

IsString (HeadsTail Char) Source # 
Instance details

Defined in Control.Monad.List.NonEmpty.Exotic

HeadHeadTail (HeadsTail a) Source # 
Instance details

Defined in Control.Monad.List.NonEmpty.Exotic

IsNonEmpty (HeadsTail a) Source # 
Instance details

Defined in Control.Monad.List.NonEmpty.Exotic

Associated Types

type ItemNE (HeadsTail a) :: Type Source #

type Item (HeadsTail a) Source # 
Instance details

Defined in Control.Monad.List.NonEmpty.Exotic

type Item (HeadsTail a) = a
type ItemNE (HeadsTail a) Source # 
Instance details

Defined in Control.Monad.List.NonEmpty.Exotic

type ItemNE (HeadsTail a) = a

foldHeadsTail :: HeadHeadTail a => (g -> a) -> HeadsTail g -> a Source #

The HeadsTail monad arises from free head-head-tail algebras, so an interpretation of generators g to a head-head-tail algebra a can be (uniquely) lifted to a homomorphism between head-head-tail algebras.

Other monads

The ΑΩ monad (?)

newtype AlphaOmega a Source #

The join of the ΑΩ (Alpha-Omega) monad takes the first element of the first list and the last element of the last list (unless the unit laws require otherwise):

join xss | isSingle xss || nonEmptyAll isSingle xss
         = nonEmptyConcat xss
         | otherwise
         =  NonEmpty.head (NonEmpty.head xss)
         :| NonEmpty.last (NonEmpty.last xss) : []

For example:

>>> toList $ unwrap (join ["John", "Paul", "George", "Ringo"] :: AlphaOmega Char)
"Jo"

Constructors

AlphaOmega 

Fields

Instances
Monad AlphaOmega Source # 
Instance details

Defined in Control.Monad.List.NonEmpty.Exotic

Methods

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

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

return :: a -> AlphaOmega a #

fail :: String -> AlphaOmega a #

Functor AlphaOmega Source # 
Instance details

Defined in Control.Monad.List.NonEmpty.Exotic

Methods

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

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

Applicative AlphaOmega Source # 
Instance details

Defined in Control.Monad.List.NonEmpty.Exotic

Methods

pure :: a -> AlphaOmega a #

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

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

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

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

HasShortRear AlphaOmega Source #

(?)

Instance details

Defined in Control.Monad.List.NonEmpty.Exotic

HasShortFront AlphaOmega Source #

(?)

Instance details

Defined in Control.Monad.List.NonEmpty.Exotic

NonEmptyMonad AlphaOmega Source # 
Instance details

Defined in Control.Monad.List.NonEmpty.Exotic

IsList (AlphaOmega a) Source # 
Instance details

Defined in Control.Monad.List.NonEmpty.Exotic

Associated Types

type Item (AlphaOmega a) :: Type #

Eq a => Eq (AlphaOmega a) Source # 
Instance details

Defined in Control.Monad.List.NonEmpty.Exotic

Methods

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

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

Show a => Show (AlphaOmega a) Source # 
Instance details

Defined in Control.Monad.List.NonEmpty.Exotic

IsString (AlphaOmega Char) Source # 
Instance details

Defined in Control.Monad.List.NonEmpty.Exotic

IsNonEmpty (AlphaOmega a) Source # 
Instance details

Defined in Control.Monad.List.NonEmpty.Exotic

Associated Types

type ItemNE (AlphaOmega a) :: Type Source #

type Item (AlphaOmega a) Source # 
Instance details

Defined in Control.Monad.List.NonEmpty.Exotic

type Item (AlphaOmega a) = a
type ItemNE (AlphaOmega a) Source # 
Instance details

Defined in Control.Monad.List.NonEmpty.Exotic

type ItemNE (AlphaOmega a) = a

Constructions on non-empty monads

The dual non-empty list monad

newtype DualNonEmptyMonad m a Source #

Every non-empty list monad has a dual, in which join is defined as

join . reverse . fmap reverse

(where join is the join of the original list monad), while return is

reverse . return

(where return is the return of the original list monad).

Constructors

DualNonEmptyMonad 

Fields

Instances
NonEmptyMonad m => Monad (DualNonEmptyMonad m) Source # 
Instance details

Defined in Control.Monad.List.NonEmpty.Exotic

Functor m => Functor (DualNonEmptyMonad m) Source # 
Instance details

Defined in Control.Monad.List.NonEmpty.Exotic

Methods

fmap :: (a -> b) -> DualNonEmptyMonad m a -> DualNonEmptyMonad m b #

(<$) :: a -> DualNonEmptyMonad m b -> DualNonEmptyMonad m a #

NonEmptyMonad m => Applicative (DualNonEmptyMonad m) Source # 
Instance details

Defined in Control.Monad.List.NonEmpty.Exotic

HasShortFront m => HasShortRear (DualNonEmptyMonad m) Source # 
Instance details

Defined in Control.Monad.List.NonEmpty.Exotic

HasShortRear m => HasShortFront (DualNonEmptyMonad m) Source # 
Instance details

Defined in Control.Monad.List.NonEmpty.Exotic

NonEmptyMonad m => NonEmptyMonad (DualNonEmptyMonad m) Source # 
Instance details

Defined in Control.Monad.List.NonEmpty.Exotic

Eq (m a) => Eq (DualNonEmptyMonad m a) Source # 
Instance details

Defined in Control.Monad.List.NonEmpty.Exotic

Show (m a) => Show (DualNonEmptyMonad m a) Source # 
Instance details

Defined in Control.Monad.List.NonEmpty.Exotic

IsNonEmpty (m a) => IsNonEmpty (DualNonEmptyMonad m a) Source # 
Instance details

Defined in Control.Monad.List.NonEmpty.Exotic

Associated Types

type ItemNE (DualNonEmptyMonad m a) :: Type Source #

type ItemNE (DualNonEmptyMonad m a) Source # 
Instance details

Defined in Control.Monad.List.NonEmpty.Exotic

type ItemNE (DualNonEmptyMonad m a) = ItemNE (m a)

The IdentityList monad

data IdXList m a Source #

NonEmpty a is isomorphic to the product (a, [a]). Thus, we can define a monadic structure on it by a product of the identity monad with any list monad. In particular:

return x          = IdXList x (return x)
IdXList x m >>= f = IdXList (componentId $ f x) (m >>= componentM . f)

where return and >>= in definition bodies come from the transformed monad.

Constructors

IdXList 

Fields

Instances
ListMonad m => Monad (IdXList m) Source # 
Instance details

Defined in Control.Monad.List.NonEmpty.Exotic

Methods

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

(>>) :: IdXList m a -> IdXList m b -> IdXList m b #

return :: a -> IdXList m a #

fail :: String -> IdXList m a #

Functor m => Functor (IdXList m) Source # 
Instance details

Defined in Control.Monad.List.NonEmpty.Exotic

Methods

fmap :: (a -> b) -> IdXList m a -> IdXList m b #

(<$) :: a -> IdXList m b -> IdXList m a #

ListMonad m => Applicative (IdXList m) Source # 
Instance details

Defined in Control.Monad.List.NonEmpty.Exotic

Methods

pure :: a -> IdXList m a #

(<*>) :: IdXList m (a -> b) -> IdXList m a -> IdXList m b #

liftA2 :: (a -> b -> c) -> IdXList m a -> IdXList m b -> IdXList m c #

(*>) :: IdXList m a -> IdXList m b -> IdXList m b #

(<*) :: IdXList m a -> IdXList m b -> IdXList m a #

ListMonad m => NonEmptyMonad (IdXList m) Source # 
Instance details

Defined in Control.Monad.List.NonEmpty.Exotic

Methods

wrap :: NonEmpty a -> IdXList m a Source #

unwrap :: IdXList m a -> NonEmpty a Source #

(Eq a, Eq (m a)) => Eq (IdXList m a) Source # 
Instance details

Defined in Control.Monad.List.NonEmpty.Exotic

Methods

(==) :: IdXList m a -> IdXList m a -> Bool #

(/=) :: IdXList m a -> IdXList m a -> Bool #

(Show a, Show (m a)) => Show (IdXList m a) Source # 
Instance details

Defined in Control.Monad.List.NonEmpty.Exotic

Methods

showsPrec :: Int -> IdXList m a -> ShowS #

show :: IdXList m a -> String #

showList :: [IdXList m a] -> ShowS #

ListMonad m => IsNonEmpty (IdXList m a) Source # 
Instance details

Defined in Control.Monad.List.NonEmpty.Exotic

Associated Types

type ItemNE (IdXList m a) :: Type Source #

type ItemNE (IdXList m a) Source # 
Instance details

Defined in Control.Monad.List.NonEmpty.Exotic

type ItemNE (IdXList m a) = a

Short-front monads

class NonEmptyMonad m => HasShortFront m Source #

Instances of this class are non-empty list monads for which the ShortFront construction gives a monad.

newtype ShortFront m (p :: Nat) a Source #

This is a transformer for a number of monads (instances of the HasShortFront class), whose return is singleton and join takes the prefix of length p + 2 of the result of the join of the transformed monad (unless the unit laws require otherwise):

joinList xss | isSingle xss || all isSingle xss = concat xss
             | otherwise = take (p + 2) (joinList xss)

where joinList in the otherwise branch is the joinList of the transformed monad.

While there are quite a few "short front" monads on non-empty lists, only one such monad on possibly-empty lists is known, StutterKeeper (the short version is ShortStutterKeeper).

Constructors

ShortFront 

Fields

Instances
(HasShortFront m, KnownNat p) => Monad (ShortFront m p) Source # 
Instance details

Defined in Control.Monad.List.NonEmpty.Exotic

Methods

(>>=) :: ShortFront m p a -> (a -> ShortFront m p b) -> ShortFront m p b #

(>>) :: ShortFront m p a -> ShortFront m p b -> ShortFront m p b #

return :: a -> ShortFront m p a #

fail :: String -> ShortFront m p a #

Functor m => Functor (ShortFront m p) Source # 
Instance details

Defined in Control.Monad.List.NonEmpty.Exotic

Methods

fmap :: (a -> b) -> ShortFront m p a -> ShortFront m p b #

(<$) :: a -> ShortFront m p b -> ShortFront m p a #

(HasShortFront m, KnownNat p) => Applicative (ShortFront m p) Source # 
Instance details

Defined in Control.Monad.List.NonEmpty.Exotic

Methods

pure :: a -> ShortFront m p a #

(<*>) :: ShortFront m p (a -> b) -> ShortFront m p a -> ShortFront m p b #

liftA2 :: (a -> b -> c) -> ShortFront m p a -> ShortFront m p b -> ShortFront m p c #

(*>) :: ShortFront m p a -> ShortFront m p b -> ShortFront m p b #

(<*) :: ShortFront m p a -> ShortFront m p b -> ShortFront m p a #

(HasShortFront m, KnownNat p) => NonEmptyMonad (ShortFront m p) Source # 
Instance details

Defined in Control.Monad.List.NonEmpty.Exotic

Methods

wrap :: NonEmpty a -> ShortFront m p a Source #

unwrap :: ShortFront m p a -> NonEmpty a Source #

Eq (m a) => Eq (ShortFront m p a) Source # 
Instance details

Defined in Control.Monad.List.NonEmpty.Exotic

Methods

(==) :: ShortFront m p a -> ShortFront m p a -> Bool #

(/=) :: ShortFront m p a -> ShortFront m p a -> Bool #

Show (m a) => Show (ShortFront m p a) Source # 
Instance details

Defined in Control.Monad.List.NonEmpty.Exotic

Methods

showsPrec :: Int -> ShortFront m p a -> ShowS #

show :: ShortFront m p a -> String #

showList :: [ShortFront m p a] -> ShowS #

(IsNonEmpty (m a), KnownNat p) => IsNonEmpty (ShortFront m p a) Source # 
Instance details

Defined in Control.Monad.List.NonEmpty.Exotic

Associated Types

type ItemNE (ShortFront m p a) :: Type Source #

type ItemNE (ShortFront m p a) Source # 
Instance details

Defined in Control.Monad.List.NonEmpty.Exotic

type ItemNE (ShortFront m p a) = ItemNE (m a)

Short-rear monads

class NonEmptyMonad m => HasShortRear m Source #

Instances of this class are non-empty list monads for which the ShortRear construction gives a monad.

newtype ShortRear m (p :: Nat) a Source #

Similar to ShortFront, but gives a monad if restricted to a suffix of the length p + 2.

Constructors

ShortRear 

Fields

Instances
(HasShortRear m, KnownNat p) => Monad (ShortRear m p) Source # 
Instance details

Defined in Control.Monad.List.NonEmpty.Exotic

Methods

(>>=) :: ShortRear m p a -> (a -> ShortRear m p b) -> ShortRear m p b #

(>>) :: ShortRear m p a -> ShortRear m p b -> ShortRear m p b #

return :: a -> ShortRear m p a #

fail :: String -> ShortRear m p a #

Functor m => Functor (ShortRear m p) Source # 
Instance details

Defined in Control.Monad.List.NonEmpty.Exotic

Methods

fmap :: (a -> b) -> ShortRear m p a -> ShortRear m p b #

(<$) :: a -> ShortRear m p b -> ShortRear m p a #

(HasShortRear m, KnownNat p) => Applicative (ShortRear m p) Source # 
Instance details

Defined in Control.Monad.List.NonEmpty.Exotic

Methods

pure :: a -> ShortRear m p a #

(<*>) :: ShortRear m p (a -> b) -> ShortRear m p a -> ShortRear m p b #

liftA2 :: (a -> b -> c) -> ShortRear m p a -> ShortRear m p b -> ShortRear m p c #

(*>) :: ShortRear m p a -> ShortRear m p b -> ShortRear m p b #

(<*) :: ShortRear m p a -> ShortRear m p b -> ShortRear m p a #

(HasShortRear m, KnownNat p) => NonEmptyMonad (ShortRear m p) Source # 
Instance details

Defined in Control.Monad.List.NonEmpty.Exotic

Methods

wrap :: NonEmpty a -> ShortRear m p a Source #

unwrap :: ShortRear m p a -> NonEmpty a Source #

Eq (m a) => Eq (ShortRear m p a) Source # 
Instance details

Defined in Control.Monad.List.NonEmpty.Exotic

Methods

(==) :: ShortRear m p a -> ShortRear m p a -> Bool #

(/=) :: ShortRear m p a -> ShortRear m p a -> Bool #

Show (m a) => Show (ShortRear m p a) Source # 
Instance details

Defined in Control.Monad.List.NonEmpty.Exotic

Methods

showsPrec :: Int -> ShortRear m p a -> ShowS #

show :: ShortRear m p a -> String #

showList :: [ShortRear m p a] -> ShowS #

(IsNonEmpty (m a), KnownNat p) => IsNonEmpty (ShortRear m p a) Source # 
Instance details

Defined in Control.Monad.List.NonEmpty.Exotic

Associated Types

type ItemNE (ShortRear m p a) :: Type Source #

type ItemNE (ShortRear m p a) Source # 
Instance details

Defined in Control.Monad.List.NonEmpty.Exotic

type ItemNE (ShortRear m p a) = ItemNE (m a)