{- | Module : Cookbook.Project.Quill.Quill2.Q2Api Copyright : (c) 2014 by Nate Pisarski License : BSD3 Maintainer : nathanpisarski@gmail.com Stability : Stable Portability : Portable (Cookbook) Q2Api is the user-facing part of Quill. It has all the functions necessar to Create, Read, Update, and Delete information from the database, and turn a database back into a Quill-readable string. -} module Cookbook.Project.Quill.Quill2.Q2Api where import qualified Cookbook.Ingredients.Tupples.Look as Lk import qualified Cookbook.Essential.Common as Cm import qualified Cookbook.Essential.Continuous as Ct import qualified Cookbook.Ingredients.Lists.Access as Ac import Cookbook.Project.Quill.Quill2.Q2Prelude -- | Get the name of a Quill. getQuillName :: Quill -> String getQuillName = fst -- | Return the element of the Quill, specifically useful for lists. getQuillBody :: Quill -> Element String getQuillBody = snd -- | Find a quill in the database by name, returning it or a possible error type. getQuill :: [Quill] -> String -> QuillStatus getQuill [] _ = QuillMissing getQuill (x:xs) c | Ac.count (map getQuillName (x:xs)) c > 1 = QuillMultiple | getQuillName x == c = QuillSuccess x | otherwise = getQuill xs c -- | Look up the value of a Quill TABLE. Will produce an error on a list. lookUp :: [Quill] -> (String, String) -> String lookUp x (a,b) = case (getQuill x a) of QuillMissing -> error $ "Table not found." QuillMultiple -> error $ "Multiple values of " ++ a ++ " detected. Database eror, fix manually." (QuillSuccess (c,d)) -> case d of (List f) -> error "Cannot look up the value of a list." (Table f) -> let c = Lk.lookList f b in if (c == []) then (error $ "Item " ++ b ++ " not found in table " ++ a) else (if (length c > 1) then multipleInnerError else (head c)) where multipleInnerError = error $ "Multiple values of " ++ b ++ " found in table " ++ a ++ ". Database corrupted, change manually." -- | Remove a quill from the database by name. removeQuill :: [Quill] -> String -> [Quill] removeQuill [] _ = [] removeQuill ((x,y):xs) c | x == c = removeQuill xs c -- See [Q2N1] | otherwise = (x,y) : removeQuill xs c -- | Remove an item from a Quill within a database. Works aggressively, meaning it removes all copies to help sanitize QuillMultiples out. removeItem :: [Quill] -> (String, String) -> [Quill] removeItem x (a,b) = case (getQuill x a) of QuillSuccess (c,j) -> case j of (Table d) -> (c,(Table [(y,t) | (y,t) <- d, y /= b])) : (removeQuill x a) (List d) -> (c,List $ Ct.remove d c) : removeQuill x a _ -> (let l = lookUp x (a,b) in x) -- This goes against everything that haskell means. -- | Adds a Quill databse to the file. addQuill :: [Quill] -> Quill -> [Quill] addQuill x c = c : x -- | Add a QuillAddition to the databse. QuillAddition is a safe encapsulation of list and table values. addItem :: [Quill] -> QuillAddition -> [Quill] addItem x qa= case getQuill x a of QuillSuccess (y, ys) -> case ys of (Table d) -> case qa of (ATable (_,b,c)) -> (y,Table $ (b,c) : d) : removeQuill x a (AList _ ) -> error $ "$ Type Mismatch! Attempted to add a List type to Table in table " ++ (show qa) (List d) -> case qa of (AList (_,b)) -> (y, List $ (b:d)) : removeQuill x a (ATable _) -> error $ "Type MisMatch! Attempted to add Table type to List in table " ++ (show qa) QuillMultiple -> error "Multiple found" QuillMissing -> error "Not found quill!" where a = case qa of (ATable (g,b,c)) -> g (AList (g,b)) -> g -- | Change an item within the database using a Quill addition. Wrapper of addItem and removeItem. changeItem :: [Quill] -> QuillAddition -> [Quill] changeItem x y = case y of (ATable (a,b,c)) -> addItem (removeItem x (a,b)) y (AList (a,b)) -> addItem (removeItem x (a,b)) y -- | Turn a Quill table into a string. toString :: Quill -> String toString (nm,typ) = case typ of (List a) -> ("list(" ++ nm ++ "){" ++ (Cm.flt (map (\c -> (c ++ ";")) a))) ++ "}" (Table a) -> ("table(" ++ nm ++ "){" ++ (Cm.flt $ stringify a)) ++ "}" where stringify [] = [] stringify ((a,b):xs) = (a ++ ":" ++ b ++ ";") : stringify xs