primus-0.3.0.0: nonempty and positive functions
Copyright(c) Grant Weyburne 2022
LicenseBSD-3
Safe HaskellSafe-Inferred
LanguageHaskell2010

Primus.AsMaybe

Description

 
Synopsis

AsMaybe

class AsMaybe x b | x -> b where Source #

converts to a Maybe for failure types

Methods

toMaybe :: x -> Maybe b Source #

Instances

Instances details
b1 ~ [b] => AsMaybe [b] b1 Source # 
Instance details

Defined in Primus.AsMaybe

Methods

toMaybe :: [b] -> Maybe b1 Source #

b ~ b1 => AsMaybe (Maybe b) b1 Source # 
Instance details

Defined in Primus.AsMaybe

Methods

toMaybe :: Maybe b -> Maybe b1 Source #

AsMaybe x z => AsMaybe (Identity x) z Source # 
Instance details

Defined in Primus.AsMaybe

Methods

toMaybe :: Identity x -> Maybe z Source #

b ~ b1 => AsMaybe (Either e b) b1 Source # 
Instance details

Defined in Primus.AsMaybe

Methods

toMaybe :: Either e b -> Maybe b1 Source #

(b ~ (b1, b2), AsMaybe x b1, AsMaybe y b2) => AsMaybe (x, y) b Source # 
Instance details

Defined in Primus.AsMaybe

Methods

toMaybe :: (x, y) -> Maybe b Source #

(z ~ Arg b1 y, AsMaybe x b1) => AsMaybe (Arg x y) z Source # 
Instance details

Defined in Primus.AsMaybe

Methods

toMaybe :: Arg x y -> Maybe z Source #

b ~ b1 => AsMaybe (These e b) b1 Source # 
Instance details

Defined in Primus.AsMaybe

Methods

toMaybe :: These e b -> Maybe b1 Source #

(b ~ (b1, b2, b3), AsMaybe x b1, AsMaybe y b2, AsMaybe z b3) => AsMaybe (x, y, z) b Source # 
Instance details

Defined in Primus.AsMaybe

Methods

toMaybe :: (x, y, z) -> Maybe b Source #

iterateT1 :: AsMaybe x a => (a -> x) -> a -> NonEmpty a Source #

similar to iterate but terminate using AsMaybe

unfoldrT :: AsMaybe t t => (t -> (a, t)) -> t -> [a] Source #

like unfoldr but terminate using AsMaybe

>>> unfoldrT (splitAt 2) [1..8]
[[1,2],[3,4],[5,6],[7,8]]

vs

>>> unfoldr (s -> if null s then Nothing else Just (splitAt 2 s)) [1..8]
[[1,2],[3,4],[5,6],[7,8]]

pairsT :: (x -> (a, x)) -> (y -> (b, y)) -> (x, y) -> ((a, b), (x, y)) Source #

run a functions against each side of a tuple and stitch them together for use with unfoldrT where "s" is a tuple and you want to stop as soon as the either terminates

ApThese

class ApThese e a x b | x e a -> b where Source #

flexible "e" to use with eg partitionTheseT: Bool is also valid

Methods

apThese :: a -> x -> These e b Source #

Instances

Instances details
(e ~ a, b ~ a) => ApThese e a Bool b Source # 
Instance details

Defined in Primus.AsMaybe

Methods

apThese :: a -> Bool -> These e b Source #

ApThese e a x z => ApThese e a (Identity x) z Source # 
Instance details

Defined in Primus.AsMaybe

Methods

apThese :: a -> Identity x -> These e z Source #

(e ~ a, b1 ~ [b]) => ApThese e a [b] b1 Source # 
Instance details

Defined in Primus.AsMaybe

Methods

apThese :: a -> [b] -> These e b1 Source #

(e ~ a, b ~ b1) => ApThese e a (Maybe b) b1 Source # 
Instance details

Defined in Primus.AsMaybe

Methods

apThese :: a -> Maybe b -> These e b1 Source #

(Semigroup e, b ~ (b1, b2), ApThese e a x b1, ApThese e a y b2) => ApThese e a (x, y) b Source # 
Instance details

Defined in Primus.AsMaybe

Methods

apThese :: a -> (x, y) -> These e b Source #

(z ~ Arg b1 y, ApThese e a x b1) => ApThese e a (Arg x y) z Source # 
Instance details

Defined in Primus.AsMaybe

Methods

apThese :: a -> Arg x y -> These e z Source #

(e ~ e1, b ~ b1) => ApThese e1 a (Either e b) b1 Source # 
Instance details

Defined in Primus.AsMaybe

Methods

apThese :: a -> Either e b -> These e1 b1 Source #

(e ~ e1, b ~ b1) => ApThese e1 a (These e b) b1 Source # 
Instance details

Defined in Primus.AsMaybe

Methods

apThese :: a -> These e b -> These e1 b1 Source #

(Semigroup e, b ~ (b1, b2, b3), ApThese e a x b1, ApThese e a y b2, ApThese e a z b3) => ApThese e a (x, y, z) b Source # 
Instance details

Defined in Primus.AsMaybe

Methods

apThese :: a -> (x, y, z) -> These e b Source #

toTheseT :: forall e a x b. ApThese e a x b => (a -> x) -> [a] -> [These e b] Source #

apply a function to a list and convert to a list of These

toTheseTS :: forall e a x b z. ApThese e a x b => (z -> a -> (z, x)) -> z -> [a] -> (z, [These e b]) Source #

like toTheseT with state

partitionEithersT :: forall e a b x. ApThese e a x b => (a -> x) -> [a] -> ([e], [b]) Source #

like toTheseT but use partitionHereThere on the results (swapped version of partition)

partitionTheseT :: forall e a b x. ApThese e a x b => (a -> x) -> [a] -> ([e], [b], [(e, b)]) Source #

like toTheseT but use partitionThese on the results

filterT :: forall e a b x. ApThese e a x b => (a -> x) -> [a] -> [b] Source #

like partitionEithersT ignoring the second element of the result

spanT :: forall e a x b. ApThese e a x b => (a -> x) -> [a] -> ([b], [a]) Source #

similar to span using ApThese for failure (support Bool and These)

spanTAlt :: forall e a x b. ApThese e a x b => (a -> x) -> [a] -> ([b], [a]) Source #

like spanT but doesn't continue in the These case

spanTS :: forall e a x b z. ApThese e a x b => (z -> a -> (z, x)) -> z -> [a] -> (z, ([b], [a])) Source #

like spanT with state

takeWhileT :: forall e a x b. ApThese e a x b => (a -> x) -> [a] -> [b] Source #

like spanT but ignore the second element of the result

takeWhileTS :: forall e a x b z. ApThese e a x b => (z -> a -> (z, x)) -> z -> [a] -> (z, [b]) Source #

like takeWhileT with state

ApTheseF for use with LRHist

class ApTheseF e a x b | x e a -> b where Source #

for use with LRHist using a fixed "e"

Methods

apTheseF :: a -> x -> These e b Source #

Instances

Instances details
(Monoid e, b ~ a) => ApTheseF e a Bool b Source # 
Instance details

Defined in Primus.AsMaybe

Methods

apTheseF :: a -> Bool -> These e b Source #

ApTheseF e a x z => ApTheseF e a (Identity x) z Source # 
Instance details

Defined in Primus.AsMaybe

Methods

apTheseF :: a -> Identity x -> These e z Source #

(Monoid e, b1 ~ [b]) => ApTheseF e a [b] b1 Source # 
Instance details

Defined in Primus.AsMaybe

Methods

apTheseF :: a -> [b] -> These e b1 Source #

(Monoid e, b ~ b1) => ApTheseF e a (Maybe b) b1 Source # 
Instance details

Defined in Primus.AsMaybe

Methods

apTheseF :: a -> Maybe b -> These e b1 Source #

(Semigroup e, b ~ (b1, b2), ApTheseF e a x b1, ApTheseF e a y b2) => ApTheseF e a (x, y) b Source # 
Instance details

Defined in Primus.AsMaybe

Methods

apTheseF :: a -> (x, y) -> These e b Source #

(z ~ Arg b1 y, ApTheseF e a x b1) => ApTheseF e a (Arg x y) z Source # 
Instance details

Defined in Primus.AsMaybe

Methods

apTheseF :: a -> Arg x y -> These e z Source #

(e ~ e1, b ~ b1) => ApTheseF e1 a (Either e b) b1 Source # 
Instance details

Defined in Primus.AsMaybe

Methods

apTheseF :: a -> Either e b -> These e1 b1 Source #

(e ~ e1, b ~ b1) => ApTheseF e1 a (These e b) b1 Source # 
Instance details

Defined in Primus.AsMaybe

Methods

apTheseF :: a -> These e b -> These e1 b1 Source #

(Semigroup e, b ~ (b1, b2, b3), ApTheseF e a x b1, ApTheseF e a y b2, ApTheseF e a z b3) => ApTheseF e a (x, y, z) b Source # 
Instance details

Defined in Primus.AsMaybe

Methods

apTheseF :: a -> (x, y, z) -> These e b Source #