Skip to content

Commit

Permalink
substitue 'tail' with 'drop 1', removed unused imports
Browse files Browse the repository at this point in the history
  • Loading branch information
sss-create committed Feb 6, 2025
1 parent a1eec82 commit 0917fc9
Show file tree
Hide file tree
Showing 6 changed files with 9 additions and 11 deletions.
2 changes: 1 addition & 1 deletion src/Sound/Tidal/Params.hs
Original file line number Diff line number Diff line change
Expand Up @@ -114,7 +114,7 @@ pStateList name sName xs =
statef sMap =
( Map.insert
sName
(VList $ tail looped)
(VList $ drop 1 looped)
sMap,
head looped

Check warning on line 119 in src/Sound/Tidal/Params.hs

View workflow job for this annotation

GitHub Actions / cabal latest - ghc latest

In the use of ‘head’

Check warning on line 119 in src/Sound/Tidal/Params.hs

View workflow job for this annotation

GitHub Actions / cabal 3.12.1.0 - ghc 9.8.2

In the use of ‘head’
)
Expand Down
1 change: 0 additions & 1 deletion src/Sound/Tidal/Pattern.hs
Original file line number Diff line number Diff line change
Expand Up @@ -31,7 +31,6 @@ module Sound.Tidal.Pattern
)
where

import Control.Applicative (liftA2)
import Control.DeepSeq (NFData)
import Control.Monad ((>=>))
import Data.Data (Data)
Expand Down
6 changes: 3 additions & 3 deletions src/Sound/Tidal/Stream/Process.hs
Original file line number Diff line number Diff line change
Expand Up @@ -185,7 +185,7 @@ toOSC maybeBusses pe osc@(OSC _ _) =
-- (but perhaps we should explicitly crash with an error message if it contains something else?).
-- Map.mapKeys tail is used to remove ^ from the keys.
-- In case (value e) has the key "", we will get a crash here.
playmap' = Map.union (Map.mapKeys tail $ Map.map (\v -> VS ('c' : (show $ toBus $ fromMaybe 0 $ getI v))) busmap) playmap
playmap' = Map.union (Map.mapKeys (drop 1) $ Map.map (\v -> VS ('c' : (show $ toBus $ fromMaybe 0 $ getI v))) busmap) playmap
val = value . peEvent
-- Only events that start within the current nowArc are included
playmsg
Expand Down Expand Up @@ -213,7 +213,7 @@ toOSC maybeBusses pe osc@(OSC _ _) =
busmsgs =
map
( \(k, b) -> do
k' <- if (not $ null k) && head k == '^' then Just (tail k) else Nothing
k' <- if (not $ null k) && head k == '^' then Just (drop 1 k) else Nothing
v <- Map.lookup k' playmap
bi <- getI b
return $
Expand Down Expand Up @@ -275,7 +275,7 @@ substitutePath str cm = parse str
| b == [] = getString cm a
| otherwise = do
v <- getString cm a
xs' <- parse (tail b)
xs' <- parse (drop 1 b)
return $ v ++ xs'
where
(a, b) = break (== '}') xs
Expand Down
1 change: 0 additions & 1 deletion src/Sound/Tidal/Time.hs
Original file line number Diff line number Diff line change
Expand Up @@ -3,7 +3,6 @@

module Sound.Tidal.Time where

import Control.Applicative
import Control.DeepSeq (NFData)
import Data.Ratio
import GHC.Generics
Expand Down
8 changes: 4 additions & 4 deletions src/Sound/Tidal/UI.hs
Original file line number Diff line number Diff line change
Expand Up @@ -986,7 +986,7 @@ _distrib xs p = boolsToPat (foldr distrib' (replicate (last xs) True) (reverse $
distrib' (_ : a) [] = False : distrib' a []
distrib' (True : a) (x : b) = x : distrib' a b
distrib' (False : a) b = False : distrib' a b
layers = map bjorklund . (zip <*> tail)
layers = map bjorklund . (zip <*> drop 1)
boolsToPat a b' = flip const <$> filterValues (== True) (fastFromList a) <* b'

-- | @euclidInv@ fills in the blanks left by `euclid`, i.e., it inverts the
Expand Down Expand Up @@ -1799,7 +1799,7 @@ randrun n' =
where
shuffled = map snd $ sortOn fst $ zip rs [0 .. (n' - 1)]
rs = timeToRands seed n' :: [Double]
arcs = zipWith Arc fractions (tail fractions)
arcs = zipWith Arc fractions (drop 1 fractions)
fractions = map (+ (sam $ start a)) [0, 1 / fromIntegral n' .. 1]
toEv (a', v) = do
a'' <- subArc a a'
Expand Down Expand Up @@ -2017,7 +2017,7 @@ _arp name p = arpWith f p
("down&up", \x -> reverse x ++ x),
("converge", converge),
("diverge", reverse . converge),
("disconverge", \x -> converge x ++ tail (reverse $ converge x)),
("disconverge", \x -> converge x ++ drop 1 (reverse $ converge x)),
("pinkyup", pinkyup),
("pinkyupdown", \x -> init (pinkyup x) ++ init (reverse $ pinkyup x)),
("thumbup", thumbup),
Expand All @@ -2030,7 +2030,7 @@ _arp name p = arpWith f p
pinkyup xs = concatMap (: [pinky]) $ init xs
where
pinky = last xs
thumbup xs = concatMap (\x -> [thumb, x]) $ tail xs
thumbup xs = concatMap (\x -> [thumb, x]) $ drop 1 xs
where
thumb = head xs

Check warning on line 2035 in src/Sound/Tidal/UI.hs

View workflow job for this annotation

GitHub Actions / cabal latest - ghc latest

In the use of ‘head’

Check warning on line 2035 in src/Sound/Tidal/UI.hs

View workflow job for this annotation

GitHub Actions / cabal 3.12.1.0 - ghc 9.8.2

In the use of ‘head’

Expand Down
2 changes: 1 addition & 1 deletion src/Sound/Tidal/Utils.hs
Original file line number Diff line number Diff line change
Expand Up @@ -119,7 +119,7 @@ applyWhen False _ x = x

-- pair up neighbours in list
pairs :: [a] -> [(a, a)]
pairs rs = zip rs (tail rs)
pairs rs = zip rs (drop 1 rs)

-- The following is from Data.Containers.ListUtils, (c) Gershom Bazerman 2018,
-- Used under a BSD 3-clause license
Expand Down

0 comments on commit 0917fc9

Please sign in to comment.