module Text.XFormat.Show (
Format(..),
Apply(..),
showsf,
showf,
CharF(..),
IntF(..),
IntegerF(..),
FloatF(..),
DoubleF(..),
StringF(..),
ShowF(..),
NumF(..),
(:%:)(..),
(%),
WrapF(..),
AlignF(..),
AlignChopF(..),
Dir(..),
SpacesF(..),
Id(..),
Arr(..),
(:.:)(..),
(<>),
) where
class (Functor f) => Format d f | d -> f where
showsf' :: d -> f ShowS
showsf :: (Format d f, Apply f ShowS a) => d -> a
showsf d = apply (showsf' d)
showf :: (Format d f, Apply f String a) => d -> a
showf d = apply (fmap (\f -> f "") (showsf' d))
newtype Id a = Id a
instance Functor Id where
fmap f (Id x) = Id (f x)
newtype Arr a b = Arr (a -> b)
instance Functor (Arr a) where
fmap f (Arr g) = Arr (f . g)
newtype (:.:) f g a = Comp (f (g a))
infixr 8 :.:
instance (Functor f, Functor g) => Functor (f :.: g) where
fmap f (Comp fga) = Comp (fmap (fmap f) fga)
(<>) :: (Functor f, Functor g) => f (b -> c) -> g (a -> b) -> (:.:) f g (a -> c)
f <> g = Comp (fmap (\s -> fmap (\t -> s . t) g) f)
infixr 8 <>
class (Functor f) => Apply f a b | f a -> b where
apply :: f a -> b
instance Apply Id a a where
apply (Id a) = a
instance Apply (Arr a) b (a -> b) where
apply (Arr f) = f
instance (Apply f b c, Apply g a b) => Apply (f :.: g) a c where
apply (Comp fga) = apply (fmap apply fga)
instance Format String Id where
showsf' s = Id (showString s)
instance Format Char Id where
showsf' c = Id (showChar c)
data CharF = Char
instance Format CharF (Arr Char) where
showsf' Char = Arr showChar
data StringF = String
instance Format StringF (Arr String) where
showsf' String = Arr showString
data IntF = Int
instance Format IntF (Arr Int) where
showsf' Int = Arr shows
data IntegerF = Integer
instance Format IntegerF (Arr Integer) where
showsf' Integer = Arr shows
data FloatF = Float
instance Format FloatF (Arr Float) where
showsf' Float = Arr shows
data DoubleF = Double
instance Format DoubleF (Arr Double) where
showsf' Double = Arr shows
data ShowF a = Show
instance (Show a) => Format (ShowF a) (Arr a) where
showsf' Show = Arr shows
data NumF a = Num
instance (Num a, Show a) => Format (NumF a) (Arr a) where
showsf' Num = Arr shows
data SpacesF = Spaces Int
instance Format SpacesF Id where
showsf' (Spaces n) = Id (showString (replicate n ' '))
data a :%: b = a :%: b
deriving (Eq, Show)
infixr 8 :%:
(%) :: a -> b -> a :%: b
(%) = (:%:)
infixr 8 %
instance (Format d1 f1, Format d2 f2) => Format (d1 :%: d2) (f1 :.: f2) where
showsf' (d1 :%: d2) = showsf' d1 <> showsf' d2
data WrapF inner outer = Wrap outer inner outer
instance (Format din fin, Format dout fout)
=> Format (WrapF din dout) (fout :.: fin :.: fout) where
showsf' (Wrap doutl din doutr) = showsf' doutl <> showsf' din <> showsf' doutr
data AlignF a = Align Dir Int a
data AlignChopF a = AlignChop Dir Int a
data Dir = L | R
align :: Bool -> Dir -> Int -> ShowS -> ShowS
align doChop dir wid input =
case dir of
L -> chop (take wid) . input . addSpaces
R -> chop (drop (len wid)) . addSpaces . input
where
len = length (input "")
spaces = replicate (wid len) ' '
chop act = if doChop && len > wid then act else id
addSpaces = if len < wid then showString spaces else id
instance (Format d f) => Format (AlignF d) f where
showsf' (Align dir wid d) = fmap (align False dir wid) (showsf' d)
instance (Format d f) => Format (AlignChopF d) f where
showsf' (AlignChop dir wid d) = fmap (align True dir wid) (showsf' d)
instance
(Format d1 f1, Format d2 f2)
=> Format
(d1, d2)
(f1 :.: f2)
where
showsf' (d1, d2) =
showsf' d1 <> showsf' d2
instance
(Format d1 f1, Format d2 f2, Format d3 f3)
=> Format
(d1, d2, d3)
(f1 :.: f2 :.: f3)
where
showsf' (d1, d2, d3) =
showsf' d1 <> showsf' d2 <> showsf' d3
instance
(Format d1 f1, Format d2 f2, Format d3 f3, Format d4 f4)
=> Format
(d1, d2, d3, d4)
(f1 :.: f2 :.: f3 :.: f4)
where
showsf' (d1, d2, d3, d4) =
showsf' d1 <> showsf' d2 <> showsf' d3 <> showsf' d4
instance
(Format d1 f1, Format d2 f2, Format d3 f3, Format d4 f4, Format d5 f5)
=> Format
(d1, d2, d3, d4, d5)
(f1 :.: f2 :.: f3 :.: f4 :.: f5)
where
showsf' (d1, d2, d3, d4, d5) =
showsf' d1 <> showsf' d2 <> showsf' d3 <> showsf' d4 <> showsf' d5
instance
(Format d1 f1, Format d2 f2, Format d3 f3, Format d4 f4, Format d5 f5,
Format d6 f6)
=> Format
(d1, d2, d3, d4, d5, d6)
(f1 :.: f2 :.: f3 :.: f4 :.: f5 :.: f6)
where
showsf' (d1, d2, d3, d4, d5, d6) =
showsf' d1 <> showsf' d2 <> showsf' d3 <> showsf' d4 <> showsf' d5 <>
showsf' d6
instance
(Format d1 f1, Format d2 f2, Format d3 f3, Format d4 f4, Format d5 f5,
Format d6 f6, Format d7 f7)
=> Format
(d1, d2, d3, d4, d5, d6, d7)
(f1 :.: f2 :.: f3 :.: f4 :.: f5 :.: f6 :.: f7)
where
showsf' (d1, d2, d3, d4, d5, d6, d7) =
showsf' d1 <> showsf' d2 <> showsf' d3 <> showsf' d4 <> showsf' d5 <>
showsf' d6 <> showsf' d7
instance
(Format d1 f1, Format d2 f2, Format d3 f3, Format d4 f4, Format d5 f5,
Format d6 f6, Format d7 f7, Format d8 f8)
=> Format
(d1, d2, d3, d4, d5, d6, d7, d8)
(f1 :.: f2 :.: f3 :.: f4 :.: f5 :.: f6 :.: f7 :.: f8)
where
showsf' (d1, d2, d3, d4, d5, d6, d7, d8) =
showsf' d1 <> showsf' d2 <> showsf' d3 <> showsf' d4 <> showsf' d5 <>
showsf' d6 <> showsf' d7 <> showsf' d8
instance
(Format d1 f1, Format d2 f2, Format d3 f3, Format d4 f4, Format d5 f5,
Format d6 f6, Format d7 f7, Format d8 f8, Format d9 f9)
=> Format
(d1, d2, d3, d4, d5, d6, d7, d8, d9)
(f1 :.: f2 :.: f3 :.: f4 :.: f5 :.: f6 :.: f7 :.: f8 :.: f9)
where
showsf' (d1, d2, d3, d4, d5, d6, d7, d8, d9) =
showsf' d1 <> showsf' d2 <> showsf' d3 <> showsf' d4 <> showsf' d5 <>
showsf' d6 <> showsf' d7 <> showsf' d8 <> showsf' d9
instance
(Format d1 f1, Format d2 f2, Format d3 f3, Format d4 f4, Format d5 f5,
Format d6 f6, Format d7 f7, Format d8 f8, Format d9 f9, Format d10 f10)
=> Format
(d1, d2, d3, d4, d5, d6, d7, d8, d9, d10)
(f1 :.: f2 :.: f3 :.: f4 :.: f5 :.: f6 :.: f7 :.: f8 :.: f9 :.: f10)
where
showsf' (d1, d2, d3, d4, d5, d6, d7, d8, d9, d10) =
showsf' d1 <> showsf' d2 <> showsf' d3 <> showsf' d4 <> showsf' d5 <>
showsf' d6 <> showsf' d7 <> showsf' d8 <> showsf' d9 <> showsf' d10
instance
(Format d1 f1, Format d2 f2, Format d3 f3, Format d4 f4, Format d5 f5,
Format d6 f6, Format d7 f7, Format d8 f8, Format d9 f9, Format d10 f10,
Format d11 f11)
=> Format
(d1, d2, d3, d4, d5, d6, d7, d8, d9, d10, d11)
(f1 :.: f2 :.: f3 :.: f4 :.: f5 :.: f6 :.: f7 :.: f8 :.: f9 :.: f10 :.: f11)
where
showsf' (d1, d2, d3, d4, d5, d6, d7, d8, d9, d10, d11) =
showsf' d1 <> showsf' d2 <> showsf' d3 <> showsf' d4 <> showsf' d5 <>
showsf' d6 <> showsf' d7 <> showsf' d8 <> showsf' d9 <> showsf' d10 <>
showsf' d11
instance
(Format d1 f1, Format d2 f2, Format d3 f3, Format d4 f4, Format d5 f5,
Format d6 f6, Format d7 f7, Format d8 f8, Format d9 f9, Format d10 f10,
Format d11 f11, Format d12 f12)
=> Format
(d1, d2, d3, d4, d5, d6, d7, d8, d9, d10, d11, d12)
(f1 :.: f2 :.: f3 :.: f4 :.: f5 :.: f6 :.: f7 :.: f8 :.: f9 :.: f10 :.:
f11 :.: f12)
where
showsf' (d1, d2, d3, d4, d5, d6, d7, d8, d9, d10, d11, d12) =
showsf' d1 <> showsf' d2 <> showsf' d3 <> showsf' d4 <> showsf' d5 <>
showsf' d6 <> showsf' d7 <> showsf' d8 <> showsf' d9 <> showsf' d10 <>
showsf' d11 <> showsf' d12
instance
(Format d1 f1, Format d2 f2, Format d3 f3, Format d4 f4, Format d5 f5,
Format d6 f6, Format d7 f7, Format d8 f8, Format d9 f9, Format d10 f10,
Format d11 f11, Format d12 f12, Format d13 f13)
=> Format
(d1, d2, d3, d4, d5, d6, d7, d8, d9, d10, d11, d12, d13)
(f1 :.: f2 :.: f3 :.: f4 :.: f5 :.: f6 :.: f7 :.: f8 :.: f9 :.: f10 :.:
f11 :.: f12 :.: f13)
where
showsf' (d1, d2, d3, d4, d5, d6, d7, d8, d9, d10, d11, d12, d13) =
showsf' d1 <> showsf' d2 <> showsf' d3 <> showsf' d4 <> showsf' d5 <>
showsf' d6 <> showsf' d7 <> showsf' d8 <> showsf' d9 <> showsf' d10 <>
showsf' d11 <> showsf' d12 <> showsf' d13
instance
(Format d1 f1, Format d2 f2, Format d3 f3, Format d4 f4, Format d5 f5,
Format d6 f6, Format d7 f7, Format d8 f8, Format d9 f9, Format d10 f10,
Format d11 f11, Format d12 f12, Format d13 f13, Format d14 f14)
=> Format
(d1, d2, d3, d4, d5, d6, d7, d8, d9, d10, d11, d12, d13, d14)
(f1 :.: f2 :.: f3 :.: f4 :.: f5 :.: f6 :.: f7 :.: f8 :.: f9 :.: f10 :.:
f11 :.: f12 :.: f13 :.: f14)
where
showsf' (d1, d2, d3, d4, d5, d6, d7, d8, d9, d10, d11, d12, d13, d14) =
showsf' d1 <> showsf' d2 <> showsf' d3 <> showsf' d4 <> showsf' d5 <>
showsf' d6 <> showsf' d7 <> showsf' d8 <> showsf' d9 <> showsf' d10 <>
showsf' d11 <> showsf' d12 <> showsf' d13 <> showsf' d14
instance
(Format d1 f1, Format d2 f2, Format d3 f3, Format d4 f4, Format d5 f5,
Format d6 f6, Format d7 f7, Format d8 f8, Format d9 f9, Format d10 f10,
Format d11 f11, Format d12 f12, Format d13 f13, Format d14 f14,
Format d15 f15)
=> Format
(d1, d2, d3, d4, d5, d6, d7, d8, d9, d10, d11, d12, d13, d14, d15)
(f1 :.: f2 :.: f3 :.: f4 :.: f5 :.: f6 :.: f7 :.: f8 :.: f9 :.: f10 :.:
f11 :.: f12 :.: f13 :.: f14 :.: f15)
where
showsf' (d1, d2, d3, d4, d5, d6, d7, d8, d9, d10, d11, d12, d13, d14, d15) =
showsf' d1 <> showsf' d2 <> showsf' d3 <> showsf' d4 <> showsf' d5 <>
showsf' d6 <> showsf' d7 <> showsf' d8 <> showsf' d9 <> showsf' d10 <>
showsf' d11 <> showsf' d12 <> showsf' d13 <> showsf' d14 <> showsf' d15