module Synthesizer.Generic.Cut where
import qualified Synthesizer.Plain.Signal as Sig
import qualified Synthesizer.State.Signal as SigS
import qualified Data.StorableVector as SV
import qualified Data.StorableVector.Lazy as Vector
import qualified Algebra.ToInteger as ToInteger
import qualified Algebra.Ring as Ring
import qualified Data.EventList.Relative.BodyTime as EventList
import qualified Algebra.NonNegative as NonNeg
import qualified Number.NonNegativeChunky as Chunky
import qualified Numeric.NonNegative.Class as NonNeg98
import qualified Numeric.NonNegative.Chunky as Chunky98
import Numeric.NonNegative.Class ((-|), )
import Foreign.Storable (Storable, )
import Control.DeepSeq (NFData, rnf, )
import qualified Data.List.HT as ListHT
import qualified Data.List.Stream as List
import Data.Function (fix, )
import Data.Tuple.HT (mapPair, mapFst, mapSnd, )
import qualified Data.Monoid as Monoid
import Data.Monoid (Monoid, mempty, )
import qualified Prelude as P
import NumericPrelude.Numeric
import Prelude
(Bool, Int, String, (++), error,
pred, (<=), (>=), (<),
(.), ($), const, snd,
not, (||), (&&), min, )
class Read sig where
null :: sig -> Bool
length :: sig -> Int
class (Read sig) => NormalForm sig where
evaluateHead :: sig -> ()
class (Read sig, Monoid sig) => Transform sig where
take :: Int -> sig -> sig
drop :: Int -> sig -> sig
dropMarginRem :: Int -> Int -> sig -> (Int, sig)
splitAt :: Int -> sig -> (sig, sig)
reverse :: sig -> sig
instance Storable y => Read (Vector.Vector y) where
null = Vector.null
length = Vector.length
instance (Storable y) => NormalForm (Vector.Vector y) where
evaluateHead =
ListHT.switchL () (\x _ -> if SV.null x then () else ()) . Vector.chunks
instance Storable y => Transform (Vector.Vector y) where
take = Vector.take
drop = Vector.drop
splitAt = Vector.splitAt
dropMarginRem = Vector.dropMarginRem
reverse = Vector.reverse
instance Read ([] y) where
null = List.null
length = List.length
instance (NFData y) => NormalForm ([] y) where
evaluateHead = ListHT.switchL () (\x _ -> rnf x)
instance Transform ([] y) where
take = List.take
drop = List.drop
dropMarginRem = Sig.dropMarginRem
splitAt = List.splitAt
reverse = List.reverse
instance Read (SigS.T y) where
null = SigS.null
length = SigS.length
instance (NFData y) => NormalForm (SigS.T y) where
evaluateHead = SigS.switchL () (\x _ -> rnf x)
instance Transform (SigS.T y) where
take = SigS.take
drop = SigS.drop
dropMarginRem = SigS.dropMarginRem
splitAt n =
mapPair (SigS.fromList, SigS.fromList) .
List.splitAt n . SigS.toList
reverse = SigS.reverse
instance (P.Integral t) => Read (EventList.T t y) where
null = EventList.null
length = fromIntegral . P.toInteger . P.sum . EventList.getTimes
instance (P.Integral t, NFData y) => NormalForm (EventList.T t y) where
evaluateHead = EventList.switchL () (\x _ _ -> rnf x)
instance (P.Integral t, NonNeg98.C t) => Transform (EventList.T t y) where
take n xs =
EventList.foldrPair
(\b t go remain ->
if remain <= NonNeg98.zero
then EventList.empty
else
let (m, ~(le,d)) = NonNeg98.split t remain
in EventList.cons b m $
go (if le then d else NonNeg98.zero))
(const EventList.empty) xs
(P.fromIntegral n)
drop =
let recourse n =
EventList.switchL EventList.empty $ \b t xs ->
let (le,d) = snd $ NonNeg98.split t n
in if le
then recourse d xs
else EventList.cons b d xs
in recourse . P.fromIntegral
dropMarginRem n m xs =
List.foldl'
(\(mi,xsi) k -> (mik, drop k xsi))
(m, xs)
(P.map P.fromIntegral $ EventList.getTimes $ take m $ drop n xs)
splitAt =
let recourse 0 = (,) EventList.empty
recourse n =
EventList.switchL (EventList.empty, EventList.empty) $ \b t xs ->
let (m, ~(le,d)) = NonNeg98.split t n
in mapFst (EventList.cons b m) $
if le
then recourse d xs
else (EventList.empty, EventList.cons b d xs)
in recourse . P.fromIntegral
reverse =
EventList.fromPairList . List.reverse . EventList.toPairList
instance (ToInteger.C a, NonNeg.C a) => Read (Chunky.T a) where
null = List.null . Chunky.toChunks
length = sum . List.map (fromIntegral . toInteger) . Chunky.toChunks
instance (ToInteger.C a, NonNeg.C a, NFData a) => NormalForm (Chunky.T a) where
evaluateHead = ListHT.switchL () (\x _ -> rnf x) . Chunky.toChunks
intToChunky :: (Ring.C a, NonNeg.C a) => String -> Int -> Chunky.T a
intToChunky name =
Chunky.fromNumber .
fromIntegral .
(\x ->
if x<zero
then error ("Generic.Cut.NonNeg.Chunky."++name++": negative argument")
else x)
instance (ToInteger.C a, NonNeg.C a) => Transform (Chunky.T a) where
take n = P.min (intToChunky "take" n)
drop n x = x NonNeg.-| intToChunky "drop" n
dropMarginRem n m x =
let (z,~(b,d)) =
Chunky.minMaxDiff
(intToChunky "dropMargin/n" n)
(x NonNeg.-| intToChunky "dropMargin/m" m)
in (if b then 0 else fromIntegral (Chunky.toNumber d),
x NonNeg.-| z)
splitAt n x =
mapSnd
(\ ~(b,d) -> if b then d else mempty)
(Chunky.minMaxDiff (intToChunky "splitAt" n) x)
reverse = Chunky.fromChunks . List.reverse . Chunky.toChunks
instance (P.Integral a) => Read (Chunky98.T a) where
null = List.null . Chunky98.toChunks
length = sum . List.map (P.fromIntegral . P.toInteger) . Chunky98.toChunks
instance (P.Integral a, NonNeg.C a, NFData a) =>
NormalForm (Chunky98.T a) where
evaluateHead = ListHT.switchL () (\x _ -> rnf x) . Chunky98.toChunks
intToChunky98 :: (P.Num a, NonNeg98.C a) => String -> Int -> Chunky98.T a
intToChunky98 name =
Chunky98.fromNumber .
P.fromIntegral .
(\x ->
if x<0
then error ("Generic.Cut.NonNeg.Chunky98."++name++": negative argument")
else x)
instance (P.Integral a, NonNeg98.C a) => Transform (Chunky98.T a) where
take n = P.min (intToChunky98 "take" n)
drop n x = x NonNeg98.-| intToChunky98 "drop" n
dropMarginRem n m x =
let (z,~(b,d)) =
NonNeg98.split
(intToChunky98 "dropMargin/n" n)
(x NonNeg98.-| intToChunky98 "dropMargin/m" m)
in (if b then 0 else P.fromIntegral (Chunky98.toNumber d),
x NonNeg98.-| z)
splitAt n x =
mapSnd
(\ ~(b,d) -> if b then d else Chunky98.zero)
(NonNeg98.split (intToChunky98 "splitAt" n) x)
reverse = Chunky98.fromChunks . List.reverse . Chunky98.toChunks
empty :: (Monoid sig) => sig
empty = Monoid.mempty
cycle :: (Monoid sig) => sig -> sig
cycle x = fix (append x)
append :: (Monoid sig) => sig -> sig -> sig
append = Monoid.mappend
concat :: (Monoid sig) => [sig] -> sig
concat = Monoid.mconcat
lengthAtLeast :: (Transform sig) =>
Int -> sig -> Bool
lengthAtLeast n xs =
n<=0 || not (null (drop (pred n) xs))
lengthAtMost :: (Transform sig) =>
Int -> sig -> Bool
lengthAtMost n xs =
n>=0 && null (drop n xs)
sliceVertical :: (Transform sig) =>
Int -> sig -> SigS.T sig
sliceVertical n =
SigS.map (take n) .
SigS.takeWhile (not . null) .
SigS.iterate (drop n)