module Data.Carbonara.Read where import Data.Carbonara.Char (isNotDigit) --carbonara import Data.Carbonara.String (replaceStrOnce) import Data.Char (isDigit, toLower, toUpper) import Data.Maybe (fromJust, isJust) import Data.Time.Calendar (Day, fromGregorian) --time import Text.Printf (printf) import Text.Read (readMaybe) import Data.List (intercalate) import Data.List.Split (chunksOf) --split readB :: Show a => a -> Maybe Bool readB x | take 5 str `elem` ["just ", "right"] = readMaybe $ drop 5 str | otherwise = readMaybe str where str = replaceStrOnce "true" "True" . replaceStrOnce "false" "False" . map toLower . filter (`notElem` ['"','\'']) . show $ x -- Test cases: -- Just True : from these input: True, "True", " TRUE", " 'true' ", Just True, Just "tURe", Right True", Right "\'true" -- Just False : from all input: False, "False", " 'FALSE", "faLSe ", Just False, Just "false ", Right "FALSe", Right "'false" -- Nothing : from all input: Nothing, "Tr ue", "Fal se", Just "T RUE", Right "falsee" readC :: Show a => a -> Maybe Char readC x | show x `elem` ["'\\''" , "\"'\"" , "Just '\\''" , "Just \"'\"" , "Right '\\''", "Right \"'\""] = Just '\'' | show x `elem` ["'\"'" , "Just '\"'" , "Right '\"'" , "\"\\\"\"" , "Just \"\\\"\"" , "Right \"\\\"\"" ] = Just '"' | take 5 str == "Just " = readMaybe . addSingleQuote . drop 5 $ str | take 6 str == "Right " = readMaybe . addSingleQuote . drop 6 $ str | otherwise = readMaybe . addSingleQuote $ str where str = filter (`notElem` ['"','\'']) . show $ x addSingleQuote s = ('\'':s) ++ "\'" readD :: Show a => a -> Maybe Double readD x | take 5 s == "Just " = readD . drop 5 $ s | take 6 s == "Right " = readD . drop 6 $ s | take 1 s == "." = readMaybe ('0': s) | take 2 s == "-." = readMaybe . ("-0" ++) . drop 1 $ s | otherwise = readMaybe s where s = filter (`notElem` ['\\', '"', '\'', ',', '%', '+', '$', '¢', '£', '¥', '€']) . show $ x readDMY :: Show a => a -> Maybe Day readDMY x | isJust y && isJust m && isJust d = Just $ fromGregorian (fromJust y) (fromJust m) (fromJust d) | otherwise = Nothing where s = dropWhile isNotDigit . show $ x d = readInt . takeWhile isDigit $ s m = readInt . takeWhile isDigit . dropWhile isNotDigit . dropWhile isDigit $ s y = readI . takeWhile isDigit . dropWhile isNotDigit . dropWhile isDigit . dropWhile isNotDigit . dropWhile isDigit $ s readMDY :: Show a => a -> Maybe Day readMDY x | isJust y && isJust m && isJust d = Just $ fromGregorian (fromJust y) (fromJust m) (fromJust d) | otherwise = Nothing where s = dropWhile isNotDigit . show $ x m = readInt . takeWhile isDigit $ s d = readInt . takeWhile isDigit . dropWhile isNotDigit . dropWhile isDigit $ s y = readI . takeWhile isDigit . dropWhile isNotDigit . dropWhile isDigit . dropWhile isNotDigit . dropWhile isDigit $ s readYMD :: Show a => a -> Maybe Day readYMD x | isJust y && isJust m && isJust d = Just $ fromGregorian (fromJust y) (fromJust m) (fromJust d) | otherwise = Nothing where s = dropWhile isNotDigit . show $ x y = readI . takeWhile isDigit $ s m = readInt . takeWhile isDigit . dropWhile isNotDigit . dropWhile isDigit $ s d = readInt . takeWhile isDigit . dropWhile isNotDigit . dropWhile isDigit . dropWhile isNotDigit . dropWhile isDigit $ s readDStr :: Show a => a -> Maybe String readDStr x = Just (++) <*> integer_part <*> decimal_part where s = printf "%.2f" <$> readD x integer_part = reverse . intercalate "," . chunksOf 3 . reverse . takeWhile (/= '.') <$> s decimal_part = dropWhile (/= '.') <$> s -- | with 2 decimal place readI :: Show a => a -> Maybe Integer readI x | take 5 s `elem` ["Just ", "Right"] = readMaybe . drop 5 $ s | otherwise = readMaybe s where s = filter (`notElem` ['\\', '"', '\'', ',', '%', '+', '$', '¢', '£', '¥', '€']) . show $ x readInt :: Show a => a -> Maybe Int readInt x | take 5 s `elem` ["Just ", "Right"] = readMaybe . drop 5 $ s | otherwise = readMaybe s where s = filter (`notElem` ['\\', '"', '\'', ',', '%', '+', '$', '¢', '£', '¥', '€']) . show $ x readIStr :: Show a => a -> Maybe String readIStr x = integer_part where s = printf "%.0f" <$> readD x integer_part = reverse . intercalate "," . chunksOf 3 . reverse <$> s readLargeNum :: Show a => a -> Maybe Double readLargeNum x | take 5 s == "Just " = readLargeNum . drop 5 $ s | take 6 s == "Right " = readLargeNum . drop 6 $ s | lastchar == "M" = (*1000000) <$> readMaybe (init s) | lastchar == "B" = (*1000000000) <$> readMaybe (init s) | lastchar == "T" = (*1000000000000) <$> readMaybe (init s) | otherwise = Nothing where s = filter (`notElem` ['\\', '"', '\'', ',', '%', '+', '$', '¢', '£', '¥', '€']) . show $ x lastchar = map toUpper . take 1 . reverse $ s readS :: Show a => a -> Maybe String readS x | s == "Nothing" = Nothing | take 5 s == "Just " = readMaybe . addDoubleQuote . drop 5 $ s | take 6 s == "Right " = readMaybe . addDoubleQuote . drop 6 $ s | otherwise = readMaybe . addDoubleQuote $ s where s = filter (`notElem` ['"', '\'', ',', '%', '+', '$', '¢', '£', '¥', '€', '\\', '[', ']']) . show $ x addDoubleQuote s = ('"':s) ++ ['"']