-- | Common core functions.
module Sound.Sc3.Common.Base where

import Data.Char {- base -}
import Data.List {- base -}
import Data.Maybe {- base -}
import Data.Ord {- base -}

import qualified Safe {- safe -}

-- * Function

-- | Unary function.
type Fn1 a b = a -> b

-- | Binary function.
type Fn2 a b c = a -> b -> c

-- | Ternary function.
type Fn3 a b c d = a -> b -> c -> d

-- | Quaternary function.
type Fn4 a b c d e = a -> b -> c -> d -> e

-- | 5-parameter function.
type Fn5 a b c d e f = a -> b -> c -> d -> e -> f

-- | 6-parameter function.
type Fn6 a b c d e f g = a -> b -> c -> d -> e -> f -> g

-- | 10-parameter function.
type Fn10 a b c d e f g h i j k = a -> b -> c -> d -> e -> f -> g -> h -> i -> j -> k

-- | 11-parameter function.
type Fn11 a b c d e f g h i j k l = a -> b -> c -> d -> e -> f -> g -> h -> i -> j -> k -> l

{- | Apply /f/ n times, ie. iterate f x !! n

>>> iter 3 (* 2) 1
8

>>> iterate (* 2) 1 !! 3
8
-}
iter :: Int -> (a -> a) -> a -> a
iter :: forall a. Int -> (a -> a) -> a -> a
iter Int
n a -> a
f a
x = if Int
n Int -> Int -> Bool
forall a. Eq a => a -> a -> Bool
== Int
0 then a
x else a -> a
f (Int -> (a -> a) -> a -> a
forall a. Int -> (a -> a) -> a -> a
iter (Int
n Int -> Int -> Int
forall a. Num a => a -> a -> a
- Int
1) a -> a
f a
x)

-- * Functor

-- | This is the same function as Control.Monad.void, which however hugs does not know of.
fvoid :: Functor f => f a -> f ()
fvoid :: forall (f :: * -> *) a. Functor f => f a -> f ()
fvoid = (a -> ()) -> f a -> f ()
forall a b. (a -> b) -> f a -> f b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap (() -> a -> ()
forall a b. a -> b -> a
const ())

-- * Read

-- | Variant of 'reads' requiring exact match.
reads_exact :: Read a => String -> Maybe a
reads_exact :: forall a. Read a => String -> Maybe a
reads_exact String
s =
  case ReadS a
forall a. Read a => ReadS a
reads String
s of
    [(a
r, String
"")] -> a -> Maybe a
forall a. a -> Maybe a
Just a
r
    [(a, String)]
_ -> Maybe a
forall a. Maybe a
Nothing

-- * String

{- | Similar to Data.List.Split.splitOn, which however hugs doesn't know of.

>>> string_split_at_char ':' "/usr/local/bin:/usr/bin:/bin"
["/usr/local/bin","/usr/bin","/bin"]

>>> string_split_at_char ':' "/usr/local/bin"
["/usr/local/bin"]
-}
string_split_at_char :: Char -> String -> [String]
string_split_at_char :: Char -> String -> [String]
string_split_at_char Char
c String
s =
  case (Char -> Bool) -> String -> (String, String)
forall a. (a -> Bool) -> [a] -> ([a], [a])
break (Char -> Char -> Bool
forall a. Eq a => a -> a -> Bool
== Char
c) String
s of
    (String
lhs, []) -> [String
lhs]
    (String
lhs, Char
_ : String
rhs) -> String
lhs String -> [String] -> [String]
forall a. a -> [a] -> [a]
: Char -> String -> [String]
string_split_at_char Char
c String
rhs

-- * String / Case

-- | Ci = Case insensitive, Cs = case sensitive, Sci = separator & case insensitive
data Case_Rule = Ci | Cs | Sci deriving (Case_Rule -> Case_Rule -> Bool
(Case_Rule -> Case_Rule -> Bool)
-> (Case_Rule -> Case_Rule -> Bool) -> Eq Case_Rule
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: Case_Rule -> Case_Rule -> Bool
== :: Case_Rule -> Case_Rule -> Bool
$c/= :: Case_Rule -> Case_Rule -> Bool
/= :: Case_Rule -> Case_Rule -> Bool
Eq)

string_op :: (String -> String -> t) -> Case_Rule -> String -> String -> t
string_op :: forall t.
(String -> String -> t) -> Case_Rule -> String -> String -> t
string_op String -> String -> t
f Case_Rule
cr String
x String
y =
  let ci_form :: String -> String
ci_form = (Char -> Char) -> String -> String
forall a b. (a -> b) -> [a] -> [b]
map Char -> Char
toLower
      sci_form :: String -> String
sci_form = (Char -> Bool) -> String -> String
forall a. (a -> Bool) -> [a] -> [a]
filter (Char -> String -> Bool
forall (t :: * -> *) a. (Foldable t, Eq a) => a -> t a -> Bool
`notElem` String
"-_") (String -> String) -> (String -> String) -> String -> String
forall b c a. (b -> c) -> (a -> b) -> a -> c
. String -> String
ci_form
  in case Case_Rule
cr of
      Case_Rule
Ci -> String -> String -> t
f (String -> String
ci_form String
x) (String -> String
ci_form String
y)
      Case_Rule
Cs -> String -> String -> t
f String
x String
y
      Case_Rule
Sci -> String -> String -> t
f (String -> String
sci_form String
x) (String -> String
sci_form String
y)

{- | String equality with 'Case_Rule'.

>>> string_eq Ci "sinOsc" "SinOsc"
True

>>> string_eq Sci "sin-osc" "SinOsc"
True
-}
string_eq :: Case_Rule -> String -> String -> Bool
string_eq :: Case_Rule -> String -> String -> Bool
string_eq = (String -> String -> Bool) -> Case_Rule -> String -> String -> Bool
forall t.
(String -> String -> t) -> Case_Rule -> String -> String -> t
string_op String -> String -> Bool
forall a. Eq a => a -> a -> Bool
(==)

string_cmp :: Case_Rule -> String -> String -> Ordering
string_cmp :: Case_Rule -> String -> String -> Ordering
string_cmp = (String -> String -> Ordering)
-> Case_Rule -> String -> String -> Ordering
forall t.
(String -> String -> t) -> Case_Rule -> String -> String -> t
string_op String -> String -> Ordering
forall a. Ord a => a -> a -> Ordering
compare

-- | 'rlookup_by' of 'string_eq'.
rlookup_str :: Case_Rule -> String -> [(a, String)] -> Maybe a
rlookup_str :: forall a. Case_Rule -> String -> [(a, String)] -> Maybe a
rlookup_str = (String -> String -> Bool) -> String -> [(a, String)] -> Maybe a
forall b a. (b -> b -> Bool) -> b -> [(a, b)] -> Maybe a
rlookup_by ((String -> String -> Bool) -> String -> [(a, String)] -> Maybe a)
-> (Case_Rule -> String -> String -> Bool)
-> Case_Rule
-> String
-> [(a, String)]
-> Maybe a
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Case_Rule -> String -> String -> Bool
string_eq

{- | 'Enum' parser with 'Case_Rule'.

>>> parse_enum Ci "false" :: Maybe Bool
Just False
-}
parse_enum :: (Show t, Enum t, Bounded t) => Case_Rule -> String -> Maybe t
parse_enum :: forall t.
(Show t, Enum t, Bounded t) =>
Case_Rule -> String -> Maybe t
parse_enum Case_Rule
cr String
nm =
  let u :: [t]
u = [t
forall a. Bounded a => a
minBound .. t
forall a. Bounded a => a
maxBound]
      t :: [(String, t)]
t = [String] -> [t] -> [(String, t)]
forall a b. [a] -> [b] -> [(a, b)]
zip ((t -> String) -> [t] -> [String]
forall a b. (a -> b) -> [a] -> [b]
map t -> String
forall a. Show a => a -> String
show [t]
u) [t]
u
  in (String -> String -> Bool) -> String -> [(String, t)] -> Maybe t
forall a t b. (a -> t -> Bool) -> a -> [(t, b)] -> Maybe b
lookup_by (Case_Rule -> String -> String -> Bool
string_eq Case_Rule
cr) String
nm [(String, t)]
t

-- * List

{- | Left to right composition of a list of functions.

>>> compose_l [(* 2),(+ 1)] 3
7
-}
compose_l :: [t -> t] -> t -> t
compose_l :: forall t. [t -> t] -> t -> t
compose_l = (t -> [t -> t] -> t) -> [t -> t] -> t -> t
forall a b c. (a -> b -> c) -> b -> a -> c
flip ((t -> (t -> t) -> t) -> t -> [t -> t] -> t
forall b a. (b -> a -> b) -> b -> [a] -> b
forall (t :: * -> *) b a.
Foldable t =>
(b -> a -> b) -> b -> t a -> b
foldl (\t
x t -> t
f -> t -> t
f t
x))

{- | Right to left composition of a list of functions.

>>> compose_r [(* 2),(+ 1)] 3
8
-}
compose_r :: [t -> t] -> t -> t
compose_r :: forall t. [t -> t] -> t -> t
compose_r = (t -> [t -> t] -> t) -> [t -> t] -> t -> t
forall a b c. (a -> b -> c) -> b -> a -> c
flip (((t -> t) -> t -> t) -> t -> [t -> t] -> t
forall a b. (a -> b -> b) -> b -> [a] -> b
forall (t :: * -> *) a b.
Foldable t =>
(a -> b -> b) -> b -> t a -> b
foldr (t -> t) -> t -> t
forall a b. (a -> b) -> a -> b
($))

{- | SequenceableCollection.differentiate

> [3,4,1,1].differentiate == [3,1,-3,0]

>>> d_dx [3,4,1,1]
[3,1,-3,0]

>>> d_dx [0,1,3,6]
[0,1,2,3]
-}
d_dx :: (Num a) => [a] -> [a]
d_dx :: forall a. Num a => [a] -> [a]
d_dx [a]
l = (a -> a -> a) -> [a] -> [a] -> [a]
forall a b c. (a -> b -> c) -> [a] -> [b] -> [c]
zipWith (-) [a]
l (a
0 a -> [a] -> [a]
forall a. a -> [a] -> [a]
: [a]
l)

{- | Variant that does not prepend zero to input, ie. 'tail' of 'd_dx'.

>> d_dx' [3,4,1,1]
[1,-3,0]

>>> d_dx' [0,1,3,6]
[1,2,3]
-}
d_dx' :: Num n => [n] -> [n]
d_dx' :: forall a. Num a => [a] -> [a]
d_dx' [n]
l = (n -> n -> n) -> [n] -> [n] -> [n]
forall a b c. (a -> b -> c) -> [a] -> [b] -> [c]
zipWith (-) (String -> [n] -> [n]
forall a. Partial => String -> [a] -> [a]
Safe.tailNote String
"d_dx'" [n]
l) [n]
l

{- | SequenceableCollection.integrate

> [3,4,1,1].integrate == [3,7,8,9]

>>> dx_d [3,4,1,1]
[3,7,8,9]

>>> dx_d (d_dx [0,1,3,6])
[0,1,3,6]

>>> dx_d [0.5,0.5]
[0.5,1.0]
-}
dx_d :: Num n => [n] -> [n]
dx_d :: forall a. Num a => [a] -> [a]
dx_d = (n -> n -> n) -> [n] -> [n]
forall a. (a -> a -> a) -> [a] -> [a]
scanl1 n -> n -> n
forall a. Num a => a -> a -> a
(+)

{- | Variant pre-prending zero to output.

>>> dx_d' [3,4,1,1]
[0,3,7,8,9]

>>> dx_d' (d_dx' [0,1,3,6])
[0,1,3,6]

>>> dx_d' [0.5,0.5]
[0.0,0.5,1.0]
-}
dx_d' :: Num n => [n] -> [n]
dx_d' :: forall a. Num a => [a] -> [a]
dx_d' = (n
0 n -> [n] -> [n]
forall a. a -> [a] -> [a]
:) ([n] -> [n]) -> ([n] -> [n]) -> [n] -> [n]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. [n] -> [n]
forall a. Num a => [a] -> [a]
dx_d

-- | 'lookup' with equality function.
lookup_by :: (a -> t -> Bool) -> a -> [(t, b)] -> Maybe b
lookup_by :: forall a t b. (a -> t -> Bool) -> a -> [(t, b)] -> Maybe b
lookup_by a -> t -> Bool
f a
x = ((t, b) -> b) -> Maybe (t, b) -> Maybe b
forall a b. (a -> b) -> Maybe a -> Maybe b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap (t, b) -> b
forall a b. (a, b) -> b
snd (Maybe (t, b) -> Maybe b)
-> ([(t, b)] -> Maybe (t, b)) -> [(t, b)] -> Maybe b
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ((t, b) -> Bool) -> [(t, b)] -> Maybe (t, b)
forall (t :: * -> *) a. Foldable t => (a -> Bool) -> t a -> Maybe a
find (a -> t -> Bool
f a
x (t -> Bool) -> ((t, b) -> t) -> (t, b) -> Bool
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (t, b) -> t
forall a b. (a, b) -> a
fst)

-- | Erroring variant, with message.
lookup_by_note :: String -> (a -> t -> Bool) -> a -> [(t, b)] -> b
lookup_by_note :: forall a t b. String -> (a -> t -> Bool) -> a -> [(t, b)] -> b
lookup_by_note String
msg a -> t -> Bool
f a
x = b -> Maybe b -> b
forall a. a -> Maybe a -> a
fromMaybe (String -> b
forall a. Partial => String -> a
error (String
"lookup_by: " String -> String -> String
forall a. [a] -> [a] -> [a]
++ String
msg)) (Maybe b -> b) -> ([(t, b)] -> Maybe b) -> [(t, b)] -> b
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (a -> t -> Bool) -> a -> [(t, b)] -> Maybe b
forall a t b. (a -> t -> Bool) -> a -> [(t, b)] -> Maybe b
lookup_by a -> t -> Bool
f a
x

-- | Erroring variant.
lookup_by_err :: (a -> t -> Bool) -> a -> [(t, b)] -> b
lookup_by_err :: forall a t b. (a -> t -> Bool) -> a -> [(t, b)] -> b
lookup_by_err = String -> (a -> t -> Bool) -> a -> [(t, b)] -> b
forall a t b. String -> (a -> t -> Bool) -> a -> [(t, b)] -> b
lookup_by_note String
"error"

-- | Reverse 'lookup' with equality function.
rlookup_by :: (b -> b -> Bool) -> b -> [(a, b)] -> Maybe a
rlookup_by :: forall b a. (b -> b -> Bool) -> b -> [(a, b)] -> Maybe a
rlookup_by b -> b -> Bool
f b
x = ((a, b) -> a) -> Maybe (a, b) -> Maybe a
forall a b. (a -> b) -> Maybe a -> Maybe b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap (a, b) -> a
forall a b. (a, b) -> a
fst (Maybe (a, b) -> Maybe a)
-> ([(a, b)] -> Maybe (a, b)) -> [(a, b)] -> Maybe a
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ((a, b) -> Bool) -> [(a, b)] -> Maybe (a, b)
forall (t :: * -> *) a. Foldable t => (a -> Bool) -> t a -> Maybe a
find (b -> b -> Bool
f b
x (b -> Bool) -> ((a, b) -> b) -> (a, b) -> Bool
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (a, b) -> b
forall a b. (a, b) -> b
snd)

{- | (prev,cur,next) triples.

>>> pcn_triples [1..3]
[(Nothing,1,Just 2),(Just 1,2,Just 3),(Just 2,3,Nothing)]
-}
pcn_triples :: [a] -> [(Maybe a, a, Maybe a)]
pcn_triples :: forall a. [a] -> [(Maybe a, a, Maybe a)]
pcn_triples =
  let f :: Maybe a -> [a] -> [(Maybe a, a, Maybe a)]
f Maybe a
e [a]
l = case [a]
l of
        a
e1 : a
e2 : [a]
l' -> (Maybe a
e, a
e1, a -> Maybe a
forall a. a -> Maybe a
Just a
e2) (Maybe a, a, Maybe a)
-> [(Maybe a, a, Maybe a)] -> [(Maybe a, a, Maybe a)]
forall a. a -> [a] -> [a]
: Maybe a -> [a] -> [(Maybe a, a, Maybe a)]
f (a -> Maybe a
forall a. a -> Maybe a
Just a
e1) (a
e2 a -> [a] -> [a]
forall a. a -> [a] -> [a]
: [a]
l')
        [a
e'] -> [(Maybe a
e, a
e', Maybe a
forall a. Maybe a
Nothing)]
        [] -> [(Maybe a, a, Maybe a)]
forall a. Partial => a
undefined
  in Maybe a -> [a] -> [(Maybe a, a, Maybe a)]
forall {a}. Maybe a -> [a] -> [(Maybe a, a, Maybe a)]
f Maybe a
forall a. Maybe a
Nothing

{- | Separate first list element.

>>> sep_first "astring"
Just ('a',"string")
-}
sep_first :: [t] -> Maybe (t, [t])
sep_first :: forall t. [t] -> Maybe (t, [t])
sep_first [t]
l =
  case [t]
l of
    t
e : [t]
l' -> (t, [t]) -> Maybe (t, [t])
forall a. a -> Maybe a
Just (t
e, [t]
l')
    [t]
_ -> Maybe (t, [t])
forall a. Maybe a
Nothing

{- | Separate last list element.

>>> sep_last "stringb"
Just ("string",'b')
-}
sep_last :: [t] -> Maybe ([t], t)
sep_last :: forall t. [t] -> Maybe ([t], t)
sep_last =
  let f :: (b, [a]) -> ([a], b)
f (b
e, [a]
l) = ([a] -> [a]
forall a. [a] -> [a]
reverse [a]
l, b
e)
  in ((t, [t]) -> ([t], t)) -> Maybe (t, [t]) -> Maybe ([t], t)
forall a b. (a -> b) -> Maybe a -> Maybe b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap (t, [t]) -> ([t], t)
forall {b} {a}. (b, [a]) -> ([a], b)
f (Maybe (t, [t]) -> Maybe ([t], t))
-> ([t] -> Maybe (t, [t])) -> [t] -> Maybe ([t], t)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. [t] -> Maybe (t, [t])
forall t. [t] -> Maybe (t, [t])
sep_first ([t] -> Maybe (t, [t])) -> ([t] -> [t]) -> [t] -> Maybe (t, [t])
forall b c a. (b -> c) -> (a -> b) -> a -> c
. [t] -> [t]
forall a. [a] -> [a]
reverse

{- | Are lists of equal length?

>>> equal_length_p ["t1","t2"]
True

>>> equal_length_p ["t","t1","t2"]
False
-}
equal_length_p :: [[a]] -> Bool
equal_length_p :: forall a. [[a]] -> Bool
equal_length_p = (Int -> Int -> Bool
forall a. Eq a => a -> a -> Bool
== Int
1) (Int -> Bool) -> ([[a]] -> Int) -> [[a]] -> Bool
forall b c a. (b -> c) -> (a -> b) -> a -> c
. [Int] -> Int
forall a. [a] -> Int
forall (t :: * -> *) a. Foldable t => t a -> Int
length ([Int] -> Int) -> ([[a]] -> [Int]) -> [[a]] -> Int
forall b c a. (b -> c) -> (a -> b) -> a -> c
. [Int] -> [Int]
forall a. Eq a => [a] -> [a]
nub ([Int] -> [Int]) -> ([[a]] -> [Int]) -> [[a]] -> [Int]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ([a] -> Int) -> [[a]] -> [Int]
forall a b. (a -> b) -> [a] -> [b]
map [a] -> Int
forall a. [a] -> Int
forall (t :: * -> *) a. Foldable t => t a -> Int
length

-- | Histogram
histogram :: Ord a => [a] -> [(a, Int)]
histogram :: forall a. Ord a => [a] -> [(a, Int)]
histogram [a]
x =
  let g :: [[a]]
g = [a] -> [[a]]
forall a. Eq a => [a] -> [[a]]
group ([a] -> [a]
forall a. Ord a => [a] -> [a]
sort [a]
x)
  in [a] -> [Int] -> [(a, Int)]
forall a b. [a] -> [b] -> [(a, b)]
zip (([a] -> a) -> [[a]] -> [a]
forall a b. (a -> b) -> [a] -> [b]
map (String -> [a] -> a
forall a. Partial => String -> [a] -> a
Safe.headNote String
"histogram") [[a]]
g) (([a] -> Int) -> [[a]] -> [Int]
forall a b. (a -> b) -> [a] -> [b]
map [a] -> Int
forall a. [a] -> Int
forall (t :: * -> *) a. Foldable t => t a -> Int
length [[a]]
g)

-- | !! with localised error message
at_with_error_message :: String -> [t] -> Int -> t
at_with_error_message :: forall t. String -> [t] -> Int -> t
at_with_error_message String
msg [t]
list Int
index =
  if Int
index Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
>= [t] -> Int
forall a. [a] -> Int
forall (t :: * -> *) a. Foldable t => t a -> Int
length [t]
list
    then String -> t
forall a. Partial => String -> a
error (String
"!!: index out of range: " String -> String -> String
forall a. [a] -> [a] -> [a]
++ String
msg)
    else [t]
list [t] -> Int -> t
forall a. Partial => [a] -> Int -> a
!! Int
index

-- | concat of intersperse.  This is the same function as intercalate, which hugs doesn't know of.
concat_intersperse :: [a] -> [[a]] -> [a]
concat_intersperse :: forall a. [a] -> [[a]] -> [a]
concat_intersperse [a]
x = [[a]] -> [a]
forall (t :: * -> *) a. Foldable t => t [a] -> [a]
concat ([[a]] -> [a]) -> ([[a]] -> [[a]]) -> [[a]] -> [a]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. [a] -> [[a]] -> [[a]]
forall a. a -> [a] -> [a]
intersperse [a]
x

{- | Similar to Data.List.Split.splitOn, which however hugs doesn't know of.

>>> list_split_at_elem ' ' "a sequence of words"
["a","sequence","of","words"]
-}
list_split_at_elem :: Eq t => t -> [t] -> [[t]]
list_split_at_elem :: forall t. Eq t => t -> [t] -> [[t]]
list_split_at_elem t
c [t]
s =
  case (t -> Bool) -> [t] -> ([t], [t])
forall a. (a -> Bool) -> [a] -> ([a], [a])
break (t -> t -> Bool
forall a. Eq a => a -> a -> Bool
== t
c) [t]
s of
    ([t]
lhs, []) -> [[t]
lhs]
    ([t]
lhs, t
_ : [t]
rhs) -> [t]
lhs [t] -> [[t]] -> [[t]]
forall a. a -> [a] -> [a]
: t -> [t] -> [[t]]
forall t. Eq t => t -> [t] -> [[t]]
list_split_at_elem t
c [t]
rhs

{- | Data.List.sortOn, which however hugs does not know of.

>>> sort_on snd [('a',1),('b',0)]
[('b',0),('a',1)]
-}
sort_on :: (Ord b) => (a -> b) -> [a] -> [a]
sort_on :: forall b a. Ord b => (a -> b) -> [a] -> [a]
sort_on = (a -> a -> Ordering) -> [a] -> [a]
forall a. (a -> a -> Ordering) -> [a] -> [a]
sortBy ((a -> a -> Ordering) -> [a] -> [a])
-> ((a -> b) -> a -> a -> Ordering) -> (a -> b) -> [a] -> [a]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (a -> b) -> a -> a -> Ordering
forall a b. Ord a => (b -> a) -> b -> b -> Ordering
comparing

{- | Inserts at the first position where it compares less but not equal to the next element.

>>> import Data.Function
>>> insertBy (compare `on` fst) (3,'x') (zip [1..5] ['a'..])
[(1,'a'),(2,'b'),(3,'x'),(3,'c'),(4,'d'),(5,'e')]

>>> insertBy_post (compare `on` fst) (3,'x') (zip [1..5] ['a'..])
[(1,'a'),(2,'b'),(3,'c'),(3,'x'),(4,'d'),(5,'e')]
-}
insertBy_post :: (a -> a -> Ordering) -> a -> [a] -> [a]
insertBy_post :: forall a. (a -> a -> Ordering) -> a -> [a] -> [a]
insertBy_post a -> a -> Ordering
cmp a
e [a]
l =
  case [a]
l of
    [] -> [a
e]
    a
h : [a]
l' -> case a -> a -> Ordering
cmp a
e a
h of
      Ordering
LT -> a
e a -> [a] -> [a]
forall a. a -> [a] -> [a]
: [a]
l
      Ordering
_ -> a
h a -> [a] -> [a]
forall a. a -> [a] -> [a]
: (a -> a -> Ordering) -> a -> [a] -> [a]
forall a. (a -> a -> Ordering) -> a -> [a] -> [a]
insertBy_post a -> a -> Ordering
cmp a
e [a]
l'

-- | 'insertBy_post' using 'compare'.
insert_post :: Ord t => t -> [t] -> [t]
insert_post :: forall t. Ord t => t -> [t] -> [t]
insert_post = (t -> t -> Ordering) -> t -> [t] -> [t]
forall a. (a -> a -> Ordering) -> a -> [a] -> [a]
insertBy_post t -> t -> Ordering
forall a. Ord a => a -> a -> Ordering
compare

{- | Apply /f/ at all but last element, and /g/ at last element.

>>> at_last (* 2) negate [1..4]
[2,4,6,-4]
-}
at_last :: (a -> b) -> (a -> b) -> [a] -> [b]
at_last :: forall a b. (a -> b) -> (a -> b) -> [a] -> [b]
at_last a -> b
f a -> b
g [a]
x =
  case [a]
x of
    [] -> []
    [a
i] -> [a -> b
g a
i]
    a
i : [a]
x' -> a -> b
f a
i b -> [b] -> [b]
forall a. a -> [a] -> [a]
: (a -> b) -> (a -> b) -> [a] -> [b]
forall a b. (a -> b) -> (a -> b) -> [a] -> [b]
at_last a -> b
f a -> b
g [a]
x'

-- * Tuples

-- | Zip two 4-tuples.
p4_zip :: (a, b, c, d) -> (e, f, g, h) -> ((a, e), (b, f), (c, g), (d, h))
p4_zip :: forall a b c d e f g h.
(a, b, c, d) -> (e, f, g, h) -> ((a, e), (b, f), (c, g), (d, h))
p4_zip (a
a, b
b, c
c, d
d) (e
e, f
f, g
g, h
h) = ((a
a, e
e), (b
b, f
f), (c
c, g
g), (d
d, h
h))

-- | Two-tuple.
type T2 a = (a, a)

-- | Three-tuple.
type T3 a = (a, a, a)

-- | Four-tuple.
type T4 a = (a, a, a, a)

-- | t -> (t,t)
dup2 :: t -> T2 t
dup2 :: forall t. t -> T2 t
dup2 t
t = (t
t, t
t)

-- | t -> (t,t,t)
dup3 :: t -> T3 t
dup3 :: forall t. t -> T3 t
dup3 t
t = (t
t, t
t, t
t)

-- | t -> (t,t,t,t)
dup4 :: t -> T4 t
dup4 :: forall t. t -> T4 t
dup4 t
t = (t
t, t
t, t
t, t
t)

-- | 'concatMap' of /f/ at /x/ and /g/ at /y/.
mk_duples :: (a -> c) -> (b -> c) -> [(a, b)] -> [c]
mk_duples :: forall a c b. (a -> c) -> (b -> c) -> [(a, b)] -> [c]
mk_duples a -> c
a b -> c
b = ((a, b) -> [c]) -> [(a, b)] -> [c]
forall (t :: * -> *) a b. Foldable t => (a -> [b]) -> t a -> [b]
concatMap (\(a
x, b
y) -> [a -> c
a a
x, b -> c
b b
y])

-- | Length prefixed list variant of 'mk_duples'.
mk_duples_l :: (Int -> c) -> (a -> c) -> (b -> c) -> [(a, [b])] -> [c]
mk_duples_l :: forall c a b.
(Int -> c) -> (a -> c) -> (b -> c) -> [(a, [b])] -> [c]
mk_duples_l Int -> c
i a -> c
a b -> c
b = ((a, [b]) -> [c]) -> [(a, [b])] -> [c]
forall (t :: * -> *) a b. Foldable t => (a -> [b]) -> t a -> [b]
concatMap (\(a
x, [b]
y) -> a -> c
a a
x c -> [c] -> [c]
forall a. a -> [a] -> [a]
: Int -> c
i ([b] -> Int
forall a. [a] -> Int
forall (t :: * -> *) a. Foldable t => t a -> Int
length [b]
y) c -> [c] -> [c]
forall a. a -> [a] -> [a]
: (b -> c) -> [b] -> [c]
forall a b. (a -> b) -> [a] -> [b]
map b -> c
b [b]
y)

-- | 'concatMap' of /f/ at /x/ and /g/ at /y/ and /h/ at /z/.
mk_triples :: (a -> d) -> (b -> d) -> (c -> d) -> [(a, b, c)] -> [d]
mk_triples :: forall a d b c.
(a -> d) -> (b -> d) -> (c -> d) -> [(a, b, c)] -> [d]
mk_triples a -> d
a b -> d
b c -> d
c = ((a, b, c) -> [d]) -> [(a, b, c)] -> [d]
forall (t :: * -> *) a b. Foldable t => (a -> [b]) -> t a -> [b]
concatMap (\(a
x, b
y, c
z) -> [a -> d
a a
x, b -> d
b b
y, c -> d
c c
z])

-- | [x,y] -> (x,y)
t2_from_list :: [t] -> T2 t
t2_from_list :: forall t. [t] -> T2 t
t2_from_list [t]
l = case [t]
l of [t
p, t
q] -> (t
p, t
q); [t]
_ -> String -> T2 t
forall a. Partial => String -> a
error String
"t2_from_list"

-- | [x,y,z] -> (x,y,z)
t3_from_list :: [t] -> (t, t, t)
t3_from_list :: forall t. [t] -> (t, t, t)
t3_from_list [t]
l = case [t]
l of [t
p, t
q, t
r] -> (t
p, t
q, t
r); [t]
_ -> String -> (t, t, t)
forall a. Partial => String -> a
error String
"t3_from_list"