{-# LANGUAGE DeriveDataTypeable #-}

module CabalCargs.Formatting
   ( Formatting(..)
   ) where

import Data.Data (Data, Typeable)
import System.Console.CmdArgs.Default (Default, def)


-- | How the fields from the cabal file should be printed out.
data Formatting = Ghc       -- ^ as ghc compatible arguments
                | Hdevtools -- ^ as hdevtools compatible arguments
                | Pure      -- ^ the field values are printed as present in the cabal file
                deriving (Typeable Formatting
Typeable Formatting =>
(forall (c :: * -> *).
 (forall d b. Data d => c (d -> b) -> d -> c b)
 -> (forall g. g -> c g) -> Formatting -> c Formatting)
-> (forall (c :: * -> *).
    (forall b r. Data b => c (b -> r) -> c r)
    -> (forall r. r -> c r) -> Constr -> c Formatting)
-> (Formatting -> Constr)
-> (Formatting -> DataType)
-> (forall (t :: * -> *) (c :: * -> *).
    Typeable t =>
    (forall d. Data d => c (t d)) -> Maybe (c Formatting))
-> (forall (t :: * -> * -> *) (c :: * -> *).
    Typeable t =>
    (forall d e. (Data d, Data e) => c (t d e))
    -> Maybe (c Formatting))
-> ((forall b. Data b => b -> b) -> Formatting -> Formatting)
-> (forall r r'.
    (r -> r' -> r)
    -> r -> (forall d. Data d => d -> r') -> Formatting -> r)
-> (forall r r'.
    (r' -> r -> r)
    -> r -> (forall d. Data d => d -> r') -> Formatting -> r)
-> (forall u. (forall d. Data d => d -> u) -> Formatting -> [u])
-> (forall u.
    Int -> (forall d. Data d => d -> u) -> Formatting -> u)
-> (forall (m :: * -> *).
    Monad m =>
    (forall d. Data d => d -> m d) -> Formatting -> m Formatting)
-> (forall (m :: * -> *).
    MonadPlus m =>
    (forall d. Data d => d -> m d) -> Formatting -> m Formatting)
-> (forall (m :: * -> *).
    MonadPlus m =>
    (forall d. Data d => d -> m d) -> Formatting -> m Formatting)
-> Data Formatting
Formatting -> Constr
Formatting -> DataType
(forall b. Data b => b -> b) -> Formatting -> Formatting
forall a.
Typeable a =>
(forall (c :: * -> *).
 (forall d b. Data d => c (d -> b) -> d -> c b)
 -> (forall g. g -> c g) -> a -> c a)
-> (forall (c :: * -> *).
    (forall b r. Data b => c (b -> r) -> c r)
    -> (forall r. r -> c r) -> Constr -> c a)
-> (a -> Constr)
-> (a -> DataType)
-> (forall (t :: * -> *) (c :: * -> *).
    Typeable t =>
    (forall d. Data d => c (t d)) -> Maybe (c a))
-> (forall (t :: * -> * -> *) (c :: * -> *).
    Typeable t =>
    (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c a))
-> ((forall b. Data b => b -> b) -> a -> a)
-> (forall r r'.
    (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> a -> r)
-> (forall r r'.
    (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> a -> r)
-> (forall u. (forall d. Data d => d -> u) -> a -> [u])
-> (forall u. Int -> (forall d. Data d => d -> u) -> a -> u)
-> (forall (m :: * -> *).
    Monad m =>
    (forall d. Data d => d -> m d) -> a -> m a)
-> (forall (m :: * -> *).
    MonadPlus m =>
    (forall d. Data d => d -> m d) -> a -> m a)
-> (forall (m :: * -> *).
    MonadPlus m =>
    (forall d. Data d => d -> m d) -> a -> m a)
-> Data a
forall u. Int -> (forall d. Data d => d -> u) -> Formatting -> u
forall u. (forall d. Data d => d -> u) -> Formatting -> [u]
forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> Formatting -> r
forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> Formatting -> r
forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> Formatting -> m Formatting
forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> Formatting -> m Formatting
forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c Formatting
forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> Formatting -> c Formatting
forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c Formatting)
forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Formatting)
$cgfoldl :: forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> Formatting -> c Formatting
gfoldl :: forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> Formatting -> c Formatting
$cgunfold :: forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c Formatting
gunfold :: forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c Formatting
$ctoConstr :: Formatting -> Constr
toConstr :: Formatting -> Constr
$cdataTypeOf :: Formatting -> DataType
dataTypeOf :: Formatting -> DataType
$cdataCast1 :: forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c Formatting)
dataCast1 :: forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c Formatting)
$cdataCast2 :: forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Formatting)
dataCast2 :: forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Formatting)
$cgmapT :: (forall b. Data b => b -> b) -> Formatting -> Formatting
gmapT :: (forall b. Data b => b -> b) -> Formatting -> Formatting
$cgmapQl :: forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> Formatting -> r
gmapQl :: forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> Formatting -> r
$cgmapQr :: forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> Formatting -> r
gmapQr :: forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> Formatting -> r
$cgmapQ :: forall u. (forall d. Data d => d -> u) -> Formatting -> [u]
gmapQ :: forall u. (forall d. Data d => d -> u) -> Formatting -> [u]
$cgmapQi :: forall u. Int -> (forall d. Data d => d -> u) -> Formatting -> u
gmapQi :: forall u. Int -> (forall d. Data d => d -> u) -> Formatting -> u
$cgmapM :: forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> Formatting -> m Formatting
gmapM :: forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> Formatting -> m Formatting
$cgmapMp :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> Formatting -> m Formatting
gmapMp :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> Formatting -> m Formatting
$cgmapMo :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> Formatting -> m Formatting
gmapMo :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> Formatting -> m Formatting
Data, Typeable, Int -> Formatting -> ShowS
[Formatting] -> ShowS
Formatting -> String
(Int -> Formatting -> ShowS)
-> (Formatting -> String)
-> ([Formatting] -> ShowS)
-> Show Formatting
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> Formatting -> ShowS
showsPrec :: Int -> Formatting -> ShowS
$cshow :: Formatting -> String
show :: Formatting -> String
$cshowList :: [Formatting] -> ShowS
showList :: [Formatting] -> ShowS
Show, Formatting -> Formatting -> Bool
(Formatting -> Formatting -> Bool)
-> (Formatting -> Formatting -> Bool) -> Eq Formatting
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: Formatting -> Formatting -> Bool
== :: Formatting -> Formatting -> Bool
$c/= :: Formatting -> Formatting -> Bool
/= :: Formatting -> Formatting -> Bool
Eq)


instance Default Formatting where
   def :: Formatting
def = Formatting
Ghc