module Music.Theory.Db.Plain where
import Data.List 
import Data.Maybe 
import qualified Data.List.Split as Split 
import qualified Safe 
import qualified Music.Theory.Io as Io 
import qualified Music.Theory.List as T 
type Sep = (String, String, String)
type Key = String
type Value = String
type Entry = (Key, [Value])
type Record = [Entry]
type Db = [Record]
sep_plain :: Sep
sep_plain :: Sep
sep_plain = ([Char
'\n',Char
'\n'],[Char
'\n'],Key
": ")
record_parse :: (String,String) -> String -> Record
record_parse :: (Key, Key) -> Key -> Record
record_parse (Key
fs,Key
es) = forall a b. Eq a => [(a, b)] -> [(a, [b])]
T.collate_adjacent forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a b. (a -> Maybe b) -> [a] -> [b]
mapMaybe (forall a. Eq a => [a] -> [a] -> Maybe ([a], [a])
T.separate_at Key
es) forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a. Eq a => [a] -> [a] -> [[a]]
Split.splitOn Key
fs
record_lookup :: Key -> Record -> [Value]
record_lookup :: Key -> Record -> [Key]
record_lookup Key
k = forall a. a -> Maybe a -> a
fromMaybe [] forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a b. Eq a => a -> [(a, b)] -> Maybe b
lookup Key
k
record_lookup_at :: (Key,Int) -> Record -> Maybe Value
record_lookup_at :: (Key, Int) -> Record -> Maybe Key
record_lookup_at (Key
k,Int
n) = forall a b c. (a -> b -> c) -> b -> a -> c
flip forall a. [a] -> Int -> Maybe a
Safe.atMay Int
n forall b c a. (b -> c) -> (a -> b) -> a -> c
. Key -> Record -> [Key]
record_lookup Key
k
record_has_key :: Key -> Record -> Bool
record_has_key :: Key -> Record -> Bool
record_has_key Key
k = forall a. Maybe a -> Bool
isJust forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a b. Eq a => a -> [(a, b)] -> Maybe b
lookup Key
k
record_lookup_uniq :: Key -> Record -> Maybe Value
record_lookup_uniq :: Key -> Record -> Maybe Key
record_lookup_uniq Key
k Record
r =
    case Key -> Record -> [Key]
record_lookup Key
k Record
r of
      [] -> forall a. Maybe a
Nothing
      [Key
v] -> forall a. a -> Maybe a
Just Key
v
      [Key]
_ -> forall a. HasCallStack => Key -> a
error Key
"record_lookup_uniq: non uniq"
db_parse :: Sep -> String -> [Record]
db_parse :: Sep -> Key -> [Record]
db_parse (Key
rs,Key
fs,Key
es) Key
s =
    let r :: [Key]
r = forall a. Eq a => [a] -> [a] -> [[a]]
Split.splitOn Key
rs Key
s
    in forall a b. (a -> b) -> [a] -> [b]
map ((Key, Key) -> Key -> Record
record_parse (Key
fs,Key
es)) [Key]
r
db_sort :: [(Key,Int)] -> [Record] -> [Record]
db_sort :: [(Key, Int)] -> [Record] -> [Record]
db_sort [(Key, Int)]
k = forall b a. Ord b => [a -> b] -> [a] -> [a]
T.sort_by_n_stage_on (forall a b. (a -> b) -> [a] -> [b]
map (Key, Int) -> Record -> Maybe Key
record_lookup_at [(Key, Int)]
k)
db_load_utf8 :: Sep -> FilePath -> IO [Record]
db_load_utf8 :: Sep -> Key -> IO [Record]
db_load_utf8 Sep
sep = forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap (Sep -> Key -> [Record]
db_parse Sep
sep) forall b c a. (b -> c) -> (a -> b) -> a -> c
. Key -> IO Key
Io.read_file_utf8
record_pp :: (String,String) -> Record -> String
record_pp :: (Key, Key) -> Record -> Key
record_pp (Key
fs,Key
es) = forall a. [a] -> [[a]] -> [a]
intercalate Key
fs forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a b. (a -> b) -> [a] -> [b]
map (\(Key
k,Key
v) -> Key
k forall a. [a] -> [a] -> [a]
++ Key
es forall a. [a] -> [a] -> [a]
++ Key
v) forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall k v. [(k, [v])] -> [(k, v)]
T.uncollate
db_store_utf8 :: Sep -> FilePath -> [Record] -> IO ()
db_store_utf8 :: Sep -> Key -> [Record] -> IO ()
db_store_utf8 (Key
rs,Key
fs,Key
es) Key
fn = Key -> Key -> IO ()
Io.write_file_utf8 Key
fn forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a. [a] -> [[a]] -> [a]
intercalate Key
rs forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a b. (a -> b) -> [a] -> [b]
map ((Key, Key) -> Record -> Key
record_pp (Key
fs,Key
es))