{-# LANGUAGE
DeriveDataTypeable
, CPP
, OverloadedStrings
, RecordWildCards
, TypeSynonymInstances
#-}
module Language.Bash.Word
(
Word
, Span(..)
, Parameter(..)
, ParamSubst(..)
, AltOp(..)
, LetterCaseOp(..)
, Direction(..)
, ProcessSubstOp(..)
, stringToWord
, unquote
) where
#if __GLASGOW_HASKELL__ >= 710
import Prelude hiding ((<>), Word)
#endif
import Data.Data (Data)
import Data.Typeable (Typeable)
import Text.PrettyPrint
import Language.Bash.Operator
import Language.Bash.Pretty
type Word = [Span]
data Span
= Char Char
| Escape Char
| Single Word
| Double Word
| ANSIC Word
| Locale Word
| Backquote Word
| ParamSubst ParamSubst
| ArithSubst String
| CommandSubst String
| ProcessSubst ProcessSubstOp String
deriving (Data, Eq, Read, Show, Typeable)
instance Pretty Span where
pretty (Char c) = char c
pretty (Escape c) = "\\" <> char c
pretty (Single w) = "\'" <> pretty w <> "\'"
pretty (Double w) = "\"" <> pretty w <> "\""
pretty (ANSIC w) = "$\'" <> pretty w <> "\'"
pretty (Locale w) = "$\"" <> pretty w <> "\""
pretty (Backquote w) = "`" <> pretty w <> "`"
pretty (ParamSubst s) = pretty s
pretty (ArithSubst s) = "$((" <> text s <> "))"
pretty (CommandSubst s) = "$(" <> text s <> ")"
pretty (ProcessSubst c s) = pretty c <> "(" <> text s <> ")"
prettyList = hcat . map pretty
data Parameter = Parameter String (Maybe Word)
deriving (Data, Eq, Read, Show, Typeable)
instance Pretty Parameter where
pretty (Parameter s sub) = text s <> subscript sub
where
subscript Nothing = empty
subscript (Just w) = "[" <> pretty w <> "]"
data ParamSubst
= Bare
{
parameter :: Parameter
}
| Brace
{
indirect :: Bool
, parameter :: Parameter
}
| Alt
{ indirect :: Bool
, parameter :: Parameter
, testNull :: Bool
, altOp :: AltOp
, altWord :: Word
}
| Substring
{ indirect :: Bool
, parameter :: Parameter
, subOffset :: Word
, subLength :: Word
}
| Prefix
{
prefix :: String
, modifier :: Char
}
| Indices
{ parameter :: Parameter
}
| Length
{ parameter :: Parameter
}
| Delete
{ indirect :: Bool
, parameter :: Parameter
, longest :: Bool
, deleteDirection :: Direction
, pattern :: Word
}
| Replace
{ indirect :: Bool
, parameter :: Parameter
, replaceAll :: Bool
, replaceDirection :: Maybe Direction
, pattern :: Word
, replacement :: Word
}
| LetterCase
{ indirect :: Bool
, parameter :: Parameter
, letterCaseOp :: LetterCaseOp
, convertAll :: Bool
, pattern :: Word
}
deriving (Data, Eq, Read, Show, Typeable)
prettyParameter :: Bool -> Parameter -> Doc -> Doc
prettyParameter bang param suffix =
"${" <> (if bang then "!" else empty) <> pretty param <> suffix <> "}"
twiceWhen :: Bool -> Doc -> Doc
twiceWhen False d = d
twiceWhen True d = d <> d
instance Pretty ParamSubst where
pretty Bare{..} = "$" <> pretty parameter
pretty Brace{..} = prettyParameter indirect parameter empty
pretty Alt{..} = prettyParameter indirect parameter $
(if testNull then ":" else empty) <>
pretty altOp <>
pretty altWord
pretty Substring{..} = prettyParameter indirect parameter $
":" <> pretty subOffset <>
(if null subLength then empty else ":") <> pretty subLength
pretty Prefix{..} = "${!" <> text prefix <> char modifier <> "}"
pretty Indices{..} = prettyParameter True parameter empty
pretty Length{..} = "${#" <> pretty parameter <> "}"
pretty Delete{..} = prettyParameter indirect parameter $
twiceWhen longest (pretty deleteDirection) <>
pretty pattern
pretty Replace{..} = prettyParameter indirect parameter $
"/" <>
(if replaceAll then "/" else empty) <>
pretty replaceDirection <>
pretty pattern <>
"/" <>
pretty replacement
pretty LetterCase{..} = prettyParameter indirect parameter $
twiceWhen convertAll (pretty letterCaseOp) <>
pretty pattern
data AltOp
= AltDefault
| AltAssign
| AltError
| AltReplace
deriving (Data, Eq, Ord, Read, Show, Typeable, Enum, Bounded)
instance Operator AltOp where
operatorTable = zip [minBound .. maxBound] ["-", "=", "?", "+"]
instance Pretty AltOp where
pretty = prettyOperator
data LetterCaseOp
= ToLower
| ToUpper
deriving (Data, Eq, Ord, Read, Show, Typeable, Enum, Bounded)
instance Operator LetterCaseOp where
operatorTable = zip [ToLower, ToUpper] [",", "^"]
instance Pretty LetterCaseOp where
pretty = prettyOperator
data Direction
= Front
| Back
deriving (Data, Eq, Ord, Read, Show, Typeable, Enum, Bounded)
instance Pretty Direction where
pretty Front = "#"
pretty Back = "%"
data ProcessSubstOp
= ProcessIn
| ProcessOut
deriving (Data, Eq, Ord, Read, Show, Typeable, Enum, Bounded)
instance Operator ProcessSubstOp where
operatorTable = zip [ProcessIn, ProcessOut] ["<", ">"]
instance Pretty ProcessSubstOp where
pretty = prettyOperator
stringToWord :: String -> Word
stringToWord = map Char
unquote :: Word -> String
unquote = render . unquoteWord
where
unquoteWord = hcat . map unquoteSpan
unquoteSpan (Char c) = char c
unquoteSpan (Escape c) = char c
unquoteSpan (Single w) = unquoteWord w
unquoteSpan (Double w) = unquoteWord w
unquoteSpan (ANSIC w) = unquoteWord w
unquoteSpan (Locale w) = unquoteWord w
unquoteSpan s = pretty s