-- ------------------------------------------------------------

{- |
   Module     : Control.Arrow.ArrowList
   Copyright  : Copyright (C) 2005 Uwe Schmidt
   License    : MIT

   Maintainer : Uwe Schmidt (uwe\@fh-wedel.de)
   Stability  : experimental
   Portability: portable

   The list arrow class

   This module defines the interface for list arrows.

   A list arrow is a function that gives a list of results
   for a given argument. A single element result represents a normal function.
   An empty list often indicates that the function is undefined
   for the given argument.
   The empty list may also represent False, non-empty lists True.
   A list with more than one element gives all results for a
   so called nondeterministic function.

-}

-- ------------------------------------------------------------

module Control.Arrow.ArrowList
    ( ArrowList(..)
    )
where

import Control.Arrow

infixl 8 >>., >.

infixl 2 $<, $<<, $<<<, $<<<<
infixl 2 $<$

-- ------------------------------------------------------------

-- | The interface for list arrows
--
-- Only 'mkA', 'isA' '(>>.)' don't have default implementations

class (Arrow a, ArrowPlus a, ArrowZero a, ArrowApply a) => ArrowList a where

    -- | construction of a 2 argument arrow from a binary function
    -- |
    -- | example: @ a1 &&& a2 >>> arr2 f @

    arr2                :: (b1 -> b2 -> c) -> a (b1, b2) c
    arr2                = ((b1, b2) -> c) -> a (b1, b2) c
forall (a :: * -> * -> *) b c. Arrow a => (b -> c) -> a b c
arr (((b1, b2) -> c) -> a (b1, b2) c)
-> ((b1 -> b2 -> c) -> (b1, b2) -> c)
-> (b1 -> b2 -> c)
-> a (b1, b2) c
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (b1 -> b2 -> c) -> (b1, b2) -> c
forall a b c. (a -> b -> c) -> (a, b) -> c
uncurry
    {-# INLINE arr2 #-}

    -- | construction of a 3 argument arrow from a 3-ary function
    -- |
    -- | example: @ a1 &&& a2 &&& a3 >>> arr3 f @

    arr3                :: (b1 -> b2 -> b3 -> c) -> a (b1, (b2, b3)) c
    arr3 b1 -> b2 -> b3 -> c
f              = ((b1, (b2, b3)) -> c) -> a (b1, (b2, b3)) c
forall (a :: * -> * -> *) b c. Arrow a => (b -> c) -> a b c
arr (\ ~(b1
x1, ~(b2
x2, b3
x3)) -> b1 -> b2 -> b3 -> c
f b1
x1 b2
x2 b3
x3)
    {-# INLINE arr3 #-}

    -- | construction of a 4 argument arrow from a 4-ary function
    -- |
    -- | example: @ a1 &&& a2 &&& a3 &&& a4 >>> arr4 f @

    arr4                :: (b1 -> b2 -> b3 -> b4 -> c) -> a (b1, (b2, (b3, b4))) c
    arr4 b1 -> b2 -> b3 -> b4 -> c
f              = ((b1, (b2, (b3, b4))) -> c) -> a (b1, (b2, (b3, b4))) c
forall (a :: * -> * -> *) b c. Arrow a => (b -> c) -> a b c
arr (\ ~(b1
x1, ~(b2
x2, ~(b3
x3, b4
x4))) -> b1 -> b2 -> b3 -> b4 -> c
f b1
x1 b2
x2 b3
x3 b4
x4)
    {-# INLINE arr4 #-}

    -- | construction of a 2 argument arrow from a singe argument arrow

    arr2A               :: (b -> a c d) -> a (b, c) d
    arr2A b -> a c d
f             = a b (a c d) -> a (b, c) (a c d, c)
forall (a :: * -> * -> *) b c d.
Arrow a =>
a b c -> a (b, d) (c, d)
first ((b -> a c d) -> a b (a c d)
forall (a :: * -> * -> *) b c. Arrow a => (b -> c) -> a b c
arr b -> a c d
f) a (b, c) (a c d, c) -> a (a c d, c) d -> a (b, c) d
forall k (cat :: k -> k -> *) (a :: k) (b :: k) (c :: k).
Category cat =>
cat a b -> cat b c -> cat a c
>>> a (a c d, c) d
forall (a :: * -> * -> *) b c. ArrowApply a => a (a b c, b) c
app
    {-# INLINE arr2A #-}

    -- | constructor for a list arrow from a function with a list as result

    arrL                :: (b -> [c]) -> a b c

    -- | constructor for a list arrow with 2 arguments

    arr2L               :: (b -> c -> [d]) -> a (b, c) d
    arr2L               = ((b, c) -> [d]) -> a (b, c) d
forall (a :: * -> * -> *) b c. ArrowList a => (b -> [c]) -> a b c
arrL (((b, c) -> [d]) -> a (b, c) d)
-> ((b -> c -> [d]) -> (b, c) -> [d])
-> (b -> c -> [d])
-> a (b, c) d
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (b -> c -> [d]) -> (b, c) -> [d]
forall a b c. (a -> b -> c) -> (a, b) -> c
uncurry
    {-# INLINE arr2L #-}

    -- | constructor for a const arrow: @ constA = arr . const @

    constA              :: c -> a b c
    constA              = (b -> c) -> a b c
forall (a :: * -> * -> *) b c. Arrow a => (b -> c) -> a b c
arr ((b -> c) -> a b c) -> (c -> b -> c) -> c -> a b c
forall b c a. (b -> c) -> (a -> b) -> a -> c
. c -> b -> c
forall a b. a -> b -> a
const
    {-# INLINE constA #-}

    -- | constructor for a const arrow: @ constL = arrL . const @

    constL              :: [c] -> a b c
    constL              = (b -> [c]) -> a b c
forall (a :: * -> * -> *) b c. ArrowList a => (b -> [c]) -> a b c
arrL ((b -> [c]) -> a b c) -> ([c] -> b -> [c]) -> [c] -> a b c
forall b c a. (b -> c) -> (a -> b) -> a -> c
. [c] -> b -> [c]
forall a b. a -> b -> a
const
    {-# INLINE constL #-}

    -- | builds an arrow from a predicate.
    -- If the predicate holds, the single list containing the input is returned, else the empty list

    isA                 :: (b -> Bool) -> a b b

    -- | combinator for converting the result of a list arrow into another list
    --
    -- example: @ foo >>. reverse @ reverses the the result of foo
    --
    -- example: @ foo >>. take 1 @ constructs a deterministic version of foo by deleting all further results

    (>>.)               :: a b c -> ([c] -> [d]) -> a b d

    -- | combinator for converting the result of an arrow into a single element result

    (>.)                :: a b c -> ([c] ->  d ) -> a b d
    a b c
af >. [c] -> d
f             = a b c
af a b c -> ([c] -> [d]) -> a b d
forall (a :: * -> * -> *) b c d.
ArrowList a =>
a b c -> ([c] -> [d]) -> a b d
>>. ((d -> [d] -> [d]
forall a. a -> [a] -> [a]
:[]) (d -> [d]) -> ([c] -> d) -> [c] -> [d]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. [c] -> d
f)
    {-# INLINE (>.) #-}

    -- | combinator for converting an arrow into a determinstic version with all results collected in a single element list
    --
    -- @ listA af = af >>. (:[]) @
    --
    -- this is useful when the list of results computed by an arrow must be manipulated (e.g. sorted)
    --
    -- example for sorting the results of a filter
    --
    -- > collectAndSort         :: a b c -> a b c
    -- >
    -- > collectAndSort collect = listA collect >>> arrL sort

    listA               :: a b c -> a b [c]
    listA a b c
af            = a b c
af a b c -> ([c] -> [[c]]) -> a b [c]
forall (a :: * -> * -> *) b c d.
ArrowList a =>
a b c -> ([c] -> [d]) -> a b d
>>.  ([c] -> [[c]] -> [[c]]
forall a. a -> [a] -> [a]
:[])
    {-# INLINE listA #-}

    -- | the inverse of 'listA'
    --
    -- @ listA af >>> unlistA = af @
    --
    -- unlistA is defined as @ arrL id @

    unlistA             :: a [b] b
    unlistA             = ([b] -> [b]) -> a [b] b
forall (a :: * -> * -> *) b c. ArrowList a => (b -> [c]) -> a b c
arrL [b] -> [b]
forall a. a -> a
id
    {-# INLINE unlistA #-}

    -- | the identity arrow, alias for returnA

    this                :: a b b
    this                = a b b
forall (a :: * -> * -> *) b. Arrow a => a b b
returnA
    {-# INLINE this #-}

    -- | the zero arrow, alias for zeroArrow

    none                :: a b c
    none                = a b c
forall (a :: * -> * -> *) b c. ArrowZero a => a b c
zeroArrow
    {-# INLINE none #-}

    -- | converts an arrow, that may fail, into an arrow that always succeeds
    --
    -- example: @ withDefault none \"abc\" @ is equivalent to @ constA \"abc\" @

    withDefault         :: a b c -> c -> a b c
    withDefault a b c
a c
d     = a b c
a a b c -> ([c] -> [c]) -> a b c
forall (a :: * -> * -> *) b c d.
ArrowList a =>
a b c -> ([c] -> [d]) -> a b d
>>. \ [c]
x -> if [c] -> Bool
forall (t :: * -> *) a. Foldable t => t a -> Bool
null [c]
x then [c
d] else [c]
x
    {-# INLINE withDefault #-}

    -- | makes a list arrow deterministic, the number of results is at most 1
    --
    -- definition
    --
    -- > single f = f >>. take 1
    --
    -- examples with strings:
    --
    -- > runLA ( single none ) "x" == []
    -- > runLA ( single this ) "x" == ["x"]
    -- > runLA ( single
    -- >         (constA "y"
    -- >          <+> this ) ) "x" == ["y"]

    single              :: a b c -> a b c
    single a b c
f            = a b c
f a b c -> ([c] -> [c]) -> a b c
forall (a :: * -> * -> *) b c d.
ArrowList a =>
a b c -> ([c] -> [d]) -> a b d
>>. Int -> [c] -> [c]
forall a. Int -> [a] -> [a]
take Int
1

    -- | compute an arrow from the input and apply the arrow to this input
    --
    -- definition: @ (f &&& this) >>> app @
    --
    -- in a point free style, there is no way to use an argument in 2 places,
    -- this is a combinator for simulating this. first the argument is used to compute an arrow,
    -- then this new arrow is applied to the input
    --
    -- applyA coresponds to: @ apply f x = let g = f x in g x @
    --
    -- see also: '$<', '$<<', '$<<<', '$<<<<', '$<$'

    applyA              :: a b (a b c) -> a b c
    applyA a b (a b c)
f            = (a b (a b c)
f a b (a b c) -> a b b -> a b (a b c, b)
forall (a :: * -> * -> *) b c c'.
Arrow a =>
a b c -> a b c' -> a b (c, c')
&&& a b b
forall (a :: * -> * -> *) b. ArrowList a => a b b
this) a b (a b c, b) -> a (a b c, b) c -> a b c
forall k (cat :: k -> k -> *) (a :: k) (b :: k) (c :: k).
Category cat =>
cat a b -> cat b c -> cat a c
>>> a (a b c, b) c
forall (a :: * -> * -> *) b c. ArrowApply a => a (a b c, b) c
app

    -- | compute the parameter for an arrow with extra parameters from the input
    -- and apply the arrow for all parameter values to the input
    --
    -- a kind of \"function call\" for arrows, useful for joining arrows
    --
    -- > infixl 2 ($<)
    --
    -- definition:
    --
    -- > g $< f = applyA (f >>> arr g)
    --
    -- if @f@ fails, the whole arrow fails, e.g. @ g \$\< none == none @
    --
    -- if @f@ computes n values and @g@ is deterministic, the whole arrow computes n values
    --
    -- examples with simple list arrows with strings
    --
    -- > prefixString   :: String -> a String String
    -- > prefixString s =  arr (s++)
    -- >
    -- > runLA ( prefixString $< none           ) "x" == []
    -- > runLA ( prefixString $< constA "y"     ) "x" == ["yx"]
    -- > runLA ( prefixString $< this           ) "x" == ["xx"]
    -- > runLA ( prefixString $< constA "y"
    -- >                         <+> constA "z" ) "x" == ["yx","zx"]
    -- > runLA ( prefixString $< constA "y"
    -- >                         <+> this
    -- >                         <+> constA "z" ) "x" == ["yx","xx","zx"]
    --
    -- see also: 'applyA', '$<<', '$<<<', '$<<<<', '$<$'

    ($<)                :: (c -> a b d) -> a b c -> a b d
    c -> a b d
g $< a b c
f              = a b (a b d) -> a b d
forall (a :: * -> * -> *) b c. ArrowList a => a b (a b c) -> a b c
applyA (a b c
f a b c -> a c (a b d) -> a b (a b d)
forall k (cat :: k -> k -> *) (a :: k) (b :: k) (c :: k).
Category cat =>
cat a b -> cat b c -> cat a c
>>> (c -> a b d) -> a c (a b d)
forall (a :: * -> * -> *) b c. Arrow a => (b -> c) -> a b c
arr c -> a b d
g)

    -- | binary version of '$<'
    --
    -- example with simple list arrows with strings
    --
    -- > infixString    :: String -> String -> a String String
    -- > infixString s1 s2
    -- >                = arr (\ s -> s1 ++ s ++ s2)
    -- >
    -- > runLA ( infixString $<< constA "y" &&& constA "z" ) "x" = ["yxz"]
    -- > runLA ( infixString $<< this &&& this             ) "x" = ["xxx"]
    -- > runLA ( infixString $<< constA "y"
    -- >                         &&& (constA "z" <+> this) ) "x" = ["yxz", "yxx"]

    ($<<)               :: (c1 -> c2 -> a b d) -> a b (c1, c2) -> a b d
    c1 -> c2 -> a b d
f $<< a b (c1, c2)
g             = a b (a b d) -> a b d
forall (a :: * -> * -> *) b c. ArrowList a => a b (a b c) -> a b c
applyA (a b (c1, c2)
g a b (c1, c2) -> a (c1, c2) (a b d) -> a b (a b d)
forall k (cat :: k -> k -> *) (a :: k) (b :: k) (c :: k).
Category cat =>
cat a b -> cat b c -> cat a c
>>> (c1 -> c2 -> a b d) -> a (c1, c2) (a b d)
forall (a :: * -> * -> *) b1 b2 c.
ArrowList a =>
(b1 -> b2 -> c) -> a (b1, b2) c
arr2 c1 -> c2 -> a b d
f)

    -- | version of '$<' for arrows with 3 extra parameters
    --
    -- typical usage
    --
    -- > f $<<< g1 &&& g2 &&& g3

    ($<<<)              :: (c1 -> c2 -> c3 -> a b d) -> a b (c1, (c2, c3)) -> a b d
    c1 -> c2 -> c3 -> a b d
f $<<< a b (c1, (c2, c3))
g            = a b (a b d) -> a b d
forall (a :: * -> * -> *) b c. ArrowList a => a b (a b c) -> a b c
applyA (a b (c1, (c2, c3))
g a b (c1, (c2, c3)) -> a (c1, (c2, c3)) (a b d) -> a b (a b d)
forall k (cat :: k -> k -> *) (a :: k) (b :: k) (c :: k).
Category cat =>
cat a b -> cat b c -> cat a c
>>> (c1 -> c2 -> c3 -> a b d) -> a (c1, (c2, c3)) (a b d)
forall (a :: * -> * -> *) b1 b2 b3 c.
ArrowList a =>
(b1 -> b2 -> b3 -> c) -> a (b1, (b2, b3)) c
arr3 c1 -> c2 -> c3 -> a b d
f)

    -- | version of '$<' for arrows with 4 extra parameters
    --
    -- typical usage
    --
    -- > f $<<<< g1 &&& g2 &&& g3 &&& g4

    ($<<<<)             :: (c1 -> c2 -> c3 -> c4 -> a b d) -> a b (c1, (c2, (c3, c4))) -> a b d
    c1 -> c2 -> c3 -> c4 -> a b d
f $<<<< a b (c1, (c2, (c3, c4)))
g           = a b (a b d) -> a b d
forall (a :: * -> * -> *) b c. ArrowList a => a b (a b c) -> a b c
applyA (a b (c1, (c2, (c3, c4)))
g a b (c1, (c2, (c3, c4)))
-> a (c1, (c2, (c3, c4))) (a b d) -> a b (a b d)
forall k (cat :: k -> k -> *) (a :: k) (b :: k) (c :: k).
Category cat =>
cat a b -> cat b c -> cat a c
>>> (c1 -> c2 -> c3 -> c4 -> a b d) -> a (c1, (c2, (c3, c4))) (a b d)
forall (a :: * -> * -> *) b1 b2 b3 b4 c.
ArrowList a =>
(b1 -> b2 -> b3 -> b4 -> c) -> a (b1, (b2, (b3, b4))) c
arr4 c1 -> c2 -> c3 -> c4 -> a b d
f)

    -- | compute the parameter for an arrow @f@ with an extra parameter by an arrow @g@
    -- and apply all the results from @g@ sequentially to the input
    --
    -- > infixl 2 ($<$)
    --
    -- typical usage:
    --
    -- > g :: a b c
    -- > g = ...
    -- >
    -- > f :: c -> a b b
    -- > f x = ... x ...
    -- >
    -- > f $<$ g
    --
    -- @f@ computes the extra parameters for @g@ from the input of type @b@ and @g@ is applied with this
    -- parameter to the input. This allows programming in a point wise style in @g@, which becomes
    -- neccessary, when a value is needed more than once.
    --
    -- this combinator is useful, when transforming a single value (document) step by step,
    -- with @g@ for collecting the data for all steps, and @f@ for transforming the input step by step
    --
    -- if @g@ is deterministic (computes exactly one result),
    -- @ g $\<$ f == g $\< f @ holds
    --
    -- if @g@ fails, @ f $<$ g == this @
    --
    -- if @g@ computes more than one result, @f@ is applied sequentially to the input for every result from @g@
    --
    -- examples with simple list arrows with strings
    --
    -- > prefixString   :: String -> a String String
    -- > prefixString s =  arr (s++)
    -- >
    -- > runLA ( prefixString $<$ none                      ) "x" == ["x"]
    -- > runLA ( prefixString $<$ constA "y"                ) "x" == ["yx"]
    -- > runLA ( prefixString $<$ constA "y" <+> constA "z" ) "x" == ["zyx"]
    -- > runLA ( prefixString $<$ constA "y" <+> this
    -- >                          <+> constA "z"            ) "x" == ["zxyx"]
    --
    -- example with two extra parameter
    --
    -- > g1 :: a b c1
    -- > g2 :: a b c2
    -- >
    -- > f          :: (c1, c2) -> a b b
    -- > f (x1, x2) =  ... x1 ... x2 ...
    -- >
    -- > f $<$ g1 &&& g2
    --
    -- see also: 'applyA', '$<'

    ($<$)               :: (c -> (a b b)) -> a b c -> a b b
    c -> a b b
g $<$ a b c
f             = a b (a b b) -> a b b
forall (a :: * -> * -> *) b c. ArrowList a => a b (a b c) -> a b c
applyA (a b (a b b) -> a b [a b b]
forall (a :: * -> * -> *) b c. ArrowList a => a b c -> a b [c]
listA (a b c
f a b c -> a c (a b b) -> a b (a b b)
forall k (cat :: k -> k -> *) (a :: k) (b :: k) (c :: k).
Category cat =>
cat a b -> cat b c -> cat a c
>>> (c -> a b b) -> a c (a b b)
forall (a :: * -> * -> *) b c. Arrow a => (b -> c) -> a b c
arr c -> a b b
g) a b [a b b] -> a [a b b] (a b b) -> a b (a b b)
forall k (cat :: k -> k -> *) (a :: k) (b :: k) (c :: k).
Category cat =>
cat a b -> cat b c -> cat a c
>>> ([a b b] -> a b b) -> a [a b b] (a b b)
forall (a :: * -> * -> *) b c. Arrow a => (b -> c) -> a b c
arr [a b b] -> a b b
forall (a :: * -> * -> *) b. ArrowList a => [a b b] -> a b b
seqA)

    -- | merge the result pairs of an arrow with type @a a1 (b1, b2)@
    -- by combining the tuple components with the @op@ arrow
    --
    -- examples with simple list arrows working on strings and XmlTrees
    --
    -- >     a1 :: a String (XmlTree, XmlTree)
    -- >     a1 = selem "foo" [this >>> mkText]
    -- >          &&&
    -- >          selem "bar" [arr (++"0") >>> mkText]
    -- >
    -- >     runLA (a1 >>> mergeA (<+>) >>> xshow this) "42" == ["<foo>42</foo>","<bar>420</bar>"]
    -- >     runLA (a1 >>> mergeA (+=)  >>> xshow this) "42" == ["<foo>42<bar>420</bar></foo>"]
    --
    -- see also: 'applyA', '$<' and '+=' in class 'Text.XML.HXT.Arrow.ArrowXml'

    mergeA              :: (a (a1, b1) a1 -> a (a1, b1) b1 -> a (a1, b1) c) ->
                           a (a1, b1) c
    mergeA a (a1, b1) a1 -> a (a1, b1) b1 -> a (a1, b1) c
op           = (\ (a1, b1)
x -> ((a1, b1) -> a1) -> a (a1, b1) a1
forall (a :: * -> * -> *) b c. Arrow a => (b -> c) -> a b c
arr (a1, b1) -> a1
forall a b. (a, b) -> a
fst a (a1, b1) a1 -> a (a1, b1) b1 -> a (a1, b1) c
`op` b1 -> a (a1, b1) b1
forall (a :: * -> * -> *) c b. ArrowList a => c -> a b c
constA ((a1, b1) -> b1
forall a b. (a, b) -> b
snd (a1, b1)
x)) ((a1, b1) -> a (a1, b1) c) -> a (a1, b1) (a1, b1) -> a (a1, b1) c
forall (a :: * -> * -> *) c b d.
ArrowList a =>
(c -> a b d) -> a b c -> a b d
$< a (a1, b1) (a1, b1)
forall (a :: * -> * -> *) b. ArrowList a => a b b
this

    -- | useful only for arrows with side effects: perform applies an arrow to the input
    -- ignores the result and returns the input
    --
    -- example: @ ... >>> perform someTraceArrow >>> ... @

    perform             :: a b c -> a b b
    perform a b c
f           = a b c -> a b [c]
forall (a :: * -> * -> *) b c. ArrowList a => a b c -> a b [c]
listA a b c
f a b [c] -> a b b -> a b ([c], b)
forall (a :: * -> * -> *) b c c'.
Arrow a =>
a b c -> a b c' -> a b (c, c')
&&& a b b
forall (a :: * -> * -> *) b. ArrowList a => a b b
this a b ([c], b) -> a ([c], b) b -> a b b
forall k (cat :: k -> k -> *) (a :: k) (b :: k) (c :: k).
Category cat =>
cat a b -> cat b c -> cat a c
>>> (([c], b) -> b) -> a ([c], b) b
forall (a :: * -> * -> *) b c. Arrow a => (b -> c) -> a b c
arr ([c], b) -> b
forall a b. (a, b) -> b
snd
    {-# INLINE perform #-}

    -- | generalization of arrow combinator '<+>'
    --
    -- definition: @ catA = foldl (\<+\>) none @

    catA                :: [a b c] -> a b c
    catA                = (a b c -> a b c -> a b c) -> a b c -> [a b c] -> a b c
forall (t :: * -> *) b a.
Foldable t =>
(b -> a -> b) -> b -> t a -> b
foldl a b c -> a b c -> a b c
forall (a :: * -> * -> *) b c.
ArrowPlus a =>
a b c -> a b c -> a b c
(<+>) a b c
forall (a :: * -> * -> *) b c. ArrowList a => a b c
none
    {-# INLINE catA #-}

    -- | generalization of arrow combinator '>>>'
    --
    -- definition: @ seqA = foldl (>>>) this @

    seqA                :: [a b b] -> a b b
    seqA                = (a b b -> a b b -> a b b) -> a b b -> [a b b] -> a b b
forall (t :: * -> *) b a.
Foldable t =>
(b -> a -> b) -> b -> t a -> b
foldl a b b -> a b b -> a b b
forall k (cat :: k -> k -> *) (a :: k) (b :: k) (c :: k).
Category cat =>
cat a b -> cat b c -> cat a c
(>>>) a b b
forall (a :: * -> * -> *) b. ArrowList a => a b b
this
    {-# INLINE seqA #-}

-- ------------------------------------------------------------