Safe Haskell | None |
---|---|
Language | Haskell2010 |
Turtle
Contents
Description
See Turtle.Tutorial to learn how to use this library or Turtle.Prelude for a quick-start guide.
Here is the recommended way to import this library:
{-# LANGUAGE OverloadedStrings #-} import Turtle import Prelude hiding (FilePath)
This module re-exports the rest of the library and also re-exports useful
modules from base
:
Turtle.Format provides type-safe string formatting
Turtle.Pattern provides Pattern
s, which are like more powerful regular
expressions
Turtle.Shell provides a Shell
abstraction for building streaming,
exception-safe pipelines
Turtle.Prelude provides a library of Unix-like utilities to get you started with basic shell-like programming within Haskell
Control.Applicative provides two classes:
Applicative
, which works withFold
,Pattern
,Managed
, andShell
Alternative
, which works withPattern
andShell
Control.Monad provides two classes:
Control.Monad.IO.Class provides one class:
Data.Monoid provides one class:
Control.Monad.Managed.Safe provides Managed
resources
Filesystem.Path.CurrentOS provides FilePath
-manipulation utilities
Additionally, you might also want to import the following modules qualified:
- Options.Applicative from
optparse-applicative
for command-line option parsing - Control.Foldl (for predefined folds)
- Control.Foldl.Text (for
Text
-specific folds) - Data.Text (for
Text
-manipulation utilities) - Data.Text.IO (for reading and writing
Text
) - Filesystem.Path.CurrentOS (for the remaining
FilePath
utilities)
Synopsis
- module Turtle.Format
- module Turtle.Pattern
- module Turtle.Options
- module Turtle.Shell
- module Turtle.Line
- module Turtle.Prelude
- class Functor f => Applicative (f :: Type -> Type) where
- (<$>) :: Functor f => (a -> b) -> f a -> f b
- class Applicative f => Alternative (f :: Type -> Type) where
- optional :: Alternative f => f a -> f (Maybe a)
- guard :: Alternative f => Bool -> f ()
- join :: Monad m => m (m a) -> m a
- when :: Applicative f => Bool -> f () -> f ()
- class (Alternative m, Monad m) => MonadPlus (m :: Type -> Type) where
- msum :: (Foldable t, MonadPlus m) => t (m a) -> m a
- (<=<) :: Monad m => (b -> m c) -> (a -> m b) -> a -> m c
- (>=>) :: Monad m => (a -> m b) -> (b -> m c) -> a -> m c
- forever :: Applicative f => f a -> f b
- mfilter :: MonadPlus m => (a -> Bool) -> m a -> m a
- replicateM_ :: Applicative m => Int -> m a -> m ()
- unless :: Applicative f => Bool -> f () -> f ()
- void :: Functor f => f a -> f ()
- class Monad m => MonadIO (m :: Type -> Type) where
- liftIO :: IO a -> m a
- (<>) :: Semigroup a => a -> a -> a
- class Semigroup a => Monoid a where
- managed :: (forall r. (a -> IO r) -> IO r) -> Managed a
- runManaged :: Managed () -> IO ()
- with :: Managed a -> (a -> IO r) -> IO r
- data Managed a
- (<.>) :: FilePath -> Text -> FilePath
- (</>) :: FilePath -> FilePath -> FilePath
- absolute :: FilePath -> Bool
- basename :: FilePath -> FilePath
- collapse :: FilePath -> FilePath
- commonPrefix :: [FilePath] -> FilePath
- directory :: FilePath -> FilePath
- dirname :: FilePath -> FilePath
- dropExtension :: FilePath -> FilePath
- extension :: FilePath -> Maybe Text
- filename :: FilePath -> FilePath
- hasExtension :: FilePath -> Text -> Bool
- parent :: FilePath -> FilePath
- relative :: FilePath -> Bool
- root :: FilePath -> FilePath
- splitDirectories :: FilePath -> [FilePath]
- splitExtension :: FilePath -> (FilePath, Maybe Text)
- stripPrefix :: FilePath -> FilePath -> Maybe FilePath
- decodeString :: String -> FilePath
- encodeString :: FilePath -> String
- fromText :: Text -> FilePath
- toText :: FilePath -> Either Text Text
- data FilePath
- data Fold a b = Fold (x -> a -> x) x (x -> b)
- data FoldM (m :: Type -> Type) a b = FoldM (x -> a -> m x) (m x) (x -> m b)
- data Text
- data UTCTime
- data NominalDiffTime
- data Handle
- data ExitCode
- = ExitSuccess
- | ExitFailure Int
- class IsString a where
- fromString :: String -> a
- (&) :: a -> (a -> b) -> b
- (<&>) :: Functor f => f a -> (a -> b) -> f b
Modules
module Turtle.Format
module Turtle.Pattern
module Turtle.Options
module Turtle.Shell
module Turtle.Line
module Turtle.Prelude
class Functor f => Applicative (f :: Type -> Type) where #
Instances
Applicative [] | |
Applicative Maybe | |
Applicative IO | |
Applicative Par1 | |
Applicative Q | |
Applicative P | |
Applicative ReadPrec | |
Applicative NonEmpty | |
Applicative ReadP | |
Applicative Identity | |
Applicative First | |
Applicative Last | |
Applicative Dual | |
Applicative Product | |
Applicative Sum | |
Applicative Down | |
Applicative Optional | |
Applicative ZipList | |
Applicative Parser | |
Applicative ParserResult | |
Defined in Options.Applicative.Types | |
Applicative ReadM | |
Applicative ParserM | |
Applicative Pattern Source # | |
Applicative STM | |
Applicative Managed | |
Applicative Seq | |
Applicative Id | |
Applicative Box | |
Applicative Shell Source # | |
Applicative Put | |
Applicative Complex | |
Applicative First | |
Applicative Last | |
Applicative Max | |
Applicative Min | |
Applicative Concurrently | |
Defined in Control.Concurrent.Async | |
Applicative Option | |
Applicative Tree | |
Applicative Array | |
Applicative SmallArray | |
Defined in Data.Primitive.SmallArray | |
Applicative Stream | |
Applicative (Either e) | |
Applicative (U1 :: Type -> Type) | |
Monoid a => Applicative ((,) a) | |
Applicative (Proxy :: Type -> Type) | |
Monad m => Applicative (WrappedMonad m) | |
Defined in Control.Applicative Methods pure :: a -> WrappedMonad m a # (<*>) :: WrappedMonad m (a -> b) -> WrappedMonad m a -> WrappedMonad m b # liftA2 :: (a -> b -> c) -> WrappedMonad m a -> WrappedMonad m b -> WrappedMonad m c # (*>) :: WrappedMonad m a -> WrappedMonad m b -> WrappedMonad m b # (<*) :: WrappedMonad m a -> WrappedMonad m b -> WrappedMonad m a # | |
(Functor m, Monad m) => Applicative (MaybeT m) | |
Applicative (Fold a) | |
Arrow a => Applicative (ArrowMonad a) | |
Defined in Control.Arrow Methods pure :: a0 -> ArrowMonad a a0 # (<*>) :: ArrowMonad a (a0 -> b) -> ArrowMonad a a0 -> ArrowMonad a b # liftA2 :: (a0 -> b -> c) -> ArrowMonad a a0 -> ArrowMonad a b -> ArrowMonad a c # (*>) :: ArrowMonad a a0 -> ArrowMonad a b -> ArrowMonad a b # (<*) :: ArrowMonad a a0 -> ArrowMonad a b -> ArrowMonad a a0 # | |
Applicative f => Applicative (Rec1 f) | |
Monoid m => Applicative (Const m :: Type -> Type) | |
Applicative f => Applicative (Ap f) | |
Applicative f => Applicative (Alt f) | |
Arrow a => Applicative (WrappedArrow a b) | |
Defined in Control.Applicative Methods pure :: a0 -> WrappedArrow a b a0 # (<*>) :: WrappedArrow a b (a0 -> b0) -> WrappedArrow a b a0 -> WrappedArrow a b b0 # liftA2 :: (a0 -> b0 -> c) -> WrappedArrow a b a0 -> WrappedArrow a b b0 -> WrappedArrow a b c # (*>) :: WrappedArrow a b a0 -> WrappedArrow a b b0 -> WrappedArrow a b b0 # (<*) :: WrappedArrow a b a0 -> WrappedArrow a b b0 -> WrappedArrow a b a0 # | |
(Functor m, Monad m) => Applicative (ExceptT e m) | |
Defined in Control.Monad.Trans.Except | |
Applicative m => Applicative (ReaderT r m) | |
Defined in Control.Monad.Trans.Reader | |
(Functor m, Monad m) => Applicative (StateT s m) | |
Defined in Control.Monad.Trans.State.Lazy | |
(Functor m, Monad m) => Applicative (ErrorT e m) | |
Defined in Control.Monad.Trans.Error | |
Applicative m => Applicative (IdentityT m) | |
Defined in Control.Monad.Trans.Identity | |
(Functor m, Monad m) => Applicative (StateT s m) | |
Defined in Control.Monad.Trans.State.Strict | |
(Monoid w, Applicative m) => Applicative (WriterT w m) | |
Defined in Control.Monad.Trans.Writer.Lazy | |
(Monoid w, Applicative m) => Applicative (WriterT w m) | |
Defined in Control.Monad.Trans.Writer.Strict | |
Applicative m => Applicative (FoldM m a) | |
(Applicative f, Monad f) => Applicative (WhenMissing f x) | |
Defined in Data.IntMap.Internal Methods pure :: a -> WhenMissing f x a # (<*>) :: WhenMissing f x (a -> b) -> WhenMissing f x a -> WhenMissing f x b # liftA2 :: (a -> b -> c) -> WhenMissing f x a -> WhenMissing f x b -> WhenMissing f x c # (*>) :: WhenMissing f x a -> WhenMissing f x b -> WhenMissing f x b # (<*) :: WhenMissing f x a -> WhenMissing f x b -> WhenMissing f x a # | |
Biapplicative p => Applicative (Join p) | |
Applicative (Tagged s) | |
Applicative (Mag a b) | |
Applicative ((->) a :: Type -> Type) | |
Monoid c => Applicative (K1 i c :: Type -> Type) | |
(Applicative f, Applicative g) => Applicative (f :*: g) | |
Applicative (ContT r m) | |
Defined in Control.Monad.Trans.Cont | |
(Applicative f, Applicative g) => Applicative (Product f g) | |
Defined in Data.Functor.Product | |
(Monad f, Applicative f) => Applicative (WhenMatched f x y) | |
Defined in Data.IntMap.Internal Methods pure :: a -> WhenMatched f x y a # (<*>) :: WhenMatched f x y (a -> b) -> WhenMatched f x y a -> WhenMatched f x y b # liftA2 :: (a -> b -> c) -> WhenMatched f x y a -> WhenMatched f x y b -> WhenMatched f x y c # (*>) :: WhenMatched f x y a -> WhenMatched f x y b -> WhenMatched f x y b # (<*) :: WhenMatched f x y a -> WhenMatched f x y b -> WhenMatched f x y a # | |
(Applicative f, Monad f) => Applicative (WhenMissing f k x) | |
Defined in Data.Map.Internal Methods pure :: a -> WhenMissing f k x a # (<*>) :: WhenMissing f k x (a -> b) -> WhenMissing f k x a -> WhenMissing f k x b # liftA2 :: (a -> b -> c) -> WhenMissing f k x a -> WhenMissing f k x b -> WhenMissing f k x c # (*>) :: WhenMissing f k x a -> WhenMissing f k x b -> WhenMissing f k x b # (<*) :: WhenMissing f k x a -> WhenMissing f k x b -> WhenMissing f k x a # | |
Applicative f => Applicative (M1 i c f) | |
(Applicative f, Applicative g) => Applicative (f :.: g) | |
(Monoid w, Functor m, Monad m) => Applicative (RWST r w s m) | |
Defined in Control.Monad.Trans.RWS.Strict | |
(Monoid w, Functor m, Monad m) => Applicative (RWST r w s m) | |
Defined in Control.Monad.Trans.RWS.Lazy | |
(Applicative f, Applicative g) => Applicative (Compose f g) | |
Defined in Data.Functor.Compose | |
(Monad f, Applicative f) => Applicative (WhenMatched f k x y) | |
Defined in Data.Map.Internal Methods pure :: a -> WhenMatched f k x y a # (<*>) :: WhenMatched f k x y (a -> b) -> WhenMatched f k x y a -> WhenMatched f k x y b # liftA2 :: (a -> b -> c) -> WhenMatched f k x y a -> WhenMatched f k x y b -> WhenMatched f k x y c # (*>) :: WhenMatched f k x y a -> WhenMatched f k x y b -> WhenMatched f k x y b # (<*) :: WhenMatched f k x y a -> WhenMatched f k x y b -> WhenMatched f k x y a # |
class Applicative f => Alternative (f :: Type -> Type) where #
Instances
Alternative [] | |
Alternative Maybe | |
Alternative IO | |
Alternative P | |
Alternative ReadPrec | |
Alternative ReadP | |
Alternative Optional | |
Alternative ZipList | |
Alternative Parser | |
Alternative ReadM | |
Alternative Pattern Source # | |
Alternative STM | |
Alternative Seq | |
Alternative Shell Source # | |
Alternative Concurrently | |
Alternative Option | |
Alternative Array | |
Alternative SmallArray | |
Alternative (U1 :: Type -> Type) | |
Alternative (Proxy :: Type -> Type) | |
MonadPlus m => Alternative (WrappedMonad m) | |
(Functor m, Monad m) => Alternative (MaybeT m) | |
ArrowPlus a => Alternative (ArrowMonad a) | |
Alternative f => Alternative (Rec1 f) | |
Alternative f => Alternative (Ap f) | |
Alternative f => Alternative (Alt f) | |
(ArrowZero a, ArrowPlus a) => Alternative (WrappedArrow a b) | |
(Functor m, Monad m, Monoid e) => Alternative (ExceptT e m) | |
Alternative m => Alternative (ReaderT r m) | |
(Functor m, MonadPlus m) => Alternative (StateT s m) | |
(Functor m, Monad m, Error e) => Alternative (ErrorT e m) | |
Alternative m => Alternative (IdentityT m) | |
(Functor m, MonadPlus m) => Alternative (StateT s m) | |
(Monoid w, Alternative m) => Alternative (WriterT w m) | |
(Monoid w, Alternative m) => Alternative (WriterT w m) | |
(Alternative f, Alternative g) => Alternative (f :*: g) | |
(Alternative f, Alternative g) => Alternative (Product f g) | |
Alternative f => Alternative (M1 i c f) | |
(Alternative f, Applicative g) => Alternative (f :.: g) | |
(Monoid w, Functor m, MonadPlus m) => Alternative (RWST r w s m) | |
(Monoid w, Functor m, MonadPlus m) => Alternative (RWST r w s m) | |
(Alternative f, Applicative g) => Alternative (Compose f g) | |
optional :: Alternative f => f a -> f (Maybe a) #
guard :: Alternative f => Bool -> f () #
when :: Applicative f => Bool -> f () -> f () #
class (Alternative m, Monad m) => MonadPlus (m :: Type -> Type) where #
Minimal complete definition
Nothing
Instances
forever :: Applicative f => f a -> f b #
replicateM_ :: Applicative m => Int -> m a -> m () #
unless :: Applicative f => Bool -> f () -> f () #
class Monad m => MonadIO (m :: Type -> Type) where #
Instances
class Semigroup a => Monoid a where #
Minimal complete definition
Instances
Monoid Ordering | |
Monoid () | |
Monoid ByteString | |
Monoid Builder | |
Monoid Line Source # | |
Monoid All | |
Monoid Any | |
Monoid PrefsMod | |
Monoid Completer | |
Monoid ParseError | |
Monoid Doc | |
Monoid ByteArray | |
Monoid IntSet | |
Monoid Doc | |
Monoid [a] | |
Semigroup a => Monoid (Maybe a) | |
Monoid a => Monoid (IO a) | |
Monoid p => Monoid (Par1 p) | |
Monoid a => Monoid (Identity a) | |
Monoid (First a) | |
Monoid (Last a) | |
Monoid a => Monoid (Dual a) | |
Monoid (Endo a) | |
Num a => Monoid (Product a) | |
Num a => Monoid (Sum a) | |
Monoid a => Monoid (Down a) | |
Monoid a => Monoid (Optional a) | |
Monoid (InfoMod a) | |
Num a => Monoid (AlphaColour a) | |
Num a => Monoid (Colour a) | |
Monoid (DefaultProp a) | |
Monoid a => Monoid (Pattern a) Source # | |
Monoid a => Monoid (Managed a) | |
(Hashable a, Eq a) => Monoid (HashSet a) | |
Monoid (Seq a) | |
Ord a => Monoid (Set a) | |
Monoid a => Monoid (Shell a) Source # | |
(Ord a, Bounded a) => Monoid (Max a) | |
(Ord a, Bounded a) => Monoid (Min a) | |
Monoid m => Monoid (WrappedMonoid m) | |
Prim a => Monoid (Vector a) | |
(Semigroup a, Monoid a) => Monoid (Concurrently a) | |
Semigroup a => Monoid (Option a) | |
Monoid (IntMap a) | |
Monoid (MergeSet a) | |
Monoid (Doc a) | |
Monoid (Array a) | |
Monoid (PrimArray a) | |
Monoid (SmallArray a) | |
Monoid b => Monoid (a -> b) | |
Monoid (U1 p) | |
(Monoid a, Monoid b) => Monoid (a, b) | |
Monoid (Proxy s) | |
Monoid (Mod f a) | |
Monad m => Monoid (EndoM m a) | |
Monoid b => Monoid (Fold a b) | |
Ord k => Monoid (Map k v) | |
(Eq k, Hashable k) => Monoid (HashMap k v) | |
Monoid (f p) => Monoid (Rec1 f p) | |
(Monoid a, Monoid b, Monoid c) => Monoid (a, b, c) | |
Monoid a => Monoid (Const a b) | |
(Applicative f, Monoid a) => Monoid (Ap f a) | |
Alternative f => Monoid (Alt f a) | |
(Monoid b, Monad m) => Monoid (FoldM m a b) | |
(Semigroup a, Monoid a) => Monoid (Tagged s a) | |
Monoid c => Monoid (K1 i c p) | |
(Monoid (f p), Monoid (g p)) => Monoid ((f :*: g) p) | |
(Monoid a, Monoid b, Monoid c, Monoid d) => Monoid (a, b, c, d) | |
Monoid (f p) => Monoid (M1 i c f p) | |
Monoid (f (g p)) => Monoid ((f :.: g) p) | |
(Monoid a, Monoid b, Monoid c, Monoid d, Monoid e) => Monoid (a, b, c, d, e) | |
runManaged :: Managed () -> IO () #
Instances
Monad Managed | |
Functor Managed | |
MonadFail Managed | |
Defined in Control.Monad.Managed | |
Applicative Managed | |
MonadIO Managed | |
Defined in Control.Monad.Managed | |
MonadManaged Managed | |
Defined in Control.Monad.Managed | |
Floating a => Floating (Managed a) | |
Defined in Control.Monad.Managed Methods sqrt :: Managed a -> Managed a (**) :: Managed a -> Managed a -> Managed a logBase :: Managed a -> Managed a -> Managed a asin :: Managed a -> Managed a acos :: Managed a -> Managed a atan :: Managed a -> Managed a sinh :: Managed a -> Managed a cosh :: Managed a -> Managed a tanh :: Managed a -> Managed a asinh :: Managed a -> Managed a acosh :: Managed a -> Managed a atanh :: Managed a -> Managed a log1p :: Managed a -> Managed a expm1 :: Managed a -> Managed a | |
Fractional a => Fractional (Managed a) | |
Defined in Control.Monad.Managed | |
Num a => Num (Managed a) | |
Semigroup a => Semigroup (Managed a) | |
Monoid a => Monoid (Managed a) | |
commonPrefix :: [FilePath] -> FilePath #
dropExtension :: FilePath -> FilePath #
hasExtension :: FilePath -> Text -> Bool #
splitDirectories :: FilePath -> [FilePath] #
splitExtension :: FilePath -> (FilePath, Maybe Text) #
stripPrefix :: FilePath -> FilePath -> Maybe FilePath #
decodeString :: String -> FilePath #
encodeString :: FilePath -> String #
Instances
Eq FilePath | |
Data FilePath | |
Defined in Filesystem.Path.Internal Methods gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> FilePath -> c FilePath gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c FilePath toConstr :: FilePath -> Constr dataTypeOf :: FilePath -> DataType dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c FilePath) dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c FilePath) gmapT :: (forall b. Data b => b -> b) -> FilePath -> FilePath gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> FilePath -> r gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> FilePath -> r gmapQ :: (forall d. Data d => d -> u) -> FilePath -> [u] gmapQi :: Int -> (forall d. Data d => d -> u) -> FilePath -> u gmapM :: Monad m => (forall d. Data d => d -> m d) -> FilePath -> m FilePath gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> FilePath -> m FilePath gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> FilePath -> m FilePath | |
Ord FilePath | |
Defined in Filesystem.Path.Internal | |
NFData FilePath | |
Defined in Filesystem.Path.Internal |
Constructors
Fold (x -> a -> x) x (x -> b) |
Instances
Choice Fold | |
Profunctor Fold | |
Defined in Control.Foldl | |
Functor (Fold a) | |
Applicative (Fold a) | |
Comonad (Fold a) | |
Semigroupoid Fold | |
Defined in Control.Foldl | |
Floating b => Floating (Fold a b) | |
Fractional b => Fractional (Fold a b) | |
Defined in Control.Foldl | |
Num b => Num (Fold a b) | |
Semigroup b => Semigroup (Fold a b) | |
Monoid b => Monoid (Fold a b) | |
data FoldM (m :: Type -> Type) a b #
Constructors
FoldM (x -> a -> m x) (m x) (x -> m b) |
Instances
Functor m => Profunctor (FoldM m) | |
Defined in Control.Foldl Methods dimap :: (a -> b) -> (c -> d) -> FoldM m b c -> FoldM m a d lmap :: (a -> b) -> FoldM m b c -> FoldM m a c rmap :: (b -> c) -> FoldM m a b -> FoldM m a c (#.) :: forall a b c q. Coercible c b => q b c -> FoldM m a b -> FoldM m a c (.#) :: forall a b c q. Coercible b a => FoldM m b c -> q a b -> FoldM m a c | |
Functor m => Functor (FoldM m a) | |
Applicative m => Applicative (FoldM m a) | |
(Monad m, Floating b) => Floating (FoldM m a b) | |
Defined in Control.Foldl Methods exp :: FoldM m a b -> FoldM m a b log :: FoldM m a b -> FoldM m a b sqrt :: FoldM m a b -> FoldM m a b (**) :: FoldM m a b -> FoldM m a b -> FoldM m a b logBase :: FoldM m a b -> FoldM m a b -> FoldM m a b sin :: FoldM m a b -> FoldM m a b cos :: FoldM m a b -> FoldM m a b tan :: FoldM m a b -> FoldM m a b asin :: FoldM m a b -> FoldM m a b acos :: FoldM m a b -> FoldM m a b atan :: FoldM m a b -> FoldM m a b sinh :: FoldM m a b -> FoldM m a b cosh :: FoldM m a b -> FoldM m a b tanh :: FoldM m a b -> FoldM m a b asinh :: FoldM m a b -> FoldM m a b acosh :: FoldM m a b -> FoldM m a b atanh :: FoldM m a b -> FoldM m a b log1p :: FoldM m a b -> FoldM m a b expm1 :: FoldM m a b -> FoldM m a b | |
(Monad m, Fractional b) => Fractional (FoldM m a b) | |
Defined in Control.Foldl | |
(Monad m, Num b) => Num (FoldM m a b) | |
Defined in Control.Foldl | |
(Semigroup b, Monad m) => Semigroup (FoldM m a b) | |
(Monoid b, Monad m) => Monoid (FoldM m a b) | |
Instances
Hashable Text | |
Defined in Data.Hashable.Class | |
type Item Text | |
Instances
Eq UTCTime | |
Data UTCTime | |
Defined in Data.Time.Clock.Internal.UTCTime Methods gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> UTCTime -> c UTCTime gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c UTCTime dataTypeOf :: UTCTime -> DataType dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c UTCTime) dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c UTCTime) gmapT :: (forall b. Data b => b -> b) -> UTCTime -> UTCTime gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> UTCTime -> r gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> UTCTime -> r gmapQ :: (forall d. Data d => d -> u) -> UTCTime -> [u] gmapQi :: Int -> (forall d. Data d => d -> u) -> UTCTime -> u gmapM :: Monad m => (forall d. Data d => d -> m d) -> UTCTime -> m UTCTime gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> UTCTime -> m UTCTime gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> UTCTime -> m UTCTime | |
Ord UTCTime | |
NFData UTCTime | |
Defined in Data.Time.Clock.Internal.UTCTime |
data NominalDiffTime #
Instances
Constructors
ExitSuccess | |
ExitFailure Int |
Instances
Eq ExitCode | |
Ord ExitCode | |
Read ExitCode | |
Defined in GHC.IO.Exception | |
Show ExitCode | |
Generic ExitCode | |
Exception ExitCode | |
Defined in GHC.IO.Exception Methods toException :: ExitCode -> SomeException fromException :: SomeException -> Maybe ExitCode displayException :: ExitCode -> String | |
type Rep ExitCode | |
Defined in GHC.IO.Exception type Rep ExitCode = D1 ('MetaData "ExitCode" "GHC.IO.Exception" "base" 'False) (C1 ('MetaCons "ExitSuccess" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "ExitFailure" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Int))) |
Methods
fromString :: String -> a #
Instances
IsString ByteString | |
Defined in Data.ByteString.Internal Methods fromString :: String -> ByteString # | |
IsString Line Source # | |
Defined in Turtle.Line Methods fromString :: String -> Line # | |
IsString Doc | |
Defined in Text.PrettyPrint.ANSI.Leijen.Internal Methods fromString :: String -> Doc # | |
IsString HelpMessage Source # | |
Defined in Turtle.Options Methods fromString :: String -> HelpMessage # | |
IsString Description Source # | |
Defined in Turtle.Options Methods fromString :: String -> Description # | |
IsString CommandName Source # | |
Defined in Turtle.Options Methods fromString :: String -> CommandName # | |
IsString ArgName Source # | |
Defined in Turtle.Options Methods fromString :: String -> ArgName # | |
IsString CmdSpec | |
Defined in System.Process.Common Methods fromString :: String -> CmdSpec # | |
IsString Doc | |
Defined in Text.PrettyPrint.HughesPJ Methods fromString :: String -> Doc # | |
a ~ Char => IsString [a] | |
Defined in Data.String Methods fromString :: String -> [a] # | |
IsString a => IsString (Identity a) | |
Defined in Data.String Methods fromString :: String -> Identity a # | |
IsString a => IsString (Optional a) | |
Defined in Data.Optional Methods fromString :: String -> Optional a # | |
a ~ Text => IsString (Pattern a) Source # | |
Defined in Turtle.Pattern Methods fromString :: String -> Pattern a # | |
a ~ Char => IsString (Seq a) | |
Defined in Data.Sequence.Internal Methods fromString :: String -> Seq a # | |
IsString a => IsString (Shell a) Source # | |
Defined in Turtle.Shell Methods fromString :: String -> Shell a # | |
(IsString a, Hashable a) => IsString (Hashed a) | |
Defined in Data.Hashable.Class Methods fromString :: String -> Hashed a # | |
IsString (Doc a) | |
Defined in Text.PrettyPrint.Annotated.HughesPJ Methods fromString :: String -> Doc a # | |
a ~ b => IsString (Format a b) Source # | |
Defined in Turtle.Format Methods fromString :: String -> Format a b # | |
IsString a => IsString (Const a b) | |
Defined in Data.String Methods fromString :: String -> Const a b # | |
IsString a => IsString (Tagged s a) | |
Defined in Data.Tagged Methods fromString :: String -> Tagged s a # |