module Text.PercentFormat.Spec where
import Data.Char (isDigit)
data Spec = Spec
{ Spec -> SpecType
ty :: SpecType
, Spec -> Int
width :: Int
, Spec -> Bool
leftAlign :: Bool
, Spec -> Char
padWith :: Char
, Spec -> Int
base :: Int
, Spec -> Maybe Int
precision :: Maybe Int
, Spec -> Int
minPrecision :: Int
, Spec -> String
positivePrefix :: String
, Spec -> Bool
capitalizeDigits :: Bool
}
deriving (Spec -> Spec -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: Spec -> Spec -> Bool
$c/= :: Spec -> Spec -> Bool
== :: Spec -> Spec -> Bool
$c== :: Spec -> Spec -> Bool
Eq, Int -> Spec -> ShowS
[Spec] -> ShowS
Spec -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [Spec] -> ShowS
$cshowList :: [Spec] -> ShowS
show :: Spec -> String
$cshow :: Spec -> String
showsPrec :: Int -> Spec -> ShowS
$cshowsPrec :: Int -> Spec -> ShowS
Show)
data SpecType = NumberSpec
| ReprSpec
| StringSpec
| CharSpec
| Percent
deriving (SpecType -> SpecType -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: SpecType -> SpecType -> Bool
$c/= :: SpecType -> SpecType -> Bool
== :: SpecType -> SpecType -> Bool
$c== :: SpecType -> SpecType -> Bool
Eq, Int -> SpecType -> ShowS
[SpecType] -> ShowS
SpecType -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [SpecType] -> ShowS
$cshowList :: [SpecType] -> ShowS
show :: SpecType -> String
$cshow :: SpecType -> String
showsPrec :: Int -> SpecType -> ShowS
$cshowsPrec :: Int -> SpecType -> ShowS
Show)
spec :: Spec
spec :: Spec
spec = Spec
{ ty :: SpecType
ty = forall a. HasCallStack => String -> a
error String
"undefined Spec ty"
, width :: Int
width = Int
0
, leftAlign :: Bool
leftAlign = Bool
False
, padWith :: Char
padWith = Char
' '
, base :: Int
base = Int
10
, precision :: Maybe Int
precision = forall a. Maybe a
Nothing
, minPrecision :: Int
minPrecision = Int
0
, positivePrefix :: String
positivePrefix = String
""
, capitalizeDigits :: Bool
capitalizeDigits = Bool
False
}
parseSpec :: String -> (Spec,String)
parseSpec :: String -> (Spec, String)
parseSpec (Char
'%':String
cs) = (Spec
spec {ty :: SpecType
ty = SpecType
Percent }, String
cs)
parseSpec (Char
'r':String
cs) = (Spec
spec {ty :: SpecType
ty = SpecType
ReprSpec }, String
cs)
parseSpec (Char
's':String
cs) = (Spec
spec {ty :: SpecType
ty = SpecType
StringSpec}, String
cs)
parseSpec (Char
'c':String
cs) = (Spec
spec {ty :: SpecType
ty = SpecType
CharSpec }, String
cs)
parseSpec (Char
'i':String
cs) = (Spec
spec {ty :: SpecType
ty = SpecType
NumberSpec, precision :: Maybe Int
precision = forall a. a -> Maybe a
Just Int
0}, String
cs)
parseSpec (Char
'd':String
cs) = (Spec
spec {ty :: SpecType
ty = SpecType
NumberSpec}, String
cs)
parseSpec (Char
'x':String
cs) = (Spec
spec {ty :: SpecType
ty = SpecType
NumberSpec, base :: Int
base = Int
16}, String
cs)
parseSpec (Char
'X':String
cs) = (Spec
spec {ty :: SpecType
ty = SpecType
NumberSpec, base :: Int
base = Int
16, capitalizeDigits :: Bool
capitalizeDigits = Bool
True}, String
cs)
parseSpec (Char
'o':String
cs) = (Spec
spec {ty :: SpecType
ty = SpecType
NumberSpec, base :: Int
base = Int
8}, String
cs)
parseSpec (Char
'b':String
cs) = (Spec
spec {ty :: SpecType
ty = SpecType
NumberSpec, base :: Int
base = Int
2}, String
cs)
parseSpec (Char
'f':String
cs) = (Spec
spec {ty :: SpecType
ty = SpecType
NumberSpec, minPrecision :: Int
minPrecision = Int
1}, String
cs)
parseSpec (Char
'q':String
cs) = forall a. HasCallStack => String -> a
error forall a b. (a -> b) -> a -> b
$ String
"`q' format will be implemented in a future version"
parseSpec (Char
'e':String
cs) = forall a. HasCallStack => String -> a
error forall a b. (a -> b) -> a -> b
$ String
"`e' format will be implemented in a future version"
parseSpec (Char
'E':String
cs) = forall a. HasCallStack => String -> a
error forall a b. (a -> b) -> a -> b
$ String
"`E' format will be implemented in a future version"
parseSpec (Char
'0':String
cs) = (Spec
s {padWith :: Char
padWith = Char
'0'}, String
cs') where (Spec
s,String
cs') = String -> (Spec, String)
parseSpec String
cs
parseSpec ( Char
n :String
cs) | Char -> Bool
isDigit Char
n = let (String
w,String
cs') = forall a. (a -> Bool) -> [a] -> ([a], [a])
span Char -> Bool
isDigit (Char
nforall a. a -> [a] -> [a]
:String
cs)
(Spec
s,String
cs'') = String -> (Spec, String)
parseSpec String
cs'
in (Spec
s {width :: Int
width = forall a. Read a => String -> a
read String
w}, String
cs'')
parseSpec (Char
'.':Char
'*':String
cs) = let (Spec
s,String
cs') = String -> (Spec, String)
parseSpec String
cs
in (Spec
s {precision :: Maybe Int
precision = forall a. Maybe a
Nothing}, String
cs')
parseSpec (Char
'.':String
cs) = let (String
w,String
cs') = forall a. (a -> Bool) -> [a] -> ([a], [a])
span Char -> Bool
isDigit String
cs
(Spec
s,String
cs'') = String -> (Spec, String)
parseSpec String
cs'
in (Spec
s {precision :: Maybe Int
precision = forall a. a -> Maybe a
Just (forall a. Read a => String -> a
read (Char
'0'forall a. a -> [a] -> [a]
:String
w))}, String
cs'')
parseSpec (Char
'-':String
cs) = (Spec
s {leftAlign :: Bool
leftAlign = Bool
True}, String
cs') where (Spec
s,String
cs') = String -> (Spec, String)
parseSpec String
cs
parseSpec (Char
' ':String
cs) = (Spec
s {positivePrefix :: String
positivePrefix = String
" "}, String
cs') where (Spec
s,String
cs') = String -> (Spec, String)
parseSpec String
cs
parseSpec (Char
'+':String
cs) = (Spec
s {positivePrefix :: String
positivePrefix = String
"+"}, String
cs') where (Spec
s,String
cs') = String -> (Spec, String)
parseSpec String
cs
parseSpec (Char
c:String
_) = forall a. HasCallStack => String -> a
error forall a b. (a -> b) -> a -> b
$ String
"unknown format string `" forall a. [a] -> [a] -> [a]
++ (Char
cforall a. a -> [a] -> [a]
:String
"'")