-- | Non-realtime score generation.
module Sound.Sc3.Server.Nrt where

import Data.Maybe {- base -}
import System.IO {- base -}

import qualified Data.ByteString.Lazy as B {- bytestring -}

import qualified Sound.Osc.Coding.Byte as Byte {- hosc -}
import qualified Sound.Osc.Coding.Decode.Binary as Decode {- hosc3 -}
import qualified Sound.Osc.Coding.Encode.Builder as Encode {- hosc3 -}
import Sound.Osc.Datum {- hosc -}
import Sound.Osc.Packet {- hosc -}

-- | Encode Bundle and prefix with encoded length.
oscWithSize :: Bundle -> B.ByteString
oscWithSize :: Bundle -> ByteString
oscWithSize Bundle
o =
    let b :: ByteString
b = Bundle -> ByteString
Encode.encodeBundle Bundle
o
        l :: ByteString
l = Int -> ByteString
Byte.encode_i32 (forall a b. (Integral a, Num b) => a -> b
fromIntegral (ByteString -> Int64
B.length ByteString
b))
    in ByteString -> ByteString -> ByteString
B.append ByteString
l ByteString
b

-- | An 'Nrt' score is a sequence of 'Bundle's.
newtype Nrt = Nrt {Nrt -> [Bundle]
nrt_bundles :: [Bundle]} deriving (Int -> Nrt -> ShowS
[Nrt] -> ShowS
Nrt -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [Nrt] -> ShowS
$cshowList :: [Nrt] -> ShowS
show :: Nrt -> String
$cshow :: Nrt -> String
showsPrec :: Int -> Nrt -> ShowS
$cshowsPrec :: Int -> Nrt -> ShowS
Show)

{- | 'span' of 'f' of 'bundleTime'.
     Can be used to separate the /initialisation/ and /remainder/ parts of a score.
-}
nrt_span :: (Time -> Bool) -> Nrt -> ([Bundle],[Bundle])
nrt_span :: (Time -> Bool) -> Nrt -> ([Bundle], [Bundle])
nrt_span Time -> Bool
f = forall a. (a -> Bool) -> [a] -> ([a], [a])
span (Time -> Bool
f forall b c a. (b -> c) -> (a -> b) -> a -> c
. Bundle -> Time
bundleTime) forall b c a. (b -> c) -> (a -> b) -> a -> c
. Nrt -> [Bundle]
nrt_bundles

-- | Encode an 'Nrt' score.
encodeNrt :: Nrt -> B.ByteString
encodeNrt :: Nrt -> ByteString
encodeNrt = [ByteString] -> ByteString
B.concat forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a b. (a -> b) -> [a] -> [b]
map Bundle -> ByteString
oscWithSize forall b c a. (b -> c) -> (a -> b) -> a -> c
. Nrt -> [Bundle]
nrt_bundles

{- | Write an 'Nrt' score.

> import Sound.Osc {- hosc -}
> import Sound.Sc3 {- hsc3 -}
> m1 = g_new [(1, AddToTail, 0)]
> m2 = d_recv (synthdef "sin" (out 0 (sinOsc ar 660 0 * 0.15)))
> m3 = s_new "sin" 100 AddToTail 1 []
> m4 = n_free [100]
> m5 = nrt_end
> sc = Nrt [bundle 0 [m1,m2],bundle 1 [m3],bundle 10 [m4],bundle 15 [m5]]
> writeNrt "/tmp/t.osc" sc
-}
writeNrt :: FilePath -> Nrt -> IO ()
writeNrt :: String -> Nrt -> IO ()
writeNrt String
fn = String -> ByteString -> IO ()
B.writeFile String
fn forall b c a. (b -> c) -> (a -> b) -> a -> c
. Nrt -> ByteString
encodeNrt

-- | Write an 'Nrt' score to a file handle.
putNrt :: Handle -> Nrt -> IO ()
putNrt :: Handle -> Nrt -> IO ()
putNrt Handle
h = Handle -> ByteString -> IO ()
B.hPut Handle
h forall b c a. (b -> c) -> (a -> b) -> a -> c
. Nrt -> ByteString
encodeNrt

-- | Decode an 'Nrt' 'B.ByteString' to a list of 'Bundle's.
decode_nrt_bundles :: B.ByteString -> [Bundle]
decode_nrt_bundles :: ByteString -> [Bundle]
decode_nrt_bundles ByteString
s =
    let (ByteString
p,ByteString
q) = Int64 -> ByteString -> (ByteString, ByteString)
B.splitAt Int64
4 ByteString
s
        n :: Int64
n = forall a b. (Integral a, Num b) => a -> b
fromIntegral (ByteString -> Int
Byte.decode_i32 ByteString
p)
        (ByteString
r,ByteString
s') = Int64 -> ByteString -> (ByteString, ByteString)
B.splitAt Int64
n ByteString
q
        r' :: Bundle
r' = ByteString -> Bundle
Decode.decodeBundle ByteString
r
    in if ByteString -> Bool
B.null ByteString
s'
       then [Bundle
r']
       else Bundle
r' forall a. a -> [a] -> [a]
: ByteString -> [Bundle]
decode_nrt_bundles ByteString
s'

-- | Decode an 'Nrt' 'B.ByteString'.
decodeNrt :: B.ByteString -> Nrt
decodeNrt :: ByteString -> Nrt
decodeNrt = [Bundle] -> Nrt
Nrt forall b c a. (b -> c) -> (a -> b) -> a -> c
. ByteString -> [Bundle]
decode_nrt_bundles

{- | 'decodeNrt' of 'B.readFile'.

> readNrt "/tmp/t.osc"
-}
readNrt :: FilePath -> IO Nrt
readNrt :: String -> IO Nrt
readNrt = forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap ByteString -> Nrt
decodeNrt forall b c a. (b -> c) -> (a -> b) -> a -> c
. String -> IO ByteString
B.readFile

-- * Query

-- | Find any non-ascending sequences.
nrt_non_ascending :: Nrt -> [(Bundle, Bundle)]
nrt_non_ascending :: Nrt -> [(Bundle, Bundle)]
nrt_non_ascending (Nrt [Bundle]
b) =
  let p :: [(Bundle, Bundle)]
p = forall a b. [a] -> [b] -> [(a, b)]
zip [Bundle]
b (forall a. [a] -> [a]
tail [Bundle]
b)
      f :: (Bundle, Bundle) -> Maybe (Bundle, Bundle)
f (Bundle
i,Bundle
j) = if Bundle -> Time
bundleTime Bundle
i forall a. Ord a => a -> a -> Bool
> Bundle -> Time
bundleTime Bundle
j then forall a. a -> Maybe a
Just (Bundle
i,Bundle
j) else forall a. Maybe a
Nothing
  in forall a b. (a -> Maybe b) -> [a] -> [b]
mapMaybe (Bundle, Bundle) -> Maybe (Bundle, Bundle)
f [(Bundle, Bundle)]
p