module Sound.Sc3.Server.Graphdef.Text where
import Control.Monad
import Data.Char
import Data.Functor.Identity
import qualified Numeric
import qualified Control.Monad.State as S
import qualified Sound.Osc.Datum as Datum
import Sound.Sc3.Server.Graphdef
print_string :: Datum.Ascii -> String
print_string :: Ascii -> String
print_string Ascii
a =
let s :: String
s = Ascii -> String
Datum.ascii_to_string Ascii
a
in if forall (t :: * -> *) a. Foldable t => (a -> Bool) -> t a -> Bool
any Char -> Bool
isSpace String
s Bool -> Bool -> Bool
|| Char
';' forall (t :: * -> *) a. (Foldable t, Eq a) => a -> t a -> Bool
`elem` String
s then forall a. HasCallStack => String -> a
error String
"print_string" else String
s
enc_text :: (String -> String) -> Encode_Functions String
enc_text :: (String -> String) -> Encode_Functions String
enc_text String -> String
com_f =
([String] -> String
unwords forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a. (a -> Bool) -> [a] -> [a]
filter (Bool -> Bool
not forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall (t :: * -> *) a. Foldable t => t a -> Bool
null),Ascii -> String
print_string,forall a. Show a => a -> String
show,forall a. Show a => a -> String
show,forall a. Show a => a -> String
show,\Double
n -> forall a. RealFloat a => Maybe Int -> a -> String -> String
Numeric.showFFloat forall a. Maybe a
Nothing Double
n String
""
,String -> String
com_f)
print_graphdef :: Bool -> Graphdef -> String
print_graphdef :: Bool -> Graphdef -> String
print_graphdef Bool
with_com =
let com_f :: String -> String
com_f = if Bool
with_com then \String
c -> forall (t :: * -> *) a. Foldable t => t [a] -> [a]
concat [String
"\n; ",String
c,String
"\n"] else forall a b. a -> b -> a
const String
""
in forall t. Encode_Functions t -> Graphdef -> t
encode_graphdef_f ((String -> String) -> Encode_Functions String
enc_text String -> String
com_f)
list_read_f :: (t -> u) -> S.State [t] u
list_read_f :: forall t u. (t -> u) -> State [t] u
list_read_f t -> u
f = do
[t]
l <- forall s (m :: * -> *). MonadState s m => m s
S.get
forall (f :: * -> *). Applicative f => Bool -> f () -> f ()
when (forall (t :: * -> *) a. Foldable t => t a -> Bool
null [t]
l) (forall a. HasCallStack => String -> a
error String
"list_read_f")
forall s (m :: * -> *). MonadState s m => s -> m ()
S.put (forall a. [a] -> [a]
tail [t]
l)
forall (m :: * -> *) a. Monad m => a -> m a
return (t -> u
f (forall a. [a] -> a
head [t]
l))
read_float :: (Fractional p, Read p) => String -> p
read_float :: forall p. (Fractional p, Read p) => String -> p
read_float String
txt =
case forall a b. (a -> b) -> [a] -> [b]
map Char -> Char
toLower String
txt of
String
"inf" -> p
1 forall a. Fractional a => a -> a -> a
/ p
0
String
"infinity" -> p
1 forall a. Fractional a => a -> a -> a
/ p
0
String
_ -> forall a. Read a => String -> a
read String
txt
text_get_f :: Get_Functions (S.StateT [String] Identity)
text_get_f :: Get_Functions (StateT [String] Identity)
text_get_f = (forall t u. (t -> u) -> State [t] u
list_read_f String -> Ascii
Datum.ascii,forall t u. (t -> u) -> State [t] u
list_read_f forall a. Read a => String -> a
read,forall t u. (t -> u) -> State [t] u
list_read_f forall a. Read a => String -> a
read,forall t u. (t -> u) -> State [t] u
list_read_f forall a. Read a => String -> a
read,forall t u. (t -> u) -> State [t] u
list_read_f forall p. (Fractional p, Read p) => String -> p
read_float)
read_graphdef :: String -> Graphdef
read_graphdef :: String -> Graphdef
read_graphdef String
txt =
let delete_comments :: [String] -> [String]
delete_comments = forall a. (a -> Bool) -> [a] -> [a]
filter (\String
x -> Bool -> Bool
not (forall (t :: * -> *) a. Foldable t => t a -> Bool
null String
x) Bool -> Bool -> Bool
&& (forall a. [a] -> a
head String
x forall a. Eq a => a -> a -> Bool
/= Char
';'))
in forall s a. State s a -> s -> a
S.evalState (forall (m :: * -> *). Monad m => Get_Functions m -> m Graphdef
get_graphdef Get_Functions (StateT [String] Identity)
text_get_f) (forall (t :: * -> *) a b. Foldable t => (a -> [b]) -> t a -> [b]
concatMap String -> [String]
words ([String] -> [String]
delete_comments (String -> [String]
lines String
txt)))
read_graphdef_file :: FilePath -> IO Graphdef
read_graphdef_file :: String -> IO Graphdef
read_graphdef_file = forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap String -> Graphdef
read_graphdef forall b c a. (b -> c) -> (a -> b) -> a -> c
. String -> IO String
readFile