module Sound.Tidal.Utils where

{-
    Utils.hs - A library of handy Haskell utility functions
    Copyright (C) 2020, Alex McLean and contributors

    This library is free software: you can redistribute it and/or modify
    it under the terms of the GNU General Public License as published by
    the Free Software Foundation, either version 3 of the License, or
    (at your option) any later version.

    This library is distributed in the hope that it will be useful,
    but WITHOUT ANY WARRANTY; without even the implied warranty of
    MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE.  See the
    GNU General Public License for more details.

    You should have received a copy of the GNU General Public License
    along with this library.  If not, see <http://www.gnu.org/licenses/>.
-}

import Data.List (delete)
import System.IO (hPutStrLn, stderr)

writeError :: String -> IO ()
writeError :: String -> IO ()
writeError = Handle -> String -> IO ()
hPutStrLn Handle
stderr

mapBoth :: (a -> a) -> (a,a) -> (a,a)
mapBoth :: forall a. (a -> a) -> (a, a) -> (a, a)
mapBoth a -> a
f (a
a,a
b) = (a -> a
f a
a, a -> a
f a
b)

mapPartTimes :: (a -> a) -> ((a,a),(a,a)) -> ((a,a),(a,a))
mapPartTimes :: forall a. (a -> a) -> ((a, a), (a, a)) -> ((a, a), (a, a))
mapPartTimes a -> a
f = forall a. (a -> a) -> (a, a) -> (a, a)
mapBoth (forall a. (a -> a) -> (a, a) -> (a, a)
mapBoth a -> a
f)

mapFst :: (a -> b) -> (a, c) -> (b, c)
mapFst :: forall a b c. (a -> b) -> (a, c) -> (b, c)
mapFst a -> b
f (a
x,c
y) = (a -> b
f a
x,c
y)

mapSnd :: (a -> b) -> (c, a) -> (c, b)
mapSnd :: forall a b c. (a -> b) -> (c, a) -> (c, b)
mapSnd a -> b
f (c
x,a
y) = (c
x,a -> b
f a
y)

delta :: Num a => (a, a) -> a
delta :: forall a. Num a => (a, a) -> a
delta (a
a,a
b) = a
bforall a. Num a => a -> a -> a
-a
a

-- | The midpoint of two values
mid :: Fractional a => (a,a) -> a
mid :: forall a. Fractional a => (a, a) -> a
mid (a
a,a
b) = a
a forall a. Num a => a -> a -> a
+ ((a
b forall a. Num a => a -> a -> a
- a
a) forall a. Fractional a => a -> a -> a
/ a
2)

removeCommon :: Eq a => [a] -> [a] -> ([a],[a])
removeCommon :: forall a. Eq a => [a] -> [a] -> ([a], [a])
removeCommon [] [a]
bs = ([],[a]
bs)
removeCommon [a]
as [] = ([a]
as,[])
removeCommon (a
a:[a]
as) [a]
bs | a
a forall (t :: * -> *) a. (Foldable t, Eq a) => a -> t a -> Bool
`elem` [a]
bs = forall a. Eq a => [a] -> [a] -> ([a], [a])
removeCommon [a]
as (forall a. Eq a => a -> [a] -> [a]
delete a
a [a]
bs)
                       | Bool
otherwise = (a
aforall a. a -> [a] -> [a]
:[a]
as',[a]
bs')
                      where ([a]
as',[a]
bs') = forall a. Eq a => [a] -> [a] -> ([a], [a])
removeCommon [a]
as [a]
bs

readMaybe :: (Read a) => String -> Maybe a
readMaybe :: forall a. Read a => String -> Maybe a
readMaybe String
s = case [a
x | (a
x,String
t) <- forall a. Read a => ReadS a
reads String
s, (String
"",String
"") <- ReadS String
lex String
t] of
                   [a
x] -> forall a. a -> Maybe a
Just a
x
                   [a]
_   -> forall a. Maybe a
Nothing

{- | like `!!` selects @n@th element from xs, but wraps over at the end of @xs@

>>> map ((!!!) [1,3,5]) [0,1,2,3,4,5]
[1,3,5,1,3,5]
-}
(!!!) :: [a] -> Int -> a
!!! :: forall a. [a] -> Int -> a
(!!!) [a]
xs Int
n = [a]
xs forall a. [a] -> Int -> a
!! (Int
n forall a. Integral a => a -> a -> a
`mod` forall (t :: * -> *) a. Foldable t => t a -> Int
length [a]
xs)


{- | Safer version of !! --}
nth :: Int -> [a] -> Maybe a
nth :: forall a. Int -> [a] -> Maybe a
nth Int
_ []       = forall a. Maybe a
Nothing
nth Int
0 (a
x : [a]
_)  = forall a. a -> Maybe a
Just a
x
nth Int
n (a
_ : [a]
xs) = forall a. Int -> [a] -> Maybe a
nth (Int
n forall a. Num a => a -> a -> a
- Int
1) [a]
xs

accumulate :: Num t => [t] -> [t]
accumulate :: forall t. Num t => [t] -> [t]
accumulate [] = []
accumulate (t
x:[t]
xs) = forall b a. (b -> a -> b) -> b -> [a] -> [b]
scanl forall a. Num a => a -> a -> a
(+) t
x [t]
xs

{- | enumerate a list of things

>>> enumerate ["foo","bar","baz"]
[(1,"foo"), (2,"bar"), (3,"baz")]
-}
enumerate :: [a] -> [(Int, a)]
enumerate :: forall a. [a] -> [(Int, a)]
enumerate = forall a b. [a] -> [b] -> [(a, b)]
zip [Int
0..]

{- | split given list of @a@ by given single a, e.g.

>>> wordsBy (== ':') "bd:3"
["bd", "3"]
-}
wordsBy :: (a -> Bool) -> [a] -> [[a]]
wordsBy :: forall a. (a -> Bool) -> [a] -> [[a]]
wordsBy a -> Bool
p [a]
s = case forall a. (a -> Bool) -> [a] -> [a]
dropWhile a -> Bool
p [a]
s of
   []      -> []
   a
s':[a]
rest -> (a
s'forall a. a -> [a] -> [a]
:[a]
w) forall a. a -> [a] -> [a]
: forall a. (a -> Bool) -> [a] -> [[a]]
wordsBy a -> Bool
p (forall a. Int -> [a] -> [a]
drop Int
1 [a]
s'')
          where ([a]
w, [a]
s'') = forall a. (a -> Bool) -> [a] -> ([a], [a])
break a -> Bool
p [a]
rest

matchMaybe :: Maybe a -> Maybe a -> Maybe a
matchMaybe :: forall a. Maybe a -> Maybe a -> Maybe a
matchMaybe Maybe a
Nothing Maybe a
y = Maybe a
y
matchMaybe Maybe a
x       Maybe a
_ = Maybe a
x

-- Available in Data.Either, but only since 4.10
fromRight :: b -> Either a b -> b
fromRight :: forall b a. b -> Either a b -> b
fromRight b
_ (Right b
b) = b
b
fromRight b
b Either a b
_         = b
b