Skip to content

Commit

Permalink
fix warnings
Browse files Browse the repository at this point in the history
  • Loading branch information
yaxu committed Apr 16, 2020
1 parent 46fb433 commit 252e3be
Show file tree
Hide file tree
Showing 3 changed files with 11 additions and 8 deletions.
5 changes: 2 additions & 3 deletions src/Sound/Tidal/Pattern.hs
Original file line number Diff line number Diff line change
Expand Up @@ -9,10 +9,9 @@ import Prelude hiding ((<*), (*>))
import Control.Applicative (liftA2)
--import Data.Bifunctor (Bifunctor(..))
import Data.Data (Data) -- toConstr
import Data.List (delete, findIndex, sort, intercalate)
import Data.List (delete, findIndex, sort)
import qualified Data.Map.Strict as Map
import Data.Maybe (isJust, fromJust, catMaybes, fromMaybe, mapMaybe)
import Data.Ratio (numerator, denominator)
import Data.Maybe (isJust, fromJust, catMaybes, mapMaybe)
import Data.Typeable (Typeable)
import Control.DeepSeq (NFData(rnf))
import Data.Word (Word8)
Expand Down
12 changes: 8 additions & 4 deletions src/Sound/Tidal/Show.hs
Original file line number Diff line number Diff line change
@@ -1,6 +1,7 @@
{-# LANGUAGE TypeSynonymInstances, FlexibleInstances, RecordWildCards #-}
{-# OPTIONS_GHC -fno-warn-orphans #-}

module Sound.Tidal.Show (show, draw, drawLine) where
module Sound.Tidal.Show (show, showAll, draw, drawLine) where

import Sound.Tidal.Pattern

Expand Down Expand Up @@ -134,6 +135,7 @@ drawLineSz sz pat = joinCycles sz $ drawCycles pat
drawCycles :: Pattern Char -> [Render]
drawCycles pat' = (draw pat'):(drawCycles $ rotL 1 pat')
joinCycles :: Int -> [Render] -> Render
joinCycles _ [] = Render 0 0 ""
joinCycles n ((Render cyc l s):cs) | l > n = Render 0 0 ""
| otherwise = Render (cyc+cyc') (l + l' + 1) $ intercalate "\n" $ map (\(a,b) -> a ++ b) lineZip
where
Expand Down Expand Up @@ -162,6 +164,7 @@ draw pat = Render 1 s $ (intercalate "\n" $ map ((\x -> ('|':x)) .drawLevel) ls)
where evStart = start $ wholeOrPart ev
evStop = stop $ wholeOrPart ev

{-
fitsWhole :: Event b -> [Event b] -> Bool
fitsWhole event events =
not $ any (\event' -> isJust $ subArc (wholeOrPart event) (wholeOrPart event')) events
Expand All @@ -176,15 +179,16 @@ addEventWhole e (level:ls)
arrangeEventsWhole :: [Event b] -> [[Event b]]
arrangeEventsWhole = foldr addEventWhole []
levelsWhole :: Eq a => Pattern a -> [[Event a]]
levelsWhole pat = arrangeEventsWhole $ sortOn' ((\Arc{..} -> 0 - (stop - start)) . wholeOrPart) (defragParts $ queryArc pat (Arc 0 1))
sortOn' :: Ord a => (b -> a) -> [b] -> [b]
sortOn' f = map snd . sortOn fst . map (\x -> let y = f x in y `seq` (y, x))
-}

fits :: Event b -> [Event b] -> Bool
fits (Event _ _ part' _) events = not $ any (\Event{..} -> isJust $ subArc part' part) events

levelsWhole :: Eq a => Pattern a -> [[Event a]]
levelsWhole pat = arrangeEventsWhole $ sortOn' ((\Arc{..} -> 0 - (stop - start)) . wholeOrPart) (defragParts $ queryArc pat (Arc 0 1))

addEvent :: Event b -> [[Event b]] -> [[Event b]]
addEvent e [] = [[e]]
addEvent e (level:ls)
Expand Down
2 changes: 1 addition & 1 deletion src/Sound/Tidal/Stream.hs
Original file line number Diff line number Diff line change
Expand Up @@ -25,7 +25,7 @@ import qualified Sound.Tidal.Tempo as T
-- import qualified Sound.OSC.Datum as O
import Data.List (sortOn)
import System.Random (getStdRandom, randomR)
import Sound.Tidal.Show
import Sound.Tidal.Show ()

data TimeStamp = BundleStamp | MessageStamp | NoStamp
deriving (Eq, Show)
Expand Down

0 comments on commit 252e3be

Please sign in to comment.