cabal-debian-3.0.4: Create a debianization for a cabal package

Safe HaskellNone

Triplets

Synopsis

Documentation

gzipWithA3 :: forall f. Applicative f => GA f -> GA fSource

gzip3 :: PM -> PMSource

The purpose of gzip3 is to map a polymorphic (generic) function over the elements of three instances of a type. The function returns a Maybe value of the same type as the elements passed. If it returns a Just the subtree is not traversed, the returned value is used. If it returns Nothing the subtree is traversed. This traversal may succeed where the top level test failed, resulting in a successful zip. For example, the merge function wouldn't merge these three values: (1, 1) (1, 2) (2, 1) -> (?, ?) but it could merge the two unzipped triples: (1, 1, 2) -> 2 (1, 2, 1) -> 2 -> (2, 2)

gzipQ3 :: GMSource

This is the minimal condition for recursing into a value - the constructors must all match.

gzipBut3 :: PM -> GM -> PMSource

This function adds a test to limit the recursion of gzip3. For example, with the merge function mentioned above you might want to avoid merging strings character by character:

gzip3 merge dim kim dip -> Just kip (no!)

so you would pass a limiting function to prevent recursing into strings:

let continue = ( x y z -> extQ3 gzipQ3 x y z) x y z where stringFail :: String -> String -> String -> Bool stringFail _ _ _ = False gzipBut3 merge continue dim kim dip -> Nothing

this can also save a lot of time examining all the heads and tails of every string.

gzipButA3 :: forall f. Applicative f => PM -> GB -> PA f -> PA fSource

gzipWithA3 plus a continue function to prevent recursion into particular types. (UNTESTED)

extQ2 :: (Typeable a, Typeable b, Typeable d, Typeable e) => (a -> b -> r) -> (d -> e -> r) -> a -> b -> rSource

Not to be confused with ext2Q, this extends queries of two arguments (rather than queries involving constructors with two type parameters.)

extQ3 :: (Typeable a, Typeable b, Typeable c, Typeable d, Typeable e, Typeable f) => (a -> b -> c -> r) -> (d -> e -> f -> r) -> a -> b -> c -> rSource

extT3 :: (Typeable a, Typeable b) => (a -> a -> a -> Maybe a) -> (b -> b -> b -> Maybe b) -> a -> a -> a -> Maybe aSource

mkQ3 :: (Typeable a, Typeable b, Typeable c, Typeable d, Typeable e, Typeable f) => r -> (a -> b -> c -> r) -> d -> e -> f -> rSource

mkQ2 :: (Data a, Data b, Data c) => (a -> b -> r) -> (c -> c -> r) -> a -> b -> rSource

mergeBy :: forall a m. MonadPlus m => (a -> a -> a -> m a) -> (a -> a -> Bool) -> a -> a -> a -> m aSource

This function implements the f function used to do three way merging. A triplet (original, new1, new2) conflicts if the two new values each differ from the original, and from each other. Otherwise, the new value that differs from the original is kept, or either of the new values if they match. However, even if the values conflict, it still might be possible to do the merge by examining the components of the value. So conflict is typically ( _ _ _ -> Nothing), while eq could be geq, but it could also just return false for more complex datatypes that we don't want to repeatedly traverse.

type GB = GenericQ (GenericQ (GenericQ Bool))Source

Generic Bool Query, (Data a, Data b, Data c) => a -> b -> c -> Bool

type GM = MonadPlus m => GenericQ (GenericQ (GenericM m))Source

Generic Maybe Query, (Data a, Data b, Data c) => a -> b -> c -> Maybe c

type GA f = GenericQ (GenericQ (GenericM f))Source

Generic Applicative Query, forall a. Data a => a -> (forall b. Data b => b -> (forall c. Data c => c -> f c))

type PB = forall x. Data x => x -> x -> x -> BoolSource

Polymorphic Bool Query

type PM = forall m x. (MonadPlus m, Data x) => x -> x -> x -> m xSource

Polymorphic Failing Query, forall x. Data x => x -> x -> x -> Failing x

type PA f = forall x. Data x => x -> x -> x -> f xSource

Polymorphic Applicative Query