{-# LANGUAGE DeriveDataTypeable, OverloadedStrings, RecordWildCards, CPP #-}
module Language.Bash.Syntax
    (
      
      Command(..)
    , ShellCommand(..)
    , WordList(..)
    , CaseClause(..)
    , CaseTerm(..)
      
    , Redir(..)
    , IODesc(..)
    , RedirOp(..)
    , HeredocOp(..)
      
    , List(..)
    , Statement(..)
    , ListTerm(..)
    , AndOr(..)
    , Pipeline(..)
      
    , Assign(..)
    , AssignOp(..)
    , RValue(..)
    ) where
#if __GLASGOW_HASKELL__ >= 710
import Prelude hiding ((<>), Word)
#endif
import Data.Data        (Data)
import Data.Typeable    (Typeable)
import Text.PrettyPrint
import Language.Bash.Cond     (CondExpr)
import Language.Bash.Operator
import Language.Bash.Pretty
import Language.Bash.Word
indent :: Pretty a => a -> Doc
indent = nest 4 . pretty
doDone :: Pretty a => a -> Doc
doDone a = "do" $+$ indent a $+$ "done"
data Command = Command ShellCommand [Redir]
    deriving (Data, Eq, Read, Show, Typeable)
instance Pretty Command where
    pretty (Command c rs) = pretty c <+> pretty rs
data ShellCommand
      
    = SimpleCommand [Assign] [Word]
      
      
    | AssignBuiltin Word [Either Assign Word]
      
    | FunctionDef String List
      
    | Coproc String Command
      
    | Subshell List
      
    | Group List
      
    | Arith String
      
    | Cond (CondExpr Word)
      
      
    | For String WordList List
      
    | ArithFor String List
      
      
    | Select String WordList List
      
    | Case Word [CaseClause]
      
      
    | If List List (Maybe List)
      
    | Until List List
      
    | While List List
    deriving (Data, Eq, Read, Show, Typeable)
instance Pretty ShellCommand where
    pretty (SimpleCommand as ws)  = pretty as <+> pretty ws
    pretty (AssignBuiltin w args) = pretty w <+> pretty args
    pretty (FunctionDef name l) =
        text name <+> "()" $+$ pretty (Group l)
    pretty (Coproc name c) =
        "coproc" <+> text name <+> pretty c
    pretty (Subshell l) =
        "(" <+> pretty l <+> ")"
    pretty (Group l) =
        "{" $+$ indent l $+$ "}"
    pretty (Arith s) =
        "((" <> text s <> "))"
    pretty (Cond e) =
        "[[" <+> pretty e <+> "]]"
    pretty (For w ws l) =
        "for" <+> pretty w <+> pretty ws <> ";" $+$ doDone l
    pretty (ArithFor s l) =
        "for" <+> "((" <> text s <> "))" $+$ doDone l
    pretty (Select w ws l) =
        "select" <+> pretty w <+> pretty ws <> ";" $+$ doDone l
    pretty (Case w cs) =
        "case" <+> pretty w <+> "in" $+$ (vcat $ map indent cs) $+$ "esac"
    pretty (If p t f) =
        "if" <+> pretty p <+> "then" $+$ indent t $+$
        pretty (fmap (\l -> "else" $+$ indent l) f) $+$
        "fi"
    pretty (Until p l) =
        "until" <+> pretty p <+> doDone l
    pretty (While p l) =
        "while" <+> pretty p <+> doDone l
data WordList
    = Args
    | WordList [Word]
    deriving (Data, Eq, Read, Show, Typeable)
instance Pretty WordList where
    pretty Args          = empty
    pretty (WordList ws) = "in" <+> pretty ws
data CaseClause = CaseClause [Word] List CaseTerm
    deriving (Data, Eq, Read, Show, Typeable)
instance Pretty CaseClause where
    pretty (CaseClause ps l term) =
        hcat (punctuate " | " (map pretty ps)) <> ")" $+$
        indent l $+$
        (indent $ pretty term)
data CaseTerm
    = Break        
    | FallThrough  
    | Continue     
    deriving (Data, Eq, Ord, Read, Show, Typeable, Bounded, Enum)
instance Operator CaseTerm where
    operatorTable = zip [minBound .. maxBound] [";;", ";&", ";;&"]
instance Pretty CaseTerm where
    pretty = prettyOperator
data Redir
      
    = Redir
        { 
          redirDesc   :: Maybe IODesc
          
        , redirOp     :: RedirOp
          
        , redirTarget :: Word
        }
      
    | Heredoc
        { 
          heredocOp          :: HeredocOp
          
        , heredocDelim       :: String
          
        , heredocDelimQuoted :: Bool
          
          
          
        , hereDocument       :: Word
        }
    deriving (Data, Eq, Read, Show, Typeable)
instance Pretty Redir where
    pretty Redir{..} =
        pretty redirDesc <> pretty redirOp <> pretty redirTarget
    pretty Heredoc{..} =
        pretty heredocOp <>
        text (if heredocDelimQuoted
              then "'" ++ heredocDelim ++ "'"
              else heredocDelim) <> "\n" <>
        pretty hereDocument <> text heredocDelim <> "\n"
    prettyList = foldr f empty
      where
        f a@Redir{}   b = pretty a <+> b
        f a@Heredoc{} b = pretty a <> b
data IODesc
      
    = IONumber Int
      
    | IOVar String
    deriving (Data, Eq, Read, Show, Typeable)
instance Pretty IODesc where
    pretty (IONumber n) = int n
    pretty (IOVar n)    = "{" <> text n <> "}"
data RedirOp
    = In          
    | Out         
    | OutOr       
    | Append      
    | AndOut      
    | AndAppend   
    | HereString  
    | InAnd       
    | OutAnd      
    | InOut       
    deriving (Data, Eq, Ord, Read, Show, Typeable, Enum, Bounded)
instance Operator RedirOp where
    operatorTable = zip [minBound .. maxBound]
        ["<", ">", ">|", ">>", "&>", "&>>", "<<<", "<&", ">&", "<>"]
instance Pretty RedirOp where
    pretty = prettyOperator
data HeredocOp
    = Here       
    | HereStrip  
    deriving (Data, Eq, Ord, Read, Show, Typeable, Enum, Bounded)
instance Operator HeredocOp where
    operatorTable = zip [Here, HereStrip] ["<<", "<<-"]
instance Pretty HeredocOp where
    pretty = prettyOperator
newtype List = List [Statement]
    deriving (Data, Eq, Read, Show, Typeable)
instance Pretty List where
    pretty (List as) = pretty as
data Statement = Statement AndOr ListTerm
    deriving (Data, Eq, Read, Show, Typeable)
instance Pretty Statement where
    pretty (Statement l Sequential)   = pretty l <> ";"
    pretty (Statement l Asynchronous) = pretty l <+> "&"
    prettyList = foldr f empty
      where
        f a@(Statement _ Sequential)   b = pretty a $+$ b
        f a@(Statement _ Asynchronous) b = pretty a <+> b
data ListTerm
    = Sequential    
    | Asynchronous  
    deriving (Data, Eq, Ord, Read, Show, Typeable, Bounded, Enum)
instance Operator ListTerm where
    operatorTable =
        [ (Sequential  , ";" )
        , (Sequential  , "\n")
        , (Asynchronous, "&" )
        ]
instance Pretty ListTerm where
    pretty = prettyOperator
data AndOr
      
    = Last Pipeline
      
    | And Pipeline AndOr
      
    | Or Pipeline AndOr
    deriving (Data, Eq, Read, Show, Typeable)
instance Pretty AndOr where
    pretty (Last p)  = pretty p
    pretty (And p a) = pretty p <+> "&&" <+> pretty a
    pretty (Or p a)  = pretty p <+> "||" <+> pretty a
data Pipeline = Pipeline
    { 
      timed      :: Bool
      
    , timedPosix :: Bool
      
    , inverted   :: Bool
      
      
      
    , commands   :: [Command]
    } deriving (Data, Eq, Read, Show, Typeable)
instance Pretty Pipeline where
    pretty Pipeline{..} =
        (if timed      then "time" else empty) <+>
        (if timedPosix then "-p"   else empty) <+>
        (if inverted   then "!"    else empty) <+>
        hcat (punctuate " | " (map pretty commands))
data Assign = Assign Parameter AssignOp RValue
    deriving (Data, Eq, Read, Show, Typeable)
instance Pretty Assign where
    pretty (Assign lhs op rhs) = pretty lhs <> pretty op <> pretty rhs
data AssignOp
    = Equals      
    | PlusEquals  
    deriving (Data, Eq, Ord, Read, Show, Typeable, Bounded, Enum)
instance Operator AssignOp where
    operatorTable = zip [Equals, PlusEquals] ["=", "+="]
instance Pretty AssignOp where
    pretty = prettyOperator
data RValue
      
    = RValue Word
      
    | RArray [(Maybe Word, Word)]
    deriving (Data, Eq, Read, Show, Typeable)
instance Pretty RValue where
    pretty (RValue w)  = pretty w
    pretty (RArray rs) = "(" <> hsep (map f rs) <> ")"
      where
        f (Nothing , w) = pretty w
        f (Just sub, w) = "[" <> pretty sub <> "]=" <> pretty w