{-# LANGUAGE FlexibleInstances, OverlappingInstances #-}
{-# OPTIONS_GHC -fno-warn-incomplete-patterns #-}

-- | Pretty-printer for PrintSciDbAFL.
--   Generated by the BNF converter.

module PrintSciDbAFL where

import AbsSciDbAFL
import Data.Char

-- | The top-level printing method.

printTree :: Print a => a -> String
printTree = render . prt 0

type Doc = [ShowS] -> [ShowS]

doc :: ShowS -> Doc
doc = (:)

render :: Doc -> String
render d = rend 0 (map ($ "") $ d []) "" where
  rend i ss = case ss of
    "["      :ts -> showChar '[' . rend i ts
    "("      :ts -> showChar '(' . rend i ts
    "{"      :ts -> showChar '{' . new (i+1) . rend (i+1) ts
    "}" : ";":ts -> new (i-1) . space "}" . showChar ';' . new (i-1) . rend (i-1) ts
    "}"      :ts -> new (i-1) . showChar '}' . new (i-1) . rend (i-1) ts
    ";"      :ts -> showChar ';' . new i . rend i ts
    t  : ts@(p:_) | closingOrPunctuation p -> showString t . rend i ts
    t        :ts -> space t . rend i ts
    _            -> id
  new i   = showChar '\n' . replicateS (2*i) (showChar ' ') . dropWhile isSpace
  space t = showString t . (\s -> if null s then "" else ' ':s)

  closingOrPunctuation :: String -> Bool
  closingOrPunctuation [c] = c `elem` closerOrPunct
  closingOrPunctuation _   = False

  closerOrPunct :: String
  closerOrPunct = ")],;"

parenth :: Doc -> Doc
parenth ss = doc (showChar '(') . ss . doc (showChar ')')

concatS :: [ShowS] -> ShowS
concatS = foldr (.) id

concatD :: [Doc] -> Doc
concatD = foldr (.) id

replicateS :: Int -> ShowS -> ShowS
replicateS n f = concatS (replicate n f)

-- | The printer class does the job.

class Print a where
  prt :: Int -> a -> Doc
  prtList :: Int -> [a] -> Doc
  prtList i = concatD . map (prt i)

instance Print a => Print [a] where
  prt = prtList

instance Print Char where
  prt _ s = doc (showChar '\'' . mkEsc '\'' s . showChar '\'')
  prtList _ s = doc (showChar '"' . concatS (map (mkEsc '"') s) . showChar '"')

mkEsc :: Char -> Char -> ShowS
mkEsc q s = case s of
  _ | s == q -> showChar '\\' . showChar s
  '\\'-> showString "\\\\"
  '\n' -> showString "\\n"
  '\t' -> showString "\\t"
  _ -> showChar s

prPrec :: Int -> Int -> Doc -> Doc
prPrec i j = if j < i then parenth else id

instance Print Integer where
  prt _ x = doc (shows x)

instance Print Double where
  prt _ x = doc (shows x)

instance Print ResAnd where
  prt _ (ResAnd i) = doc (showString i)

instance Print ResArray where
  prt _ (ResArray i) = doc (showString i)

instance Print ResAs where
  prt _ (ResAs i) = doc (showString i)

instance Print ResAsc where
  prt _ (ResAsc i) = doc (showString i)

instance Print ResCompression where
  prt _ (ResCompression i) = doc (showString i)

instance Print ResCreate where
  prt _ (ResCreate i) = doc (showString i)

instance Print ResDefault where
  prt _ (ResDefault i) = doc (showString i)

instance Print ResDesc where
  prt _ (ResDesc i) = doc (showString i)

instance Print ResFalse where
  prt _ (ResFalse i) = doc (showString i)

instance Print ResNot where
  prt _ (ResNot i) = doc (showString i)

instance Print ResNull where
  prt _ (ResNull i) = doc (showString i)

instance Print ResOr where
  prt _ (ResOr i) = doc (showString i)

instance Print ResTemp where
  prt _ (ResTemp i) = doc (showString i)

instance Print ResTrue where
  prt _ (ResTrue i) = doc (showString i)

instance Print ADouble where
  prt _ (ADouble i) = doc (showString i)

instance Print AString where
  prt _ (AString i) = doc (showString i)

instance Print Id where
  prt _ (Id i) = doc (showString i)

instance Print Exp where
  prt i e = case e of
    Eor exp1 resor exp2 -> prPrec i 0 (concatD [prt 0 exp1, prt 0 resor, prt 1 exp2])
    Eand exp1 resand exp2 -> prPrec i 1 (concatD [prt 1 exp1, prt 0 resand, prt 2 exp2])
    Eeq exp1 exp2 -> prPrec i 2 (concatD [prt 2 exp1, doc (showString "="), prt 3 exp2])
    Ene exp1 exp2 -> prPrec i 2 (concatD [prt 2 exp1, doc (showString "<>"), prt 3 exp2])
    Elt exp1 exp2 -> prPrec i 3 (concatD [prt 3 exp1, doc (showString "<"), prt 4 exp2])
    Egt exp1 exp2 -> prPrec i 3 (concatD [prt 3 exp1, doc (showString ">"), prt 4 exp2])
    Ele exp1 exp2 -> prPrec i 3 (concatD [prt 3 exp1, doc (showString "<="), prt 4 exp2])
    Ege exp1 exp2 -> prPrec i 3 (concatD [prt 3 exp1, doc (showString ">="), prt 4 exp2])
    EAdd exp1 exp2 -> prPrec i 4 (concatD [prt 4 exp1, doc (showString "+"), prt 5 exp2])
    ESub exp1 exp2 -> prPrec i 4 (concatD [prt 4 exp1, doc (showString "-"), prt 5 exp2])
    EMul exp1 exp2 -> prPrec i 5 (concatD [prt 5 exp1, doc (showString "*"), prt 6 exp2])
    EDiv exp1 exp2 -> prPrec i 5 (concatD [prt 5 exp1, doc (showString "/"), prt 6 exp2])
    EMod exp1 exp2 -> prPrec i 5 (concatD [prt 5 exp1, doc (showString "%"), prt 6 exp2])
    ENeg exp -> prPrec i 7 (concatD [doc (showString "-"), prt 6 exp])
    EFunc id exps -> prPrec i 8 (concatD [prt 0 id, doc (showString "("), prt 0 exps, doc (showString ")")])
    EVersion id n -> prPrec i 8 (concatD [prt 0 id, doc (showString "@"), prt 0 n])
    EArrayVar id1 id2 -> prPrec i 8 (concatD [prt 0 id1, doc (showString "."), prt 0 id2])
    EOption id exp -> prPrec i 8 (concatD [prt 0 id, doc (showString ":"), prt 0 exp])
    EAsId exp resas id -> prPrec i 9 (concatD [prt 8 exp, prt 0 resas, prt 0 id])
    EAsc exp resasc -> prPrec i 9 (concatD [prt 8 exp, prt 0 resasc])
    EDesc exp resdesc -> prPrec i 9 (concatD [prt 8 exp, prt 0 resdesc])
    EVar id -> prPrec i 10 (concatD [prt 0 id])
    EScheme schema -> prPrec i 10 (concatD [prt 0 schema])
    EString astring -> prPrec i 10 (concatD [prt 0 astring])
    EFalse resfalse -> prPrec i 10 (concatD [prt 0 resfalse])
    ETrue restrue -> prPrec i 10 (concatD [prt 0 restrue])
    ENull resnull -> prPrec i 10 (concatD [prt 0 resnull])
    EInt n -> prPrec i 10 (concatD [prt 0 n])
    EDouble adouble -> prPrec i 10 (concatD [prt 0 adouble])
    EWildcard -> prPrec i 10 (concatD [doc (showString "*")])
    EDefault -> prPrec i 10 (concatD [doc (showString "?")])
  prtList _ [] = concatD []
  prtList _ [x] = concatD [prt 0 x]
  prtList _ (x:xs) = concatD [prt 0 x, doc (showString ","), prt 0 xs]

instance Print [Exp] where
  prt = prtList

instance Print AFL where
  prt i e = case e of
    Queries querys -> prPrec i 0 (concatD [prt 0 querys])

instance Print [Query] where
  prt = prtList

instance Print Query where
  prt i e = case e of
    QueryNil -> prPrec i 0 (concatD [])
    QueryExp exp -> prPrec i 0 (concatD [prt 0 exp])
    QueryArray rescreate resarray id schema -> prPrec i 0 (concatD [prt 0 rescreate, prt 0 resarray, prt 0 id, prt 0 schema])
    QueryTemp rescreate restemp resarray id schema -> prPrec i 0 (concatD [prt 0 rescreate, prt 0 restemp, prt 0 resarray, prt 0 id, prt 0 schema])
  prtList _ [] = concatD []
  prtList _ (x:xs) = concatD [prt 0 x, doc (showString ";"), prt 0 xs]

instance Print Schema where
  prt i e = case e of
    Scheme attributes dimensions -> prPrec i 0 (concatD [doc (showString "<"), prt 0 attributes, doc (showString ">"), doc (showString "["), prt 0 dimensions, doc (showString "]")])

instance Print [Attribute] where
  prt = prtList

instance Print Attribute where
  prt i e = case e of
    Attrib id1 id2 nullableoption defaultoption compressionoption -> prPrec i 0 (concatD [prt 0 id1, doc (showString ":"), prt 0 id2, prt 0 nullableoption, prt 0 defaultoption, prt 0 compressionoption])
  prtList _ [x] = concatD [prt 0 x]
  prtList _ (x:xs) = concatD [prt 0 x, doc (showString ","), prt 0 xs]

instance Print NullableOption where
  prt i e = case e of
    NullabeOff -> prPrec i 0 (concatD [])
    NullableOn resnull -> prPrec i 0 (concatD [prt 0 resnull])
    NullableNot resnot resnull -> prPrec i 0 (concatD [prt 0 resnot, prt 0 resnull])

instance Print DefaultOption where
  prt i e = case e of
    DefaultOff -> prPrec i 0 (concatD [])
    DefaultOn resdefault exp -> prPrec i 0 (concatD [prt 0 resdefault, prt 6 exp])

instance Print CompressionOption where
  prt i e = case e of
    CompressionOff -> prPrec i 0 (concatD [])
    CompressionOn rescompression astring -> prPrec i 0 (concatD [prt 0 rescompression, prt 0 astring])

instance Print Dimensions where
  prt i e = case e of
    Dim dimension -> prPrec i 0 (concatD [prt 0 dimension])
    DimSemicolon dimension dimensions -> prPrec i 0 (concatD [prt 0 dimension, doc (showString ";"), prt 0 dimensions])
    DimComma dimension dimensions -> prPrec i 0 (concatD [prt 0 dimension, doc (showString ","), prt 0 dimensions])

instance Print Dimension where
  prt i e = case e of
    DimId id -> prPrec i 0 (concatD [prt 0 id])
    DimLoHi id exp1 exp2 -> prPrec i 0 (concatD [prt 0 id, doc (showString "="), prt 0 exp1, doc (showString ":"), prt 0 exp2])
    DimLoHiOverlap id exp1 exp2 exp3 -> prPrec i 0 (concatD [prt 0 id, doc (showString "="), prt 0 exp1, doc (showString ":"), prt 0 exp2, doc (showString ":"), prt 0 exp3])
    DimAll id exp1 exp2 exp3 exp4 -> prPrec i 0 (concatD [prt 0 id, doc (showString "="), prt 0 exp1, doc (showString ":"), prt 0 exp2, doc (showString ":"), prt 0 exp3, doc (showString ":"), prt 0 exp4])
    DimDeprecated id exp1 exp2 exp3 exp4 -> prPrec i 0 (concatD [prt 0 id, doc (showString "="), prt 0 exp1, doc (showString ":"), prt 0 exp2, doc (showString ","), prt 0 exp3, doc (showString ","), prt 0 exp4])