Copyright | (c) Red Hat 2022 |
---|---|
License | Apache-2.0 |
Maintainer | tdecacqu@redhat.com, fboucher@redhat.com |
Stability | provisional |
Portability | portable |
Safe Haskell | Safe-Inferred |
Language | GHC2021 |
This module exports common functions and helpers.
Synopsis
- getSec :: IO Int64
- intervalMilliSec :: IO (IO Int64)
- gitVersion :: Text
- data Logger
- info :: Logger -> ByteString -> IO ()
- withLogger :: (Logger -> IO a) -> IO a
- pPrint :: (MonadIO m, Show a) => a -> m ()
- pShowNoColor :: Show a => a -> Text
- data SomeException
- try :: Exception e => IO a -> IO (Either e a)
- catchAll :: MonadCatch m => m a -> (SomeException -> m a) -> m a
- newtype FilePathT = FilePathT Text
- (</>) :: FilePathT -> FilePathT -> FilePathT
- getPath :: FilePathT -> FilePath
- listDirectory :: FilePathT -> IO [FilePathT]
- doesDirectoryExist :: FilePathT -> IO Bool
- readFileBS :: FilePathT -> IO ByteString
- readFileText :: FilePathT -> IO Text
- writeFileText :: FilePathT -> Text -> IO ()
- data Text
- data ByteString
- data Map k a
- data Set a
- type Forest a = [Tree a]
- data Tree a = Node {}
- class From source target
- from :: From source target => source -> target
- via :: forall through source target. (From source through, From through target) => source -> target
- into :: forall target source. From source target => source -> target
- unsafeFrom :: (HasCallStack, TryFrom source target, Show source, Typeable source, Typeable target) => source -> target
- unsafeInto :: forall target source. (HasCallStack, TryFrom source target, Show source, Typeable source, Typeable target) => source -> target
- lift :: (MonadTrans t, Monad m) => m a -> t m a
- type Reader r = ReaderT r Identity
- data ReaderT r (m :: Type -> Type) a
- runReaderT :: ReaderT r m a -> r -> m a
- type State s = StateT s Identity
- data StateT s (m :: Type -> Type) a
- execStateT :: Monad m => StateT s m a -> s -> m s
- data ExceptT e (m :: Type -> Type) a
- runExceptT :: ExceptT e m a -> m (Either e a)
- throwError :: MonadError e m => e -> m a
- except :: forall (m :: Type -> Type) e a. Monad m => Either e a -> ExceptT e m a
- runIdentity :: Identity a -> a
- set :: ASetter s t a b -> b -> s -> t
- over :: ASetter s t a b -> (a -> b) -> s -> t
- use :: MonadState s m => Getting a s a -> m a
- (%=) :: MonadState s m => ASetter s s a b -> (a -> b) -> m ()
- class FromJSON a where
- class FromJSONKey a where
- class ToJSON a where
- toJSON :: a -> Value
- toEncoding :: a -> Encoding
- toJSONList :: [a] -> Value
- toEncodingList :: [a] -> Encoding
- class ToJSONKey a where
- toJSONKey :: ToJSONKeyFunction a
- toJSONKeyList :: ToJSONKeyFunction [a]
- data Value = Object !Object
- genericParseJSON :: (Generic a, GFromJSON Zero (Rep a)) => Options -> Value -> Parser a
- genericToJSON :: (Generic a, GToJSON' Value Zero (Rep a)) => Options -> a -> Value
- defaultOptions :: Options
- omitNothingFields :: Options -> Bool
- encodeJSON :: ToJSON a => a -> ByteString
- decodeJSON :: FromJSON a => ByteString -> Either String a
- newtype Decoder a = Decoder (Either (Text, Value) a)
- decodeFail :: Text -> Value -> Decoder a
- decodeObject :: Value -> Decoder Object
- decodeObjectAttribute :: Key -> Object -> Decoder Value
- decodeAsList :: Key -> (Text -> a) -> Object -> Decoder [a]
- decodeString :: Value -> Decoder Text
- decodeList :: Value -> Decoder [Value]
- s :: QuasiQuoter
- withUtf8 :: (MonadIO m, MonadMask m) => m r -> m r
- whenM :: Monad m => m Bool -> m () -> m ()
- orDie :: Maybe a -> b -> Either b a
- fromEither :: Show a => Either a b -> b
- forkIO :: IO () -> IO ThreadId
- threadDelay :: Int -> IO ()
- data IORef a
- newIORef :: a -> IO (IORef a)
- readIORef :: IORef a -> IO a
- writeIORef :: IORef a -> a -> IO ()
- data MVar a
- newMVar :: a -> IO (MVar a)
- modifyMVar :: MVar a -> (a -> IO (a, b)) -> IO b
- sort :: Ord a => [a] -> [a]
- nub :: Eq a => [a] -> [a]
- data NonEmpty a
- nonEmpty :: [a] -> Maybe (NonEmpty a)
- data Int64
- (&) :: a -> (a -> b) -> b
- data Proxy (t :: k) = Proxy
- first :: Bifunctor p => (a -> b) -> p a c -> p b c
- bool :: a -> a -> Bool -> a
- traverse_ :: (Foldable t, Applicative f) => (a -> f b) -> t a -> f ()
- foldl' :: Foldable t => (b -> a -> b) -> b -> t a -> b
- catMaybes :: [Maybe a] -> [a]
- mapMaybe :: (a -> Maybe b) -> [a] -> [b]
- isJust :: Maybe a -> Bool
- isNothing :: Maybe a -> Bool
- fromMaybe :: a -> Maybe a -> a
- fromRight :: b -> Either a b -> b
- forM_ :: (Foldable t, Monad m) => t a -> (a -> m b) -> m ()
- foldM :: (Foldable t, Monad m) => (b -> a -> m b) -> b -> t a -> m b
- unless :: Applicative f => Bool -> f () -> f ()
- when :: Applicative f => Bool -> f () -> f ()
- void :: Functor f => f a -> f ()
- liftIO :: MonadIO m => IO 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
- (<|>) :: Alternative f => f a -> f a -> f a
- trace :: String -> a -> a
- hPutStrLn :: Handle -> String -> IO ()
- stderr :: Handle
- printf :: PrintfType r => String -> r
- type HasCallStack = ?callStack :: CallStack
- showVersion :: Version -> String
- lookupEnv :: String -> IO (Maybe String)
- getArgs :: IO [String]
- timeout :: Int -> IO a -> IO (Maybe a)
- hash :: Hashable a => a -> Int
- class Eq a => Hashable a
- module Prelude
- class Generic a
clock
intervalMilliSec :: IO (IO Int64) Source #
Compute the time interval in milli-seconds ellapsed between now and the provided action.
th-env
gitVersion :: Text Source #
The content of the GIT_COMMIT environment variable, default to HEAD.
fast-logger
pretty-simple
pPrint :: (MonadIO m, Show a) => a -> m () #
Pretty-print any data type that has a Show
instance.
If you've never seen MonadIO
before, you can think of this function as
having the following type signature:
pPrint :: Show a => a -> IO ()
This function will only use colors if it detects it's printing to a TTY.
This function is for printing to a dark background. Use pPrintLightBg
for
printing to a terminal with a light background. Different colors are used.
Prints to stdout
. Use pHPrint
to print to a different Handle
.
>>>
pPrint [Just (1, "hello")]
[ Just ( 1 , "hello" ) ]
pShowNoColor :: Show a => a -> Text #
Like pShow
, but without color.
>>>
pShowNoColor [ Nothing, Just (1, "hello") ]
"[ Nothing\n, Just\n ( 1\n , \"hello\"\n )\n]"
exceptions
data SomeException #
The SomeException
type is the root of the exception type hierarchy.
When an exception of type e
is thrown, behind the scenes it is
encapsulated in a SomeException
.
Instances
Exception SomeException | Since: base-3.0 |
Defined in GHC.Exception.Type | |
Show SomeException | Since: base-3.0 |
Defined in GHC.Exception.Type showsPrec :: Int -> SomeException -> ShowS # show :: SomeException -> String # showList :: [SomeException] -> ShowS # |
try :: Exception e => IO a -> IO (Either e a) #
Similar to catch
, but returns an Either
result which is
(
if no exception of type Right
a)e
was raised, or (
if an exception of type Left
ex)e
was raised and its value is ex
.
If any other type of exception is raised then it will be propagated
up to the next enclosing exception handler.
try a = catch (Right `liftM` a) (return . Left)
catchAll :: MonadCatch m => m a -> (SomeException -> m a) -> m a #
Catches all exceptions, and somewhat defeats the purpose of the extensible exception system. Use sparingly.
NOTE This catches all exceptions, but if the monad supports other ways of aborting the computation, those other kinds of errors will not be caught.
filepath text
A FilePath encoded with UTF-8.
Instances
FromJSON FilePathT Source # | |
ToJSON FilePathT Source # | |
Defined in ZuulWeeder.Prelude | |
IsString FilePathT Source # | |
Defined in ZuulWeeder.Prelude fromString :: String -> FilePathT # | |
Monoid FilePathT Source # | |
Semigroup FilePathT Source # | |
Generic FilePathT Source # | |
Show FilePathT Source # | |
Eq FilePathT Source # | |
Ord FilePathT Source # | |
Defined in ZuulWeeder.Prelude | |
Hashable FilePathT Source # | |
Defined in ZuulWeeder.Prelude | |
From FilePathT Text Source # | |
Defined in ZuulWeeder.Prelude | |
type Rep FilePathT Source # | |
Defined in ZuulWeeder.Prelude |
listDirectory :: FilePathT -> IO [FilePathT] Source #
Wrapper for listDirectory
.
doesDirectoryExist :: FilePathT -> IO Bool Source #
Wrapper for doesDirectoryExist
readFileBS :: FilePathT -> IO ByteString Source #
Wrapper for readFile
text, bytestring
A space efficient, packed, unboxed Unicode text type.
Instances
data ByteString #
A space-efficient representation of a Word8
vector, supporting many
efficient operations.
A ByteString
contains 8-bit bytes, or by using the operations from
Data.ByteString.Char8 it can be interpreted as containing 8-bit
characters.
Instances
containers
A Map from keys k
to values a
.
The Semigroup
operation for Map
is union
, which prefers
values from the left operand. If m1
maps a key k
to a value
a1
, and m2
maps the same key to a different value a2
, then
their union m1 <> m2
maps k
to a1
.
Instances
Bifoldable Map | Since: containers-0.6.3.1 |
Eq2 Map | Since: containers-0.5.9 |
Ord2 Map | Since: containers-0.5.9 |
Defined in Data.Map.Internal | |
Show2 Map | Since: containers-0.5.9 |
Hashable2 Map | Since: hashable-1.3.4.0 |
Defined in Data.Hashable.Class | |
(FromJSONKey k, Ord k) => FromJSON1 (Map k) | |
ToJSONKey k => ToJSON1 (Map k) | |
Defined in Data.Aeson.Types.ToJSON liftToJSON :: (a -> Value) -> ([a] -> Value) -> Map k a -> Value # liftToJSONList :: (a -> Value) -> ([a] -> Value) -> [Map k a] -> Value # liftToEncoding :: (a -> Encoding) -> ([a] -> Encoding) -> Map k a -> Encoding # liftToEncodingList :: (a -> Encoding) -> ([a] -> Encoding) -> [Map k a] -> Encoding # | |
Foldable (Map k) | Folds in order of increasing key. |
Defined in Data.Map.Internal fold :: Monoid m => Map k m -> m # foldMap :: Monoid m => (a -> m) -> Map k a -> m # foldMap' :: Monoid m => (a -> m) -> Map k a -> m # foldr :: (a -> b -> b) -> b -> Map k a -> b # foldr' :: (a -> b -> b) -> b -> Map k a -> b # foldl :: (b -> a -> b) -> b -> Map k a -> b # foldl' :: (b -> a -> b) -> b -> Map k a -> b # foldr1 :: (a -> a -> a) -> Map k a -> a # foldl1 :: (a -> a -> a) -> Map k a -> a # elem :: Eq a => a -> Map k a -> Bool # maximum :: Ord a => Map k a -> a # minimum :: Ord a => Map k a -> a # | |
Eq k => Eq1 (Map k) | Since: containers-0.5.9 |
Ord k => Ord1 (Map k) | Since: containers-0.5.9 |
Defined in Data.Map.Internal | |
(Ord k, Read k) => Read1 (Map k) | Since: containers-0.5.9 |
Defined in Data.Map.Internal | |
Show k => Show1 (Map k) | Since: containers-0.5.9 |
Traversable (Map k) | Traverses in order of increasing key. |
Functor (Map k) | |
Hashable k => Hashable1 (Map k) | Since: hashable-1.3.4.0 |
Defined in Data.Hashable.Class | |
(FromJSONKey k, Ord k, FromJSON v) => FromJSON (Map k v) | |
(ToJSON v, ToJSONKey k) => ToJSON (Map k v) | |
Defined in Data.Aeson.Types.ToJSON | |
(Data k, Data a, Ord k) => Data (Map k a) | |
Defined in Data.Map.Internal gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Map k a -> c (Map k a) # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (Map k a) # toConstr :: Map k a -> Constr # dataTypeOf :: Map k a -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (Map k a)) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (Map k a)) # gmapT :: (forall b. Data b => b -> b) -> Map k a -> Map k a # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Map k a -> r # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Map k a -> r # gmapQ :: (forall d. Data d => d -> u) -> Map k a -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> Map k a -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> Map k a -> m (Map k a) # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Map k a -> m (Map k a) # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Map k a -> m (Map k a) # | |
Ord k => Monoid (Map k v) | |
Ord k => Semigroup (Map k v) | |
Ord k => IsList (Map k v) | Since: containers-0.5.6.2 |
(Ord k, Read k, Read e) => Read (Map k e) | |
(Show k, Show a) => Show (Map k a) | |
(NFData k, NFData a) => NFData (Map k a) | |
Defined in Data.Map.Internal | |
(Eq k, Eq a) => Eq (Map k a) | |
(Ord k, Ord v) => Ord (Map k v) | |
(Hashable k, Hashable v) => Hashable (Map k v) | Since: hashable-1.3.4.0 |
Defined in Data.Hashable.Class | |
(Ord k, FromFormKey k, FromHttpApiData v) => FromForm (Map k [v]) | |
(ToFormKey k, ToHttpApiData v) => ToForm (Map k [v]) | |
Defined in Web.Internal.FormUrlEncoded | |
Ord k => At (Map k a) | |
Ord k => Ixed (Map k a) | |
Defined in Control.Lens.At | |
Ord k => Wrapped (Map k a) | |
(t ~ Map k' a', Ord k) => Rewrapped (Map k a) t | Use |
Defined in Control.Lens.Wrapped | |
type Item (Map k v) | |
Defined in Data.Map.Internal | |
type Index (Map k a) | |
Defined in Control.Lens.At | |
type IxValue (Map k a) | |
Defined in Control.Lens.At | |
type Unwrapped (Map k a) | |
Defined in Control.Lens.Wrapped |
A set of values a
.
Instances
ToJSON1 Set | |
Defined in Data.Aeson.Types.ToJSON | |
Foldable Set | Folds in order of increasing key. |
Defined in Data.Set.Internal fold :: Monoid m => Set m -> m # foldMap :: Monoid m => (a -> m) -> Set a -> m # foldMap' :: Monoid m => (a -> m) -> Set a -> m # foldr :: (a -> b -> b) -> b -> Set a -> b # foldr' :: (a -> b -> b) -> b -> Set a -> b # foldl :: (b -> a -> b) -> b -> Set a -> b # foldl' :: (b -> a -> b) -> b -> Set a -> b # foldr1 :: (a -> a -> a) -> Set a -> a # foldl1 :: (a -> a -> a) -> Set a -> a # elem :: Eq a => a -> Set a -> Bool # maximum :: Ord a => Set a -> a # | |
Eq1 Set | Since: containers-0.5.9 |
Ord1 Set | Since: containers-0.5.9 |
Defined in Data.Set.Internal | |
Show1 Set | Since: containers-0.5.9 |
Hashable1 Set | Since: hashable-1.3.4.0 |
Defined in Data.Hashable.Class | |
(Ord a, FromJSON a) => FromJSON (Set a) | |
ToJSON a => ToJSON (Set a) | |
Defined in Data.Aeson.Types.ToJSON | |
(Data a, Ord a) => Data (Set a) | |
Defined in Data.Set.Internal gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Set a -> c (Set a) # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (Set a) # dataTypeOf :: Set a -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (Set a)) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (Set a)) # gmapT :: (forall b. Data b => b -> b) -> Set a -> Set a # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Set a -> r # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Set a -> r # gmapQ :: (forall d. Data d => d -> u) -> Set a -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> Set a -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> Set a -> m (Set a) # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Set a -> m (Set a) # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Set a -> m (Set a) # | |
Ord a => Monoid (Set a) | |
Ord a => Semigroup (Set a) | Since: containers-0.5.7 |
Ord a => IsList (Set a) | Since: containers-0.5.6.2 |
(Read a, Ord a) => Read (Set a) | |
Show a => Show (Set a) | |
NFData a => NFData (Set a) | |
Defined in Data.Set.Internal | |
Eq a => Eq (Set a) | |
Ord a => Ord (Set a) | |
Hashable v => Hashable (Set v) | Since: hashable-1.3.4.0 |
Defined in Data.Hashable.Class | |
Ord k => At (Set k) | |
Ord a => Contains (Set a) | |
Ord k => Ixed (Set k) | |
Defined in Control.Lens.At | |
Ord a => Wrapped (Set a) | |
(t ~ Set a', Ord a) => Rewrapped (Set a) t | Use |
Defined in Control.Lens.Wrapped | |
type Item (Set a) | |
Defined in Data.Set.Internal | |
type Index (Set a) | |
Defined in Control.Lens.At | |
type IxValue (Set k) | |
Defined in Control.Lens.At | |
type Unwrapped (Set a) | |
Defined in Control.Lens.Wrapped |
Non-empty, possibly infinite, multi-way trees; also known as rose trees.
Instances
FromJSON1 Tree | |
ToJSON1 Tree | |
Defined in Data.Aeson.Types.ToJSON | |
MonadFix Tree | Since: containers-0.5.11 |
MonadZip Tree | |
Foldable Tree | |
Defined in Data.Tree fold :: Monoid m => Tree m -> m # foldMap :: Monoid m => (a -> m) -> Tree a -> m # foldMap' :: Monoid m => (a -> m) -> Tree a -> m # foldr :: (a -> b -> b) -> b -> Tree a -> b # foldr' :: (a -> b -> b) -> b -> Tree a -> b # foldl :: (b -> a -> b) -> b -> Tree a -> b # foldl' :: (b -> a -> b) -> b -> Tree a -> b # foldr1 :: (a -> a -> a) -> Tree a -> a # foldl1 :: (a -> a -> a) -> Tree a -> a # elem :: Eq a => a -> Tree a -> Bool # maximum :: Ord a => Tree a -> a # | |
Eq1 Tree | Since: containers-0.5.9 |
Ord1 Tree | Since: containers-0.5.9 |
Read1 Tree | Since: containers-0.5.9 |
Show1 Tree | Since: containers-0.5.9 |
Traversable Tree | |
Applicative Tree | |
Functor Tree | |
Monad Tree | |
Hashable1 Tree | Since: hashable-1.3.4.0 |
Defined in Data.Hashable.Class | |
Generic1 Tree | |
FromJSON v => FromJSON (Tree v) | |
ToJSON v => ToJSON (Tree v) | |
Defined in Data.Aeson.Types.ToJSON | |
Data a => Data (Tree a) | |
Defined in Data.Tree gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Tree a -> c (Tree a) # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (Tree a) # toConstr :: Tree a -> Constr # dataTypeOf :: Tree a -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (Tree a)) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (Tree a)) # gmapT :: (forall b. Data b => b -> b) -> Tree a -> Tree a # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Tree a -> r # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Tree a -> r # gmapQ :: (forall d. Data d => d -> u) -> Tree a -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> Tree a -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> Tree a -> m (Tree a) # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Tree a -> m (Tree a) # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Tree a -> m (Tree a) # | |
Generic (Tree a) | |
Read a => Read (Tree a) | |
Show a => Show (Tree a) | |
NFData a => NFData (Tree a) | |
Eq a => Eq (Tree a) | |
Ord a => Ord (Tree a) | Since: containers-0.6.5 |
Hashable v => Hashable (Tree v) | Since: hashable-1.3.4.0 |
Defined in Data.Hashable.Class | |
Ixed (Tree a) | |
Defined in Control.Lens.At | |
type Rep1 Tree | Since: containers-0.5.8 |
Defined in Data.Tree type Rep1 Tree = D1 ('MetaData "Tree" "Data.Tree" "containers-0.6.5.1" 'False) (C1 ('MetaCons "Node" 'PrefixI 'True) (S1 ('MetaSel ('Just "rootLabel") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) Par1 :*: S1 ('MetaSel ('Just "subForest") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) ([] :.: Rec1 Tree))) | |
type Rep (Tree a) | Since: containers-0.5.8 |
Defined in Data.Tree type Rep (Tree a) = D1 ('MetaData "Tree" "Data.Tree" "containers-0.6.5.1" 'False) (C1 ('MetaCons "Node" 'PrefixI 'True) (S1 ('MetaSel ('Just "rootLabel") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 a) :*: S1 ('MetaSel ('Just "subForest") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [Tree a]))) | |
type Index (Tree a) | |
Defined in Control.Lens.At | |
type IxValue (Tree a) | |
Defined in Control.Lens.At |
witch
This type class is for converting values from some source
type into
some other target
type. The constraint
means that
you can convert from a value of type From
source targetsource
into a value of type
target
.
This type class is for conversions that always succeed. If your conversion
sometimes fails, consider implementing TryFrom
instead.
Instances
from :: From source target => source -> target #
This method implements the conversion of a value between types. At call
sites you may prefer to use into
instead.
-- Avoid this: from (x :: s) -- Prefer this: from @s x
The default implementation of this method simply calls coerce
,
which works for types that have the same runtime representation. This
means that for newtype
s you do not need to implement this method at
all. For example:
>>>
newtype Name = Name String
>>>
instance From Name String
>>>
instance From String Name
via :: forall through source target. (From source through, From through target) => source -> target #
This function first converts from some source
type into some through
type, and then converts that into some target
type. Usually this is used
when writing From
instances. Sometimes this can be used to work
around the lack of an instance that should probably exist.
-- Avoid this: from @u . into @u -- Prefer this: via @u
into :: forall target source. From source target => source -> target #
This is the same as from
except that the type variables are in the
opposite order.
-- Avoid this: from x :: t -- Prefer this: into @t x
unsafeFrom :: (HasCallStack, TryFrom source target, Show source, Typeable source, Typeable target) => source -> target #
This function is like tryFrom
except that it will throw an
impure exception if the conversion fails.
-- Avoid this: either throw id . tryFrom @s -- Prefer this: unsafeFrom @s
unsafeInto :: forall target source. (HasCallStack, TryFrom source target, Show source, Typeable source, Typeable target) => source -> target #
This function is like tryInto
except that it will throw an impure
exception if the conversion fails.
-- Avoid this: either throw id . tryInto @t -- Prefer this: unsafeInto @t
mtl
lift :: (MonadTrans t, Monad m) => m a -> t m a #
Lift a computation from the argument monad to the constructed monad.
type Reader r = ReaderT r Identity #
The parameterizable reader monad.
Computations are functions of a shared environment.
The return
function ignores the environment, while >>=
passes
the inherited environment to both subcomputations.
data ReaderT r (m :: Type -> Type) a #
The reader monad transformer, which adds a read-only environment to the given monad.
The return
function ignores the environment, while >>=
passes
the inherited environment to both subcomputations.
Instances
runReaderT :: ReaderT r m a -> r -> m a #
type State s = StateT s Identity #
A state monad parameterized by the type s
of the state to carry.
The return
function leaves the state unchanged, while >>=
uses
the final state of the first computation as the initial state of
the second.
data StateT s (m :: Type -> Type) a #
A state transformer monad parameterized by:
s
- The state.m
- The inner monad.
The return
function leaves the state unchanged, while >>=
uses
the final state of the first computation as the initial state of
the second.
Instances
execStateT :: Monad m => StateT s m a -> s -> m s #
Evaluate a state computation with the given initial state and return the final state, discarding the final value.
execStateT
m s =liftM
snd
(runStateT
m s)
data ExceptT e (m :: Type -> Type) a #
A monad transformer that adds exceptions to other monads.
ExceptT
constructs a monad parameterized over two things:
- e - The exception type.
- m - The inner monad.
The return
function yields a computation that produces the given
value, while >>=
sequences two subcomputations, exiting on the
first exception.
Instances
runExceptT :: ExceptT e m a -> m (Either e a) #
The inverse of ExceptT
.
throwError :: MonadError e m => e -> m a #
Is used within a monadic computation to begin exception processing.
except :: forall (m :: Type -> Type) e a. Monad m => Either e a -> ExceptT e m a #
Constructor for computations in the exception monad.
(The inverse of runExcept
).
runIdentity :: Identity a -> a #
lens
set :: ASetter s t a b -> b -> s -> t #
Replace the target of a Lens
or all of the targets of a Setter
or Traversal
with a constant value.
(<$
) ≡set
mapped
>>>
set _2 "hello" (1,())
(1,"hello")
>>>
set mapped () [1,2,3,4]
[(),(),(),()]
Note: Attempting to set
a Fold
or Getter
will fail at compile time with an
relatively nice error message.
set
::Setter
s t a b -> b -> s -> tset
::Iso
s t a b -> b -> s -> tset
::Lens
s t a b -> b -> s -> tset
::Traversal
s t a b -> b -> s -> t
over :: ASetter s t a b -> (a -> b) -> s -> t #
Modify the target of a Lens
or all the targets of a Setter
or Traversal
with a function.
fmap
≡over
mapped
fmapDefault
≡over
traverse
sets
.
over
≡id
over
.
sets
≡id
Given any valid Setter
l
, you can also rely on the law:
over
l f.
over
l g =over
l (f.
g)
e.g.
>>>
over mapped f (over mapped g [a,b,c]) == over mapped (f . g) [a,b,c]
True
Another way to view over
is to say that it transforms a Setter
into a
"semantic editor combinator".
>>>
over mapped f (Just a)
Just (f a)
>>>
over mapped (*10) [1,2,3]
[10,20,30]
>>>
over _1 f (a,b)
(f a,b)
>>>
over _1 show (10,20)
("10",20)
over
::Setter
s t a b -> (a -> b) -> s -> tover
::ASetter
s t a b -> (a -> b) -> s -> t
use :: MonadState s m => Getting a s a -> m a #
Use the target of a Lens
, Iso
, or
Getter
in the current state, or use a summary of a
Fold
or Traversal
that points
to a monoidal value.
>>>
evalState (use _1) (a,b)
a
>>>
evalState (use _1) ("hello","world")
"hello"
use
::MonadState
s m =>Getter
s a -> m ause
:: (MonadState
s m,Monoid
r) =>Fold
s r -> m ruse
::MonadState
s m =>Iso'
s a -> m ause
::MonadState
s m =>Lens'
s a -> m ause
:: (MonadState
s m,Monoid
r) =>Traversal'
s r -> m r
(%=) :: MonadState s m => ASetter s s a b -> (a -> b) -> m () infix 4 #
Map over the target of a Lens
or all of the targets of a Setter
or Traversal
in our monadic state.
>>>
execState (do _1 %= f;_2 %= g) (a,b)
(f a,g b)
>>>
execState (do both %= f) (a,b)
(f a,f b)
(%=
) ::MonadState
s m =>Iso'
s a -> (a -> a) -> m () (%=
) ::MonadState
s m =>Lens'
s a -> (a -> a) -> m () (%=
) ::MonadState
s m =>Traversal'
s a -> (a -> a) -> m () (%=
) ::MonadState
s m =>Setter'
s a -> (a -> a) -> m ()
(%=
) ::MonadState
s m =>ASetter
s s a b -> (a -> b) -> m ()
aeson
A type that can be converted from JSON, with the possibility of failure.
In many cases, you can get the compiler to generate parsing code for you (see below). To begin, let's cover writing an instance by hand.
There are various reasons a conversion could fail. For example, an
Object
could be missing a required key, an Array
could be of
the wrong size, or a value could be of an incompatible type.
The basic ways to signal a failed conversion are as follows:
fail
yields a custom error message: it is the recommended way of reporting a failure;empty
(ormzero
) is uninformative: use it when the error is meant to be caught by some(
;<|>
)typeMismatch
can be used to report a failure when the encountered value is not of the expected JSON type;unexpected
is an appropriate alternative when more than one type may be expected, or to keep the expected type implicit.
prependFailure
(or modifyFailure
) add more information to a parser's
error messages.
An example type and instance using typeMismatch
and prependFailure
:
-- Allow ourselves to writeText
literals. {-# LANGUAGE OverloadedStrings #-} data Coord = Coord { x :: Double, y :: Double } instanceFromJSON
Coord whereparseJSON
(Object
v) = Coord<$>
v.:
"x"<*>
v.:
"y" -- We do not expect a non-Object
value here. -- We could useempty
to fail, buttypeMismatch
-- gives a much more informative error message.parseJSON
invalid =prependFailure
"parsing Coord failed, " (typeMismatch
"Object" invalid)
For this common case of only being concerned with a single
type of JSON value, the functions withObject
, withScientific
, etc.
are provided. Their use is to be preferred when possible, since
they are more terse. Using withObject
, we can rewrite the above instance
(assuming the same language extension and data type) as:
instanceFromJSON
Coord whereparseJSON
=withObject
"Coord" $ \v -> Coord<$>
v.:
"x"<*>
v.:
"y"
Instead of manually writing your FromJSON
instance, there are two options
to do it automatically:
- Data.Aeson.TH provides Template Haskell functions which will derive an instance at compile time. The generated instance is optimized for your type so it will probably be more efficient than the following option.
- The compiler can provide a default generic implementation for
parseJSON
.
To use the second, simply add a deriving
clause to your
datatype and declare a Generic
FromJSON
instance for your datatype without giving
a definition for parseJSON
.
For example, the previous example can be simplified to just:
{-# LANGUAGE DeriveGeneric #-} import GHC.Generics data Coord = Coord { x :: Double, y :: Double } derivingGeneric
instanceFromJSON
Coord
The default implementation will be equivalent to
parseJSON =
; if you need different
options, you can customize the generic decoding by defining:genericParseJSON
defaultOptions
customOptions =defaultOptions
{fieldLabelModifier
=map
toUpper
} instanceFromJSON
Coord whereparseJSON
=genericParseJSON
customOptions
Nothing
Instances
class FromJSONKey a where #
Read the docs for ToJSONKey
first. This class is a conversion
in the opposite direction. If you have a newtype wrapper around Text
,
the recommended way to define instances is with generalized newtype deriving:
newtype SomeId = SomeId { getSomeId :: Text } deriving (Eq,Ord,Hashable,FromJSONKey)
If you have a sum of nullary constructors, you may use the generic implementation:
data Color = Red | Green | Blue deriving Generic instanceFromJSONKey
Color wherefromJSONKey
=genericFromJSONKey
defaultJSONKeyOptions
Nothing
fromJSONKey :: FromJSONKeyFunction a #
Strategy for parsing the key of a map-like container.
fromJSONKeyList :: FromJSONKeyFunction [a] #
Instances
A type that can be converted to JSON.
Instances in general must specify toJSON
and should (but don't need
to) specify toEncoding
.
An example type and instance:
-- Allow ourselves to writeText
literals. {-# LANGUAGE OverloadedStrings #-} data Coord = Coord { x :: Double, y :: Double } instanceToJSON
Coord wheretoJSON
(Coord x y) =object
["x".=
x, "y".=
y]toEncoding
(Coord x y) =pairs
("x".=
x<>
"y".=
y)
Instead of manually writing your ToJSON
instance, there are two options
to do it automatically:
- Data.Aeson.TH provides Template Haskell functions which will derive an instance at compile time. The generated instance is optimized for your type so it will probably be more efficient than the following option.
- The compiler can provide a default generic implementation for
toJSON
.
To use the second, simply add a deriving
clause to your
datatype and declare a Generic
ToJSON
instance. If you require nothing other than
defaultOptions
, it is sufficient to write (and this is the only
alternative where the default toJSON
implementation is sufficient):
{-# LANGUAGE DeriveGeneric #-} import GHC.Generics data Coord = Coord { x :: Double, y :: Double } derivingGeneric
instanceToJSON
Coord wheretoEncoding
=genericToEncoding
defaultOptions
If on the other hand you wish to customize the generic decoding, you have to implement both methods:
customOptions =defaultOptions
{fieldLabelModifier
=map
toUpper
} instanceToJSON
Coord wheretoJSON
=genericToJSON
customOptionstoEncoding
=genericToEncoding
customOptions
Previous versions of this library only had the toJSON
method. Adding
toEncoding
had two reasons:
- toEncoding is more efficient for the common case that the output of
toJSON
is directly serialized to aByteString
. Further, expressing either method in terms of the other would be non-optimal. - The choice of defaults allows a smooth transition for existing users:
Existing instances that do not define
toEncoding
still compile and have the correct semantics. This is ensured by making the default implementation oftoEncoding
usetoJSON
. This produces correct results, but since it performs an intermediate conversion to aValue
, it will be less efficient than directly emitting anEncoding
. (this also means that specifying nothing more thaninstance ToJSON Coord
would be sufficient as a generically decoding instance, but there probably exists no good reason to not specifytoEncoding
in new instances.)
Nothing
Convert a Haskell value to a JSON-friendly intermediate type.
toEncoding :: a -> Encoding #
Encode a Haskell value as JSON.
The default implementation of this method creates an
intermediate Value
using toJSON
. This provides
source-level compatibility for people upgrading from older
versions of this library, but obviously offers no performance
advantage.
To benefit from direct encoding, you must provide an
implementation for this method. The easiest way to do so is by
having your types implement Generic
using the DeriveGeneric
extension, and then have GHC generate a method body as follows.
instanceToJSON
Coord wheretoEncoding
=genericToEncoding
defaultOptions
toJSONList :: [a] -> Value #
toEncodingList :: [a] -> Encoding #