Safe Haskell | None |
---|---|
Language | Haskell2010 |
B9 is a library and build tool with which one can create/convert different types of VM images. Additionally installation steps - like installing software - can be done in a LXC container, running on the disk images.
B9 allows to create and convert virtual machine image files as well as related ISO and VFAT disk images for e.g. cloud-init configuration sources.
This module re-exports the modules needed to build a tool around the
library, e.g. see src/cli/Main.hs
as an example.
B9.Artifact.Generator is the module containing the basic data structure used to describe a B9 build.
Synopsis
- b9Version :: Version
- b9VersionString :: String
- runShowVersion :: MonadIO m => m ()
- runBuildArtifacts :: [FilePath] -> B9ConfigAction String
- runFormatBuildFiles :: MonadIO m => [FilePath] -> m ()
- runPush :: SharedImageName -> B9ConfigAction ()
- runPull :: Maybe SharedImageName -> B9ConfigAction ()
- runRun :: SharedImageName -> [String] -> B9ConfigAction String
- runGcLocalRepoCache :: B9ConfigAction ()
- runGcRemoteRepoCache :: B9ConfigAction ()
- runListSharedImages :: B9ConfigAction (Set SharedImage)
- runAddRepo :: RemoteRepo -> B9ConfigAction ()
- runLookupLocalSharedImage :: SharedImageName -> B9ConfigAction (Maybe SharedImageBuildId)
- (++) :: [a] -> [a] -> [a]
- filter :: (a -> Bool) -> [a] -> [a]
- zip :: [a] -> [b] -> [(a, b)]
- map :: (a -> b) -> [a] -> [b]
- guard :: Alternative f => Bool -> f ()
- join :: Monad m => m (m a) -> m a
- class Applicative m => Monad (m :: Type -> Type) where
- class Functor (f :: Type -> Type) where
- class Functor f => Applicative (f :: Type -> Type) where
- foldr :: Foldable t => (a -> b -> b) -> b -> t a -> b
- length :: Foldable t => t a -> Int
- null :: Foldable t => t a -> Bool
- foldl :: Foldable t => (b -> a -> b) -> b -> t a -> b
- foldl' :: Foldable t => (b -> a -> b) -> b -> t a -> b
- foldl1 :: Foldable t => (a -> a -> a) -> t a -> a
- sum :: (Foldable t, Num a) => t a -> a
- product :: (Foldable t, Num a) => t a -> a
- foldr1 :: Foldable t => (a -> a -> a) -> t a -> a
- maximum :: (Foldable t, Ord a) => t a -> a
- minimum :: (Foldable t, Ord a) => t a -> a
- elem :: (Foldable t, Eq a) => a -> t a -> Bool
- mapM :: (Traversable t, Monad m) => (a -> m b) -> t a -> m (t b)
- sequence :: (Traversable t, Monad m) => t (m a) -> m (t a)
- (<>) :: Semigroup a => a -> a -> a
- class Semigroup a => Monoid a where
- data Maybe a
- unlines :: [String] -> String
- lines :: String -> [String]
- isInfixOf :: Eq a => [a] -> [a] -> Bool
- delete :: Eq a => a -> [a] -> [a]
- data Version = Version {
- versionBranch :: [Int]
- versionTags :: [String]
- liftM :: Monad m => (a1 -> r) -> m a1 -> m r
- local :: MonadReader r m => (r -> r) -> m a -> m a
- ask :: MonadReader r m => m r
- data ByteString
- (<$>) :: Functor f => (a -> b) -> f a -> f b
- data Text
- class Applicative f => Alternative (f :: Type -> Type) where
- class (Alternative m, Monad m) => MonadPlus (m :: Type -> Type) where
- class Monad m => MonadIO (m :: Type -> Type) where
- exitWith :: ExitCode -> IO a
- printf :: PrintfType r => String -> r
- mfilter :: MonadPlus m => (a -> Bool) -> m a -> m a
- (<$!>) :: Monad m => (a -> b) -> m a -> m b
- unless :: Applicative f => Bool -> f () -> f ()
- replicateM_ :: Applicative m => Int -> m a -> m ()
- replicateM :: Applicative m => Int -> m a -> m [a]
- foldM_ :: (Foldable t, Monad m) => (b -> a -> m b) -> b -> t a -> m ()
- foldM :: (Foldable t, Monad m) => (b -> a -> m b) -> b -> t a -> m b
- zipWithM_ :: Applicative m => (a -> b -> m c) -> [a] -> [b] -> m ()
- zipWithM :: Applicative m => (a -> b -> m c) -> [a] -> [b] -> m [c]
- mapAndUnzipM :: Applicative m => (a -> m (b, c)) -> [a] -> m ([b], [c])
- forever :: Applicative f => f a -> f b
- (<=<) :: Monad m => (b -> m c) -> (a -> m b) -> a -> m c
- (>=>) :: Monad m => (a -> m b) -> (b -> m c) -> a -> m c
- filterM :: Applicative m => (a -> m Bool) -> [a] -> m [a]
- makeVersion :: [Int] -> Version
- parseVersion :: ReadP Version
- showVersion :: Version -> String
- isSubsequenceOf :: Eq a => [a] -> [a] -> Bool
- mapAccumR :: Traversable t => (a -> b -> (a, c)) -> a -> t b -> (a, t c)
- mapAccumL :: Traversable t => (a -> b -> (a, c)) -> a -> t b -> (a, t c)
- forM :: (Traversable t, Monad m) => t a -> (a -> m b) -> m (t b)
- optional :: Alternative f => f a -> f (Maybe a)
- newtype WrappedMonad (m :: Type -> Type) a = WrapMonad {
- unwrapMonad :: m a
- newtype WrappedArrow (a :: Type -> Type -> Type) b c = WrapArrow {
- unwrapArrow :: a b c
- newtype ZipList a = ZipList {
- getZipList :: [a]
- data ExitCode
- newtype Const a (b :: k) :: forall k. Type -> k -> Type = Const {
- getConst :: a
- find :: Foldable t => (a -> Bool) -> t a -> Maybe a
- notElem :: (Foldable t, Eq a) => a -> t a -> Bool
- minimumBy :: Foldable t => (a -> a -> Ordering) -> t a -> a
- maximumBy :: Foldable t => (a -> a -> Ordering) -> t a -> a
- all :: Foldable t => (a -> Bool) -> t a -> Bool
- any :: Foldable t => (a -> Bool) -> t a -> Bool
- or :: Foldable t => t Bool -> Bool
- and :: Foldable t => t Bool -> Bool
- concatMap :: Foldable t => (a -> [b]) -> t a -> [b]
- concat :: Foldable t => t [a] -> [a]
- msum :: (Foldable t, MonadPlus m) => t (m a) -> m a
- sequence_ :: (Foldable t, Monad m) => t (m a) -> m ()
- forM_ :: (Foldable t, Monad m) => t a -> (a -> m b) -> m ()
- mapM_ :: (Foldable t, Monad m) => (a -> m b) -> t a -> m ()
- newtype First a = First {}
- newtype Last a = Last {}
- newtype Ap (f :: k -> Type) (a :: k) :: forall k. (k -> Type) -> k -> Type = Ap {
- getAp :: f a
- newtype Dual a = Dual {
- getDual :: a
- newtype Endo a = Endo {
- appEndo :: a -> a
- newtype All = All {}
- newtype Any = Any {}
- newtype Sum a = Sum {
- getSum :: a
- newtype Product a = Product {
- getProduct :: a
- newtype Alt (f :: k -> Type) (a :: k) :: forall k. (k -> Type) -> k -> Type = Alt {
- getAlt :: f a
- unwords :: [String] -> String
- words :: String -> [String]
- unfoldr :: (b -> Maybe (a, b)) -> b -> [a]
- sortOn :: Ord b => (a -> b) -> [a] -> [a]
- sortBy :: (a -> a -> Ordering) -> [a] -> [a]
- sort :: Ord a => [a] -> [a]
- permutations :: [a] -> [[a]]
- subsequences :: [a] -> [[a]]
- tails :: [a] -> [[a]]
- inits :: [a] -> [[a]]
- groupBy :: (a -> a -> Bool) -> [a] -> [[a]]
- group :: Eq a => [a] -> [[a]]
- deleteFirstsBy :: (a -> a -> Bool) -> [a] -> [a] -> [a]
- unzip7 :: [(a, b, c, d, e, f, g)] -> ([a], [b], [c], [d], [e], [f], [g])
- unzip6 :: [(a, b, c, d, e, f)] -> ([a], [b], [c], [d], [e], [f])
- unzip5 :: [(a, b, c, d, e)] -> ([a], [b], [c], [d], [e])
- unzip4 :: [(a, b, c, d)] -> ([a], [b], [c], [d])
- zipWith7 :: (a -> b -> c -> d -> e -> f -> g -> h) -> [a] -> [b] -> [c] -> [d] -> [e] -> [f] -> [g] -> [h]
- zipWith6 :: (a -> b -> c -> d -> e -> f -> g) -> [a] -> [b] -> [c] -> [d] -> [e] -> [f] -> [g]
- zipWith5 :: (a -> b -> c -> d -> e -> f) -> [a] -> [b] -> [c] -> [d] -> [e] -> [f]
- zipWith4 :: (a -> b -> c -> d -> e) -> [a] -> [b] -> [c] -> [d] -> [e]
- zip7 :: [a] -> [b] -> [c] -> [d] -> [e] -> [f] -> [g] -> [(a, b, c, d, e, f, g)]
- zip6 :: [a] -> [b] -> [c] -> [d] -> [e] -> [f] -> [(a, b, c, d, e, f)]
- zip5 :: [a] -> [b] -> [c] -> [d] -> [e] -> [(a, b, c, d, e)]
- zip4 :: [a] -> [b] -> [c] -> [d] -> [(a, b, c, d)]
- genericReplicate :: Integral i => i -> a -> [a]
- genericIndex :: Integral i => [a] -> i -> a
- genericSplitAt :: Integral i => i -> [a] -> ([a], [a])
- genericDrop :: Integral i => i -> [a] -> [a]
- genericTake :: Integral i => i -> [a] -> [a]
- genericLength :: Num i => [a] -> i
- insertBy :: (a -> a -> Ordering) -> a -> [a] -> [a]
- insert :: Ord a => a -> [a] -> [a]
- partition :: (a -> Bool) -> [a] -> ([a], [a])
- transpose :: [[a]] -> [[a]]
- intercalate :: [a] -> [[a]] -> [a]
- intersperse :: a -> [a] -> [a]
- intersectBy :: (a -> a -> Bool) -> [a] -> [a] -> [a]
- intersect :: Eq a => [a] -> [a] -> [a]
- unionBy :: (a -> a -> Bool) -> [a] -> [a] -> [a]
- union :: Eq a => [a] -> [a] -> [a]
- (\\) :: Eq a => [a] -> [a] -> [a]
- deleteBy :: (a -> a -> Bool) -> a -> [a] -> [a]
- nubBy :: (a -> a -> Bool) -> [a] -> [a]
- nub :: Eq a => [a] -> [a]
- isSuffixOf :: Eq a => [a] -> [a] -> Bool
- isPrefixOf :: Eq a => [a] -> [a] -> Bool
- findIndices :: (a -> Bool) -> [a] -> [Int]
- findIndex :: (a -> Bool) -> [a] -> Maybe Int
- elemIndices :: Eq a => a -> [a] -> [Int]
- elemIndex :: Eq a => a -> [a] -> Maybe Int
- stripPrefix :: Eq a => [a] -> [a] -> Maybe [a]
- dropWhileEnd :: (a -> Bool) -> [a] -> [a]
- (&) :: a -> (a -> b) -> b
- void :: Functor f => f a -> f ()
- unzip3 :: [(a, b, c)] -> ([a], [b], [c])
- unzip :: [(a, b)] -> ([a], [b])
- zipWith3 :: (a -> b -> c -> d) -> [a] -> [b] -> [c] -> [d]
- zipWith :: (a -> b -> c) -> [a] -> [b] -> [c]
- zip3 :: [a] -> [b] -> [c] -> [(a, b, c)]
- (!!) :: [a] -> Int -> a
- lookup :: Eq a => a -> [(a, b)] -> Maybe b
- reverse :: [a] -> [a]
- break :: (a -> Bool) -> [a] -> ([a], [a])
- span :: (a -> Bool) -> [a] -> ([a], [a])
- splitAt :: Int -> [a] -> ([a], [a])
- drop :: Int -> [a] -> [a]
- take :: Int -> [a] -> [a]
- dropWhile :: (a -> Bool) -> [a] -> [a]
- takeWhile :: (a -> Bool) -> [a] -> [a]
- cycle :: [a] -> [a]
- replicate :: Int -> a -> [a]
- repeat :: a -> [a]
- iterate' :: (a -> a) -> a -> [a]
- iterate :: (a -> a) -> a -> [a]
- scanr1 :: (a -> a -> a) -> [a] -> [a]
- scanr :: (a -> b -> b) -> b -> [a] -> [b]
- scanl' :: (b -> a -> b) -> b -> [a] -> [b]
- scanl1 :: (a -> a -> a) -> [a] -> [a]
- scanl :: (b -> a -> b) -> b -> [a] -> [b]
- foldl1' :: (a -> a -> a) -> [a] -> a
- init :: [a] -> [a]
- last :: [a] -> a
- tail :: [a] -> [a]
- uncons :: [a] -> Maybe (a, [a])
- head :: [a] -> a
- mapMaybe :: (a -> Maybe b) -> [a] -> [b]
- catMaybes :: [Maybe a] -> [a]
- listToMaybe :: [a] -> Maybe a
- maybeToList :: Maybe a -> [a]
- fromMaybe :: a -> Maybe a -> a
- fromJust :: Maybe a -> a
- isNothing :: Maybe a -> Bool
- isJust :: Maybe a -> Bool
- maybe :: b -> (a -> b) -> Maybe a -> b
- ap :: Monad m => m (a -> b) -> m a -> m b
- liftM5 :: Monad m => (a1 -> a2 -> a3 -> a4 -> a5 -> r) -> m a1 -> m a2 -> m a3 -> m a4 -> m a5 -> m r
- liftM4 :: Monad m => (a1 -> a2 -> a3 -> a4 -> r) -> m a1 -> m a2 -> m a3 -> m a4 -> m r
- liftM3 :: Monad m => (a1 -> a2 -> a3 -> r) -> m a1 -> m a2 -> m a3 -> m r
- liftM2 :: Monad m => (a1 -> a2 -> r) -> m a1 -> m a2 -> m r
- when :: Applicative f => Bool -> f () -> f ()
- (=<<) :: Monad m => (a -> m b) -> m a -> m b
- liftA3 :: Applicative f => (a -> b -> c -> d) -> f a -> f b -> f c -> f d
- liftA :: Applicative f => (a -> b) -> f a -> f b
- (<**>) :: Applicative f => f a -> f (a -> b) -> f b
- data ReaderT r (m :: Type -> Type) a
- (</>) :: FilePath -> FilePath -> FilePath
- takeDirectory :: FilePath -> FilePath
- takeFileName :: FilePath -> FilePath
- (<.>) :: FilePath -> String -> FilePath
- replaceExtension :: FilePath -> String -> FilePath
- (^.) :: s -> Getting a s a -> a
- (.~) :: ASetter s t a b -> b -> s -> t
- (%~) :: ASetter s t a b -> (a -> b) -> s -> t
- type Lens s t a b = forall (f :: Type -> Type). Functor f => (a -> f b) -> s -> f t
- ppShow :: Show a => a -> String
- newtype B9Error = MkB9Error {}
- type WithIoExceptions e = SetMember Exc (Exc SomeException) e
- type ExcB9 = Exc SomeException
- runExcB9 :: Eff (ExcB9 ': e) a -> Eff e (Either SomeException a)
- errorOnException :: Lifted IO e => Eff (ExcB9 ': e) a -> Eff e a
- throwSomeException :: (Member ExcB9 e, Exception x) => x -> Eff e a
- throwSomeException_ :: (Member ExcB9 e, Exception x) => x -> Eff e ()
- throwB9Error :: Member ExcB9 e => String -> Eff e a
- throwB9Error_ :: Member ExcB9 e => String -> Eff e ()
- catchB9Error :: Member ExcB9 e => Eff e a -> (SomeException -> Eff e a) -> Eff e a
- catchB9ErrorAsEither :: Member ExcB9 e => Eff e a -> Eff e (Either SomeException a)
- finallyB9 :: Member ExcB9 e => Eff e a -> Eff e () -> Eff e a
- arbitraryEnv :: Arbitrary a => Gen [(String, a)]
- halfSize :: Gen a -> Gen a
- smaller :: Gen a -> Gen a
- arbitraryFilePath :: Gen FilePath
- arbitraryLetter :: Gen Char
- arbitraryLetterUpper :: Gen Char
- arbitraryLetterLower :: Gen Char
- arbitraryDigit :: Gen Char
- newtype SharedImageBuildId = SharedImageBuildId String
- newtype SharedImageDate = SharedImageDate String
- newtype SharedImageName = SharedImageName String
- data SharedImage = SharedImage SharedImageName SharedImageDate SharedImageBuildId ImageType FileSystem
- type Mounted a = (a, MountPoint)
- data ImageResize
- data SizeUnit
- data ImageSize = ImageSize Int SizeUnit
- data FileSystem
- = NoFileSystem
- | Ext4
- | Ext4_64
- | ISO9660
- | VFAT
- data ImageType
- data Image = Image FilePath ImageType FileSystem
- data Partition
- data ImageSource
- data ImageDestination
- data MountPoint
- data ImageTarget = ImageTarget ImageDestination ImageSource MountPoint
- bytesToKiloBytes :: Int -> ImageSize
- imageSizeToKiB :: ImageSize -> Int
- sizeUnitKiB :: SizeUnit -> Int
- normalizeSize :: ImageSize -> ImageSize
- addImageSize :: ImageSize -> ImageSize -> ImageSize
- fromSharedImageName :: SharedImageName -> String
- fromSharedImageBuildId :: SharedImageBuildId -> String
- sharedImagesToMap :: [SharedImage] -> Map SharedImageName (Set SharedImage)
- takeLatestSharedImage :: [SharedImage] -> Maybe SharedImage
- imageFileName :: Image -> FilePath
- imageImageType :: Image -> ImageType
- getImageDestinationOutputFiles :: ImageTarget -> [FilePath]
- imageDestinationSharedImageName :: ImageDestination -> Maybe SharedImageName
- imageSourceSharedImageName :: ImageSource -> Maybe SharedImageName
- itImageDestination :: ImageTarget -> ImageDestination
- itImageSource :: ImageTarget -> ImageSource
- itImageMountPoint :: ImageTarget -> MountPoint
- isPartitioned :: Partition -> Bool
- getPartition :: Partition -> Int
- imageFileExtension :: ImageType -> String
- changeImageFormat :: ImageType -> Image -> Image
- changeImageDirectory :: FilePath -> Image -> Image
- getImageSourceImageType :: ImageSource -> Maybe ImageType
- sharedImageName :: SharedImage -> SharedImageName
- sharedImageDate :: SharedImage -> SharedImageDate
- sharedImageBuildId :: SharedImage -> SharedImageBuildId
- prettyPrintSharedImages :: Set SharedImage -> String
- sharedImageImage :: SharedImage -> Image
- sharedImageFileName :: SharedImage -> FilePath
- sharedImagesRootDirectory :: FilePath
- sharedImageFileExtension :: String
- sharedImageDefaultImageType :: ImageType
- transientCOWImage :: FilePath -> FilePath -> ImageTarget
- transientSharedImage :: SharedImageName -> FilePath -> ImageTarget
- transientLocalImage :: FilePath -> FilePath -> ImageTarget
- shareCOWImage :: FilePath -> SharedImageName -> FilePath -> ImageTarget
- shareSharedImage :: SharedImageName -> SharedImageName -> FilePath -> ImageTarget
- shareLocalImage :: FilePath -> SharedImageName -> FilePath -> ImageTarget
- cowToliveInstallerImage :: String -> FilePath -> FilePath -> FilePath -> ImageTarget
- cowToLocalImage :: FilePath -> FilePath -> FilePath -> ImageTarget
- localToLocalImage :: FilePath -> FilePath -> FilePath -> ImageTarget
- partition1ToLocalImage :: FilePath -> FilePath -> FilePath -> ImageTarget
- splitToIntermediateSharedImage :: ImageTarget -> SharedImageName -> (ImageTarget, ImageTarget)
- arbitrarySharedImageName :: Gen String
- unitTests :: Spec
- data RamSize
- data CPUArch
- data Resources = Resources {}
- data SharedDirectory
- data ExecEnv = ExecEnv {}
- noResources :: Resources
- data User
- data Cwd
- data CmdVerbosity
- = Debug
- | Verbose
- | OnlyStdErr
- | Quiet
- data Script
- writeSh :: FilePath -> Script -> IO ()
- emptyScript :: Script -> Bool
- renderScript :: Script -> String
- class Textual a where
- renderToText :: HasCallStack => a -> Either String Text
- parseFromText :: HasCallStack => Text -> Either String a
- type LazyText = Text
- type LazyByteString = ByteString
- writeTextFile :: (HasCallStack, MonadIO m) => FilePath -> Text -> m ()
- unsafeRenderToText :: (Textual a, HasCallStack) => a -> Text
- unsafeParseFromText :: (Textual a, HasCallStack) => Text -> a
- encodeAsUtf8LazyByteString :: HasCallStack => String -> LazyByteString
- parseFromTextWithErrorMessage :: (HasCallStack, Textual a) => String -> Text -> Either String a
- data KeyNotFound = MkKeyNotFound Text Environment
- data DuplicateKey = MkDuplicateKey {}
- type EnvironmentReader = Reader Environment
- data Environment
- addPositionalArguments :: [Text] -> Environment -> Environment
- addLocalPositionalArguments :: Member EnvironmentReader e => [String] -> Eff e a -> Eff e a
- fromStringPairs :: [(String, String)] -> Environment
- addBinding :: Member ExcB9 e => (Text, Text) -> Environment -> Eff e Environment
- addStringBinding :: Member ExcB9 e => (String, String) -> Environment -> Eff e Environment
- addLocalStringBinding :: (Member EnvironmentReader e, Member ExcB9 e) => (String, String) -> Eff e a -> Eff e a
- runEnvironmentReader :: Environment -> Eff (EnvironmentReader ': e) a -> Eff e a
- askEnvironment :: Member EnvironmentReader e => Eff e Environment
- localEnvironment :: Member EnvironmentReader e => (Environment -> Environment) -> Eff e a -> Eff e a
- lookupOrThrow :: '[ExcB9, EnvironmentReader] <:: e => Text -> Eff e Text
- lookupEither :: Member EnvironmentReader e => Text -> Eff e (Either KeyNotFound Text)
- hasKey :: Member EnvironmentReader e => Text -> Eff e Bool
- data SimpleErlangTerm
- parseErlTerm :: String -> Text -> Either String SimpleErlangTerm
- renderErlTerm :: SimpleErlangTerm -> Text
- erlTermParser :: Parser SimpleErlangTerm
- arbitraryErlSimpleAtom :: Gen SimpleErlangTerm
- arbitraryErlString :: Gen SimpleErlangTerm
- arbitraryErlNumber :: Gen SimpleErlangTerm
- arbitraryErlNatural :: Gen SimpleErlangTerm
- arbitraryErlFloat :: Gen SimpleErlangTerm
- arbitraryErlNameChar :: Gen Char
- data UUID
- data ConsultException = ConsultException FilePath String
- data SystemPath
- overSystemPath :: (FilePath -> FilePath) -> SystemPath -> SystemPath
- resolve :: MonadIO m => SystemPath -> m FilePath
- getDirectoryFiles :: MonadIO m => FilePath -> m [FilePath]
- ensureSystemPath :: MonadIO m => SystemPath -> m ()
- ensureDir :: MonadIO m => FilePath -> m ()
- prettyPrintToFile :: (MonadIO m, Show a) => FilePath -> a -> m ()
- consult :: (MonadIO m, Read a) => FilePath -> m a
- randomUUID :: MonadIO m => m UUID
- removeIfExists :: FilePath -> IO ()
- newtype SshRemoteUser = SshRemoteUser String
- newtype SshRemoteHost = SshRemoteHost (String, Int)
- newtype SshPrivKey = SshPrivKey FilePath
- data RemoteRepo = RemoteRepo String FilePath SshPrivKey SshRemoteHost SshRemoteUser
- newtype RepoCache = RepoCache FilePath
- remoteRepoRepoId :: RemoteRepo -> String
- remoteRepoToCPDocument :: RemoteRepo -> CPDocument -> Either CPError CPDocument
- parseRemoteRepos :: CPDocument -> Either CPError [RemoteRepo]
- data ContainerCapability
- = CAP_MKNOD
- | CAP_AUDIT_CONTROL
- | CAP_AUDIT_READ
- | CAP_AUDIT_WRITE
- | CAP_BLOCK_SUSPEND
- | CAP_CHOWN
- | CAP_DAC_OVERRIDE
- | CAP_DAC_READ_SEARCH
- | CAP_FOWNER
- | CAP_FSETID
- | CAP_IPC_LOCK
- | CAP_IPC_OWNER
- | CAP_KILL
- | CAP_LEASE
- | CAP_LINUX_IMMUTABLE
- | CAP_MAC_ADMIN
- | CAP_MAC_OVERRIDE
- | CAP_NET_ADMIN
- | CAP_NET_BIND_SERVICE
- | CAP_NET_BROADCAST
- | CAP_NET_RAW
- | CAP_SETGID
- | CAP_SETFCAP
- | CAP_SETPCAP
- | CAP_SETUID
- | CAP_SYS_ADMIN
- | CAP_SYS_BOOT
- | CAP_SYS_CHROOT
- | CAP_SYS_MODULE
- | CAP_SYS_NICE
- | CAP_SYS_PACCT
- | CAP_SYS_PTRACE
- | CAP_SYS_RAWIO
- | CAP_SYS_RESOURCE
- | CAP_SYS_TIME
- | CAP_SYS_TTY_CONFIG
- | CAP_SYSLOG
- | CAP_WAKE_ALARM
- containerCapsToCPDocument :: CPDocument -> CPSectionSpec -> [ContainerCapability] -> Either CPError CPDocument
- parseContainerCapabilities :: CPDocument -> CPSectionSpec -> Either CPError [ContainerCapability]
- data SystemdNspawnConsole
- data SystemdNspawnConfig = SystemdNspawnConfig {}
- systemdNspawnCapabilities :: Lens' SystemdNspawnConfig [ContainerCapability]
- systemdNspawnConsole :: Lens' SystemdNspawnConfig SystemdNspawnConsole
- systemdNspawnExecutable :: Lens' SystemdNspawnConfig (Maybe FilePath)
- systemdNspawnExtraArgs :: Lens' SystemdNspawnConfig (Maybe String)
- systemdNspawnMaxLifetimeSeconds :: Lens' SystemdNspawnConfig (Maybe Int)
- systemdNspawnUseSudo :: Lens' SystemdNspawnConfig Bool
- defaultSystemdNspawnConfig :: SystemdNspawnConfig
- systemdNspawnConfigToCPDocument :: SystemdNspawnConfig -> CPDocument -> Either CPError CPDocument
- parseSystemdNspawnConfig :: CPDocument -> Either CPError SystemdNspawnConfig
- data PodmanConfig = PodmanConfig {}
- podmanCapabilities :: Lens' PodmanConfig [ContainerCapability]
- podmanNetworkId :: Lens' PodmanConfig (Maybe String)
- defaultPodmanConfig :: PodmanConfig
- podmanConfigToCPDocument :: PodmanConfig -> CPDocument -> Either CPError CPDocument
- parsePodmanConfig :: CPDocument -> Either CPError PodmanConfig
- data LibVirtLXCConfig = LibVirtLXCConfig {}
- networkId :: Lens' LibVirtLXCConfig (Maybe String)
- defaultLibVirtLXCConfig :: LibVirtLXCConfig
- libVirtLXCConfigToCPDocument :: LibVirtLXCConfig -> CPDocument -> Either CPError CPDocument
- parseLibVirtLXCConfig :: CPDocument -> Either CPError LibVirtLXCConfig
- getEmulatorPath :: MonadIO m => LibVirtLXCConfig -> m FilePath
- data DockerConfig = DockerConfig {}
- dockerCapabilities :: Lens' DockerConfig [ContainerCapability]
- dockerNetworkId :: Lens' DockerConfig (Maybe String)
- defaultDockerConfig :: DockerConfig
- dockerConfigToCPDocument :: DockerConfig -> CPDocument -> Either CPError CPDocument
- parseDockerConfig :: CPDocument -> Either CPError DockerConfig
- data B9ConfigOverride = B9ConfigOverride {}
- type B9ConfigReader = Reader B9Config
- data B9Config = B9Config {
- _verbosity :: Maybe LogLevel
- _logFile :: Maybe FilePath
- _projectRoot :: Maybe FilePath
- _keepTempDirs :: Bool
- _uniqueBuildDirs :: Bool
- _repositoryCache :: Maybe SystemPath
- _repository :: Maybe String
- _interactive :: Bool
- _maxLocalSharedImageRevisions :: Maybe Int
- _systemdNspawnConfigs :: Maybe SystemdNspawnConfig
- _podmanConfigs :: Maybe PodmanConfig
- _dockerConfigs :: Maybe DockerConfig
- _libVirtLXCConfigs :: Maybe LibVirtLXCConfig
- _remoteRepos :: [RemoteRepo]
- _defaultTimeout :: Maybe Timeout
- _timeoutFactor :: Maybe Int
- data LogLevel
- newtype Timeout = TimeoutMicros Int
- runB9ConfigReader :: HasCallStack => B9Config -> Eff (B9ConfigReader ': e) a -> Eff e a
- getB9Config :: Member B9ConfigReader e => Eff e B9Config
- localB9Config :: Member B9ConfigReader e => (B9Config -> B9Config) -> Eff e a -> Eff e a
- getConfig :: Member B9ConfigReader e => Eff e B9Config
- isInteractive :: Member B9ConfigReader e => Eff e Bool
- getRemoteRepos :: Member B9ConfigReader e => Eff e [RemoteRepo]
- getLogVerbosity :: Member B9ConfigReader e => Eff e (Maybe LogLevel)
- getProjectRoot :: Member B9ConfigReader e => Eff e FilePath
- noB9ConfigOverride :: B9ConfigOverride
- defaultTimeout :: Lens' B9Config (Maybe Timeout)
- dockerConfigs :: Lens' B9Config (Maybe DockerConfig)
- interactive :: Lens' B9Config Bool
- keepTempDirs :: Lens' B9Config Bool
- libVirtLXCConfigs :: Lens' B9Config (Maybe LibVirtLXCConfig)
- logFile :: Lens' B9Config (Maybe FilePath)
- maxLocalSharedImageRevisions :: Lens' B9Config (Maybe Int)
- podmanConfigs :: Lens' B9Config (Maybe PodmanConfig)
- projectRoot :: Lens' B9Config (Maybe FilePath)
- remoteRepos :: Lens' B9Config [RemoteRepo]
- repository :: Lens' B9Config (Maybe String)
- repositoryCache :: Lens' B9Config (Maybe SystemPath)
- systemdNspawnConfigs :: Lens' B9Config (Maybe SystemdNspawnConfig)
- timeoutFactor :: Lens' B9Config (Maybe Int)
- uniqueBuildDirs :: Lens' B9Config Bool
- verbosity :: Lens' B9Config (Maybe LogLevel)
- type B9ConfigWriter = Writer (Endo B9Config)
- type B9ConfigAction a = Eff '[B9ConfigWriter, B9ConfigReader, EnvironmentReader, Lift IO] a
- customB9Config :: Lens' B9ConfigOverride (Endo B9Config)
- customB9ConfigPath :: Lens' B9ConfigOverride (Maybe SystemPath)
- customDefaulB9ConfigPath :: Lens' B9ConfigOverride (Maybe SystemPath)
- customEnvironment :: Lens' B9ConfigOverride Environment
- overrideB9ConfigPath :: SystemPath -> B9ConfigOverride -> B9ConfigOverride
- overrideB9Config :: (B9Config -> B9Config) -> B9ConfigOverride -> B9ConfigOverride
- overrideDefaultB9ConfigPath :: SystemPath -> B9ConfigOverride -> B9ConfigOverride
- overrideWorkingDirectory :: FilePath -> B9ConfigOverride -> B9ConfigOverride
- overrideDefaultTimeout :: Maybe Timeout -> B9ConfigOverride -> B9ConfigOverride
- overrideTimeoutFactor :: Maybe Int -> B9ConfigOverride -> B9ConfigOverride
- overrideVerbosity :: LogLevel -> B9ConfigOverride -> B9ConfigOverride
- overrideKeepBuildDirs :: Bool -> B9ConfigOverride -> B9ConfigOverride
- modifyPermanentConfig :: (HasCallStack, Member B9ConfigWriter e) => Endo B9Config -> Eff e ()
- runB9ConfigActionWithOverrides :: HasCallStack => B9ConfigAction a -> B9ConfigOverride -> IO a
- runB9ConfigAction :: HasCallStack => B9ConfigAction a -> IO a
- openOrCreateB9Config :: (HasCallStack, MonadIO m) => FilePath -> m CPDocument
- writeB9CPDocument :: (HasCallStack, MonadIO m) => Maybe SystemPath -> CPDocument -> m ()
- defaultB9Config :: B9Config
- defaultRepositoryCache :: SystemPath
- defaultB9ConfigFile :: SystemPath
- maxLocalSharedImageRevisionsK :: String
- modifyCPDocument :: CPDocument -> Endo B9Config -> Either CPError CPDocument
- b9ConfigToCPDocument :: HasCallStack => B9Config -> Either CPError CPDocument
- readB9Config :: (HasCallStack, MonadIO m) => Maybe SystemPath -> m CPDocument
- parseB9Config :: HasCallStack => CPDocument -> Either CPError B9Config
- type RepoImagesMap = Map Repository (Set SharedImage)
- type SelectedRemoteRepoReader = Reader SelectedRemoteRepo
- newtype SelectedRemoteRepo = MkSelectedRemoteRepo {}
- type RepoCacheReader = Reader RepoCache
- data Repository
- toRemoteRepository :: RemoteRepo -> Repository
- getRepoCache :: Member RepoCacheReader e => Eff e RepoCache
- withSelectedRemoteRepo :: (Member B9ConfigReader e, Member ExcB9 e) => Eff (SelectedRemoteRepoReader ': e) a -> Eff e a
- getSelectedRemoteRepo :: Member SelectedRemoteRepoReader e => Eff e SelectedRemoteRepo
- remoteRepoCacheDir :: RepoCache -> String -> FilePath
- localRepoDir :: RepoCache -> FilePath
- lookupRemoteRepo :: [RemoteRepo] -> String -> Maybe RemoteRepo
- filterRepoImagesMap :: (Repository -> Bool) -> (SharedImage -> Bool) -> RepoImagesMap -> RepoImagesMap
- lookupCachedImages :: SharedImageName -> RepoImagesMap -> Set SharedImage
- allRepositories :: RepoImagesMap -> Set Repository
- allSharedImages :: RepoImagesMap -> Set SharedImage
- allSharedImagesWithRepo :: RepoImagesMap -> Set (SharedImage, Repository)
- maxSharedImageOfAllRepos :: RepoImagesMap -> Maybe (SharedImage, Repository)
- allSharedImagesInRepo :: Repository -> RepoImagesMap -> Set SharedImage
- allCachedSharedImages :: RepoImagesMap -> Set SharedImage
- keepNLatestSharedImages :: Int -> Set SharedImage -> Set SharedImage
- dropAllButNLatestSharedImages :: Int -> Set SharedImage -> Set SharedImage
- groupBySharedImageName :: Set SharedImage -> Map SharedImageName (Set SharedImage)
- type CommandIO e = (MonadBaseControl IO (Eff e), MonadIO (Eff e), Member LoggerReader e, Member B9ConfigReader e)
- type LoggerReader = Reader Logger
- newtype Logger = MkLogger {}
- withLogger :: (MonadBaseControl IO (Eff e), MonadIO (Eff e), Member B9ConfigReader e) => Eff (LoggerReader ': e) a -> Eff e a
- traceL :: CommandIO e => String -> Eff e ()
- dbgL :: CommandIO e => String -> Eff e ()
- infoL :: CommandIO e => String -> Eff e ()
- errorL :: CommandIO e => String -> Eff e ()
- errorExitL :: (CommandIO e, Member ExcB9 e) => String -> Eff e a
- b9Log :: CommandIO e => LogLevel -> String -> Eff e ()
- printHash :: Hashable a => a -> String
- type BuildInfoReader = Reader BuildInfo
- withBuildInfo :: (Lifted IO e, MonadBaseControl IO (Eff e), Member B9ConfigReader e, Member ExcB9 e, Member EnvironmentReader e, Member LoggerReader e, HasCallStack) => Eff (BuildInfoReader ': e) a -> Eff e a
- getBuildId :: Member BuildInfoReader e => Eff e String
- getBuildDate :: Member BuildInfoReader e => Eff e String
- getBuildDir :: Member BuildInfoReader e => Eff e FilePath
- data HostCommandStdin
- cmd :: (HasCallStack, Member ExcB9 e, CommandIO e) => String -> Eff e ()
- hostCmd :: (CommandIO e, Member ExcB9 e) => String -> Maybe Timeout -> Eff e Bool
- hostCmdStdIn :: (CommandIO e, Member ExcB9 e) => HostCommandStdin -> String -> Maybe Timeout -> Eff e Bool
- hostCmdEither :: forall e. CommandIO e => HostCommandStdin -> String -> Maybe Timeout -> Eff e (Either Timeout ExitCode)
- newtype FilePathGlob = FileExtension String
- withRemoteRepos :: (Member B9ConfigReader e, Lifted IO e) => Eff (RepoCacheReader ': e) a -> Eff e a
- remoteRepoCheckSshPrivKey :: MonadIO m => RemoteRepo -> m RemoteRepo
- cleanRemoteRepo :: MonadIO m => RepoCache -> RemoteRepo -> m ()
- repoSearch :: forall e. (CommandIO e, Member RepoCacheReader e) => FilePath -> FilePathGlob -> Eff e [(Repository, [FilePath])]
- pushToRepo :: (Member ExcB9 e, CommandIO e) => RemoteRepo -> FilePath -> FilePath -> Eff e ()
- pullFromRepo :: (Member ExcB9 e, CommandIO e) => RemoteRepo -> FilePath -> FilePath -> Eff e ()
- pullGlob :: (Member ExcB9 e, CommandIO e, Member RepoCacheReader e) => FilePath -> FilePathGlob -> RemoteRepo -> Eff e ()
- getSharedImages :: (HasCallStack, CommandIO e, Lifted IO e, Member RepoCacheReader e) => Eff e (Map Repository (Set SharedImage))
- pullRemoteRepos :: (HasCallStack, Member ExcB9 e, Lifted IO e, CommandIO e, '[SelectedRemoteRepoReader, RepoCacheReader] <:: e) => Eff e ()
- pullLatestImage :: (HasCallStack, Lifted IO e, CommandIO e, '[ExcB9, RepoCacheReader, SelectedRemoteRepoReader] <:: e) => SharedImageName -> Eff e (Maybe SharedImageBuildId)
- getLatestImageByName :: (HasCallStack, Lifted IO e, CommandIO e, Member RepoCacheReader e) => SharedImageName -> Eff e (Maybe Image)
- cleanOldSharedImageRevisionsFromCache :: ('[RepoCacheReader, ExcB9] <:: e, Lifted IO e, CommandIO e) => SharedImageName -> Eff e ()
- cleanLocalRepoCache :: ('[RepoCacheReader, ExcB9] <:: e, Lifted IO e, CommandIO e) => Eff e ()
- pushSharedImageLatestVersion :: (Lifted IO e, CommandIO e, '[SelectedRemoteRepoReader, RepoCacheReader, ExcB9] <:: e) => SharedImageName -> Eff e ()
- pushToSelectedRepo :: (Member ExcB9 e, Lifted IO e, CommandIO e, '[RepoCacheReader, SelectedRemoteRepoReader] <:: e) => SharedImage -> Eff e ()
- getSelectedRepos :: '[B9ConfigReader, SelectedRemoteRepoReader] <:: e => Eff e [RemoteRepo]
- getSharedImagesCacheDir :: '[RepoCacheReader] <:: e => Eff e FilePath
- type IsB9 e = (HasCallStack, Lifted IO e, CommandIO e, B9Eff <:: e)
- type B9Eff = '[SelectedRemoteRepoReader, RepoCacheReader, BuildInfoReader, LoggerReader, B9ConfigReader, EnvironmentReader, ExcB9, Lift IO]
- type B9 a = Eff B9Eff a
- runB9 :: HasCallStack => B9 a -> B9ConfigAction a
- class ToContentGenerator c where
- toContentGenerator :: (HasCallStack, IsB9 e) => c -> Eff e Text
- type ContentGenerator = B9 Text
- data SourceFileConversion
- data SourceFile = Source SourceFileConversion FilePath
- readTemplateFile :: (MonadIO (Eff e), '[ExcB9, EnvironmentReader] <:: e) => SourceFile -> Eff e Text
- subst :: (Member ExcB9 e, Member EnvironmentReader e) => Text -> Eff e Text
- substStr :: (Member ExcB9 e, Member EnvironmentReader e) => String -> Eff e String
- substFile :: (Member EnvironmentReader e, Member ExcB9 e, MonadIO (Eff e)) => FilePath -> FilePath -> Eff e ()
- substPath :: (Member EnvironmentReader e, Member ExcB9 e) => SystemPath -> Eff e SystemPath
- withSubstitutedStringBindings :: (Member EnvironmentReader e, Member ExcB9 e) => [(String, String)] -> Eff e s -> Eff e s
- data VmScript
- substVmScript :: forall e. (Member EnvironmentReader e, Member ExcB9 e) => VmScript -> Eff e VmScript
- substImageTarget :: forall e. (HasCallStack, Member EnvironmentReader e, Member ExcB9 e) => ImageTarget -> Eff e ImageTarget
- resolveImageSource :: IsB9 e => ImageSource -> Eff e Image
- preferredDestImageTypes :: IsB9 e => ImageSource -> Eff e [ImageType]
- preferredSourceImageTypes :: HasCallStack => ImageDestination -> [ImageType]
- ensureAbsoluteImageDirExists :: IsB9 e => Image -> Eff e Image
- materializeImageSource :: IsB9 e => ImageSource -> Image -> Eff e ()
- createDestinationImage :: IsB9 e => Image -> ImageDestination -> Eff e ()
- resizeImage :: IsB9 e => ImageResize -> Image -> Eff e ()
- importImage :: IsB9 e => Image -> Image -> Eff e ()
- exportImage :: IsB9 e => Image -> Image -> Eff e ()
- exportAndRemoveImage :: IsB9 e => Image -> Image -> Eff e ()
- convertImage :: IsB9 e => Image -> Image -> Eff e ()
- shareImage :: IsB9 e => Image -> SharedImageName -> Eff e SharedImage
- class FromAST a where
- fromAST :: (IsB9 e, ToContentGenerator c) => AST c a -> Eff e a
- data AST c a
- newtype YamlObject = YamlObject {}
- newtype ErlangPropList = ErlangPropList SimpleErlangTerm
- textToErlangAst :: Text -> AST c ErlangPropList
- stringToErlangAst :: String -> AST c ErlangPropList
- newtype CloudConfigYaml = MkCloudConfigYaml {}
- cloudConfigFileHeader :: Text
- type ErlangAst = AST Content ErlangPropList
- data Content
- data ArtifactSource
- getArtifactSourceFiles :: ArtifactSource -> [FilePath]
- data AssemblyOutput
- data CloudInitType
- data ArtifactTarget
- data AssembledArtifact = AssembledArtifact InstanceId [ArtifactTarget]
- data ArtifactAssembly
- newtype InstanceId = IID String
- data ArtifactGenerator
- = Sources [ArtifactSource] [ArtifactGenerator]
- | Let [(String, String)] [ArtifactGenerator]
- | LetX [(String, [String])] [ArtifactGenerator]
- | Each [(String, [String])] [ArtifactGenerator]
- | EachT [String] [[String]] [ArtifactGenerator]
- | Artifact InstanceId ArtifactAssembly
- | EmptyArtifact
- instanceIdKey :: String
- buildIdKey :: String
- buildDateKey :: String
- getAssemblyOutput :: ArtifactAssembly -> [AssemblyOutput]
- buildWithVm :: IsB9 e => InstanceId -> [ImageTarget] -> FilePath -> VmScript -> Eff e Bool
- data InstanceGenerator e = IG InstanceId e ArtifactAssembly
- data InstanceSources = InstanceSources {
- isEnv :: Environment
- isSources :: [ArtifactSource]
- buildArtifacts :: ArtifactGenerator -> B9 String
- getArtifactOutputFiles :: ArtifactGenerator -> Either SomeException [FilePath]
- assemble :: ArtifactGenerator -> B9 [AssembledArtifact]
- runArtifactGenerator :: Environment -> String -> String -> ArtifactGenerator -> Either SomeException [InstanceGenerator [TextFileWriter]]
- runInstanceGenerator :: IsB9 e => InstanceGenerator FilePath -> Eff e AssembledArtifact
- runArtifactAssembly :: IsB9 e => InstanceId -> FilePath -> ArtifactAssembly -> Eff e [ArtifactTarget]
Documentation
b9VersionString :: String Source #
Return the cabal package version of the B9 library,
formatted using showVersion
.
runShowVersion :: MonadIO m => m () Source #
Just print the b9VersionString
runBuildArtifacts :: [FilePath] -> B9ConfigAction String Source #
Execute the artifact generators defined in a list of text files.
Read the text files in the list and parse them as ArtifactGenerator
s
then mappend
them and apply buildArtifacts
to them.
runFormatBuildFiles :: MonadIO m => [FilePath] -> m () Source #
Read all text files and parse them as ArtifactGenerator
s.
Then overwrite the files with their contents but _pretty printed_
(i.e. formatted).
runPush :: SharedImageName -> B9ConfigAction () Source #
Upload a SharedImageName
to the default remote repository.
Note: The remote repository is specified in the B9Config
.
runPull :: Maybe SharedImageName -> B9ConfigAction () Source #
Either pull a list of available SharedImageName
s from the remote
repository if Nothing
is passed as parameter, or pull the latest version
of the image from the remote repository. Note: The remote repository is
specified in the B9Config
.
runRun :: SharedImageName -> [String] -> B9ConfigAction String Source #
Execute an interactive root shell in a running container from a
SharedImageName
.
runGcLocalRepoCache :: B9ConfigAction () Source #
Delete all obsolete versions of all SharedImageName
s.
runGcRemoteRepoCache :: B9ConfigAction () Source #
Clear the shared image cache for a remote. Note: The remote repository is
specified in the B9Config
.
runListSharedImages :: B9ConfigAction (Set SharedImage) Source #
Print a list of shared images cached locally or remotely, if a remote
repository was selected. Note: The remote repository is
specified in the B9Config
.
runAddRepo :: RemoteRepo -> B9ConfigAction () Source #
Check the SSH settings for a remote repository and add it to the user wide B9 configuration file.
runLookupLocalSharedImage :: SharedImageName -> B9ConfigAction (Maybe SharedImageBuildId) Source #
Find the most recent version of a SharedImageName
in the local image cache.
(++) :: [a] -> [a] -> [a] infixr 5 #
Append two lists, i.e.,
[x1, ..., xm] ++ [y1, ..., yn] == [x1, ..., xm, y1, ..., yn] [x1, ..., xm] ++ [y1, ...] == [x1, ..., xm, y1, ...]
If the first list is not finite, the result is the first list.
filter :: (a -> Bool) -> [a] -> [a] #
filter
, applied to a predicate and a list, returns the list of
those elements that satisfy the predicate; i.e.,
filter p xs = [ x | x <- xs, p x]
map :: (a -> b) -> [a] -> [b] #
map
f xs
is the list obtained by applying f
to each element
of xs
, i.e.,
map f [x1, x2, ..., xn] == [f x1, f x2, ..., f xn] map f [x1, x2, ...] == [f x1, f x2, ...]
guard :: Alternative f => Bool -> f () #
Conditional failure of Alternative
computations. Defined by
guard True =pure
() guard False =empty
Examples
Common uses of guard
include conditionally signaling an error in
an error monad and conditionally rejecting the current choice in an
Alternative
-based parser.
As an example of signaling an error in the error monad Maybe
,
consider a safe division function safeDiv x y
that returns
Nothing
when the denominator y
is zero and
otherwise. For example:Just
(x `div`
y)
>>> safeDiv 4 0 Nothing >>> safeDiv 4 2 Just 2
A definition of safeDiv
using guards, but not guard
:
safeDiv :: Int -> Int -> Maybe Int safeDiv x y | y /= 0 = Just (x `div` y) | otherwise = Nothing
A definition of safeDiv
using guard
and Monad
do
-notation:
safeDiv :: Int -> Int -> Maybe Int safeDiv x y = do guard (y /= 0) return (x `div` y)
join :: Monad m => m (m a) -> m a #
The join
function is the conventional monad join operator. It
is used to remove one level of monadic structure, projecting its
bound argument into the outer level.
Examples
A common use of join
is to run an IO
computation returned from
an STM
transaction, since STM
transactions
can't perform IO
directly. Recall that
atomically
:: STM a -> IO a
is used to run STM
transactions atomically. So, by
specializing the types of atomically
and join
to
atomically
:: STM (IO b) -> IO (IO b)join
:: IO (IO b) -> IO b
we can compose them as
join
.atomically
:: STM (IO b) -> IO b
class Applicative m => Monad (m :: Type -> Type) where #
The Monad
class defines the basic operations over a monad,
a concept from a branch of mathematics known as category theory.
From the perspective of a Haskell programmer, however, it is best to
think of a monad as an abstract datatype of actions.
Haskell's do
expressions provide a convenient syntax for writing
monadic expressions.
Instances of Monad
should satisfy the following laws:
Furthermore, the Monad
and Applicative
operations should relate as follows:
The above laws imply:
and that pure
and (<*>
) satisfy the applicative functor laws.
The instances of Monad
for lists, Maybe
and IO
defined in the Prelude satisfy these laws.
(>>=) :: m a -> (a -> m b) -> m b infixl 1 #
Sequentially compose two actions, passing any value produced by the first as an argument to the second.
(>>) :: m a -> m b -> m b infixl 1 #
Sequentially compose two actions, discarding any value produced by the first, like sequencing operators (such as the semicolon) in imperative languages.
Inject a value into the monadic type.
Fail with a message. This operation is not part of the
mathematical definition of a monad, but is invoked on pattern-match
failure in a do
expression.
As part of the MonadFail proposal (MFP), this function is moved
to its own class MonadFail
(see Control.Monad.Fail for more
details). The definition here will be removed in a future
release.
Instances
Monad [] | Since: base-2.1 |
Monad Maybe | Since: base-2.1 |
Monad IO | Since: base-2.1 |
Monad Par1 | Since: base-4.9.0.0 |
Monad Q | |
Monad Rose | |
Monad Gen | |
Monad IResult | |
Monad Result | |
Monad Parser | |
Monad Complex | Since: base-4.9.0.0 |
Monad Min | Since: base-4.9.0.0 |
Monad Max | Since: base-4.9.0.0 |
Monad First | Since: base-4.9.0.0 |
Monad Last | Since: base-4.9.0.0 |
Monad Option | Since: base-4.9.0.0 |
Monad Identity | Since: base-4.8.0.0 |
Monad STM | Since: base-4.3.0.0 |
Monad First | Since: base-4.8.0.0 |
Monad Last | Since: base-4.8.0.0 |
Monad Dual | Since: base-4.8.0.0 |
Monad Sum | Since: base-4.8.0.0 |
Monad Product | Since: base-4.8.0.0 |
Monad Down | Since: base-4.11.0.0 |
Monad ReadPrec | Since: base-2.1 |
Monad ReadP | Since: base-2.1 |
Monad NonEmpty | Since: base-4.9.0.0 |
Monad PutM | |
Monad Get | |
Monad Tree | |
Monad Seq | |
Monad DList | |
Monad Eval | |
Monad Vector | |
Monad SmallArray | |
Defined in Data.Primitive.SmallArray (>>=) :: SmallArray a -> (a -> SmallArray b) -> SmallArray b # (>>) :: SmallArray a -> SmallArray b -> SmallArray b # return :: a -> SmallArray a # fail :: String -> SmallArray a # | |
Monad Array | |
Monad Rules | |
Monad Action | |
Monad Id | |
Monad Box | |
Monad P | Since: base-2.1 |
Monad SIO | |
Monad (Either e) | Since: base-4.4.0.0 |
Monad (U1 :: Type -> Type) | Since: base-4.9.0.0 |
Monoid a => Monad ((,) a) | Since: base-4.9.0.0 |
Monad (ST s) | Since: base-2.1 |
Representable f => Monad (Co f) | |
Monad (Parser i) | |
Monad (ST s) | Since: base-2.1 |
Monad m => Monad (WrappedMonad m) | Since: base-4.7.0.0 |
Defined in Control.Applicative (>>=) :: WrappedMonad m a -> (a -> WrappedMonad m b) -> WrappedMonad m b # (>>) :: WrappedMonad m a -> WrappedMonad m b -> WrappedMonad m b # return :: a -> WrappedMonad m a # fail :: String -> WrappedMonad m a # | |
ArrowApply a => Monad (ArrowMonad a) | Since: base-2.1 |
Defined in Control.Arrow (>>=) :: ArrowMonad a a0 -> (a0 -> ArrowMonad a b) -> ArrowMonad a b # (>>) :: ArrowMonad a a0 -> ArrowMonad a b -> ArrowMonad a b # return :: a0 -> ArrowMonad a a0 # fail :: String -> ArrowMonad a a0 # | |
Monad (Proxy :: Type -> Type) | Since: base-4.7.0.0 |
Monad m => Monad (MaybeT m) | |
Monad m => Monad (ResourceT m) | |
Monad (Eff r) | |
Alternative f => Monad (Cofree f) | |
Functor f => Monad (Free f) | |
Monad (SpecM a) | |
Monad m => Monad (Yoneda m) | |
Monad (ReifiedGetter s) | |
Defined in Control.Lens.Reified (>>=) :: ReifiedGetter s a -> (a -> ReifiedGetter s b) -> ReifiedGetter s b # (>>) :: ReifiedGetter s a -> ReifiedGetter s b -> ReifiedGetter s b # return :: a -> ReifiedGetter s a # fail :: String -> ReifiedGetter s a # | |
Monad (ReifiedFold s) | |
Defined in Control.Lens.Reified (>>=) :: ReifiedFold s a -> (a -> ReifiedFold s b) -> ReifiedFold s b # (>>) :: ReifiedFold s a -> ReifiedFold s b -> ReifiedFold s b # return :: a -> ReifiedFold s a # fail :: String -> ReifiedFold s a # | |
Monad m => Monad (ListT m) | |
Monad f => Monad (WrappedPoly f) | |
Defined in Data.MonoTraversable (>>=) :: WrappedPoly f a -> (a -> WrappedPoly f b) -> WrappedPoly f b # (>>) :: WrappedPoly f a -> WrappedPoly f b -> WrappedPoly f b # return :: a -> WrappedPoly f a # fail :: String -> WrappedPoly f a # | |
(Monad (Rep p), Representable p) => Monad (Prep p) | |
Monad f => Monad (Rec1 f) | Since: base-4.9.0.0 |
Monad f => Monad (Ap f) | Since: base-4.12.0.0 |
Monad f => Monad (Alt f) | Since: base-4.8.0.0 |
Monad m => Monad (IdentityT m) | |
(Monoid w, Monad m) => Monad (WriterT w m) | |
(Monoid w, Monad m) => Monad (WriterT w m) | |
Monad m => Monad (StateT s m) | |
Monad m => Monad (StateT s m) | |
Monad m => Monad (ReaderT r m) | |
Monad m => Monad (ExceptT e m) | |
(Applicative f, Monad f) => Monad (WhenMissing f x) | Equivalent to Since: containers-0.5.9 |
Defined in Data.IntMap.Internal (>>=) :: WhenMissing f x a -> (a -> WhenMissing f x b) -> WhenMissing f x b # (>>) :: WhenMissing f x a -> WhenMissing f x b -> WhenMissing f x b # return :: a -> WhenMissing f x a # fail :: String -> WhenMissing f x a # | |
(Functor f, Monad m) => Monad (FreeT f m) | |
(Alternative f, Monad w) => Monad (CofreeT f w) | |
(Monad m, Error e) => Monad (ErrorT e m) | |
Monad (Indexed i a) | |
Monad (Tagged s) | |
(Monoid w, Functor m, Monad m) => Monad (AccumT w m) | |
Monad m => Monad (SelectT r m) | |
Monad ((->) r :: Type -> Type) | Since: base-2.1 |
(Monad f, Monad g) => Monad (f :*: g) | Since: base-4.9.0.0 |
(Monad f, Monad g) => Monad (Product f g) | Since: base-4.9.0.0 |
Monad (ConduitT i o m) | |
(Monad f, Applicative f) => Monad (WhenMatched f x y) | Equivalent to Since: containers-0.5.9 |
Defined in Data.IntMap.Internal (>>=) :: WhenMatched f x y a -> (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 b # return :: a -> WhenMatched f x y a # fail :: String -> WhenMatched f x y a # | |
(Applicative f, Monad f) => Monad (WhenMissing f k x) | Equivalent to Since: containers-0.5.9 |
Defined in Data.Map.Internal (>>=) :: WhenMissing f k x a -> (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 b # return :: a -> WhenMissing f k x a # fail :: String -> WhenMissing f k x a # | |
Monad (ContT r m) | |
Monad (ParsecT s u m) | |
Monad f => Monad (M1 i c f) | Since: base-4.9.0.0 |
(Monoid w, Monad m) => Monad (RWST r w s m) | |
(Monoid w, Monad m) => Monad (RWST r w s m) | |
(Monad f, Applicative f) => Monad (WhenMatched f k x y) | Equivalent to Since: containers-0.5.9 |
Defined in Data.Map.Internal (>>=) :: WhenMatched f k x y a -> (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 b # return :: a -> WhenMatched f k x y a # fail :: String -> WhenMatched f k x y a # | |
Monad (RAW k v ro rw) | |
Monad m => Monad (Pipe l i o u m) | |
class Functor (f :: Type -> Type) where #
The Functor
class is used for types that can be mapped over.
Instances of Functor
should satisfy the following laws:
fmap id == id fmap (f . g) == fmap f . fmap g
The instances of Functor
for lists, Maybe
and IO
satisfy these laws.
Instances
class Functor f => Applicative (f :: Type -> Type) where #
A functor with application, providing operations to
A minimal complete definition must include implementations of pure
and of either <*>
or liftA2
. If it defines both, then they must behave
the same as their default definitions:
(<*>
) =liftA2
id
liftA2
f x y = f<$>
x<*>
y
Further, any definition must satisfy the following:
- identity
pure
id
<*>
v = v- composition
pure
(.)<*>
u<*>
v<*>
w = u<*>
(v<*>
w)- homomorphism
pure
f<*>
pure
x =pure
(f x)- interchange
u
<*>
pure
y =pure
($
y)<*>
u
The other methods have the following default definitions, which may be overridden with equivalent specialized implementations:
As a consequence of these laws, the Functor
instance for f
will satisfy
It may be useful to note that supposing
forall x y. p (q x y) = f x . g y
it follows from the above that
liftA2
p (liftA2
q u v) =liftA2
f u .liftA2
g v
If f
is also a Monad
, it should satisfy
(which implies that pure
and <*>
satisfy the applicative functor laws).
Lift a value.
(<*>) :: f (a -> b) -> f a -> f b infixl 4 #
Sequential application.
A few functors support an implementation of <*>
that is more
efficient than the default one.
liftA2 :: (a -> b -> c) -> f a -> f b -> f c #
Lift a binary function to actions.
Some functors support an implementation of liftA2
that is more
efficient than the default one. In particular, if fmap
is an
expensive operation, it is likely better to use liftA2
than to
fmap
over the structure and then use <*>
.
(*>) :: f a -> f b -> f b infixl 4 #
Sequence actions, discarding the value of the first argument.
(<*) :: f a -> f b -> f a infixl 4 #
Sequence actions, discarding the value of the second argument.
Instances
foldr :: Foldable t => (a -> b -> b) -> b -> t a -> b #
Right-associative fold of a structure.
In the case of lists, foldr
, when applied to a binary operator, a
starting value (typically the right-identity of the operator), and a
list, reduces the list using the binary operator, from right to left:
foldr f z [x1, x2, ..., xn] == x1 `f` (x2 `f` ... (xn `f` z)...)
Note that, since the head of the resulting expression is produced by
an application of the operator to the first element of the list,
foldr
can produce a terminating expression from an infinite list.
For a general Foldable
structure this should be semantically identical
to,
foldr f z =foldr
f z .toList
length :: Foldable t => t a -> Int #
Returns the size/length of a finite structure as an Int
. The
default implementation is optimized for structures that are similar to
cons-lists, because there is no general way to do better.
null :: Foldable t => t a -> Bool #
Test whether the structure is empty. The default implementation is optimized for structures that are similar to cons-lists, because there is no general way to do better.
foldl :: Foldable t => (b -> a -> b) -> b -> t a -> b #
Left-associative fold of a structure.
In the case of lists, foldl
, when applied to a binary
operator, a starting value (typically the left-identity of the operator),
and a list, reduces the list using the binary operator, from left to
right:
foldl f z [x1, x2, ..., xn] == (...((z `f` x1) `f` x2) `f`...) `f` xn
Note that to produce the outermost application of the operator the
entire input list must be traversed. This means that foldl'
will
diverge if given an infinite list.
Also note that if you want an efficient left-fold, you probably want to
use foldl'
instead of foldl
. The reason for this is that latter does
not force the "inner" results (e.g. z
in the above example)
before applying them to the operator (e.g. to f
x1(
). This results
in a thunk chain f
x2)O(n)
elements long, which then must be evaluated from
the outside-in.
For a general Foldable
structure this should be semantically identical
to,
foldl f z =foldl
f z .toList
foldl' :: Foldable t => (b -> a -> b) -> b -> t a -> b #
Left-associative fold of a structure but with strict application of the operator.
This ensures that each step of the fold is forced to weak head normal
form before being applied, avoiding the collection of thunks that would
otherwise occur. This is often what you want to strictly reduce a finite
list to a single, monolithic result (e.g. length
).
For a general Foldable
structure this should be semantically identical
to,
foldl f z =foldl'
f z .toList
sum :: (Foldable t, Num a) => t a -> a #
The sum
function computes the sum of the numbers of a structure.
product :: (Foldable t, Num a) => t a -> a #
The product
function computes the product of the numbers of a
structure.
mapM :: (Traversable t, Monad m) => (a -> m b) -> t a -> m (t b) #
Map each element of a structure to a monadic action, evaluate
these actions from left to right, and collect the results. For
a version that ignores the results see mapM_
.
sequence :: (Traversable t, Monad m) => t (m a) -> m (t a) #
Evaluate each monadic action in the structure from left to
right, and collect the results. For a version that ignores the
results see sequence_
.
class Semigroup a => Monoid a where #
The class of monoids (types with an associative binary operation that has an identity). Instances should satisfy the following laws:
x
<>
mempty
= xmempty
<>
x = xx
(<>
(y<>
z) = (x<>
y)<>
zSemigroup
law)mconcat
=foldr
'(<>)'mempty
The method names refer to the monoid of lists under concatenation, but there are many other instances.
Some types can be viewed as a monoid in more than one way,
e.g. both addition and multiplication on numbers.
In such cases we often define newtype
s and make those instances
of Monoid
, e.g. Sum
and Product
.
NOTE: Semigroup
is a superclass of Monoid
since base-4.11.0.0.
Identity of mappend
An associative operation
NOTE: This method is redundant and has the default
implementation
since base-4.11.0.0.mappend
= '(<>)'
Fold a list using the monoid.
For most types, the default definition for mconcat
will be
used, but the function is included in the class definition so
that an optimized version can be provided for specific types.
Instances
The Maybe
type encapsulates an optional value. A value of type
either contains a value of type Maybe
aa
(represented as
),
or it is empty (represented as Just
aNothing
). Using Maybe
is a good way to
deal with errors or exceptional cases without resorting to drastic
measures such as error
.
The Maybe
type is also a monad. It is a simple kind of error
monad, where all errors are represented by Nothing
. A richer
error monad can be built using the Either
type.
Instances
Monad Maybe | Since: base-2.1 |
Functor Maybe | Since: base-2.1 |
MonadFix Maybe | Since: base-2.1 |
Defined in Control.Monad.Fix | |
MonadFail Maybe | Since: base-4.9.0.0 |
Defined in Control.Monad.Fail | |
Applicative Maybe | Since: base-2.1 |
Foldable Maybe | Since: base-2.1 |
Defined in Data.Foldable fold :: Monoid m => Maybe m -> m # foldMap :: Monoid m => (a -> m) -> Maybe a -> m # foldr :: (a -> b -> b) -> b -> Maybe a -> b # foldr' :: (a -> b -> b) -> b -> Maybe a -> b # foldl :: (b -> a -> b) -> b -> Maybe a -> b # foldl' :: (b -> a -> b) -> b -> Maybe a -> b # foldr1 :: (a -> a -> a) -> Maybe a -> a # foldl1 :: (a -> a -> a) -> Maybe a -> a # elem :: Eq a => a -> Maybe a -> Bool # maximum :: Ord a => Maybe a -> a # minimum :: Ord a => Maybe a -> a # | |
Traversable Maybe | Since: base-2.1 |
Arbitrary1 Maybe | |
Defined in Test.QuickCheck.Arbitrary liftArbitrary :: Gen a -> Gen (Maybe a) # liftShrink :: (a -> [a]) -> Maybe a -> [Maybe a] # | |
ToJSON1 Maybe | |
Defined in Data.Aeson.Types.ToJSON liftToJSON :: (a -> Value) -> ([a] -> Value) -> Maybe a -> Value # liftToJSONList :: (a -> Value) -> ([a] -> Value) -> [Maybe a] -> Value # liftToEncoding :: (a -> Encoding) -> ([a] -> Encoding) -> Maybe a -> Encoding # liftToEncodingList :: (a -> Encoding) -> ([a] -> Encoding) -> [Maybe a] -> Encoding # | |
FromJSON1 Maybe | |
Alternative Maybe | Since: base-2.1 |
MonadPlus Maybe | Since: base-2.1 |
Eq1 Maybe | Since: base-4.9.0.0 |
Ord1 Maybe | Since: base-4.9.0.0 |
Defined in Data.Functor.Classes | |
Read1 Maybe | Since: base-4.9.0.0 |
Defined in Data.Functor.Classes | |
Show1 Maybe | Since: base-4.9.0.0 |
MonadThrow Maybe | |
Defined in Control.Monad.Catch | |
NFData1 Maybe | Since: deepseq-1.4.3.0 |
Defined in Control.DeepSeq | |
Hashable1 Maybe | |
Defined in Data.Hashable.Class | |
MonadBaseControl Maybe Maybe | |
MonadError () Maybe | Since: mtl-2.2.2 |
Defined in Control.Monad.Error.Class throwError :: () -> Maybe a # catchError :: Maybe a -> (() -> Maybe a) -> Maybe a # | |
MonadBase Maybe Maybe | |
Defined in Control.Monad.Base | |
(Selector s, GToJSON enc arity (K1 i (Maybe a) :: Type -> Type), KeyValuePair enc pairs, Monoid pairs) => RecordToPairs enc pairs arity (S1 s (K1 i (Maybe a) :: Type -> Type)) | |
Defined in Data.Aeson.Types.ToJSON | |
(Selector s, FromJSON a) => RecordFromJSON arity (S1 s (K1 i (Maybe a) :: Type -> Type)) | |
Defined in Data.Aeson.Types.FromJSON | |
Eq a => Eq (Maybe a) | Since: base-2.1 |
Data a => Data (Maybe a) | Since: base-4.0.0.0 |
Defined in Data.Data gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Maybe a -> c (Maybe a) # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (Maybe a) # toConstr :: Maybe a -> Constr # dataTypeOf :: Maybe a -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (Maybe a)) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (Maybe a)) # gmapT :: (forall b. Data b => b -> b) -> Maybe a -> Maybe a # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Maybe a -> r # gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Maybe a -> r # gmapQ :: (forall d. Data d => d -> u) -> Maybe a -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> Maybe a -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> Maybe a -> m (Maybe a) # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Maybe a -> m (Maybe a) # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Maybe a -> m (Maybe a) # | |
Ord a => Ord (Maybe a) | Since: base-2.1 |
Read a => Read (Maybe a) | Since: base-2.1 |
Show a => Show (Maybe a) | Since: base-2.1 |
Generic (Maybe a) | |
Semigroup a => Semigroup (Maybe a) | Since: base-4.9.0.0 |
Semigroup a => Monoid (Maybe a) | Lift a semigroup into Since 4.11.0: constraint on inner Since: base-2.1 |
Lift a => Lift (Maybe a) | |
Testable prop => Testable (Maybe prop) | |
Function a => Function (Maybe a) | |
Arbitrary a => Arbitrary (Maybe a) | |
CoArbitrary a => CoArbitrary (Maybe a) | |
Defined in Test.QuickCheck.Arbitrary coarbitrary :: Maybe a -> Gen b -> Gen b # | |
Hashable a => Hashable (Maybe a) | |
Defined in Data.Hashable.Class | |
ToJSON a => ToJSON (Maybe a) | |
Defined in Data.Aeson.Types.ToJSON | |
FromJSON a => FromJSON (Maybe a) | |
SingKind a => SingKind (Maybe a) | Since: base-4.9.0.0 |
Binary a => Binary (Maybe a) | |
NFData a => NFData (Maybe a) | |
Defined in Control.DeepSeq | |
Ixed (Maybe a) | |
Defined in Control.Lens.At | |
At (Maybe a) | |
MonoFunctor (Maybe a) | |
MonoFoldable (Maybe a) | |
Defined in Data.MonoTraversable ofoldMap :: Monoid m => (Element (Maybe a) -> m) -> Maybe a -> m # ofoldr :: (Element (Maybe a) -> b -> b) -> b -> Maybe a -> b # ofoldl' :: (a0 -> Element (Maybe a) -> a0) -> a0 -> Maybe a -> a0 # otoList :: Maybe a -> [Element (Maybe a)] # oall :: (Element (Maybe a) -> Bool) -> Maybe a -> Bool # oany :: (Element (Maybe a) -> Bool) -> Maybe a -> Bool # olength64 :: Maybe a -> Int64 # ocompareLength :: Integral i => Maybe a -> i -> Ordering # otraverse_ :: Applicative f => (Element (Maybe a) -> f b) -> Maybe a -> f () # ofor_ :: Applicative f => Maybe a -> (Element (Maybe a) -> f b) -> f () # omapM_ :: Applicative m => (Element (Maybe a) -> m ()) -> Maybe a -> m () # oforM_ :: Applicative m => Maybe a -> (Element (Maybe a) -> m ()) -> m () # ofoldlM :: Monad m => (a0 -> Element (Maybe a) -> m a0) -> a0 -> Maybe a -> m a0 # ofoldMap1Ex :: Semigroup m => (Element (Maybe a) -> m) -> Maybe a -> m # ofoldr1Ex :: (Element (Maybe a) -> Element (Maybe a) -> Element (Maybe a)) -> Maybe a -> Element (Maybe a) # ofoldl1Ex' :: (Element (Maybe a) -> Element (Maybe a) -> Element (Maybe a)) -> Maybe a -> Element (Maybe a) # headEx :: Maybe a -> Element (Maybe a) # lastEx :: Maybe a -> Element (Maybe a) # unsafeHead :: Maybe a -> Element (Maybe a) # unsafeLast :: Maybe a -> Element (Maybe a) # maximumByEx :: (Element (Maybe a) -> Element (Maybe a) -> Ordering) -> Maybe a -> Element (Maybe a) # minimumByEx :: (Element (Maybe a) -> Element (Maybe a) -> Ordering) -> Maybe a -> Element (Maybe a) # | |
MonoTraversable (Maybe a) | |
MonoPointed (Maybe a) | |
PrettyVal a => PrettyVal (Maybe a) | |
IsCmdArgument a => IsCmdArgument (Maybe a) | |
Defined in Development.Shake.Command toCmdArgument :: Maybe a -> CmdArgument # | |
Generic1 Maybe | |
SingI (Nothing :: Maybe a) | Since: base-4.9.0.0 |
Defined in GHC.Generics | |
SingI a2 => SingI (Just a2 :: Maybe a1) | Since: base-4.9.0.0 |
Defined in GHC.Generics | |
type StM Maybe a | |
Defined in Control.Monad.Trans.Control | |
type Rep (Maybe a) | Since: base-4.6.0.0 |
data Sing (b :: Maybe a) | |
type DemoteRep (Maybe a) | |
Defined in GHC.Generics | |
type Index (Maybe a) | |
Defined in Control.Lens.At | |
type IxValue (Maybe a) | |
Defined in Control.Lens.At | |
type Element (Maybe a) | |
Defined in Data.MonoTraversable | |
type Rep1 Maybe | Since: base-4.6.0.0 |
lines
breaks a string up into a list of strings at newline
characters. The resulting strings do not contain newlines.
Note that after splitting the string at newline characters, the last part of the string is considered a line even if it doesn't end with a newline. For example,
>>>
lines ""
[]
>>>
lines "\n"
[""]
>>>
lines "one"
["one"]
>>>
lines "one\n"
["one"]
>>>
lines "one\n\n"
["one",""]
>>>
lines "one\ntwo"
["one","two"]
>>>
lines "one\ntwo\n"
["one","two"]
Thus
contains at least as many elements as newlines in lines
ss
.
A Version
represents the version of a software entity.
An instance of Eq
is provided, which implements exact equality
modulo reordering of the tags in the versionTags
field.
An instance of Ord
is also provided, which gives lexicographic
ordering on the versionBranch
fields (i.e. 2.1 > 2.0, 1.2.3 > 1.2.2,
etc.). This is expected to be sufficient for many uses, but note that
you may need to use a more specific ordering for your versioning
scheme. For example, some versioning schemes may include pre-releases
which have tags "pre1"
, "pre2"
, and so on, and these would need to
be taken into account when determining ordering. In some cases, date
ordering may be more appropriate, so the application would have to
look for date
tags in the versionTags
field and compare those.
The bottom line is, don't always assume that compare
and other Ord
operations are the right thing for every Version
.
Similarly, concrete representations of versions may differ. One
possible concrete representation is provided (see showVersion
and
parseVersion
), but depending on the application a different concrete
representation may be more appropriate.
Version | |
|
Instances
IsList Version | Since: base-4.8.0.0 |
Eq Version | Since: base-2.1 |
Data Version | Since: base-4.7.0.0 |
Defined in Data.Data gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Version -> c Version # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Version # toConstr :: Version -> Constr # dataTypeOf :: Version -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c Version) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Version) # gmapT :: (forall b. Data b => b -> b) -> Version -> Version # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Version -> r # gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Version -> r # gmapQ :: (forall d. Data d => d -> u) -> Version -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> Version -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> Version -> m Version # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Version -> m Version # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Version -> m Version # | |
Ord Version | Since: base-2.1 |
Read Version | Since: base-2.1 |
Show Version | Since: base-2.1 |
Generic Version | |
Arbitrary Version | Generates |
CoArbitrary Version | |
Defined in Test.QuickCheck.Arbitrary coarbitrary :: Version -> Gen b -> Gen b # | |
Hashable Version | |
Defined in Data.Hashable.Class | |
ToJSON Version | |
Defined in Data.Aeson.Types.ToJSON | |
ToJSONKey Version | |
Defined in Data.Aeson.Types.ToJSON | |
FromJSON Version | |
FromJSONKey Version | |
Binary Version | Since: 0.8.0.0 |
NFData Version | Since: deepseq-1.3.0.0 |
Defined in Control.DeepSeq | |
type Rep Version | Since: base-4.9.0.0 |
Defined in Data.Version type Rep Version = D1 (MetaData "Version" "Data.Version" "base" False) (C1 (MetaCons "Version" PrefixI True) (S1 (MetaSel (Just "versionBranch") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 [Int]) :*: S1 (MetaSel (Just "versionTags") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 [String]))) | |
type Item Version | |
:: MonadReader r m | |
=> (r -> r) | The function to modify the environment. |
-> m a |
|
-> m a |
Executes a computation in a modified environment.
ask :: MonadReader r m => m r #
Retrieves the monad environment.
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
(<$>) :: Functor f => (a -> b) -> f a -> f b infixl 4 #
An infix synonym for fmap
.
The name of this operator is an allusion to $
.
Note the similarities between their types:
($) :: (a -> b) -> a -> b (<$>) :: Functor f => (a -> b) -> f a -> f b
Whereas $
is function application, <$>
is function
application lifted over a Functor
.
Examples
Convert from a
to a Maybe
Int
using Maybe
String
show
:
>>>
show <$> Nothing
Nothing>>>
show <$> Just 3
Just "3"
Convert from an
to an Either
Int
Int
Either
Int
String
using show
:
>>>
show <$> Left 17
Left 17>>>
show <$> Right 17
Right "17"
Double each element of a list:
>>>
(*2) <$> [1,2,3]
[2,4,6]
Apply even
to the second element of a pair:
>>>
even <$> (2,2)
(2,True)
A space efficient, packed, unboxed Unicode text type.
Instances
class Applicative f => Alternative (f :: Type -> Type) where #
A monoid on applicative functors.
If defined, some
and many
should be the least solutions
of the equations:
The identity of <|>
(<|>) :: f a -> f a -> f a infixl 3 #
An associative binary operation
One or more.
Zero or more.
Instances
class (Alternative m, Monad m) => MonadPlus (m :: Type -> Type) where #
Monads that also support choice and failure.
Nothing
The identity of mplus
. It should also satisfy the equations
mzero >>= f = mzero v >> mzero = mzero
The default definition is
mzero = empty
An associative operation. The default definition is
mplus = (<|>
)
Instances
class Monad m => MonadIO (m :: Type -> Type) where #
Monads in which IO
computations may be embedded.
Any monad built by applying a sequence of monad transformers to the
IO
monad will be an instance of this class.
Instances should satisfy the following laws, which state that liftIO
is a transformer of monads:
Instances
exitWith :: ExitCode -> IO a #
Computation exitWith
code
throws ExitCode
code
.
Normally this terminates the program, returning code
to the
program's caller.
On program termination, the standard Handle
s stdout
and
stderr
are flushed automatically; any other buffered Handle
s
need to be flushed manually, otherwise the buffered data will be
discarded.
A program that fails in any other way is treated as if it had
called exitFailure
.
A program that terminates successfully without calling exitWith
explicitly is treated as if it had called exitWith
ExitSuccess
.
As an ExitCode
is not an IOException
, exitWith
bypasses
the error handling in the IO
monad and cannot be intercepted by
catch
from the Prelude. However it is a SomeException
, and can
be caught using the functions of Control.Exception. This means
that cleanup computations added with bracket
(from Control.Exception) are also executed properly on exitWith
.
Note: in GHC, exitWith
should be called from the main program
thread in order to exit the process. When called from another
thread, exitWith
will throw an ExitException
as normal, but the
exception will not cause the process itself to exit.
printf :: PrintfType r => String -> r #
Format a variable number of arguments with the C-style formatting string.
>>>
printf "%s, %d, %.4f" "hello" 123 pi
hello, 123, 3.1416
The return value is either String
or (
(which
should be IO
a)(
, but Haskell's type system
makes this hard).IO
'()')
The format string consists of ordinary characters and
conversion specifications, which specify how to format
one of the arguments to printf
in the output string. A
format specification is introduced by the %
character;
this character can be self-escaped into the format string
using %%
. A format specification ends with a /format
character/ that provides the primary information about
how to format the value. The rest of the conversion
specification is optional. In order, one may have flag
characters, a width specifier, a precision specifier, and
type-specific modifier characters.
Unlike C printf(3)
, the formatting of this printf
is driven by the argument type; formatting is type specific. The
types formatted by printf
"out of the box" are:
printf
is also extensible to support other types: see below.
A conversion specification begins with the
character %
, followed by zero or more of the following flags:
- left adjust (default is right adjust) + always use a sign (+ or -) for signed conversions space leading space for positive numbers in signed conversions 0 pad with zeros rather than spaces # use an \"alternate form\": see below
When both flags are given, -
overrides 0
and +
overrides space.
A negative width specifier in a *
conversion is treated as
positive but implies the left adjust flag.
The "alternate form" for unsigned radix conversions is
as in C printf(3)
:
%o prefix with a leading 0 if needed %x prefix with a leading 0x if nonzero %X prefix with a leading 0X if nonzero %b prefix with a leading 0b if nonzero %[eEfFgG] ensure that the number contains a decimal point
Any flags are followed optionally by a field width:
num field width * as num, but taken from argument list
The field width is a minimum, not a maximum: it will be expanded as needed to avoid mutilating a value.
Any field width is followed optionally by a precision:
.num precision . same as .0 .* as num, but taken from argument list
Negative precision is taken as 0. The meaning of the precision depends on the conversion type.
Integral minimum number of digits to show RealFloat number of digits after the decimal point String maximum number of characters
The precision for Integral types is accomplished by zero-padding. If both precision and zero-pad are given for an Integral field, the zero-pad is ignored.
Any precision is followed optionally for Integral types by a width modifier; the only use of this modifier being to set the implicit size of the operand for conversion of a negative operand to unsigned:
hh Int8 h Int16 l Int32 ll Int64 L Int64
The specification ends with a format character:
c character Integral d decimal Integral o octal Integral x hexadecimal Integral X hexadecimal Integral b binary Integral u unsigned decimal Integral f floating point RealFloat F floating point RealFloat g general format float RealFloat G general format float RealFloat e exponent format float RealFloat E exponent format float RealFloat s string String v default format any type
The "%v" specifier is provided for all built-in types, and should be provided for user-defined type formatters as well. It picks a "best" representation for the given type. For the built-in types the "%v" specifier is converted as follows:
c Char u other unsigned Integral d other signed Integral g RealFloat s String
Mismatch between the argument types and the format string, as well as any other syntactic or semantic errors in the format string, will cause an exception to be thrown at runtime.
Note that the formatting for RealFloat
types is
currently a bit different from that of C printf(3)
,
conforming instead to showEFloat
,
showFFloat
and showGFloat
(and their
alternate versions showFFloatAlt
and
showGFloatAlt
). This is hard to fix: the fixed
versions would format in a backward-incompatible way.
In any case the Haskell behavior is generally more
sensible than the C behavior. A brief summary of some
key differences:
- Haskell
printf
never uses the default "6-digit" precision used by C printf. - Haskell
printf
treats the "precision" specifier as indicating the number of digits after the decimal point. - Haskell
printf
prints the exponent of e-format numbers without a gratuitous plus sign, and with the minimum possible number of digits. - Haskell
printf
will place a zero after a decimal point when possible.
unless :: Applicative f => Bool -> f () -> f () #
The reverse of when
.
replicateM_ :: Applicative m => Int -> m a -> m () #
Like replicateM
, but discards the result.
replicateM :: Applicative m => Int -> m a -> m [a] #
performs the action replicateM
n actn
times,
gathering the results.
foldM_ :: (Foldable t, Monad m) => (b -> a -> m b) -> b -> t a -> m () #
Like foldM
, but discards the result.
foldM :: (Foldable t, Monad m) => (b -> a -> m b) -> b -> t a -> m b #
The foldM
function is analogous to foldl
, except that its result is
encapsulated in a monad. Note that foldM
works from left-to-right over
the list arguments. This could be an issue where (
and the `folded
function' are not commutative.>>
)
foldM f a1 [x1, x2, ..., xm] == do a2 <- f a1 x1 a3 <- f a2 x2 ... f am xm
If right-to-left evaluation is required, the input list should be reversed.
zipWithM_ :: Applicative m => (a -> b -> m c) -> [a] -> [b] -> m () #
zipWithM :: Applicative m => (a -> b -> m c) -> [a] -> [b] -> m [c] #
mapAndUnzipM :: Applicative m => (a -> m (b, c)) -> [a] -> m ([b], [c]) #
The mapAndUnzipM
function maps its first argument over a list, returning
the result as a pair of lists. This function is mainly used with complicated
data structures or a state-transforming monad.
forever :: Applicative f => f a -> f b #
Repeat an action indefinitely.
Examples
A common use of forever
is to process input from network sockets,
Handle
s, and channels
(e.g. MVar
and
Chan
).
For example, here is how we might implement an echo
server, using
forever
both to listen for client connections on a network socket
and to echo client input on client connection handles:
echoServer :: Socket -> IO () echoServer socket =forever
$ do client <- accept socketforkFinally
(echo client) (\_ -> hClose client) where echo :: Handle -> IO () echo client =forever
$ hGetLine client >>= hPutStrLn client
(>=>) :: Monad m => (a -> m b) -> (b -> m c) -> a -> m c infixr 1 #
Left-to-right composition of Kleisli arrows.
filterM :: Applicative m => (a -> m Bool) -> [a] -> m [a] #
This generalizes the list-based filter
function.
makeVersion :: [Int] -> Version #
Construct tag-less Version
Since: base-4.8.0.0
parseVersion :: ReadP Version #
A parser for versions in the format produced by showVersion
.
showVersion :: Version -> String #
Provides one possible concrete representation for Version
. For
a version with versionBranch
= [1,2,3]
and versionTags
= ["tag1","tag2"]
, the output will be 1.2.3-tag1-tag2
.
isSubsequenceOf :: Eq a => [a] -> [a] -> Bool #
The isSubsequenceOf
function takes two lists and returns True
if all
the elements of the first list occur, in order, in the second. The
elements do not have to occur consecutively.
is equivalent to isSubsequenceOf
x y
.elem
x (subsequences
y)
Examples
>>>
isSubsequenceOf "GHC" "The Glorious Haskell Compiler"
True>>>
isSubsequenceOf ['a','d'..'z'] ['a'..'z']
True>>>
isSubsequenceOf [1..10] [10,9..0]
False
Since: base-4.8.0.0
mapAccumR :: Traversable t => (a -> b -> (a, c)) -> a -> t b -> (a, t c) #
mapAccumL :: Traversable t => (a -> b -> (a, c)) -> a -> t b -> (a, t c) #
forM :: (Traversable t, Monad m) => t a -> (a -> m b) -> m (t b) #
optional :: Alternative f => f a -> f (Maybe a) #
One or none.
newtype WrappedMonad (m :: Type -> Type) a #
WrapMonad | |
|
Instances
newtype WrappedArrow (a :: Type -> Type -> Type) b c #
WrapArrow | |
|
Instances
Lists, but with an Applicative
functor based on zipping.
ZipList | |
|
Instances
Functor ZipList | Since: base-2.1 |
Applicative ZipList | f '<$>' 'ZipList' xs1 '<*>' ... '<*>' 'ZipList' xsN = 'ZipList' (zipWithN f xs1 ... xsN) where (\a b c -> stimes c [a, b]) <$> ZipList "abcd" <*> ZipList "567" <*> ZipList [1..] = ZipList (zipWith3 (\a b c -> stimes c [a, b]) "abcd" "567" [1..]) = ZipList {getZipList = ["a5","b6b6","c7c7c7"]} Since: base-2.1 |
Foldable ZipList | Since: base-4.9.0.0 |
Defined in Control.Applicative fold :: Monoid m => ZipList m -> m # foldMap :: Monoid m => (a -> m) -> ZipList a -> m # foldr :: (a -> b -> b) -> b -> ZipList a -> b # foldr' :: (a -> b -> b) -> b -> ZipList a -> b # foldl :: (b -> a -> b) -> b -> ZipList a -> b # foldl' :: (b -> a -> b) -> b -> ZipList a -> b # foldr1 :: (a -> a -> a) -> ZipList a -> a # foldl1 :: (a -> a -> a) -> ZipList a -> a # elem :: Eq a => a -> ZipList a -> Bool # maximum :: Ord a => ZipList a -> a # minimum :: Ord a => ZipList a -> a # | |
Traversable ZipList | Since: base-4.9.0.0 |
Arbitrary1 ZipList | |
Defined in Test.QuickCheck.Arbitrary liftArbitrary :: Gen a -> Gen (ZipList a) # liftShrink :: (a -> [a]) -> ZipList a -> [ZipList a] # | |
Alternative ZipList | Since: base-4.11.0.0 |
NFData1 ZipList | Since: deepseq-1.4.3.0 |
Defined in Control.DeepSeq | |
Eq a => Eq (ZipList a) | Since: base-4.7.0.0 |
Ord a => Ord (ZipList a) | Since: base-4.7.0.0 |
Defined in Control.Applicative | |
Read a => Read (ZipList a) | Since: base-4.7.0.0 |
Show a => Show (ZipList a) | Since: base-4.7.0.0 |
Generic (ZipList a) | |
Arbitrary a => Arbitrary (ZipList a) | |
CoArbitrary a => CoArbitrary (ZipList a) | |
Defined in Test.QuickCheck.Arbitrary coarbitrary :: ZipList a -> Gen b -> Gen b # | |
NFData a => NFData (ZipList a) | Since: deepseq-1.4.0.0 |
Defined in Control.DeepSeq | |
Wrapped (ZipList a) | |
MonoFunctor (ZipList a) | |
MonoPointed (ZipList a) | |
Generic1 ZipList | |
t ~ ZipList b => Rewrapped (ZipList a) t | |
Defined in Control.Lens.Wrapped | |
type Rep (ZipList a) | Since: base-4.7.0.0 |
Defined in Control.Applicative | |
type Item (ZipList a) | |
Defined in Data.Orphans | |
type Unwrapped (ZipList a) | |
Defined in Control.Lens.Wrapped | |
type Element (ZipList a) | |
Defined in Data.MonoTraversable | |
type Rep1 ZipList | Since: base-4.7.0.0 |
Defined in Control.Applicative |
Defines the exit codes that a program can return.
ExitSuccess | indicates successful termination; |
ExitFailure Int | indicates program failure with an exit code. The exact interpretation of the code is operating-system dependent. In particular, some values may be prohibited (e.g. 0 on a POSIX-compliant system). |
Instances
Eq ExitCode | |
Ord ExitCode | |
Defined in GHC.IO.Exception | |
Read ExitCode | |
Show ExitCode | |
Generic ExitCode | |
Arbitrary ExitCode | |
Exception ExitCode | Since: base-4.1.0.0 |
Defined in GHC.IO.Exception toException :: ExitCode -> SomeException # fromException :: SomeException -> Maybe ExitCode # displayException :: ExitCode -> String # | |
NFData ExitCode | Since: deepseq-1.4.2.0 |
Defined in Control.DeepSeq | |
CmdResult ExitCode | |
Defined in Development.Shake.Command | |
type Rep ExitCode | |
Defined in GHC.IO.Exception |
newtype Const a (b :: k) :: forall k. Type -> k -> Type #
The Const
functor.
Instances
Generic1 (Const a :: k -> Type) | |
Unbox a => Vector Vector (Const a b) | |
Defined in Data.Vector.Unboxed.Base basicUnsafeFreeze :: PrimMonad m => Mutable Vector (PrimState m) (Const a b) -> m (Vector (Const a b)) # basicUnsafeThaw :: PrimMonad m => Vector (Const a b) -> m (Mutable Vector (PrimState m) (Const a b)) # basicLength :: Vector (Const a b) -> Int # basicUnsafeSlice :: Int -> Int -> Vector (Const a b) -> Vector (Const a b) # basicUnsafeIndexM :: Monad m => Vector (Const a b) -> Int -> m (Const a b) # basicUnsafeCopy :: PrimMonad m => Mutable Vector (PrimState m) (Const a b) -> Vector (Const a b) -> m () # | |
Unbox a => MVector MVector (Const a b) | |
Defined in Data.Vector.Unboxed.Base basicLength :: MVector s (Const a b) -> Int # basicUnsafeSlice :: Int -> Int -> MVector s (Const a b) -> MVector s (Const a b) # basicOverlaps :: MVector s (Const a b) -> MVector s (Const a b) -> Bool # basicUnsafeNew :: PrimMonad m => Int -> m (MVector (PrimState m) (Const a b)) # basicInitialize :: PrimMonad m => MVector (PrimState m) (Const a b) -> m () # basicUnsafeReplicate :: PrimMonad m => Int -> Const a b -> m (MVector (PrimState m) (Const a b)) # basicUnsafeRead :: PrimMonad m => MVector (PrimState m) (Const a b) -> Int -> m (Const a b) # basicUnsafeWrite :: PrimMonad m => MVector (PrimState m) (Const a b) -> Int -> Const a b -> m () # basicClear :: PrimMonad m => MVector (PrimState m) (Const a b) -> m () # basicSet :: PrimMonad m => MVector (PrimState m) (Const a b) -> Const a b -> m () # basicUnsafeCopy :: PrimMonad m => MVector (PrimState m) (Const a b) -> MVector (PrimState m) (Const a b) -> m () # basicUnsafeMove :: PrimMonad m => MVector (PrimState m) (Const a b) -> MVector (PrimState m) (Const a b) -> m () # basicUnsafeGrow :: PrimMonad m => MVector (PrimState m) (Const a b) -> Int -> m (MVector (PrimState m) (Const a b)) # | |
Arbitrary2 (Const :: Type -> Type -> Type) | |
Defined in Test.QuickCheck.Arbitrary liftArbitrary2 :: Gen a -> Gen b -> Gen (Const a b) # liftShrink2 :: (a -> [a]) -> (b -> [b]) -> Const a b -> [Const a b] # | |
ToJSON2 (Const :: Type -> Type -> Type) | |
Defined in Data.Aeson.Types.ToJSON liftToJSON2 :: (a -> Value) -> ([a] -> Value) -> (b -> Value) -> ([b] -> Value) -> Const a b -> Value # liftToJSONList2 :: (a -> Value) -> ([a] -> Value) -> (b -> Value) -> ([b] -> Value) -> [Const a b] -> Value # liftToEncoding2 :: (a -> Encoding) -> ([a] -> Encoding) -> (b -> Encoding) -> ([b] -> Encoding) -> Const a b -> Encoding # liftToEncodingList2 :: (a -> Encoding) -> ([a] -> Encoding) -> (b -> Encoding) -> ([b] -> Encoding) -> [Const a b] -> Encoding # | |
FromJSON2 (Const :: Type -> Type -> Type) | |
Defined in Data.Aeson.Types.FromJSON | |
Bifunctor (Const :: Type -> Type -> Type) | Since: base-4.8.0.0 |
Eq2 (Const :: Type -> Type -> Type) | Since: base-4.9.0.0 |
Ord2 (Const :: Type -> Type -> Type) | Since: base-4.9.0.0 |
Defined in Data.Functor.Classes | |
Read2 (Const :: Type -> Type -> Type) | Since: base-4.9.0.0 |
Defined in Data.Functor.Classes liftReadsPrec2 :: (Int -> ReadS a) -> ReadS [a] -> (Int -> ReadS b) -> ReadS [b] -> Int -> ReadS (Const a b) # liftReadList2 :: (Int -> ReadS a) -> ReadS [a] -> (Int -> ReadS b) -> ReadS [b] -> ReadS [Const a b] # liftReadPrec2 :: ReadPrec a -> ReadPrec [a] -> ReadPrec b -> ReadPrec [b] -> ReadPrec (Const a b) # liftReadListPrec2 :: ReadPrec a -> ReadPrec [a] -> ReadPrec b -> ReadPrec [b] -> ReadPrec [Const a b] # | |
Show2 (Const :: Type -> Type -> Type) | Since: base-4.9.0.0 |
Biapplicative (Const :: Type -> Type -> Type) | |
NFData2 (Const :: Type -> Type -> Type) | Since: deepseq-1.4.3.0 |
Defined in Control.DeepSeq | |
Hashable2 (Const :: Type -> Type -> Type) | |
Defined in Data.Hashable.Class | |
Functor (Const m :: Type -> Type) | Since: base-2.1 |
Monoid m => Applicative (Const m :: Type -> Type) | Since: base-2.0.1 |
Foldable (Const m :: Type -> Type) | Since: base-4.7.0.0 |
Defined in Data.Functor.Const fold :: Monoid m0 => Const m m0 -> m0 # foldMap :: Monoid m0 => (a -> m0) -> Const m a -> m0 # foldr :: (a -> b -> b) -> b -> Const m a -> b # foldr' :: (a -> b -> b) -> b -> Const m a -> b # foldl :: (b -> a -> b) -> b -> Const m a -> b # foldl' :: (b -> a -> b) -> b -> Const m a -> b # foldr1 :: (a -> a -> a) -> Const m a -> a # foldl1 :: (a -> a -> a) -> Const m a -> a # elem :: Eq a => a -> Const m a -> Bool # maximum :: Ord a => Const m a -> a # minimum :: Ord a => Const m a -> a # | |
Traversable (Const m :: Type -> Type) | Since: base-4.7.0.0 |
Arbitrary a => Arbitrary1 (Const a :: Type -> Type) | |
Defined in Test.QuickCheck.Arbitrary liftArbitrary :: Gen a0 -> Gen (Const a a0) # liftShrink :: (a0 -> [a0]) -> Const a a0 -> [Const a a0] # | |
ToJSON a => ToJSON1 (Const a :: Type -> Type) | |
Defined in Data.Aeson.Types.ToJSON liftToJSON :: (a0 -> Value) -> ([a0] -> Value) -> Const a a0 -> Value # liftToJSONList :: (a0 -> Value) -> ([a0] -> Value) -> [Const a a0] -> Value # liftToEncoding :: (a0 -> Encoding) -> ([a0] -> Encoding) -> Const a a0 -> Encoding # liftToEncodingList :: (a0 -> Encoding) -> ([a0] -> Encoding) -> [Const a a0] -> Encoding # | |
FromJSON a => FromJSON1 (Const a :: Type -> Type) | |
Eq a => Eq1 (Const a :: Type -> Type) | Since: base-4.9.0.0 |
Ord a => Ord1 (Const a :: Type -> Type) | Since: base-4.9.0.0 |
Defined in Data.Functor.Classes | |
Read a => Read1 (Const a :: Type -> Type) | Since: base-4.9.0.0 |
Defined in Data.Functor.Classes | |
Show a => Show1 (Const a :: Type -> Type) | Since: base-4.9.0.0 |
NFData a => NFData1 (Const a :: Type -> Type) | Since: deepseq-1.4.3.0 |
Defined in Control.DeepSeq | |
Hashable a => Hashable1 (Const a :: Type -> Type) | |
Defined in Data.Hashable.Class | |
Bounded a => Bounded (Const a b) | Since: base-4.9.0.0 |
Enum a => Enum (Const a b) | Since: base-4.9.0.0 |
Defined in Data.Functor.Const succ :: Const a b -> Const a b # pred :: Const a b -> Const a b # fromEnum :: Const a b -> Int # enumFrom :: Const a b -> [Const a b] # enumFromThen :: Const a b -> Const a b -> [Const a b] # enumFromTo :: Const a b -> Const a b -> [Const a b] # enumFromThenTo :: Const a b -> Const a b -> Const a b -> [Const a b] # | |
Eq a => Eq (Const a b) | Since: base-4.9.0.0 |
Floating a => Floating (Const a b) | Since: base-4.9.0.0 |
Defined in Data.Functor.Const exp :: Const a b -> Const a b # log :: Const a b -> Const a b # sqrt :: Const a b -> Const a b # (**) :: Const a b -> Const a b -> Const a b # logBase :: Const a b -> Const a b -> Const a b # sin :: Const a b -> Const a b # cos :: Const a b -> Const a b # tan :: Const a b -> Const a b # asin :: Const a b -> Const a b # acos :: Const a b -> Const a b # atan :: Const a b -> Const a b # sinh :: Const a b -> Const a b # cosh :: Const a b -> Const a b # tanh :: Const a b -> Const a b # asinh :: Const a b -> Const a b # acosh :: Const a b -> Const a b # atanh :: Const a b -> Const a b # log1p :: Const a b -> Const a b # expm1 :: Const a b -> Const a b # | |
Fractional a => Fractional (Const a b) | Since: base-4.9.0.0 |
Integral a => Integral (Const a b) | Since: base-4.9.0.0 |
Defined in Data.Functor.Const | |
(Typeable k, Data a, Typeable b) => Data (Const a b) | Since: base-4.10.0.0 |
Defined in Data.Data gfoldl :: (forall d b0. Data d => c (d -> b0) -> d -> c b0) -> (forall g. g -> c g) -> Const a b -> c (Const a b) # gunfold :: (forall b0 r. Data b0 => c (b0 -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (Const a b) # toConstr :: Const a b -> Constr # dataTypeOf :: Const a b -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (Const a b)) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (Const a b)) # gmapT :: (forall b0. Data b0 => b0 -> b0) -> Const a b -> Const a b # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Const a b -> r # gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Const a b -> r # gmapQ :: (forall d. Data d => d -> u) -> Const a b -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> Const a b -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> Const a b -> m (Const a b) # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Const a b -> m (Const a b) # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Const a b -> m (Const a b) # | |
Num a => Num (Const a b) | Since: base-4.9.0.0 |
Ord a => Ord (Const a b) | Since: base-4.9.0.0 |
Defined in Data.Functor.Const | |
Read a => Read (Const a b) | This instance would be equivalent to the derived instances of the
Since: base-4.8.0.0 |
Real a => Real (Const a b) | Since: base-4.9.0.0 |
Defined in Data.Functor.Const toRational :: Const a b -> Rational # | |
RealFloat a => RealFloat (Const a b) | Since: base-4.9.0.0 |
Defined in Data.Functor.Const floatRadix :: Const a b -> Integer # floatDigits :: Const a b -> Int # floatRange :: Const a b -> (Int, Int) # decodeFloat :: Const a b -> (Integer, Int) # encodeFloat :: Integer -> Int -> Const a b # exponent :: Const a b -> Int # significand :: Const a b -> Const a b # scaleFloat :: Int -> Const a b -> Const a b # isInfinite :: Const a b -> Bool # isDenormalized :: Const a b -> Bool # isNegativeZero :: Const a b -> Bool # | |
RealFrac a => RealFrac (Const a b) | Since: base-4.9.0.0 |
Show a => Show (Const a b) | This instance would be equivalent to the derived instances of the
Since: base-4.8.0.0 |
Ix a => Ix (Const a b) | Since: base-4.9.0.0 |
Defined in Data.Functor.Const range :: (Const a b, Const a b) -> [Const a b] # index :: (Const a b, Const a b) -> Const a b -> Int # unsafeIndex :: (Const a b, Const a b) -> Const a b -> Int inRange :: (Const a b, Const a b) -> Const a b -> Bool # rangeSize :: (Const a b, Const a b) -> Int # unsafeRangeSize :: (Const a b, Const a b) -> Int | |
IsString a => IsString (Const a b) | Since: base-4.9.0.0 |
Defined in Data.String fromString :: String -> Const a b # | |
Generic (Const a b) | |
Semigroup a => Semigroup (Const a b) | Since: base-4.9.0.0 |
Monoid a => Monoid (Const a b) | Since: base-4.9.0.0 |
Function a => Function (Const a b) | |
Arbitrary a => Arbitrary (Const a b) | |
CoArbitrary a => CoArbitrary (Const a b) | |
Defined in Test.QuickCheck.Arbitrary coarbitrary :: Const a b -> Gen b0 -> Gen b0 # | |
Hashable a => Hashable (Const a b) | |
Defined in Data.Hashable.Class | |
ToJSON a => ToJSON (Const a b) | |
Defined in Data.Aeson.Types.ToJSON | |
FromJSON a => FromJSON (Const a b) | |
Storable a => Storable (Const a b) | Since: base-4.9.0.0 |
Defined in Data.Functor.Const | |
Bits a => Bits (Const a b) | Since: base-4.9.0.0 |
Defined in Data.Functor.Const (.&.) :: Const a b -> Const a b -> Const a b # (.|.) :: Const a b -> Const a b -> Const a b # xor :: Const a b -> Const a b -> Const a b # complement :: Const a b -> Const a b # shift :: Const a b -> Int -> Const a b # rotate :: Const a b -> Int -> Const a b # setBit :: Const a b -> Int -> Const a b # clearBit :: Const a b -> Int -> Const a b # complementBit :: Const a b -> Int -> Const a b # testBit :: Const a b -> Int -> Bool # bitSizeMaybe :: Const a b -> Maybe Int # isSigned :: Const a b -> Bool # shiftL :: Const a b -> Int -> Const a b # unsafeShiftL :: Const a b -> Int -> Const a b # shiftR :: Const a b -> Int -> Const a b # unsafeShiftR :: Const a b -> Int -> Const a b # rotateL :: Const a b -> Int -> Const a b # | |
FiniteBits a => FiniteBits (Const a b) | Since: base-4.9.0.0 |
Defined in Data.Functor.Const finiteBitSize :: Const a b -> Int # countLeadingZeros :: Const a b -> Int # countTrailingZeros :: Const a b -> Int # | |
NFData a => NFData (Const a b) | Since: deepseq-1.4.0.0 |
Defined in Control.DeepSeq | |
Unbox a => Unbox (Const a b) | |
Defined in Data.Vector.Unboxed.Base | |
Wrapped (Const a x) | |
MonoFunctor (Const m a) | |
MonoFoldable (Const m a) | |
Defined in Data.MonoTraversable ofoldMap :: Monoid m0 => (Element (Const m a) -> m0) -> Const m a -> m0 # ofoldr :: (Element (Const m a) -> b -> b) -> b -> Const m a -> b # ofoldl' :: (a0 -> Element (Const m a) -> a0) -> a0 -> Const m a -> a0 # otoList :: Const m a -> [Element (Const m a)] # oall :: (Element (Const m a) -> Bool) -> Const m a -> Bool # oany :: (Element (Const m a) -> Bool) -> Const m a -> Bool # olength64 :: Const m a -> Int64 # ocompareLength :: Integral i => Const m a -> i -> Ordering # otraverse_ :: Applicative f => (Element (Const m a) -> f b) -> Const m a -> f () # ofor_ :: Applicative f => Const m a -> (Element (Const m a) -> f b) -> f () # omapM_ :: Applicative m0 => (Element (Const m a) -> m0 ()) -> Const m a -> m0 () # oforM_ :: Applicative m0 => Const m a -> (Element (Const m a) -> m0 ()) -> m0 () # ofoldlM :: Monad m0 => (a0 -> Element (Const m a) -> m0 a0) -> a0 -> Const m a -> m0 a0 # ofoldMap1Ex :: Semigroup m0 => (Element (Const m a) -> m0) -> Const m a -> m0 # ofoldr1Ex :: (Element (Const m a) -> Element (Const m a) -> Element (Const m a)) -> Const m a -> Element (Const m a) # ofoldl1Ex' :: (Element (Const m a) -> Element (Const m a) -> Element (Const m a)) -> Const m a -> Element (Const m a) # headEx :: Const m a -> Element (Const m a) # lastEx :: Const m a -> Element (Const m a) # unsafeHead :: Const m a -> Element (Const m a) # unsafeLast :: Const m a -> Element (Const m a) # maximumByEx :: (Element (Const m a) -> Element (Const m a) -> Ordering) -> Const m a -> Element (Const m a) # minimumByEx :: (Element (Const m a) -> Element (Const m a) -> Ordering) -> Const m a -> Element (Const m a) # | |
MonoTraversable (Const m a) | |
Monoid m => MonoPointed (Const m a) | |
t ~ Const a' x' => Rewrapped (Const a x) t | |
Defined in Control.Lens.Wrapped | |
type Rep1 (Const a :: k -> Type) | Since: base-4.9.0.0 |
Defined in Data.Functor.Const | |
newtype MVector s (Const a b) | |
Defined in Data.Vector.Unboxed.Base | |
type Rep (Const a b) | Since: base-4.9.0.0 |
Defined in Data.Functor.Const | |
newtype Vector (Const a b) | |
Defined in Data.Vector.Unboxed.Base | |
type Unwrapped (Const a x) | |
Defined in Control.Lens.Wrapped | |
type Element (Const m a) | |
Defined in Data.MonoTraversable |
minimumBy :: Foldable t => (a -> a -> Ordering) -> t a -> a #
The least element of a non-empty structure with respect to the given comparison function.
maximumBy :: Foldable t => (a -> a -> Ordering) -> t a -> a #
The largest element of a non-empty structure with respect to the given comparison function.
all :: Foldable t => (a -> Bool) -> t a -> Bool #
Determines whether all elements of the structure satisfy the predicate.
any :: Foldable t => (a -> Bool) -> t a -> Bool #
Determines whether any element of the structure satisfies the predicate.
concatMap :: Foldable t => (a -> [b]) -> t a -> [b] #
Map a function over all the elements of a container and concatenate the resulting lists.
concat :: Foldable t => t [a] -> [a] #
The concatenation of all the elements of a container of lists.
sequence_ :: (Foldable t, Monad m) => t (m a) -> m () #
Evaluate each monadic action in the structure from left to right,
and ignore the results. For a version that doesn't ignore the
results see sequence
.
As of base 4.8.0.0, sequence_
is just sequenceA_
, specialized
to Monad
.
Maybe monoid returning the leftmost non-Nothing value.
is isomorphic to First
a
, but precedes it
historically.Alt
Maybe
a
>>>
getFirst (First (Just "hello") <> First Nothing <> First (Just "world"))
Just "hello"
Use of this type is discouraged. Note the following equivalence:
Data.Monoid.First x === Maybe (Data.Semigroup.First x)
In addition to being equivalent in the structural sense, the two
also have Monoid
instances that behave the same. This type will
be marked deprecated in GHC 8.8, and removed in GHC 8.10.
Users are advised to use the variant from Data.Semigroup and wrap
it in Maybe
.
Instances
Monad First | Since: base-4.8.0.0 |
Functor First | Since: base-4.8.0.0 |
MonadFix First | Since: base-4.8.0.0 |
Defined in Control.Monad.Fix | |
Applicative First | Since: base-4.8.0.0 |
Foldable First | Since: base-4.8.0.0 |
Defined in Data.Foldable fold :: Monoid m => First m -> m # foldMap :: Monoid m => (a -> m) -> First a -> m # foldr :: (a -> b -> b) -> b -> First a -> b # foldr' :: (a -> b -> b) -> b -> First a -> b # foldl :: (b -> a -> b) -> b -> First a -> b # foldl' :: (b -> a -> b) -> b -> First a -> b # foldr1 :: (a -> a -> a) -> First a -> a # foldl1 :: (a -> a -> a) -> First a -> a # elem :: Eq a => a -> First a -> Bool # maximum :: Ord a => First a -> a # minimum :: Ord a => First a -> a # | |
Traversable First | Since: base-4.8.0.0 |
ToJSON1 First | |
Defined in Data.Aeson.Types.ToJSON liftToJSON :: (a -> Value) -> ([a] -> Value) -> First a -> Value # liftToJSONList :: (a -> Value) -> ([a] -> Value) -> [First a] -> Value # liftToEncoding :: (a -> Encoding) -> ([a] -> Encoding) -> First a -> Encoding # liftToEncodingList :: (a -> Encoding) -> ([a] -> Encoding) -> [First a] -> Encoding # | |
FromJSON1 First | |
NFData1 First | Since: deepseq-1.4.3.0 |
Defined in Control.DeepSeq | |
Eq a => Eq (First a) | Since: base-2.1 |
Data a => Data (First a) | Since: base-4.8.0.0 |
Defined in Data.Data gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> First a -> c (First a) # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (First a) # toConstr :: First a -> Constr # dataTypeOf :: First a -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (First a)) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (First a)) # gmapT :: (forall b. Data b => b -> b) -> First a -> First a # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> First a -> r # gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> First a -> r # gmapQ :: (forall d. Data d => d -> u) -> First a -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> First a -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> First a -> m (First a) # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> First a -> m (First a) # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> First a -> m (First a) # | |
Ord a => Ord (First a) | Since: base-2.1 |
Read a => Read (First a) | Since: base-2.1 |
Show a => Show (First a) | Since: base-2.1 |
Generic (First a) | |
Semigroup (First a) | Since: base-4.9.0.0 |
Monoid (First a) | Since: base-2.1 |
Function a => Function (First a) | |
Arbitrary a => Arbitrary (First a) | |
CoArbitrary a => CoArbitrary (First a) | |
Defined in Test.QuickCheck.Arbitrary coarbitrary :: First a -> Gen b -> Gen b # | |
ToJSON a => ToJSON (First a) | |
Defined in Data.Aeson.Types.ToJSON | |
FromJSON a => FromJSON (First a) | |
Binary a => Binary (First a) | Since: 0.8.4.0 |
NFData a => NFData (First a) | Since: deepseq-1.4.0.0 |
Defined in Control.DeepSeq | |
Wrapped (First a) | |
Generic1 First | |
t ~ First b => Rewrapped (First a) t | |
Defined in Control.Lens.Wrapped | |
type Rep (First a) | Since: base-4.7.0.0 |
Defined in Data.Monoid | |
type Unwrapped (First a) | |
Defined in Control.Lens.Wrapped | |
type Rep1 First | Since: base-4.7.0.0 |
Defined in Data.Monoid |
Maybe monoid returning the rightmost non-Nothing value.
is isomorphic to Last
a
, and thus to
Dual
(First
a)Dual
(Alt
Maybe
a)
>>>
getLast (Last (Just "hello") <> Last Nothing <> Last (Just "world"))
Just "world"
Use of this type is discouraged. Note the following equivalence:
Data.Monoid.Last x === Maybe (Data.Semigroup.Last x)
In addition to being equivalent in the structural sense, the two
also have Monoid
instances that behave the same. This type will
be marked deprecated in GHC 8.8, and removed in GHC 8.10.
Users are advised to use the variant from Data.Semigroup and wrap
it in Maybe
.
Instances
Monad Last | Since: base-4.8.0.0 |
Functor Last | Since: base-4.8.0.0 |
MonadFix Last | Since: base-4.8.0.0 |
Defined in Control.Monad.Fix | |
Applicative Last | Since: base-4.8.0.0 |
Foldable Last | Since: base-4.8.0.0 |
Defined in Data.Foldable fold :: Monoid m => Last m -> m # foldMap :: Monoid m => (a -> m) -> Last a -> m # foldr :: (a -> b -> b) -> b -> Last a -> b # foldr' :: (a -> b -> b) -> b -> Last a -> b # foldl :: (b -> a -> b) -> b -> Last a -> b # foldl' :: (b -> a -> b) -> b -> Last a -> b # foldr1 :: (a -> a -> a) -> Last a -> a # foldl1 :: (a -> a -> a) -> Last a -> a # elem :: Eq a => a -> Last a -> Bool # maximum :: Ord a => Last a -> a # | |
Traversable Last | Since: base-4.8.0.0 |
ToJSON1 Last | |
Defined in Data.Aeson.Types.ToJSON | |
FromJSON1 Last | |
NFData1 Last | Since: deepseq-1.4.3.0 |
Defined in Control.DeepSeq | |
Eq a => Eq (Last a) | Since: base-2.1 |
Data a => Data (Last a) | Since: base-4.8.0.0 |
Defined in Data.Data gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Last a -> c (Last a) # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (Last a) # toConstr :: Last a -> Constr # dataTypeOf :: Last a -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (Last a)) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (Last a)) # gmapT :: (forall b. Data b => b -> b) -> Last a -> Last a # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Last a -> r # gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Last a -> r # gmapQ :: (forall d. Data d => d -> u) -> Last a -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> Last a -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> Last a -> m (Last a) # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Last a -> m (Last a) # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Last a -> m (Last a) # | |
Ord a => Ord (Last a) | Since: base-2.1 |
Read a => Read (Last a) | Since: base-2.1 |
Show a => Show (Last a) | Since: base-2.1 |
Generic (Last a) | |
Semigroup (Last a) | Since: base-4.9.0.0 |
Monoid (Last a) | Since: base-2.1 |
Function a => Function (Last a) | |
Arbitrary a => Arbitrary (Last a) | |
CoArbitrary a => CoArbitrary (Last a) | |
Defined in Test.QuickCheck.Arbitrary coarbitrary :: Last a -> Gen b -> Gen b # | |
ToJSON a => ToJSON (Last a) | |
Defined in Data.Aeson.Types.ToJSON | |
FromJSON a => FromJSON (Last a) | |
Binary a => Binary (Last a) | Since: 0.8.4.0 |
NFData a => NFData (Last a) | Since: deepseq-1.4.0.0 |
Defined in Control.DeepSeq | |
Wrapped (Last a) | |
Generic1 Last | |
t ~ Last b => Rewrapped (Last a) t | |
Defined in Control.Lens.Wrapped | |
type Rep (Last a) | Since: base-4.7.0.0 |
Defined in Data.Monoid | |
type Unwrapped (Last a) | |
Defined in Control.Lens.Wrapped | |
type Rep1 Last | Since: base-4.7.0.0 |
Defined in Data.Monoid |
newtype Ap (f :: k -> Type) (a :: k) :: forall k. (k -> Type) -> k -> Type #
This data type witnesses the lifting of a Monoid
into an
Applicative
pointwise.
Since: base-4.12.0.0
Instances
Generic1 (Ap f :: k -> Type) | |
Monad f => Monad (Ap f) | Since: base-4.12.0.0 |
Functor f => Functor (Ap f) | Since: base-4.12.0.0 |
MonadFix f => MonadFix (Ap f) | Since: base-4.12.0.0 |
Defined in Control.Monad.Fix | |
MonadFail f => MonadFail (Ap f) | Since: base-4.12.0.0 |
Defined in Data.Monoid | |
Applicative f => Applicative (Ap f) | Since: base-4.12.0.0 |
Foldable f => Foldable (Ap f) | Since: base-4.12.0.0 |
Defined in Data.Foldable fold :: Monoid m => Ap f m -> m # foldMap :: Monoid m => (a -> m) -> Ap f a -> m # foldr :: (a -> b -> b) -> b -> Ap f a -> b # foldr' :: (a -> b -> b) -> b -> Ap f a -> b # foldl :: (b -> a -> b) -> b -> Ap f a -> b # foldl' :: (b -> a -> b) -> b -> Ap f a -> b # foldr1 :: (a -> a -> a) -> Ap f a -> a # foldl1 :: (a -> a -> a) -> Ap f a -> a # elem :: Eq a => a -> Ap f a -> Bool # maximum :: Ord a => Ap f a -> a # | |
Traversable f => Traversable (Ap f) | Since: base-4.12.0.0 |
Alternative f => Alternative (Ap f) | Since: base-4.12.0.0 |
MonadPlus f => MonadPlus (Ap f) | Since: base-4.12.0.0 |
(Applicative f, Bounded a) => Bounded (Ap f a) | Since: base-4.12.0.0 |
Enum (f a) => Enum (Ap f a) | Since: base-4.12.0.0 |
Defined in Data.Monoid | |
Eq (f a) => Eq (Ap f a) | Since: base-4.12.0.0 |
(Data (f a), Data a, Typeable f) => Data (Ap f a) | Since: base-4.12.0.0 |
Defined in Data.Data gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Ap f a -> c (Ap f a) # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (Ap f a) # toConstr :: Ap f a -> Constr # dataTypeOf :: Ap f a -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (Ap f a)) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (Ap f a)) # gmapT :: (forall b. Data b => b -> b) -> Ap f a -> Ap f a # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Ap f a -> r # gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Ap f a -> r # gmapQ :: (forall d. Data d => d -> u) -> Ap f a -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> Ap f a -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> Ap f a -> m (Ap f a) # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Ap f a -> m (Ap f a) # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Ap f a -> m (Ap f a) # | |
(Applicative f, Num a) => Num (Ap f a) | Since: base-4.12.0.0 |
Ord (f a) => Ord (Ap f a) | Since: base-4.12.0.0 |
Read (f a) => Read (Ap f a) | Since: base-4.12.0.0 |
Show (f a) => Show (Ap f a) | Since: base-4.12.0.0 |
Generic (Ap f a) | |
(Applicative f, Semigroup a) => Semigroup (Ap f a) | Since: base-4.12.0.0 |
(Applicative f, Monoid a) => Monoid (Ap f a) | Since: base-4.12.0.0 |
Wrapped (Ap f a) | |
t ~ Ap g b => Rewrapped (Ap f a) t | |
Defined in Control.Lens.Wrapped | |
type Rep1 (Ap f :: k -> Type) | Since: base-4.12.0.0 |
Defined in Data.Monoid | |
type Rep (Ap f a) | Since: base-4.12.0.0 |
Defined in Data.Monoid | |
type Unwrapped (Ap f a) | |
Defined in Control.Lens.Wrapped |
The dual of a Monoid
, obtained by swapping the arguments of mappend
.
>>>
getDual (mappend (Dual "Hello") (Dual "World"))
"WorldHello"
Instances
Monad Dual | Since: base-4.8.0.0 |
Functor Dual | Since: base-4.8.0.0 |
MonadFix Dual | Since: base-4.8.0.0 |
Defined in Control.Monad.Fix | |
Applicative Dual | Since: base-4.8.0.0 |
Foldable Dual | Since: base-4.8.0.0 |
Defined in Data.Foldable fold :: Monoid m => Dual m -> m # foldMap :: Monoid m => (a -> m) -> Dual a -> m # foldr :: (a -> b -> b) -> b -> Dual a -> b # foldr' :: (a -> b -> b) -> b -> Dual a -> b # foldl :: (b -> a -> b) -> b -> Dual a -> b # foldl' :: (b -> a -> b) -> b -> Dual a -> b # foldr1 :: (a -> a -> a) -> Dual a -> a # foldl1 :: (a -> a -> a) -> Dual a -> a # elem :: Eq a => a -> Dual a -> Bool # maximum :: Ord a => Dual a -> a # | |
Traversable Dual | Since: base-4.8.0.0 |
Representable Dual | |
ToJSON1 Dual | |
Defined in Data.Aeson.Types.ToJSON | |
FromJSON1 Dual | |
NFData1 Dual | Since: deepseq-1.4.3.0 |
Defined in Control.DeepSeq | |
Unbox a => Vector Vector (Dual a) | |
Defined in Data.Vector.Unboxed.Base basicUnsafeFreeze :: PrimMonad m => Mutable Vector (PrimState m) (Dual a) -> m (Vector (Dual a)) # basicUnsafeThaw :: PrimMonad m => Vector (Dual a) -> m (Mutable Vector (PrimState m) (Dual a)) # basicLength :: Vector (Dual a) -> Int # basicUnsafeSlice :: Int -> Int -> Vector (Dual a) -> Vector (Dual a) # basicUnsafeIndexM :: Monad m => Vector (Dual a) -> Int -> m (Dual a) # basicUnsafeCopy :: PrimMonad m => Mutable Vector (PrimState m) (Dual a) -> Vector (Dual a) -> m () # | |
Unbox a => MVector MVector (Dual a) | |
Defined in Data.Vector.Unboxed.Base basicLength :: MVector s (Dual a) -> Int # basicUnsafeSlice :: Int -> Int -> MVector s (Dual a) -> MVector s (Dual a) # basicOverlaps :: MVector s (Dual a) -> MVector s (Dual a) -> Bool # basicUnsafeNew :: PrimMonad m => Int -> m (MVector (PrimState m) (Dual a)) # basicInitialize :: PrimMonad m => MVector (PrimState m) (Dual a) -> m () # basicUnsafeReplicate :: PrimMonad m => Int -> Dual a -> m (MVector (PrimState m) (Dual a)) # basicUnsafeRead :: PrimMonad m => MVector (PrimState m) (Dual a) -> Int -> m (Dual a) # basicUnsafeWrite :: PrimMonad m => MVector (PrimState m) (Dual a) -> Int -> Dual a -> m () # basicClear :: PrimMonad m => MVector (PrimState m) (Dual a) -> m () # basicSet :: PrimMonad m => MVector (PrimState m) (Dual a) -> Dual a -> m () # basicUnsafeCopy :: PrimMonad m => MVector (PrimState m) (Dual a) -> MVector (PrimState m) (Dual a) -> m () # basicUnsafeMove :: PrimMonad m => MVector (PrimState m) (Dual a) -> MVector (PrimState m) (Dual a) -> m () # basicUnsafeGrow :: PrimMonad m => MVector (PrimState m) (Dual a) -> Int -> m (MVector (PrimState m) (Dual a)) # | |
Bounded a => Bounded (Dual a) | Since: base-2.1 |
Eq a => Eq (Dual a) | Since: base-2.1 |
Data a => Data (Dual a) | Since: base-4.8.0.0 |
Defined in Data.Data gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Dual a -> c (Dual a) # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (Dual a) # toConstr :: Dual a -> Constr # dataTypeOf :: Dual a -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (Dual a)) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (Dual a)) # gmapT :: (forall b. Data b => b -> b) -> Dual a -> Dual a # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Dual a -> r # gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Dual a -> r # gmapQ :: (forall d. Data d => d -> u) -> Dual a -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> Dual a -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> Dual a -> m (Dual a) # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Dual a -> m (Dual a) # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Dual a -> m (Dual a) # | |
Ord a => Ord (Dual a) | Since: base-2.1 |
Read a => Read (Dual a) | Since: base-2.1 |
Show a => Show (Dual a) | Since: base-2.1 |
Generic (Dual a) | |
Semigroup a => Semigroup (Dual a) | Since: base-4.9.0.0 |
Monoid a => Monoid (Dual a) | Since: base-2.1 |
Function a => Function (Dual a) | |
Arbitrary a => Arbitrary (Dual a) | |
CoArbitrary a => CoArbitrary (Dual a) | |
Defined in Test.QuickCheck.Arbitrary coarbitrary :: Dual a -> Gen b -> Gen b # | |
ToJSON a => ToJSON (Dual a) | |
Defined in Data.Aeson.Types.ToJSON | |
FromJSON a => FromJSON (Dual a) | |
Binary a => Binary (Dual a) | Since: 0.8.4.0 |
NFData a => NFData (Dual a) | Since: deepseq-1.4.0.0 |
Defined in Control.DeepSeq | |
Unbox a => Unbox (Dual a) | |
Defined in Data.Vector.Unboxed.Base | |
Wrapped (Dual a) | |
Generic1 Dual | |
t ~ Dual b => Rewrapped (Dual a) t | |
Defined in Control.Lens.Wrapped | |
type Rep Dual | |
Defined in Data.Functor.Rep | |
newtype MVector s (Dual a) | |
Defined in Data.Vector.Unboxed.Base | |
type Rep (Dual a) | Since: base-4.7.0.0 |
Defined in Data.Semigroup.Internal | |
newtype Vector (Dual a) | |
Defined in Data.Vector.Unboxed.Base | |
type Unwrapped (Dual a) | |
Defined in Control.Lens.Wrapped | |
type Rep1 Dual | Since: base-4.7.0.0 |
Defined in Data.Semigroup.Internal |
The monoid of endomorphisms under composition.
>>>
let computation = Endo ("Hello, " ++) <> Endo (++ "!")
>>>
appEndo computation "Haskell"
"Hello, Haskell!"
Instances
Generic (Endo a) | |
Semigroup (Endo a) | Since: base-4.9.0.0 |
Monoid (Endo a) | Since: base-2.1 |
(Arbitrary a, CoArbitrary a) => Arbitrary (Endo a) | |
(Arbitrary a, CoArbitrary a) => CoArbitrary (Endo a) | |
Defined in Test.QuickCheck.Arbitrary coarbitrary :: Endo a -> Gen b -> Gen b # | |
Wrapped (Endo a) | |
t ~ Endo b => Rewrapped (Endo a) t | |
Defined in Control.Lens.Wrapped | |
type Rep (Endo a) | Since: base-4.7.0.0 |
Defined in Data.Semigroup.Internal | |
type Unwrapped (Endo a) | |
Defined in Control.Lens.Wrapped |
Boolean monoid under conjunction (&&
).
>>>
getAll (All True <> mempty <> All False)
False
>>>
getAll (mconcat (map (\x -> All (even x)) [2,4,6,7,8]))
False
Instances
Boolean monoid under disjunction (||
).
>>>
getAny (Any True <> mempty <> Any False)
True
>>>
getAny (mconcat (map (\x -> Any (even x)) [2,4,6,7,8]))
True
Instances
Monoid under addition.
>>>
getSum (Sum 1 <> Sum 2 <> mempty)
3
Instances
Monad Sum | Since: base-4.8.0.0 |
Functor Sum | Since: base-4.8.0.0 |
MonadFix Sum | Since: base-4.8.0.0 |
Defined in Control.Monad.Fix | |
Applicative Sum | Since: base-4.8.0.0 |
Foldable Sum | Since: base-4.8.0.0 |
Defined in Data.Foldable fold :: Monoid m => Sum m -> m # foldMap :: Monoid m => (a -> m) -> Sum a -> m # foldr :: (a -> b -> b) -> b -> Sum a -> b # foldr' :: (a -> b -> b) -> b -> Sum a -> b # foldl :: (b -> a -> b) -> b -> Sum a -> b # foldl' :: (b -> a -> b) -> b -> Sum a -> b # foldr1 :: (a -> a -> a) -> Sum a -> a # foldl1 :: (a -> a -> a) -> Sum a -> a # elem :: Eq a => a -> Sum a -> Bool # maximum :: Ord a => Sum a -> a # | |
Traversable Sum | Since: base-4.8.0.0 |
Representable Sum | |
NFData1 Sum | Since: deepseq-1.4.3.0 |
Defined in Control.DeepSeq | |
Unbox a => Vector Vector (Sum a) | |
Defined in Data.Vector.Unboxed.Base basicUnsafeFreeze :: PrimMonad m => Mutable Vector (PrimState m) (Sum a) -> m (Vector (Sum a)) # basicUnsafeThaw :: PrimMonad m => Vector (Sum a) -> m (Mutable Vector (PrimState m) (Sum a)) # basicLength :: Vector (Sum a) -> Int # basicUnsafeSlice :: Int -> Int -> Vector (Sum a) -> Vector (Sum a) # basicUnsafeIndexM :: Monad m => Vector (Sum a) -> Int -> m (Sum a) # basicUnsafeCopy :: PrimMonad m => Mutable Vector (PrimState m) (Sum a) -> Vector (Sum a) -> m () # | |
Unbox a => MVector MVector (Sum a) | |
Defined in Data.Vector.Unboxed.Base basicLength :: MVector s (Sum a) -> Int # basicUnsafeSlice :: Int -> Int -> MVector s (Sum a) -> MVector s (Sum a) # basicOverlaps :: MVector s (Sum a) -> MVector s (Sum a) -> Bool # basicUnsafeNew :: PrimMonad m => Int -> m (MVector (PrimState m) (Sum a)) # basicInitialize :: PrimMonad m => MVector (PrimState m) (Sum a) -> m () # basicUnsafeReplicate :: PrimMonad m => Int -> Sum a -> m (MVector (PrimState m) (Sum a)) # basicUnsafeRead :: PrimMonad m => MVector (PrimState m) (Sum a) -> Int -> m (Sum a) # basicUnsafeWrite :: PrimMonad m => MVector (PrimState m) (Sum a) -> Int -> Sum a -> m () # basicClear :: PrimMonad m => MVector (PrimState m) (Sum a) -> m () # basicSet :: PrimMonad m => MVector (PrimState m) (Sum a) -> Sum a -> m () # basicUnsafeCopy :: PrimMonad m => MVector (PrimState m) (Sum a) -> MVector (PrimState m) (Sum a) -> m () # basicUnsafeMove :: PrimMonad m => MVector (PrimState m) (Sum a) -> MVector (PrimState m) (Sum a) -> m () # basicUnsafeGrow :: PrimMonad m => MVector (PrimState m) (Sum a) -> Int -> m (MVector (PrimState m) (Sum a)) # | |
Bounded a => Bounded (Sum a) | Since: base-2.1 |
Eq a => Eq (Sum a) | Since: base-2.1 |
Data a => Data (Sum a) | Since: base-4.8.0.0 |
Defined in Data.Data gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Sum a -> c (Sum a) # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (Sum a) # dataTypeOf :: Sum a -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (Sum a)) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (Sum a)) # gmapT :: (forall b. Data b => b -> b) -> Sum a -> Sum a # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Sum a -> r # gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Sum a -> r # gmapQ :: (forall d. Data d => d -> u) -> Sum a -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> Sum a -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> Sum a -> m (Sum a) # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Sum a -> m (Sum a) # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Sum a -> m (Sum a) # | |
Num a => Num (Sum a) | Since: base-4.7.0.0 |
Ord a => Ord (Sum a) | Since: base-2.1 |
Read a => Read (Sum a) | Since: base-2.1 |
Show a => Show (Sum a) | Since: base-2.1 |
Generic (Sum a) | |
Num a => Semigroup (Sum a) | Since: base-4.9.0.0 |
Num a => Monoid (Sum a) | Since: base-2.1 |
Function a => Function (Sum a) | |
Arbitrary a => Arbitrary (Sum a) | |
CoArbitrary a => CoArbitrary (Sum a) | |
Defined in Test.QuickCheck.Arbitrary coarbitrary :: Sum a -> Gen b -> Gen b # | |
Binary a => Binary (Sum a) | Since: 0.8.4.0 |
NFData a => NFData (Sum a) | Since: deepseq-1.4.0.0 |
Defined in Control.DeepSeq | |
Unbox a => Unbox (Sum a) | |
Defined in Data.Vector.Unboxed.Base | |
Wrapped (Sum a) | |
Generic1 Sum | |
t ~ Sum b => Rewrapped (Sum a) t | |
Defined in Control.Lens.Wrapped | |
type Rep Sum | |
Defined in Data.Functor.Rep | |
newtype MVector s (Sum a) | |
Defined in Data.Vector.Unboxed.Base | |
type Rep (Sum a) | Since: base-4.7.0.0 |
Defined in Data.Semigroup.Internal | |
newtype Vector (Sum a) | |
Defined in Data.Vector.Unboxed.Base | |
type Unwrapped (Sum a) | |
Defined in Control.Lens.Wrapped | |
type Rep1 Sum | Since: base-4.7.0.0 |
Defined in Data.Semigroup.Internal |
Monoid under multiplication.
>>>
getProduct (Product 3 <> Product 4 <> mempty)
12
Product | |
|
Instances
newtype Alt (f :: k -> Type) (a :: k) :: forall k. (k -> Type) -> k -> Type #
Monoid under <|>
.
Since: base-4.8.0.0
Instances
Generic1 (Alt f :: k -> Type) | |
Unbox (f a) => Vector Vector (Alt f a) | |
Defined in Data.Vector.Unboxed.Base basicUnsafeFreeze :: PrimMonad m => Mutable Vector (PrimState m) (Alt f a) -> m (Vector (Alt f a)) # basicUnsafeThaw :: PrimMonad m => Vector (Alt f a) -> m (Mutable Vector (PrimState m) (Alt f a)) # basicLength :: Vector (Alt f a) -> Int # basicUnsafeSlice :: Int -> Int -> Vector (Alt f a) -> Vector (Alt f a) # basicUnsafeIndexM :: Monad m => Vector (Alt f a) -> Int -> m (Alt f a) # basicUnsafeCopy :: PrimMonad m => Mutable Vector (PrimState m) (Alt f a) -> Vector (Alt f a) -> m () # | |
Unbox (f a) => MVector MVector (Alt f a) | |
Defined in Data.Vector.Unboxed.Base basicLength :: MVector s (Alt f a) -> Int # basicUnsafeSlice :: Int -> Int -> MVector s (Alt f a) -> MVector s (Alt f a) # basicOverlaps :: MVector s (Alt f a) -> MVector s (Alt f a) -> Bool # basicUnsafeNew :: PrimMonad m => Int -> m (MVector (PrimState m) (Alt f a)) # basicInitialize :: PrimMonad m => MVector (PrimState m) (Alt f a) -> m () # basicUnsafeReplicate :: PrimMonad m => Int -> Alt f a -> m (MVector (PrimState m) (Alt f a)) # basicUnsafeRead :: PrimMonad m => MVector (PrimState m) (Alt f a) -> Int -> m (Alt f a) # basicUnsafeWrite :: PrimMonad m => MVector (PrimState m) (Alt f a) -> Int -> Alt f a -> m () # basicClear :: PrimMonad m => MVector (PrimState m) (Alt f a) -> m () # basicSet :: PrimMonad m => MVector (PrimState m) (Alt f a) -> Alt f a -> m () # basicUnsafeCopy :: PrimMonad m => MVector (PrimState m) (Alt f a) -> MVector (PrimState m) (Alt f a) -> m () # basicUnsafeMove :: PrimMonad m => MVector (PrimState m) (Alt f a) -> MVector (PrimState m) (Alt f a) -> m () # basicUnsafeGrow :: PrimMonad m => MVector (PrimState m) (Alt f a) -> Int -> m (MVector (PrimState m) (Alt f a)) # | |
Monad f => Monad (Alt f) | Since: base-4.8.0.0 |
Functor f => Functor (Alt f) | Since: base-4.8.0.0 |
MonadFix f => MonadFix (Alt f) | Since: base-4.8.0.0 |
Defined in Control.Monad.Fix | |
Applicative f => Applicative (Alt f) | Since: base-4.8.0.0 |
Foldable f => Foldable (Alt f) | Since: base-4.12.0.0 |
Defined in Data.Foldable fold :: Monoid m => Alt f m -> m # foldMap :: Monoid m => (a -> m) -> Alt f a -> m # foldr :: (a -> b -> b) -> b -> Alt f a -> b # foldr' :: (a -> b -> b) -> b -> Alt f a -> b # foldl :: (b -> a -> b) -> b -> Alt f a -> b # foldl' :: (b -> a -> b) -> b -> Alt f a -> b # foldr1 :: (a -> a -> a) -> Alt f a -> a # foldl1 :: (a -> a -> a) -> Alt f a -> a # elem :: Eq a => a -> Alt f a -> Bool # maximum :: Ord a => Alt f a -> a # minimum :: Ord a => Alt f a -> a # | |
Traversable f => Traversable (Alt f) | Since: base-4.12.0.0 |
Alternative f => Alternative (Alt f) | Since: base-4.8.0.0 |
MonadPlus f => MonadPlus (Alt f) | Since: base-4.8.0.0 |
Enum (f a) => Enum (Alt f a) | Since: base-4.8.0.0 |
Eq (f a) => Eq (Alt f a) | Since: base-4.8.0.0 |
(Data (f a), Data a, Typeable f) => Data (Alt f a) | Since: base-4.8.0.0 |
Defined in Data.Data gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Alt f a -> c (Alt f a) # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (Alt f a) # toConstr :: Alt f a -> Constr # dataTypeOf :: Alt f a -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (Alt f a)) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (Alt f a)) # gmapT :: (forall b. Data b => b -> b) -> Alt f a -> Alt f a # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Alt f a -> r # gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Alt f a -> r # gmapQ :: (forall d. Data d => d -> u) -> Alt f a -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> Alt f a -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> Alt f a -> m (Alt f a) # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Alt f a -> m (Alt f a) # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Alt f a -> m (Alt f a) # | |
Num (f a) => Num (Alt f a) | Since: base-4.8.0.0 |
Ord (f a) => Ord (Alt f a) | Since: base-4.8.0.0 |
Read (f a) => Read (Alt f a) | Since: base-4.8.0.0 |
Show (f a) => Show (Alt f a) | Since: base-4.8.0.0 |
Generic (Alt f a) | |
Alternative f => Semigroup (Alt f a) | Since: base-4.9.0.0 |
Alternative f => Monoid (Alt f a) | Since: base-4.8.0.0 |
Function (f a) => Function (Alt f a) | |
Arbitrary (f a) => Arbitrary (Alt f a) | |
CoArbitrary (f a) => CoArbitrary (Alt f a) | |
Defined in Test.QuickCheck.Arbitrary coarbitrary :: Alt f a -> Gen b -> Gen b # | |
Binary (f a) => Binary (Alt f a) | Since: 0.8.4.0 |
Unbox (f a) => Unbox (Alt f a) | |
Defined in Data.Vector.Unboxed.Base | |
Wrapped (Alt f a) | |
t ~ Alt g b => Rewrapped (Alt f a) t | |
Defined in Control.Lens.Wrapped | |
type Rep1 (Alt f :: k -> Type) | Since: base-4.8.0.0 |
Defined in Data.Semigroup.Internal | |
newtype MVector s (Alt f a) | |
Defined in Data.Vector.Unboxed.Base | |
type Rep (Alt f a) | Since: base-4.8.0.0 |
Defined in Data.Semigroup.Internal | |
newtype Vector (Alt f a) | |
Defined in Data.Vector.Unboxed.Base | |
type Unwrapped (Alt f a) | |
Defined in Control.Lens.Wrapped |
words
breaks a string up into a list of words, which were delimited
by white space.
>>>
words "Lorem ipsum\ndolor"
["Lorem","ipsum","dolor"]
unfoldr :: (b -> Maybe (a, b)) -> b -> [a] #
The unfoldr
function is a `dual' to foldr
: while foldr
reduces a list to a summary value, unfoldr
builds a list from
a seed value. The function takes the element and returns Nothing
if it is done producing the list or returns Just
(a,b)
, in which
case, a
is a prepended to the list and b
is used as the next
element in a recursive call. For example,
iterate f == unfoldr (\x -> Just (x, f x))
In some cases, unfoldr
can undo a foldr
operation:
unfoldr f' (foldr f z xs) == xs
if the following holds:
f' (f x y) = Just (x,y) f' z = Nothing
A simple use of unfoldr:
>>>
unfoldr (\b -> if b == 0 then Nothing else Just (b, b-1)) 10
[10,9,8,7,6,5,4,3,2,1]
sortOn :: Ord b => (a -> b) -> [a] -> [a] #
Sort a list by comparing the results of a key function applied to each
element. sortOn f
is equivalent to sortBy (comparing f)
, but has the
performance advantage of only evaluating f
once for each element in the
input list. This is called the decorate-sort-undecorate paradigm, or
Schwartzian transform.
Elements are arranged from from lowest to highest, keeping duplicates in the order they appeared in the input.
>>>
sortOn fst [(2, "world"), (4, "!"), (1, "Hello")]
[(1,"Hello"),(2,"world"),(4,"!")]
Since: base-4.8.0.0
The sort
function implements a stable sorting algorithm.
It is a special case of sortBy
, which allows the programmer to supply
their own comparison function.
Elements are arranged from from lowest to highest, keeping duplicates in the order they appeared in the input.
>>>
sort [1,6,4,3,2,5]
[1,2,3,4,5,6]
permutations :: [a] -> [[a]] #
The permutations
function returns the list of all permutations of the argument.
>>>
permutations "abc"
["abc","bac","cba","bca","cab","acb"]
subsequences :: [a] -> [[a]] #
The subsequences
function returns the list of all subsequences of the argument.
>>>
subsequences "abc"
["","a","b","ab","c","ac","bc","abc"]
group :: Eq a => [a] -> [[a]] #
The group
function takes a list and returns a list of lists such
that the concatenation of the result is equal to the argument. Moreover,
each sublist in the result contains only equal elements. For example,
>>>
group "Mississippi"
["M","i","ss","i","ss","i","pp","i"]
It is a special case of groupBy
, which allows the programmer to supply
their own equality test.
deleteFirstsBy :: (a -> a -> Bool) -> [a] -> [a] -> [a] #
The deleteFirstsBy
function takes a predicate and two lists and
returns the first list with the first occurrence of each element of
the second list removed.
zipWith7 :: (a -> b -> c -> d -> e -> f -> g -> h) -> [a] -> [b] -> [c] -> [d] -> [e] -> [f] -> [g] -> [h] #
genericReplicate :: Integral i => i -> a -> [a] #
The genericReplicate
function is an overloaded version of replicate
,
which accepts any Integral
value as the number of repetitions to make.
genericIndex :: Integral i => [a] -> i -> a #
The genericIndex
function is an overloaded version of !!
, which
accepts any Integral
value as the index.
genericSplitAt :: Integral i => i -> [a] -> ([a], [a]) #
The genericSplitAt
function is an overloaded version of splitAt
, which
accepts any Integral
value as the position at which to split.
genericDrop :: Integral i => i -> [a] -> [a] #
The genericDrop
function is an overloaded version of drop
, which
accepts any Integral
value as the number of elements to drop.
genericTake :: Integral i => i -> [a] -> [a] #
The genericTake
function is an overloaded version of take
, which
accepts any Integral
value as the number of elements to take.
genericLength :: Num i => [a] -> i #
The genericLength
function is an overloaded version of length
. In
particular, instead of returning an Int
, it returns any type which is
an instance of Num
. It is, however, less efficient than length
.
insert :: Ord a => a -> [a] -> [a] #
The insert
function takes an element and a list and inserts the
element into the list at the first position where it is less
than or equal to the next element. In particular, if the list
is sorted before the call, the result will also be sorted.
It is a special case of insertBy
, which allows the programmer to
supply their own comparison function.
>>>
insert 4 [1,2,3,5,6,7]
[1,2,3,4,5,6,7]
partition :: (a -> Bool) -> [a] -> ([a], [a]) #
The partition
function takes a predicate a list and returns
the pair of lists of elements which do and do not satisfy the
predicate, respectively; i.e.,
partition p xs == (filter p xs, filter (not . p) xs)
>>>
partition (`elem` "aeiou") "Hello World!"
("eoo","Hll Wrld!")
The transpose
function transposes the rows and columns of its argument.
For example,
>>>
transpose [[1,2,3],[4,5,6]]
[[1,4],[2,5],[3,6]]
If some of the rows are shorter than the following rows, their elements are skipped:
>>>
transpose [[10,11],[20],[],[30,31,32]]
[[10,20,30],[11,31],[32]]
intercalate :: [a] -> [[a]] -> [a] #
intercalate
xs xss
is equivalent to (
.
It inserts the list concat
(intersperse
xs xss))xs
in between the lists in xss
and concatenates the
result.
>>>
intercalate ", " ["Lorem", "ipsum", "dolor"]
"Lorem, ipsum, dolor"
intersperse :: a -> [a] -> [a] #
The intersperse
function takes an element and a list and
`intersperses' that element between the elements of the list.
For example,
>>>
intersperse ',' "abcde"
"a,b,c,d,e"
intersectBy :: (a -> a -> Bool) -> [a] -> [a] -> [a] #
The intersectBy
function is the non-overloaded version of intersect
.
intersect :: Eq a => [a] -> [a] -> [a] #
The intersect
function takes the list intersection of two lists.
For example,
>>>
[1,2,3,4] `intersect` [2,4,6,8]
[2,4]
If the first list contains duplicates, so will the result.
>>>
[1,2,2,3,4] `intersect` [6,4,4,2]
[2,2,4]
It is a special case of intersectBy
, which allows the programmer to
supply their own equality test. If the element is found in both the first
and the second list, the element from the first list will be used.
union :: Eq a => [a] -> [a] -> [a] #
The union
function returns the list union of the two lists.
For example,
>>>
"dog" `union` "cow"
"dogcw"
Duplicates, and elements of the first list, are removed from the
the second list, but if the first list contains duplicates, so will
the result.
It is a special case of unionBy
, which allows the programmer to supply
their own equality test.
(\\) :: Eq a => [a] -> [a] -> [a] infix 5 #
The \\
function is list difference (non-associative).
In the result of xs
\\
ys
, the first occurrence of each element of
ys
in turn (if any) has been removed from xs
. Thus
(xs ++ ys) \\ xs == ys.
>>>
"Hello World!" \\ "ell W"
"Hoorld!"
It is a special case of deleteFirstsBy
, which allows the programmer
to supply their own equality test.
O(n^2). The nub
function removes duplicate elements from a list.
In particular, it keeps only the first occurrence of each element.
(The name nub
means `essence'.)
It is a special case of nubBy
, which allows the programmer to supply
their own equality test.
>>>
nub [1,2,3,4,3,2,1,2,4,3,5]
[1,2,3,4,5]
isSuffixOf :: Eq a => [a] -> [a] -> Bool #
The isSuffixOf
function takes two lists and returns True
iff
the first list is a suffix of the second. The second list must be
finite.
>>>
"ld!" `isSuffixOf` "Hello World!"
True
>>>
"World" `isSuffixOf` "Hello World!"
False
isPrefixOf :: Eq a => [a] -> [a] -> Bool #
The isPrefixOf
function takes two lists and returns True
iff the first list is a prefix of the second.
>>>
"Hello" `isPrefixOf` "Hello World!"
True
>>>
"Hello" `isPrefixOf` "Wello Horld!"
False
findIndices :: (a -> Bool) -> [a] -> [Int] #
The findIndices
function extends findIndex
, by returning the
indices of all elements satisfying the predicate, in ascending order.
>>>
findIndices (`elem` "aeiou") "Hello World!"
[1,4,7]
elemIndices :: Eq a => a -> [a] -> [Int] #
The elemIndices
function extends elemIndex
, by returning the
indices of all elements equal to the query element, in ascending order.
>>>
elemIndices 'o' "Hello World"
[4,7]
stripPrefix :: Eq a => [a] -> [a] -> Maybe [a] #
The stripPrefix
function drops the given prefix from a list.
It returns Nothing
if the list did not start with the prefix
given, or Just
the list after the prefix, if it does.
>>>
stripPrefix "foo" "foobar"
Just "bar"
>>>
stripPrefix "foo" "foo"
Just ""
>>>
stripPrefix "foo" "barfoo"
Nothing
>>>
stripPrefix "foo" "barfoobaz"
Nothing
dropWhileEnd :: (a -> Bool) -> [a] -> [a] #
The dropWhileEnd
function drops the largest suffix of a list
in which the given predicate holds for all elements. For example:
>>>
dropWhileEnd isSpace "foo\n"
"foo"
>>>
dropWhileEnd isSpace "foo bar"
"foo bar"
dropWhileEnd isSpace ("foo\n" ++ undefined) == "foo" ++ undefined
Since: base-4.5.0.0
void :: Functor f => f a -> f () #
discards or ignores the result of evaluation, such
as the return value of an void
valueIO
action.
Examples
Replace the contents of a
with unit:Maybe
Int
>>>
void Nothing
Nothing>>>
void (Just 3)
Just ()
Replace the contents of an
with unit,
resulting in an Either
Int
Int
:Either
Int
'()'
>>>
void (Left 8675309)
Left 8675309>>>
void (Right 8675309)
Right ()
Replace every element of a list with unit:
>>>
void [1,2,3]
[(),(),()]
Replace the second element of a pair with unit:
>>>
void (1,2)
(1,())
Discard the result of an IO
action:
>>>
mapM print [1,2]
1 2 [(),()]>>>
void $ mapM print [1,2]
1 2
unzip :: [(a, b)] -> ([a], [b]) #
unzip
transforms a list of pairs into a list of first components
and a list of second components.
(!!) :: [a] -> Int -> a infixl 9 #
List index (subscript) operator, starting from 0.
It is an instance of the more general genericIndex
,
which takes an index of any integral type.
lookup :: Eq a => a -> [(a, b)] -> Maybe b #
lookup
key assocs
looks up a key in an association list.
break :: (a -> Bool) -> [a] -> ([a], [a]) #
break
, applied to a predicate p
and a list xs
, returns a tuple where
first element is longest prefix (possibly empty) of xs
of elements that
do not satisfy p
and second element is the remainder of the list:
break (> 3) [1,2,3,4,1,2,3,4] == ([1,2,3],[4,1,2,3,4]) break (< 9) [1,2,3] == ([],[1,2,3]) break (> 9) [1,2,3] == ([1,2,3],[])
span :: (a -> Bool) -> [a] -> ([a], [a]) #
span
, applied to a predicate p
and a list xs
, returns a tuple where
first element is longest prefix (possibly empty) of xs
of elements that
satisfy p
and second element is the remainder of the list:
span (< 3) [1,2,3,4,1,2,3,4] == ([1,2],[3,4,1,2,3,4]) span (< 9) [1,2,3] == ([1,2,3],[]) span (< 0) [1,2,3] == ([],[1,2,3])
splitAt :: Int -> [a] -> ([a], [a]) #
splitAt
n xs
returns a tuple where first element is xs
prefix of
length n
and second element is the remainder of the list:
splitAt 6 "Hello World!" == ("Hello ","World!") splitAt 3 [1,2,3,4,5] == ([1,2,3],[4,5]) splitAt 1 [1,2,3] == ([1],[2,3]) splitAt 3 [1,2,3] == ([1,2,3],[]) splitAt 4 [1,2,3] == ([1,2,3],[]) splitAt 0 [1,2,3] == ([],[1,2,3]) splitAt (-1) [1,2,3] == ([],[1,2,3])
It is equivalent to (
when take
n xs, drop
n xs)n
is not _|_
(splitAt _|_ xs = _|_
).
splitAt
is an instance of the more general genericSplitAt
,
in which n
may be of any integral type.
drop
n xs
returns the suffix of xs
after the first n
elements, or []
if n >
:length
xs
drop 6 "Hello World!" == "World!" drop 3 [1,2,3,4,5] == [4,5] drop 3 [1,2] == [] drop 3 [] == [] drop (-1) [1,2] == [1,2] drop 0 [1,2] == [1,2]
It is an instance of the more general genericDrop
,
in which n
may be of any integral type.
take
n
, applied to a list xs
, returns the prefix of xs
of length n
, or xs
itself if n >
:length
xs
take 5 "Hello World!" == "Hello" take 3 [1,2,3,4,5] == [1,2,3] take 3 [1,2] == [1,2] take 3 [] == [] take (-1) [1,2] == [] take 0 [1,2] == []
It is an instance of the more general genericTake
,
in which n
may be of any integral type.
takeWhile :: (a -> Bool) -> [a] -> [a] #
takeWhile
, applied to a predicate p
and a list xs
, returns the
longest prefix (possibly empty) of xs
of elements that satisfy p
:
takeWhile (< 3) [1,2,3,4,1,2,3,4] == [1,2] takeWhile (< 9) [1,2,3] == [1,2,3] takeWhile (< 0) [1,2,3] == []
cycle
ties a finite list into a circular one, or equivalently,
the infinite repetition of the original list. It is the identity
on infinite lists.
replicate :: Int -> a -> [a] #
replicate
n x
is a list of length n
with x
the value of
every element.
It is an instance of the more general genericReplicate
,
in which n
may be of any integral type.
iterate' :: (a -> a) -> a -> [a] #
'iterate\'' is the strict version of iterate
.
It ensures that the result of each application of force to weak head normal form before proceeding.
Return all the elements of a list except the last one. The list must be non-empty.
mapMaybe :: (a -> Maybe b) -> [a] -> [b] #
The mapMaybe
function is a version of map
which can throw
out elements. In particular, the functional argument returns
something of type
. If this is Maybe
bNothing
, no element
is added on to the result list. If it is
, then Just
bb
is
included in the result list.
Examples
Using
is a shortcut for mapMaybe
f x
in most cases:catMaybes
$ map
f x
>>>
import Text.Read ( readMaybe )
>>>
let readMaybeInt = readMaybe :: String -> Maybe Int
>>>
mapMaybe readMaybeInt ["1", "Foo", "3"]
[1,3]>>>
catMaybes $ map readMaybeInt ["1", "Foo", "3"]
[1,3]
If we map the Just
constructor, the entire list should be returned:
>>>
mapMaybe Just [1,2,3]
[1,2,3]
catMaybes :: [Maybe a] -> [a] #
The catMaybes
function takes a list of Maybe
s and returns
a list of all the Just
values.
Examples
Basic usage:
>>>
catMaybes [Just 1, Nothing, Just 3]
[1,3]
When constructing a list of Maybe
values, catMaybes
can be used
to return all of the "success" results (if the list is the result
of a map
, then mapMaybe
would be more appropriate):
>>>
import Text.Read ( readMaybe )
>>>
[readMaybe x :: Maybe Int | x <- ["1", "Foo", "3"] ]
[Just 1,Nothing,Just 3]>>>
catMaybes $ [readMaybe x :: Maybe Int | x <- ["1", "Foo", "3"] ]
[1,3]
listToMaybe :: [a] -> Maybe a #
The listToMaybe
function returns Nothing
on an empty list
or
where Just
aa
is the first element of the list.
Examples
Basic usage:
>>>
listToMaybe []
Nothing
>>>
listToMaybe [9]
Just 9
>>>
listToMaybe [1,2,3]
Just 1
Composing maybeToList
with listToMaybe
should be the identity
on singleton/empty lists:
>>>
maybeToList $ listToMaybe [5]
[5]>>>
maybeToList $ listToMaybe []
[]
But not on lists with more than one element:
>>>
maybeToList $ listToMaybe [1,2,3]
[1]
maybeToList :: Maybe a -> [a] #
The maybeToList
function returns an empty list when given
Nothing
or a singleton list when not given Nothing
.
Examples
Basic usage:
>>>
maybeToList (Just 7)
[7]
>>>
maybeToList Nothing
[]
One can use maybeToList
to avoid pattern matching when combined
with a function that (safely) works on lists:
>>>
import Text.Read ( readMaybe )
>>>
sum $ maybeToList (readMaybe "3")
3>>>
sum $ maybeToList (readMaybe "")
0
fromMaybe :: a -> Maybe a -> a #
The fromMaybe
function takes a default value and and Maybe
value. If the Maybe
is Nothing
, it returns the default values;
otherwise, it returns the value contained in the Maybe
.
Examples
Basic usage:
>>>
fromMaybe "" (Just "Hello, World!")
"Hello, World!"
>>>
fromMaybe "" Nothing
""
Read an integer from a string using readMaybe
. If we fail to
parse an integer, we want to return 0
by default:
>>>
import Text.Read ( readMaybe )
>>>
fromMaybe 0 (readMaybe "5")
5>>>
fromMaybe 0 (readMaybe "")
0
maybe :: b -> (a -> b) -> Maybe a -> b #
The maybe
function takes a default value, a function, and a Maybe
value. If the Maybe
value is Nothing
, the function returns the
default value. Otherwise, it applies the function to the value inside
the Just
and returns the result.
Examples
Basic usage:
>>>
maybe False odd (Just 3)
True
>>>
maybe False odd Nothing
False
Read an integer from a string using readMaybe
. If we succeed,
return twice the integer; that is, apply (*2)
to it. If instead
we fail to parse an integer, return 0
by default:
>>>
import Text.Read ( readMaybe )
>>>
maybe 0 (*2) (readMaybe "5")
10>>>
maybe 0 (*2) (readMaybe "")
0
Apply show
to a Maybe Int
. If we have Just n
, we want to show
the underlying Int
n
. But if we have Nothing
, we return the
empty string instead of (for example) "Nothing":
>>>
maybe "" show (Just 5)
"5">>>
maybe "" show Nothing
""
liftM5 :: Monad m => (a1 -> a2 -> a3 -> a4 -> a5 -> r) -> m a1 -> m a2 -> m a3 -> m a4 -> m a5 -> m r #
Promote a function to a monad, scanning the monadic arguments from
left to right (cf. liftM2
).
liftM4 :: Monad m => (a1 -> a2 -> a3 -> a4 -> r) -> m a1 -> m a2 -> m a3 -> m a4 -> m r #
Promote a function to a monad, scanning the monadic arguments from
left to right (cf. liftM2
).
liftM3 :: Monad m => (a1 -> a2 -> a3 -> r) -> m a1 -> m a2 -> m a3 -> m r #
Promote a function to a monad, scanning the monadic arguments from
left to right (cf. liftM2
).
liftM2 :: Monad m => (a1 -> a2 -> r) -> m a1 -> m a2 -> m r #
Promote a function to a monad, scanning the monadic arguments from left to right. For example,
liftM2 (+) [0,1] [0,2] = [0,2,1,3] liftM2 (+) (Just 1) Nothing = Nothing
when :: Applicative f => Bool -> f () -> f () #
Conditional execution of Applicative
expressions. For example,
when debug (putStrLn "Debugging")
will output the string Debugging
if the Boolean value debug
is True
, and otherwise do nothing.
(=<<) :: Monad m => (a -> m b) -> m a -> m b infixr 1 #
Same as >>=
, but with the arguments interchanged.
liftA3 :: Applicative f => (a -> b -> c -> d) -> f a -> f b -> f c -> f d #
Lift a ternary function to actions.
liftA :: Applicative f => (a -> b) -> f a -> f b #
(<**>) :: Applicative f => f a -> f (a -> b) -> f b infixl 4 #
A variant of <*>
with the arguments reversed.
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
(</>) :: FilePath -> FilePath -> FilePath infixr 5 #
Combine two paths with a path separator.
If the second path starts with a path separator or a drive letter, then it returns the second.
The intention is that readFile (dir
will access the same file as
</>
file)setCurrentDirectory dir; readFile file
.
Posix: "/directory" </> "file.ext" == "/directory/file.ext" Windows: "/directory" </> "file.ext" == "/directory\\file.ext" "directory" </> "/file.ext" == "/file.ext" Valid x => (takeDirectory x </> takeFileName x) `equalFilePath` x
Combined:
Posix: "/" </> "test" == "/test" Posix: "home" </> "bob" == "home/bob" Posix: "x:" </> "foo" == "x:/foo" Windows: "C:\\foo" </> "bar" == "C:\\foo\\bar" Windows: "home" </> "bob" == "home\\bob"
Not combined:
Posix: "home" </> "/bob" == "/bob" Windows: "home" </> "C:\\bob" == "C:\\bob"
Not combined (tricky):
On Windows, if a filepath starts with a single slash, it is relative to the
root of the current drive. In [1], this is (confusingly) referred to as an
absolute path.
The current behavior of </>
is to never combine these forms.
Windows: "home" </> "/bob" == "/bob" Windows: "home" </> "\\bob" == "\\bob" Windows: "C:\\home" </> "\\bob" == "\\bob"
On Windows, from [1]: "If a file name begins with only a disk designator
but not the backslash after the colon, it is interpreted as a relative path
to the current directory on the drive with the specified letter."
The current behavior of </>
is to never combine these forms.
Windows: "D:\\foo" </> "C:bar" == "C:bar" Windows: "C:\\foo" </> "C:bar" == "C:bar"
takeDirectory :: FilePath -> FilePath #
Get the directory name, move up one level.
takeDirectory "/directory/other.ext" == "/directory" takeDirectory x `isPrefixOf` x || takeDirectory x == "." takeDirectory "foo" == "." takeDirectory "/" == "/" takeDirectory "/foo" == "/" takeDirectory "/foo/bar/baz" == "/foo/bar" takeDirectory "/foo/bar/baz/" == "/foo/bar/baz" takeDirectory "foo/bar/baz" == "foo/bar" Windows: takeDirectory "foo\\bar" == "foo" Windows: takeDirectory "foo\\bar\\\\" == "foo\\bar" Windows: takeDirectory "C:\\" == "C:\\"
takeFileName :: FilePath -> FilePath #
Get the file name.
takeFileName "/directory/file.ext" == "file.ext" takeFileName "test/" == "" takeFileName x `isSuffixOf` x takeFileName x == snd (splitFileName x) Valid x => takeFileName (replaceFileName x "fred") == "fred" Valid x => takeFileName (x </> "fred") == "fred" Valid x => isRelative (takeFileName x)
(<.>) :: FilePath -> String -> FilePath infixr 7 #
Add an extension, even if there is already one there, equivalent to addExtension
.
"/directory/path" <.> "ext" == "/directory/path.ext" "/directory/path" <.> ".ext" == "/directory/path.ext"
replaceExtension :: FilePath -> String -> FilePath #
Set the extension of a file, overwriting one if already present, equivalent to -<.>
.
replaceExtension "/directory/path.txt" "ext" == "/directory/path.ext" replaceExtension "/directory/path.txt" ".ext" == "/directory/path.ext" replaceExtension "file.txt" ".bob" == "file.bob" replaceExtension "file.txt" "bob" == "file.bob" replaceExtension "file" ".bob" == "file.bob" replaceExtension "file.txt" "" == "file" replaceExtension "file.fred.bob" "txt" == "file.fred.txt" replaceExtension x y == addExtension (dropExtension x) y
(^.) :: s -> Getting a s a -> a infixl 8 #
View the value pointed to by a Getter
or Lens
or the
result of folding over all the results of a Fold
or
Traversal
that points at a monoidal values.
This is the same operation as view
with the arguments flipped.
The fixity and semantics are such that subsequent field accesses can be
performed with (.
).
>>>
(a,b)^._2
b
>>>
("hello","world")^._2
"world"
>>>
import Data.Complex
>>>
((0, 1 :+ 2), 3)^._1._2.to magnitude
2.23606797749979
(^.
) :: s ->Getter
s a -> a (^.
) ::Monoid
m => s ->Fold
s m -> m (^.
) :: s ->Iso'
s a -> a (^.
) :: s ->Lens'
s a -> a (^.
) ::Monoid
m => s ->Traversal'
s m -> m
(.~) :: ASetter s t a b -> b -> s -> t infixr 4 #
Replace the target of a Lens
or all of the targets of a Setter
or Traversal
with a constant value.
This is an infix version of set
, provided for consistency with (.=
).
f<$
a ≡mapped
.~
f$
a
>>>
(a,b,c,d) & _4 .~ e
(a,b,c,e)
>>>
(42,"world") & _1 .~ "hello"
("hello","world")
>>>
(a,b) & both .~ c
(c,c)
(.~
) ::Setter
s t a b -> b -> s -> t (.~
) ::Iso
s t a b -> b -> s -> t (.~
) ::Lens
s t a b -> b -> s -> t (.~
) ::Traversal
s t a b -> b -> s -> t
(%~) :: ASetter s t a b -> (a -> b) -> s -> t infixr 4 #
Modifies the target of a Lens
or all of the targets of a Setter
or
Traversal
with a user supplied function.
This is an infix version of over
.
fmap
f ≡mapped
%~
ffmapDefault
f ≡traverse
%~
f
>>>
(a,b,c) & _3 %~ f
(a,b,f c)
>>>
(a,b) & both %~ f
(f a,f b)
>>>
_2 %~ length $ (1,"hello")
(1,5)
>>>
traverse %~ f $ [a,b,c]
[f a,f b,f c]
>>>
traverse %~ even $ [1,2,3]
[False,True,False]
>>>
traverse.traverse %~ length $ [["hello","world"],["!!!"]]
[[5,5],[3]]
(%~
) ::Setter
s t a b -> (a -> b) -> s -> t (%~
) ::Iso
s t a b -> (a -> b) -> s -> t (%~
) ::Lens
s t a b -> (a -> b) -> s -> t (%~
) ::Traversal
s t a b -> (a -> b) -> s -> t
type Lens s t a b = forall (f :: Type -> Type). Functor f => (a -> f b) -> s -> f t #
A Lens
is actually a lens family as described in
http://comonad.com/reader/2012/mirrored-lenses/.
With great power comes great responsibility and a Lens
is subject to the
three common sense Lens
laws:
1) You get back what you put in:
view
l (set
l v s) ≡ v
2) Putting back what you got doesn't change anything:
set
l (view
l s) s ≡ s
3) Setting twice is the same as setting once:
set
l v' (set
l v s) ≡set
l v' s
These laws are strong enough that the 4 type parameters of a Lens
cannot
vary fully independently. For more on how they interact, read the "Why is
it a Lens Family?" section of
http://comonad.com/reader/2012/mirrored-lenses/.
There are some emergent properties of these laws:
1)
must be injective for every set
l ss
This is a consequence of law #1
2)
must be surjective, because of law #2, which indicates that it is possible to obtain any set
lv
from some s
such that set
s v = s
3) Given just the first two laws you can prove a weaker form of law #3 where the values v
that you are setting match:
set
l v (set
l v s) ≡set
l v s
Every Lens
can be used directly as a Setter
or Traversal
.
You can also use a Lens
for Getting
as if it were a
Fold
or Getter
.
Since every Lens
is a valid Traversal
, the
Traversal
laws are required of any Lens
you create:
lpure
≡pure
fmap
(l f).
l g ≡getCompose
.
l (Compose
.
fmap
f.
g)
typeLens
s t a b = forall f.Functor
f =>LensLike
f s t a b
This is a simple runtime exception to indicate that B9 code encountered some exceptional event.
Since: 0.5.64
Instances
Show B9Error Source # | |
IsString B9Error Source # | |
Defined in B9.B9Error fromString :: String -> B9Error # | |
Exception B9Error Source # | |
Defined in B9.B9Error toException :: B9Error -> SomeException # fromException :: SomeException -> Maybe B9Error # displayException :: B9Error -> String # |
type WithIoExceptions e = SetMember Exc (Exc SomeException) e Source #
Constraint alias for the exception effect that allows to
throw SomeException
.
Since: 1.0.0
type ExcB9 = Exc SomeException Source #
The exception effect used in most places in B9.
This is Exc
specialized with SomeException
.
Since: 0.5.64
throwSomeException :: (Member ExcB9 e, Exception x) => x -> Eff e a Source #
SomeException
wrapped into Exc
ecption Eff
ects
Since: 0.5.64
throwSomeException_ :: (Member ExcB9 e, Exception x) => x -> Eff e () Source #
SomeException
wrapped into Exc
ecption Eff
ects
Since: 0.5.64
throwB9Error :: Member ExcB9 e => String -> Eff e a Source #
SomeException
wrapped into Exc
ecption Eff
ects
Since: 0.5.64
throwB9Error_ :: Member ExcB9 e => String -> Eff e () Source #
SomeException
wrapped into Exc
ecption Eff
ects
Since: 0.5.64
catchB9Error :: Member ExcB9 e => Eff e a -> (SomeException -> Eff e a) -> Eff e a Source #
Catch exceptions.
Since: 0.5.64
catchB9ErrorAsEither :: Member ExcB9 e => Eff e a -> Eff e (Either SomeException a) Source #
Catch exceptions and return them via Either
.
Since: 0.5.64
finallyB9 :: Member ExcB9 e => Eff e a -> Eff e () -> Eff e a Source #
Always execute an action and rethrow any exceptions caught.
Since: 1.0.0
arbitraryDigit :: Gen Char Source #
newtype SharedImageBuildId Source #
Every B9 build running in a B9Monad
contains a random unique id that is generated once per build (no matter how
many artifacts are created in that build) This field contains the build id
of the build that created the shared image instance. This is A wrapper
around a string contains the build id of a SharedImage
; this is purely
additional convenience and typesafety
newtype SharedImageDate Source #
The exact time that build job started.
This is a wrapper around a string contains the build date of a
SharedImage
; this is purely additional convenience and typesafety
newtype SharedImageName Source #
The name of the image is the de-facto identifier for push, pull, From
and
Share
. B9 always selects the newest version the shared image identified
by that name when using a shared image as an ImageSource
. This is a
wrapper around a string that identifies a SharedImage
data SharedImage Source #
SharedImage
holds all data necessary to describe an instance of a shared
image identified by a SharedImageName
. Shared images are stored in
Repository
s.
type Mounted a = (a, MountPoint) Source #
A type alias that indicates that something of type a
is mount at a
MountPoint
data ImageResize Source #
How to resize an image file.
ResizeImage ImageSize | Resize the image but not the file system. Note that
a file system contained in the image file might be
corrupted by this operation. To not only resize the image
file but also the fil system contained in it, use
|
Resize ImageSize | Resize an image and the contained file system. |
ShrinkToMinimumAndIncrease ImageSize | Shrink to minimum size needed and increase by the amount given. |
ShrinkToMinimum | Resize an image and the contained file system to the smallest size to fit the contents of the file system. |
KeepSize | Do not change the image size. |
Instances
Enumeration of size multipliers. The exact semantics may vary depending on
what external tools look at these. E.g. the size unit is convert to a size
parameter of the qemu-img
command line tool.
Instances
Bounded SizeUnit Source # | |
Enum SizeUnit Source # | |
Eq SizeUnit Source # | |
Data SizeUnit Source # | |
Defined in B9.DiskImages gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> SizeUnit -> c SizeUnit # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c SizeUnit # toConstr :: SizeUnit -> Constr # dataTypeOf :: SizeUnit -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c SizeUnit) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c SizeUnit) # gmapT :: (forall b. Data b => b -> b) -> SizeUnit -> SizeUnit # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> SizeUnit -> r # gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> SizeUnit -> r # gmapQ :: (forall d. Data d => d -> u) -> SizeUnit -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> SizeUnit -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> SizeUnit -> m SizeUnit # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> SizeUnit -> m SizeUnit # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> SizeUnit -> m SizeUnit # | |
Ord SizeUnit Source # | |
Defined in B9.DiskImages | |
Read SizeUnit Source # | |
Show SizeUnit Source # | |
Generic SizeUnit Source # | |
Arbitrary SizeUnit Source # | |
Hashable SizeUnit Source # | |
Defined in B9.DiskImages | |
Binary SizeUnit Source # | |
NFData SizeUnit Source # | |
Defined in B9.DiskImages | |
type Rep SizeUnit Source # | |
A data type for image file or file system size; instead of passing Int
s
around this also captures a size unit so that the Int
can be kept small
Instances
data FileSystem Source #
The file systems that b9 can use and convert.
Instances
An image type defines the actual file format of a file containing file systems. These are like virtual harddrives
Instances
Eq ImageType Source # | |
Data ImageType Source # | |
Defined in B9.DiskImages gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> ImageType -> c ImageType # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c ImageType # toConstr :: ImageType -> Constr # dataTypeOf :: ImageType -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c ImageType) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c ImageType) # gmapT :: (forall b. Data b => b -> b) -> ImageType -> ImageType # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> ImageType -> r # gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> ImageType -> r # gmapQ :: (forall d. Data d => d -> u) -> ImageType -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> ImageType -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> ImageType -> m ImageType # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> ImageType -> m ImageType # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> ImageType -> m ImageType # | |
Read ImageType Source # | |
Show ImageType Source # | |
Generic ImageType Source # | |
Function ImageType Source # | |
Arbitrary ImageType Source # | |
CoArbitrary ImageType Source # | |
Defined in B9.DiskImages coarbitrary :: ImageType -> Gen b -> Gen b # | |
Hashable ImageType Source # | |
Defined in B9.DiskImages | |
Binary ImageType Source # | |
NFData ImageType Source # | |
Defined in B9.DiskImages | |
type Rep ImageType Source # | |
A vm disk image file consisting of a path to the image file, and the type and file system.
Instances
Eq Image Source # | |
Data Image Source # | |
Defined in B9.DiskImages gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Image -> c Image # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Image # dataTypeOf :: Image -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c Image) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Image) # gmapT :: (forall b. Data b => b -> b) -> Image -> Image # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Image -> r # gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Image -> r # gmapQ :: (forall d. Data d => d -> u) -> Image -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> Image -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> Image -> m Image # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Image -> m Image # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Image -> m Image # | |
Read Image Source # | |
Show Image Source # | |
Generic Image Source # | |
Arbitrary Image Source # | |
Hashable Image Source # | |
Defined in B9.DiskImages | |
Binary Image Source # | |
NFData Image Source # | |
Defined in B9.DiskImages | |
type Rep Image Source # | |
Defined in B9.DiskImages type Rep Image = D1 (MetaData "Image" "B9.DiskImages" "b9-1.1.0-inplace" False) (C1 (MetaCons "Image" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 FilePath) :*: (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 ImageType) :*: S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 FileSystem)))) |
The partition to extract.
Instances
Eq Partition Source # | |
Data Partition Source # | |
Defined in B9.DiskImages gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Partition -> c Partition # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Partition # toConstr :: Partition -> Constr # dataTypeOf :: Partition -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c Partition) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Partition) # gmapT :: (forall b. Data b => b -> b) -> Partition -> Partition # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Partition -> r # gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Partition -> r # gmapQ :: (forall d. Data d => d -> u) -> Partition -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> Partition -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> Partition -> m Partition # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Partition -> m Partition # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Partition -> m Partition # | |
Read Partition Source # | |
Show Partition Source # | |
Generic Partition Source # | |
Arbitrary Partition Source # | |
Hashable Partition Source # | |
Defined in B9.DiskImages | |
Binary Partition Source # | |
NFData Partition Source # | |
Defined in B9.DiskImages | |
type Rep Partition Source # | |
Defined in B9.DiskImages |
data ImageSource Source #
Specification of how the image to build is obtained.
EmptyImage String FileSystem ImageType ImageSize | Create an empty image file having a file system label
(first parameter), a file system type (e.g. |
CopyOnWrite Image | DEPRECATED |
SourceImage Image Partition ImageResize | Clone an existing image file; if the image file contains
partitions, select the partition to use, b9 will extract
that partition by reading the offset of the partition from
the partition table and extract it using |
From String ImageResize | Use an image previously shared by via |
Instances
data ImageDestination Source #
The destination of an image.
Share String ImageType ImageResize | Create the image and some meta data so that other
builds can use them as |
LiveInstallerImage String FilePath ImageResize | DEPRECATED Export a raw image that can directly be booted. |
LocalFile Image ImageResize | Write an image file to the path in the first argument., possible resizing it, |
Transient | Do not export the image. Usefule if the main objective of the b9 build is not an image file, but rather some artifact produced by executing by a containerize build. |
Instances
data MountPoint Source #
A mount point or NotMounted
Instances
data ImageTarget Source #
Build target for disk images; the destination, format and size of the image
to generate, as well as how to create or obtain the image before a
VmScript
is executed with the image mounted at a MountPoint
.
Instances
sizeUnitKiB :: SizeUnit -> Int Source #
Convert a SizeUnit
to the number of kibi bytes one element represents.
normalizeSize :: ImageSize -> ImageSize Source #
Choose the greatest unit possible to exactly represent an ImageSize
.
fromSharedImageName :: SharedImageName -> String Source #
Get the String representation of a SharedImageName
.
fromSharedImageBuildId :: SharedImageBuildId -> String Source #
Get the String representation of a SharedImageBuildId
.
sharedImagesToMap :: [SharedImage] -> Map SharedImageName (Set SharedImage) Source #
Transform a list of SharedImage
values into a Map
that associates
each SharedImageName
with a Set
of the actual images with that name.
The Set
contains values of type
.SharedImage
The Ord
instance of SharedImage
sorts by name first and then by
sharedImageDate
, since the values in a Set
share the same sharedImageName
,
they are effectively orderd by build date, which is useful the shared image cleanup.
Since: 1.1.0
takeLatestSharedImage :: [SharedImage] -> Maybe SharedImage Source #
Return the SharedImage
with the highest sharedImageDate
.
Since: 1.1.0
getImageDestinationOutputFiles :: ImageTarget -> [FilePath] Source #
Return the files generated for a LocalFile
or a LiveInstallerImage
; SharedImage
and Transient
are treated like they have no output files because the output files are manged
by B9.
imageDestinationSharedImageName :: ImageDestination -> Maybe SharedImageName Source #
Return the name of a shared image, if the ImageDestination
is a Share
destination
imageSourceSharedImageName :: ImageSource -> Maybe SharedImageName Source #
Return the name of a shared source image, if the ImageSource
is a From
source
itImageDestination :: ImageTarget -> ImageDestination Source #
Get the ImageDestination
of an ImageTarget
itImageSource :: ImageTarget -> ImageSource Source #
Get the ImageSource
of an ImageTarget
itImageMountPoint :: ImageTarget -> MountPoint Source #
Get the MountPoint
of an ImageTarget
isPartitioned :: Partition -> Bool Source #
getPartition :: Partition -> Int Source #
imageFileExtension :: ImageType -> String Source #
Return the file name extension of an image file with a specific image format.
changeImageFormat :: ImageType -> Image -> Image Source #
Change the image file format and also rename the image file name to
have the appropriate file name extension. See imageFileExtension
and
replaceExtension
sharedImageName :: SharedImage -> SharedImageName Source #
Return the name of a shared image.
sharedImageDate :: SharedImage -> SharedImageDate Source #
Return the build date of a shared image.
sharedImageBuildId :: SharedImage -> SharedImageBuildId Source #
Return the build id of a shared image.
prettyPrintSharedImages :: Set SharedImage -> String Source #
Print the contents of the shared image in one line
sharedImageImage :: SharedImage -> Image Source #
Return the disk image of an sharedImage
sharedImageFileName :: SharedImage -> FilePath Source #
Calculate the path to the text file holding the serialized SharedImage
relative to the directory of shared images in a repository.
sharedImageDefaultImageType :: ImageType Source #
The internal image type to use as best guess when dealing with a From
value.
transientCOWImage :: FilePath -> FilePath -> ImageTarget Source #
transientSharedImage :: SharedImageName -> FilePath -> ImageTarget Source #
Use a shared image
transientLocalImage :: FilePath -> FilePath -> ImageTarget Source #
Use a shared image
shareCOWImage :: FilePath -> SharedImageName -> FilePath -> ImageTarget Source #
shareSharedImage :: SharedImageName -> SharedImageName -> FilePath -> ImageTarget Source #
Share an image based on a shared image
shareLocalImage :: FilePath -> SharedImageName -> FilePath -> ImageTarget Source #
cowToliveInstallerImage :: String -> FilePath -> FilePath -> FilePath -> ImageTarget Source #
cowToLocalImage :: FilePath -> FilePath -> FilePath -> ImageTarget Source #
localToLocalImage :: FilePath -> FilePath -> FilePath -> ImageTarget Source #
partition1ToLocalImage :: FilePath -> FilePath -> FilePath -> ImageTarget Source #
Create a local image file from the contents of the first partition
of a local QCow2
image.
splitToIntermediateSharedImage :: ImageTarget -> SharedImageName -> (ImageTarget, ImageTarget) Source #
Split any image target into two image targets, one for creating an intermediate shared image and one from the intermediate shared image to the output image.
Instances
Eq RamSize Source # | |
Data RamSize Source # | |
Defined in B9.ExecEnv gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> RamSize -> c RamSize # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c RamSize # toConstr :: RamSize -> Constr # dataTypeOf :: RamSize -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c RamSize) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c RamSize) # gmapT :: (forall b. Data b => b -> b) -> RamSize -> RamSize # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> RamSize -> r # gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> RamSize -> r # gmapQ :: (forall d. Data d => d -> u) -> RamSize -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> RamSize -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> RamSize -> m RamSize # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> RamSize -> m RamSize # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> RamSize -> m RamSize # | |
Ord RamSize Source # | |
Read RamSize Source # | |
Show RamSize Source # | |
Generic RamSize Source # | |
Semigroup RamSize Source # | |
Monoid RamSize Source # | |
Hashable RamSize Source # | |
Defined in B9.ExecEnv | |
Binary RamSize Source # | |
NFData RamSize Source # | |
Defined in B9.ExecEnv | |
type Rep RamSize Source # | |
Defined in B9.ExecEnv type Rep RamSize = D1 (MetaData "RamSize" "B9.ExecEnv" "b9-1.1.0-inplace" False) (C1 (MetaCons "RamSize" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Int) :*: S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 SizeUnit)) :+: C1 (MetaCons "AutomaticRamSize" PrefixI False) (U1 :: Type -> Type)) |
Instances
Eq CPUArch Source # | |
Data CPUArch Source # | |
Defined in B9.ExecEnv gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> CPUArch -> c CPUArch # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c CPUArch # toConstr :: CPUArch -> Constr # dataTypeOf :: CPUArch -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c CPUArch) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c CPUArch) # gmapT :: (forall b. Data b => b -> b) -> CPUArch -> CPUArch # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> CPUArch -> r # gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> CPUArch -> r # gmapQ :: (forall d. Data d => d -> u) -> CPUArch -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> CPUArch -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> CPUArch -> m CPUArch # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> CPUArch -> m CPUArch # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> CPUArch -> m CPUArch # | |
Read CPUArch Source # | |
Show CPUArch Source # | |
Generic CPUArch Source # | |
Semigroup CPUArch Source # | |
Monoid CPUArch Source # | |
Hashable CPUArch Source # | |
Defined in B9.ExecEnv | |
Binary CPUArch Source # | |
NFData CPUArch Source # | |
Defined in B9.ExecEnv | |
type Rep CPUArch Source # | |
Instances
data SharedDirectory Source #
The environment for the execution of Script
s inside a Container
ExecEnv | |
|
Instances
Eq ExecEnv Source # | |
Data ExecEnv Source # | |
Defined in B9.ExecEnv gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> ExecEnv -> c ExecEnv # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c ExecEnv # toConstr :: ExecEnv -> Constr # dataTypeOf :: ExecEnv -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c ExecEnv) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c ExecEnv) # gmapT :: (forall b. Data b => b -> b) -> ExecEnv -> ExecEnv # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> ExecEnv -> r # gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> ExecEnv -> r # gmapQ :: (forall d. Data d => d -> u) -> ExecEnv -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> ExecEnv -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> ExecEnv -> m ExecEnv # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> ExecEnv -> m ExecEnv # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> ExecEnv -> m ExecEnv # | |
Read ExecEnv Source # | |
Show ExecEnv Source # | |
Generic ExecEnv Source # | |
Hashable ExecEnv Source # | |
Defined in B9.ExecEnv | |
Binary ExecEnv Source # | |
NFData ExecEnv Source # | |
Defined in B9.ExecEnv | |
type Rep ExecEnv Source # | |
Defined in B9.ExecEnv type Rep ExecEnv = D1 (MetaData "ExecEnv" "B9.ExecEnv" "b9-1.1.0-inplace" False) (C1 (MetaCons "ExecEnv" PrefixI True) ((S1 (MetaSel (Just "envName") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 String) :*: S1 (MetaSel (Just "envImageMounts") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 [Mounted Image])) :*: (S1 (MetaSel (Just "envSharedDirectories") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 [SharedDirectory]) :*: S1 (MetaSel (Just "envResources") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Resources)))) |
Instances
Eq User Source # | |
Data User Source # | |
Defined in B9.ShellScript gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> User -> c User # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c User # dataTypeOf :: User -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c User) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c User) # gmapT :: (forall b. Data b => b -> b) -> User -> User # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> User -> r # gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> User -> r # gmapQ :: (forall d. Data d => d -> u) -> User -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> User -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> User -> m User # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> User -> m User # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> User -> m User # | |
Read User Source # | |
Show User Source # | |
Generic User Source # | |
Hashable User Source # | |
Defined in B9.ShellScript | |
Binary User Source # | |
NFData User Source # | |
Defined in B9.ShellScript | |
type Rep User Source # | |
Defined in B9.ShellScript |
Instances
Eq Cwd Source # | |
Data Cwd Source # | |
Defined in B9.ShellScript gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Cwd -> c Cwd # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Cwd # dataTypeOf :: Cwd -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c Cwd) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Cwd) # gmapT :: (forall b. Data b => b -> b) -> Cwd -> Cwd # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Cwd -> r # gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Cwd -> r # gmapQ :: (forall d. Data d => d -> u) -> Cwd -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> Cwd -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> Cwd -> m Cwd # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Cwd -> m Cwd # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Cwd -> m Cwd # | |
Read Cwd Source # | |
Show Cwd Source # | |
Generic Cwd Source # | |
Hashable Cwd Source # | |
Defined in B9.ShellScript | |
Binary Cwd Source # | |
NFData Cwd Source # | |
Defined in B9.ShellScript | |
type Rep Cwd Source # | |
Defined in B9.ShellScript |
data CmdVerbosity Source #
Instances
In FilePath [Script] | |
As String [Script] | |
IgnoreErrors Bool [Script] | |
Verbosity CmdVerbosity [Script] | |
Begin [Script] | |
Run FilePath [String] | |
NoOP |
Instances
writeSh :: FilePath -> Script -> IO () Source #
Convert script
to bash-shell-script written to file
and make file
executable.
renderScript :: Script -> String Source #
class Textual a where Source #
A class for values that can be converted to/from Text
.
Since: 0.5.67
renderToText :: HasCallStack => a -> Either String Text Source #
parseFromText :: HasCallStack => Text -> Either String a Source #
Instances
Textual String Source # | |
Textual ByteString Source # | Convert a Since: 0.5.67 |
Defined in B9.Text renderToText :: ByteString -> Either String Text Source # parseFromText :: Text -> Either String ByteString Source # | |
Textual Text Source # | |
Textual LazyByteString Source # | Convert a Since: 0.5.67 |
Defined in B9.Text | |
Textual YamlObject Source # | |
Defined in B9.Artifact.Content.YamlObject renderToText :: YamlObject -> Either String Text Source # parseFromText :: Text -> Either String YamlObject Source # | |
Textual ErlangPropList Source # | |
Defined in B9.Artifact.Content.ErlangPropList | |
Textual CloudConfigYaml Source # | |
Defined in B9.Artifact.Content.CloudConfigYaml |
Lazy texts.
A type alias to Text
that can be used everywhere such that
references don't need to be qualified with the complete module name everywere.
Since: 0.5.67
type LazyByteString = ByteString Source #
Lazy byte strings.
A type alias to ByteString
that can be used everywhere such that
references don't need to be qualified with the complete module name everywere.
Since: 0.5.67
writeTextFile :: (HasCallStack, MonadIO m) => FilePath -> Text -> m () Source #
Render a Text
to a file.
Since: 0.5.67
unsafeRenderToText :: (Textual a, HasCallStack) => a -> Text Source #
Render a Text
via renderToText
and throw a runtime exception when rendering fails.
Since: 0.5.67
unsafeParseFromText :: (Textual a, HasCallStack) => Text -> a Source #
Parse a Text
via parseFromText
and throw a runtime exception when parsing fails.
Since: 0.5.67
encodeAsUtf8LazyByteString :: HasCallStack => String -> LazyByteString Source #
Encode a String
as UTF-8 encoded into a LazyByteString
.
Since: 0.5.67
parseFromTextWithErrorMessage Source #
:: (HasCallStack, Textual a) | |
=> String | An arbitrary string for error messages |
-> Text | |
-> Either String a |
Parse the given Text
. -- Return Left errorMessage
or Right a
.
data KeyNotFound Source #
An Exception
thrown by lookupOrThrow
indicating that a key does not exist.
@Since 0.5.62
Instances
Eq KeyNotFound Source # | |
Defined in B9.Environment (==) :: KeyNotFound -> KeyNotFound -> Bool # (/=) :: KeyNotFound -> KeyNotFound -> Bool # | |
Show KeyNotFound Source # | |
Defined in B9.Environment showsPrec :: Int -> KeyNotFound -> ShowS # show :: KeyNotFound -> String # showList :: [KeyNotFound] -> ShowS # | |
Exception KeyNotFound Source # | |
Defined in B9.Environment |
data DuplicateKey Source #
An Exception
thrown by addBinding
indicating that a key already exists.
@Since 0.5.62
Instances
Eq DuplicateKey Source # | |
Defined in B9.Environment (==) :: DuplicateKey -> DuplicateKey -> Bool # (/=) :: DuplicateKey -> DuplicateKey -> Bool # | |
Show DuplicateKey Source # | |
Defined in B9.Environment showsPrec :: Int -> DuplicateKey -> ShowS # show :: DuplicateKey -> String # showList :: [DuplicateKey] -> ShowS # | |
Exception DuplicateKey Source # | |
Defined in B9.Environment |
type EnvironmentReader = Reader Environment Source #
A monad transformer providing a MonadReader
instance for Environment
Since: 0.5.62
data Environment Source #
A map of textual keys to textual values.
Since: 0.5.62
Instances
addPositionalArguments :: [Text] -> Environment -> Environment Source #
If environment variables arg_1 .. arg_n
are bound
and a list of k
additional values are passed to this function,
store them with keys arg_(n+1) .. arg_(n+k)
.
Note that the Environment contains an index of the next position.
Since: 0.5.62
addLocalPositionalArguments :: Member EnvironmentReader e => [String] -> Eff e a -> Eff e a Source #
Convenient wrapper around addPositionalArguments
and localEnvironment
.
Since: 0.5.65
fromStringPairs :: [(String, String)] -> Environment Source #
Create an Environment
from a list of pairs (String
s).
Duplicated entries are ignored.
Since: 0.5.62
addBinding :: Member ExcB9 e => (Text, Text) -> Environment -> Eff e Environment Source #
Insert a key value binding to the Environment
.
Throw DuplicateKey
if the key already exists, but
the value is not equal to the given value.
Since: 0.5.67
addStringBinding :: Member ExcB9 e => (String, String) -> Environment -> Eff e Environment Source #
Insert String
s into the Environment
, see addBinding
.
Since: 0.5.62
addLocalStringBinding :: (Member EnvironmentReader e, Member ExcB9 e) => (String, String) -> Eff e a -> Eff e a Source #
Insert a value into an Environment
like addStringBinding
,
but add it to the environment of the given effect, as in localEnvironment
.
Since: 0.5.65
runEnvironmentReader :: Environment -> Eff (EnvironmentReader ': e) a -> Eff e a Source #
Run a ReaderT
of Environment
.
Since: 0.5.62
askEnvironment :: Member EnvironmentReader e => Eff e Environment Source #
Get the current Environment
Since: 0.5.62
localEnvironment :: Member EnvironmentReader e => (Environment -> Environment) -> Eff e a -> Eff e a Source #
Run a computation with a modified Environment
Since: 0.5.62
lookupOrThrow :: '[ExcB9, EnvironmentReader] <:: e => Text -> Eff e Text Source #
Lookup a key for a value.
throwM
a KeyNotFound
Exception
if no value with the given key exists
in the Environment
.
@Since 0.5.62
lookupEither :: Member EnvironmentReader e => Text -> Eff e (Either KeyNotFound Text) Source #
Lookup a key for a value.
Return Either
Left
KeyNotFound
, if no value with the given key exists
in the Environment
, or Right
the value.
@Since 0.5.62
hasKey :: Member EnvironmentReader e => Text -> Eff e Bool Source #
A predicate that is satisfied when a key exists in the environment.
Since: 0.5.64
data SimpleErlangTerm Source #
Simplified Erlang term representation.
ErlString String | |
ErlFloat Double | |
ErlNatural Integer | |
ErlAtom String | |
ErlChar Char | |
ErlBinary String | |
ErlList [SimpleErlangTerm] | |
ErlTuple [SimpleErlangTerm] |
Instances
parseErlTerm :: String -> Text -> Either String SimpleErlangTerm Source #
Parse a subset of valid Erlang terms. It parses no maps and binaries are restricted to either empty binaries or binaries with a string. The input encoding must be restricted to ascii compatible 8-bit characters (e.g. latin-1 or UTF8).
renderErlTerm :: SimpleErlangTerm -> Text Source #
Convert an abstract Erlang term to a pretty byte string preserving the encoding.
A bunch of numbers, enough to make globally unique IDs. Create one of these
using randomUUID
.
data ConsultException Source #
Instances
Show ConsultException Source # | |
Defined in System.IO.B9Extras showsPrec :: Int -> ConsultException -> ShowS # show :: ConsultException -> String # showList :: [ConsultException] -> ShowS # | |
Exception ConsultException Source # | |
Defined in System.IO.B9Extras |
data SystemPath Source #
A data type encapsulating different kinds of relative or absolute paths.
Path FilePath | A path that will just be passed through |
InHomeDir FilePath | A OS specific path relative to the home directory of a user. |
InB9UserDir FilePath | A path relative to the |
InTempDir FilePath | A path relative to the systems temporary directory. |
Instances
Eq SystemPath Source # | |
Defined in System.IO.B9Extras (==) :: SystemPath -> SystemPath -> Bool # (/=) :: SystemPath -> SystemPath -> Bool # | |
Data SystemPath Source # | |
Defined in System.IO.B9Extras gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> SystemPath -> c SystemPath # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c SystemPath # toConstr :: SystemPath -> Constr # dataTypeOf :: SystemPath -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c SystemPath) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c SystemPath) # gmapT :: (forall b. Data b => b -> b) -> SystemPath -> SystemPath # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> SystemPath -> r # gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> SystemPath -> r # gmapQ :: (forall d. Data d => d -> u) -> SystemPath -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> SystemPath -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> SystemPath -> m SystemPath # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> SystemPath -> m SystemPath # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> SystemPath -> m SystemPath # | |
Read SystemPath Source # | |
Defined in System.IO.B9Extras readsPrec :: Int -> ReadS SystemPath # readList :: ReadS [SystemPath] # readPrec :: ReadPrec SystemPath # readListPrec :: ReadPrec [SystemPath] # | |
Show SystemPath Source # | |
Defined in System.IO.B9Extras showsPrec :: Int -> SystemPath -> ShowS # show :: SystemPath -> String # showList :: [SystemPath] -> ShowS # |
overSystemPath :: (FilePath -> FilePath) -> SystemPath -> SystemPath Source #
Transform a SystemPath
resolve :: MonadIO m => SystemPath -> m FilePath Source #
Convert a SystemPath
to a FilePath
.
getDirectoryFiles :: MonadIO m => FilePath -> m [FilePath] Source #
Get all files from dir
that is get ONLY files not directories
ensureSystemPath :: MonadIO m => SystemPath -> m () Source #
Create all missing parent directories of a file path.
Since: 1.1.0
ensureDir :: MonadIO m => FilePath -> m () Source #
Create all missing parent directories of a file path.
Note that the file path is assumed to be of a regular file, and
takeDirectory
is applied before creating the directory.
consult :: (MonadIO m, Read a) => FilePath -> m a Source #
Read a value of a type that is an instance of Read
from a file.
This function throws a ConsultException
when the read the file failed.
removeIfExists :: FilePath -> IO () Source #
newtype SshRemoteUser Source #
Instances
newtype SshRemoteHost Source #
Instances
newtype SshPrivKey Source #
Instances
data RemoteRepo Source #
Instances
Instances
Data RepoCache Source # | |
Defined in B9.B9Config.Repository gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> RepoCache -> c RepoCache # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c RepoCache # toConstr :: RepoCache -> Constr # dataTypeOf :: RepoCache -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c RepoCache) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c RepoCache) # gmapT :: (forall b. Data b => b -> b) -> RepoCache -> RepoCache # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> RepoCache -> r # gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> RepoCache -> r # gmapQ :: (forall d. Data d => d -> u) -> RepoCache -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> RepoCache -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> RepoCache -> m RepoCache # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> RepoCache -> m RepoCache # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> RepoCache -> m RepoCache # | |
Read RepoCache Source # | |
Show RepoCache Source # | |
remoteRepoRepoId :: RemoteRepo -> String Source #
remoteRepoToCPDocument :: RemoteRepo -> CPDocument -> Either CPError CPDocument Source #
Persist a repo to a configuration file.
parseRemoteRepos :: CPDocument -> Either CPError [RemoteRepo] Source #
Load a repository from a configuration file that has been written by
writeRepositoryToB9Config
.
data ContainerCapability Source #
Available capabilities for Linux containers. This maps directly to the capabilities defined in 'man 7 capabilities'.
Instances
Eq ContainerCapability Source # | |
Defined in B9.B9Config.Container (==) :: ContainerCapability -> ContainerCapability -> Bool # (/=) :: ContainerCapability -> ContainerCapability -> Bool # | |
Read ContainerCapability Source # | |
Defined in B9.B9Config.Container | |
Show ContainerCapability Source # | |
Defined in B9.B9Config.Container showsPrec :: Int -> ContainerCapability -> ShowS # show :: ContainerCapability -> String # showList :: [ContainerCapability] -> ShowS # |
containerCapsToCPDocument :: CPDocument -> CPSectionSpec -> [ContainerCapability] -> Either CPError CPDocument Source #
parseContainerCapabilities :: CPDocument -> CPSectionSpec -> Either CPError [ContainerCapability] Source #
data SystemdNspawnConsole Source #
Instances
Eq SystemdNspawnConsole Source # | |
Defined in B9.B9Config.SystemdNspawn (==) :: SystemdNspawnConsole -> SystemdNspawnConsole -> Bool # (/=) :: SystemdNspawnConsole -> SystemdNspawnConsole -> Bool # | |
Read SystemdNspawnConsole Source # | |
Defined in B9.B9Config.SystemdNspawn | |
Show SystemdNspawnConsole Source # | |
Defined in B9.B9Config.SystemdNspawn showsPrec :: Int -> SystemdNspawnConsole -> ShowS # show :: SystemdNspawnConsole -> String # showList :: [SystemdNspawnConsole] -> ShowS # |
data SystemdNspawnConfig Source #
Instances
Eq SystemdNspawnConfig Source # | |
Defined in B9.B9Config.SystemdNspawn (==) :: SystemdNspawnConfig -> SystemdNspawnConfig -> Bool # (/=) :: SystemdNspawnConfig -> SystemdNspawnConfig -> Bool # | |
Read SystemdNspawnConfig Source # | |
Defined in B9.B9Config.SystemdNspawn | |
Show SystemdNspawnConfig Source # | |
Defined in B9.B9Config.SystemdNspawn showsPrec :: Int -> SystemdNspawnConfig -> ShowS # show :: SystemdNspawnConfig -> String # showList :: [SystemdNspawnConfig] -> ShowS # |
systemdNspawnConfigToCPDocument :: SystemdNspawnConfig -> CPDocument -> Either CPError CPDocument Source #
data PodmanConfig Source #
Instances
Eq PodmanConfig Source # | |
Defined in B9.B9Config.Podman (==) :: PodmanConfig -> PodmanConfig -> Bool # (/=) :: PodmanConfig -> PodmanConfig -> Bool # | |
Read PodmanConfig Source # | |
Defined in B9.B9Config.Podman readsPrec :: Int -> ReadS PodmanConfig # readList :: ReadS [PodmanConfig] # | |
Show PodmanConfig Source # | |
Defined in B9.B9Config.Podman showsPrec :: Int -> PodmanConfig -> ShowS # show :: PodmanConfig -> String # showList :: [PodmanConfig] -> ShowS # |
data LibVirtLXCConfig Source #
LibVirtLXCConfig | |
|
Instances
Eq LibVirtLXCConfig Source # | |
Defined in B9.B9Config.LibVirtLXC (==) :: LibVirtLXCConfig -> LibVirtLXCConfig -> Bool # (/=) :: LibVirtLXCConfig -> LibVirtLXCConfig -> Bool # | |
Read LibVirtLXCConfig Source # | |
Defined in B9.B9Config.LibVirtLXC | |
Show LibVirtLXCConfig Source # | |
Defined in B9.B9Config.LibVirtLXC showsPrec :: Int -> LibVirtLXCConfig -> ShowS # show :: LibVirtLXCConfig -> String # showList :: [LibVirtLXCConfig] -> ShowS # |
libVirtLXCConfigToCPDocument :: LibVirtLXCConfig -> CPDocument -> Either CPError CPDocument Source #
getEmulatorPath :: MonadIO m => LibVirtLXCConfig -> m FilePath Source #
Return the path to usrliblibvirtlibexec/libvirt_lxc
the emulatorK
field from the config file, or set the path
in the environment variable named like the value in emulatorEnvVar
dictates.
Since: 0.5.66
data DockerConfig Source #
Instances
Eq DockerConfig Source # | |
Defined in B9.B9Config.Docker (==) :: DockerConfig -> DockerConfig -> Bool # (/=) :: DockerConfig -> DockerConfig -> Bool # | |
Read DockerConfig Source # | |
Defined in B9.B9Config.Docker readsPrec :: Int -> ReadS DockerConfig # readList :: ReadS [DockerConfig] # | |
Show DockerConfig Source # | |
Defined in B9.B9Config.Docker showsPrec :: Int -> DockerConfig -> ShowS # show :: DockerConfig -> String # showList :: [DockerConfig] -> ShowS # |
data B9ConfigOverride Source #
Override b9 configuration items and/or the path of the b9 configuration file. This is useful, i.e. when dealing with command line parameters.
Instances
Show B9ConfigOverride Source # | |
Defined in B9.B9Config showsPrec :: Int -> B9ConfigOverride -> ShowS # show :: B9ConfigOverride -> String # showList :: [B9ConfigOverride] -> ShowS # |
type B9ConfigReader = Reader B9Config Source #
Reader for B9Config
. See getB9Config
and localB9Config
.
Since: 0.5.65
A way to specify a time intervall for example for the timeouts of system commands.
Since: 1.1.0
runB9ConfigReader :: HasCallStack => B9Config -> Eff (B9ConfigReader ': e) a -> Eff e a Source #
Run a B9ConfigReader
.
Since: 0.5.65
getB9Config :: Member B9ConfigReader e => Eff e B9Config Source #
Return the runtime configuration, that should be the configuration merged from all configuration sources. This is the configuration to be used during a VM image build.
Since: 0.5.65
localB9Config :: Member B9ConfigReader e => (B9Config -> B9Config) -> Eff e a -> Eff e a Source #
Run an action with an updated runtime configuration.
Since: 0.5.65
isInteractive :: Member B9ConfigReader e => Eff e Bool Source #
Ask whether stdin
of the B9
process should be redirected to the
external commands executed during the build.
Since: 0.5.65
getRemoteRepos :: Member B9ConfigReader e => Eff e [RemoteRepo] Source #
Ask for the RemoteRepo
s.
Since: 0.5.65
getLogVerbosity :: Member B9ConfigReader e => Eff e (Maybe LogLevel) Source #
Ask for the LogLevel
.
Since: 0.5.65
getProjectRoot :: Member B9ConfigReader e => Eff e FilePath Source #
Ask for the project root directory.
Since: 0.5.65
noB9ConfigOverride :: B9ConfigOverride Source #
An empty default B9ConfigOverride
value, that will neither apply any
additional B9Config
nor change the path of the configuration file.
type B9ConfigWriter = Writer (Endo B9Config) Source #
Accumulate B9Config
changes that go back to the config file. See
B9ConfigAction
and modifyPermanentConfig
.
Since: 0.5.65
type B9ConfigAction a = Eff '[B9ConfigWriter, B9ConfigReader, EnvironmentReader, Lift IO] a Source #
A monad that gives access to the (transient) B9Config
to be used at
_runtime_ with getB9Config
or localB9Config
, and that allows
to write permanent B9Config
changes back to the configuration file using
modifyPermanentConfig
. This is the amalgamation of B9ConfigWriter
B9ConfigReader
and IO
.
Since: 0.5.65
overrideB9ConfigPath :: SystemPath -> B9ConfigOverride -> B9ConfigOverride Source #
Convenience utility to override the B9 configuration file path.
overrideB9Config :: (B9Config -> B9Config) -> B9ConfigOverride -> B9ConfigOverride Source #
Modify the runtime configuration.
overrideDefaultB9ConfigPath :: SystemPath -> B9ConfigOverride -> B9ConfigOverride Source #
Convenience utility to override the *default* B9 configuration file path.
Since: 1.1.0
overrideWorkingDirectory :: FilePath -> B9ConfigOverride -> B9ConfigOverride Source #
Define the current working directory to be used when building.
overrideDefaultTimeout :: Maybe Timeout -> B9ConfigOverride -> B9ConfigOverride Source #
Define the default timeout for external commands.
Since: 1.1.0
overrideTimeoutFactor :: Maybe Int -> B9ConfigOverride -> B9ConfigOverride Source #
Define the timeout factor for external commands.
Since: 1.1.0
overrideVerbosity :: LogLevel -> B9ConfigOverride -> B9ConfigOverride Source #
Overwrite the verbosity
settings in the configuration with those given.
overrideKeepBuildDirs :: Bool -> B9ConfigOverride -> B9ConfigOverride Source #
Overwrite the keepTempDirs
flag in the configuration with those given.
modifyPermanentConfig :: (HasCallStack, Member B9ConfigWriter e) => Endo B9Config -> Eff e () Source #
Add a modification to the permanent configuration file.
runB9ConfigActionWithOverrides :: HasCallStack => B9ConfigAction a -> B9ConfigOverride -> IO a Source #
Execute a B9ConfigAction
.
It will take a B9ConfigOverride
as input. The B9Config
in that value is
treated as the _runtime_ configuration, and the _customConfigPath
is used
as the alternative location of the configuration file.
The configuration file is read from either the path in _customB9ConfigPath
or from defaultB9ConfigFile
.
Every modification done via modifyPermanentConfig
is applied to
the **contents** of the configuration file
and written back to that file, note that these changes are ONLY reflected
in the configuration file and **not** in the _runtime configuration_.
See also runB9ConfigAction
, which does not need the B9ConfigOverride
parameter.
Since: 0.5.65
runB9ConfigAction :: HasCallStack => B9ConfigAction a -> IO a Source #
Run a B9ConfigAction
using noB9ConfigOverride
.
See runB9ConfigActionWithOverrides
for more details.
Since: 0.5.65
openOrCreateB9Config :: (HasCallStack, MonadIO m) => FilePath -> m CPDocument Source #
Open the configuration file that contains the B9Config
.
If the configuration does not exist, write a default configuration file,
and create a all missing directories.
writeB9CPDocument :: (HasCallStack, MonadIO m) => Maybe SystemPath -> CPDocument -> m () Source #
Write the configuration in the CPDocument
to either the user supplied
configuration file path or to defaultB9ConfigFile
.
Create all missing (parent) directories.
modifyCPDocument :: CPDocument -> Endo B9Config -> Either CPError CPDocument Source #
Parse a B9Config
, modify it, and merge it back to the given CPDocument
.
b9ConfigToCPDocument :: HasCallStack => B9Config -> Either CPError CPDocument Source #
Append a config file section for the B9Config
to an empty CPDocument
.
readB9Config :: (HasCallStack, MonadIO m) => Maybe SystemPath -> m CPDocument Source #
parseB9Config :: HasCallStack => CPDocument -> Either CPError B9Config Source #
type RepoImagesMap = Map Repository (Set SharedImage) Source #
A Map
that maps Repository
s to the SharedImage
s they hold.
Since: 1.1.0
type SelectedRemoteRepoReader = Reader SelectedRemoteRepo Source #
Alias for a Reader
Eff
ect that reads the RemoteRepo
selected by the B9Config
value _repository
. See withSelectedRemoteRepo
.
Since: 0.5.65
newtype SelectedRemoteRepo Source #
Contains the Just
the RemoteRepo
selected by the B9Config
value _repository
,
or Nothing
of no RemoteRepo
was selected in the B9Config
.
Since: 0.5.65
type RepoCacheReader = Reader RepoCache Source #
Alias for a Reader
Eff
ect that reads a list of RemoteRepo
s.
Since: 0.5.65
data Repository Source #
Instances
toRemoteRepository :: RemoteRepo -> Repository Source #
Convert a RemoteRepo
down to a mere Repository
getRepoCache :: Member RepoCacheReader e => Eff e RepoCache Source #
Ask for the RepoCache
initialized by withRemoteRepos
.
Since: 0.5.65
withSelectedRemoteRepo :: (Member B9ConfigReader e, Member ExcB9 e) => Eff (SelectedRemoteRepoReader ': e) a -> Eff e a Source #
Run a SelectedRemoteRepoReader
with the SelectedRemoteRepo
selected
in the B9Config
.
If the selected repo does not exist, and exception is thrown.
Since: 0.5.65
getSelectedRemoteRepo :: Member SelectedRemoteRepoReader e => Eff e SelectedRemoteRepo Source #
Ask for the RemoteRepo
selected by the B9Config
value _repository
. See withSelectedRemoteRepo
.
Since: 0.5.65
:: RepoCache | The repository cache directory |
-> String | Id of the repository |
-> FilePath | The existing, absolute path to the cache directory |
Return the cache directory for a remote repository relative to the root cache dir.
Return the local repository directory.
lookupRemoteRepo :: [RemoteRepo] -> String -> Maybe RemoteRepo Source #
Select the first RemoteRepo
with a given repoId
.
filterRepoImagesMap :: (Repository -> Bool) -> (SharedImage -> Bool) -> RepoImagesMap -> RepoImagesMap Source #
Filter the SharedImage
s returned by getSharedImages
using a Repository
-, and a SharedImage
predicate.
Since: 1.1.0
lookupCachedImages :: SharedImageName -> RepoImagesMap -> Set SharedImage Source #
Return the versions of a shared image named name
from the local cache.
Since: 1.1.0
allRepositories :: RepoImagesMap -> Set Repository Source #
Return a Set
of Repository
names from a RepoImagesMap
Since: 1.1.0
allSharedImages :: RepoImagesMap -> Set SharedImage Source #
Get a Set
of all SharedImage
s in all Repository
s.
Since: 1.1.0
allSharedImagesWithRepo :: RepoImagesMap -> Set (SharedImage, Repository) Source #
Fetch all SharedImage
s like allSharedImages
but attach
the Repository
that the image belongs to.
Usage example: In combination with filterRepoImagesMap
to find
the latest version of a certain image in all known repositories.
Since: 1.1.0
maxSharedImageOfAllRepos :: RepoImagesMap -> Maybe (SharedImage, Repository) Source #
Return the maximum with regard to the Ord
instance of SharedImage
from an RepoImagesMap
Since: 1.1.0
allSharedImagesInRepo :: Repository -> RepoImagesMap -> Set SharedImage Source #
Return the SharedImage
s, that are contained in a Repository
.
Since: 1.1.0
allCachedSharedImages :: RepoImagesMap -> Set SharedImage Source #
Keep SharedImage
s that are in the Cache
Repository
.
Since: 1.1.0
keepNLatestSharedImages :: Int -> Set SharedImage -> Set SharedImage Source #
Take a subset that contains the n
latest versions of SharedImage
s with the same name.
For example, if the input contains:
@@
fromList
[ SharedImage "foo" "2020-07-07 13:34:31"
, SharedImage "foo" "2020-07-07 13:34:32"
, SharedImage "foo" "2020-07-07 13:34:33"
, SharedImage "bar" "2020-07-07 13:34:34"
, SharedImage "bar" "2020-07-07 13:34:35"
, SharedImage "bar" "2020-07-07 13:34:36"
]
@@
The output of keepNLatestSharedImages 2
will be:
@@
fromList
[ SharedImage "foo" "2020-07-07 13:34:32"
, SharedImage "foo" "2020-07-07 13:34:33"
, SharedImage "bar" "2020-07-07 13:34:35"
, SharedImage "bar" "2020-07-07 13:34:36"
]
@@
Since: 1.1.0
dropAllButNLatestSharedImages :: Int -> Set SharedImage -> Set SharedImage Source #
Take a subset that contains obsolete images.
Do the opposite of keepNLatestSharedImages
,
and return all **but** the n
latest versions of SharedImage
s with the same name.
For example, if the input contains:
@@
fromList
[ SharedImage "foo" "2020-07-07 13:34:31"
, SharedImage "foo" "2020-07-07 13:34:32"
, SharedImage "foo" "2020-07-07 13:34:33"
, SharedImage "bar" "2020-07-07 13:34:34"
, SharedImage "bar" "2020-07-07 13:34:35"
, SharedImage "bar" "2020-07-07 13:34:36"
]
@@
The output of keepNLatestSharedImages 2
will be:
@@
fromList
[ SharedImage "foo" "2020-07-07 13:34:31"
, SharedImage "bar" "2020-07-07 13:34:34"
]
@@
Since: 1.1.0
groupBySharedImageName :: Set SharedImage -> Map SharedImageName (Set SharedImage) Source #
Group by SharedImageName
.
Since: 1.1.0
type CommandIO e = (MonadBaseControl IO (Eff e), MonadIO (Eff e), Member LoggerReader e, Member B9ConfigReader e) Source #
Convenience type alias for Eff
ects that have a B9Config
, a Logger
, MonadIO
and MonadBaseControl
.
Since: 0.5.65
The logger to write log messages to.
Since: 0.5.65
withLogger :: (MonadBaseControl IO (Eff e), MonadIO (Eff e), Member B9ConfigReader e) => Eff (LoggerReader ': e) a -> Eff e a Source #
Lookup the selected getLogVerbosity
and _logFile
from the B9Config
and open it.
Then run the given action; if the action crashes, the log file will be closed.
Since: 0.5.65
type BuildInfoReader = Reader BuildInfo Source #
Type alias for a BuildInfo
Reader
Since: 0.5.65
withBuildInfo :: (Lifted IO e, MonadBaseControl IO (Eff e), Member B9ConfigReader e, Member ExcB9 e, Member EnvironmentReader e, Member LoggerReader e, HasCallStack) => Eff (BuildInfoReader ': e) a -> Eff e a Source #
Create the build directories, generate (hash) the build-id and execute the given action.
Bindings added to the text template parameter environment:
projectRoot
the directory that contains the sources of the project to buildbuildDir
the temporary directory used store the build artifacts passed into- or outof the build
Unless _keepTempDirs
is True
clean up the build directories after the actions
returns - even if the action throws a runtime exception.
Since: 0.5.65
getBuildId :: Member BuildInfoReader e => Eff e String Source #
getBuildDate :: Member BuildInfoReader e => Eff e String Source #
getBuildDir :: Member BuildInfoReader e => Eff e FilePath Source #
data HostCommandStdin Source #
Ways to process std-input.
Since: 1.0.0
HostCommandNoStdin | Disbale std-in |
HostCommandInheritStdin | Inherit std-in |
HostCommandStdInConduit (ConduitT () ByteString IO ()) | Produce std-in |
cmd :: (HasCallStack, Member ExcB9 e, CommandIO e) => String -> Eff e () Source #
Execute the given shell command.
If isInteractive
is true, the standard-in will be passed to the external command,
and all output of the program will be directed to standard-out.
The command and the output is either logged to the logfile with traceL
or errorL
or
written to stdout.
If the command exists with non-zero exit code, the current process exists with the same exit code.
Since: 0.5.65
:: (CommandIO e, Member ExcB9 e) | |
=> String | The shell command to execute. |
-> Maybe Timeout | An optional |
-> Eff e Bool | An action that performs the shell command and returns |
Run a shell command defined by a string and optionally interrupt the command
after a given time has elapsed.
If the shell command did not exit with ExitSuccess
, or the timer elapsed,
a B9Error
is thrown.
This is only useful for non-interactive commands.
Since: 1.0.0
:: (CommandIO e, Member ExcB9 e) | |
=> HostCommandStdin | A |
-> String | The shell command to execute. |
-> Maybe Timeout | An optional |
-> Eff e Bool | An action that performs the shell command and returns |
Like hostCmd
but with std-input attached.
Since: 1.0.0
:: CommandIO e | |
=> HostCommandStdin | A |
-> String | The shell command to execute. |
-> Maybe Timeout | An optional |
-> Eff e (Either Timeout ExitCode) |
Run a shell command defined by a string and optionally interrupt the command after a given time has elapsed. This is only useful for non-interactive commands.
Since: 1.0.0
newtype FilePathGlob Source #
Express a pattern for file paths, used when searching repositories.
withRemoteRepos :: (Member B9ConfigReader e, Lifted IO e) => Eff (RepoCacheReader ': e) a -> Eff e a Source #
Initialize the local repository cache directory and the RemoteRepo
s.
Run the given action with a B9Config
that contains the initialized
repositories in _remoteRepos
.
Since: 0.5.65
remoteRepoCheckSshPrivKey :: MonadIO m => RemoteRepo -> m RemoteRepo Source #
Check for existance of priv-key and make it an absolute path.
cleanRemoteRepo :: MonadIO m => RepoCache -> RemoteRepo -> m () Source #
Empty the repository; load the corresponding settings from the config file, check that the priv key exists and create the correspondig cache directory.
repoSearch :: forall e. (CommandIO e, Member RepoCacheReader e) => FilePath -> FilePathGlob -> Eff e [(Repository, [FilePath])] Source #
Find files which are in subDir
and match glob
in the repository
cache. NOTE: This operates on the repository cache, but does not enforce a
repository cache update.
pushToRepo :: (Member ExcB9 e, CommandIO e) => RemoteRepo -> FilePath -> FilePath -> Eff e () Source #
Push a file from the cache to a remote repository
pullFromRepo :: (Member ExcB9 e, CommandIO e) => RemoteRepo -> FilePath -> FilePath -> Eff e () Source #
Pull a file from a remote repository to cache
pullGlob :: (Member ExcB9 e, CommandIO e, Member RepoCacheReader e) => FilePath -> FilePathGlob -> RemoteRepo -> Eff e () Source #
Push a file from the cache to a remote repository
getSharedImages :: (HasCallStack, CommandIO e, Lifted IO e, Member RepoCacheReader e) => Eff e (Map Repository (Set SharedImage)) Source #
Return a list of all existing sharedImages from cached repositories.
pullRemoteRepos :: (HasCallStack, Member ExcB9 e, Lifted IO e, CommandIO e, '[SelectedRemoteRepoReader, RepoCacheReader] <:: e) => Eff e () Source #
Pull metadata files from all remote repositories.
pullLatestImage :: (HasCallStack, Lifted IO e, CommandIO e, '[ExcB9, RepoCacheReader, SelectedRemoteRepoReader] <:: e) => SharedImageName -> Eff e (Maybe SharedImageBuildId) Source #
Pull the latest version of an image, either from the selected remote repo or from the repo that has the latest version.
getLatestImageByName :: (HasCallStack, Lifted IO e, CommandIO e, Member RepoCacheReader e) => SharedImageName -> Eff e (Maybe Image) Source #
Return the Image
of the latest version of a shared image named name
from the local cache.
cleanOldSharedImageRevisionsFromCache :: ('[RepoCacheReader, ExcB9] <:: e, Lifted IO e, CommandIO e) => SharedImageName -> Eff e () Source #
Depending on the maxLocalSharedImageRevisions
B9Config
settings either
do nothing or delete all but the configured number of most recent shared
images with the given name from the local cache.
cleanLocalRepoCache :: ('[RepoCacheReader, ExcB9] <:: e, Lifted IO e, CommandIO e) => Eff e () Source #
Clean all obsolete images in the local image cache.
Since: 1.1.0
pushSharedImageLatestVersion :: (Lifted IO e, CommandIO e, '[SelectedRemoteRepoReader, RepoCacheReader, ExcB9] <:: e) => SharedImageName -> Eff e () Source #
Publish the latest version of a shared image identified by name to the selected repository from the cache.
pushToSelectedRepo :: (Member ExcB9 e, Lifted IO e, CommandIO e, '[RepoCacheReader, SelectedRemoteRepoReader] <:: e) => SharedImage -> Eff e () Source #
Upload a shared image from the cache to a selected remote repository
getSelectedRepos :: '[B9ConfigReader, SelectedRemoteRepoReader] <:: e => Eff e [RemoteRepo] Source #
Return either all remote repos or just the single selected repo.
getSharedImagesCacheDir :: '[RepoCacheReader] <:: e => Eff e FilePath Source #
Return the path to the sub directory in the cache that contains files of shared images.
type IsB9 e = (HasCallStack, Lifted IO e, CommandIO e, B9Eff <:: e) Source #
A constraint that contains all effects of B9Eff
Since: 0.5.65
type B9Eff = '[SelectedRemoteRepoReader, RepoCacheReader, BuildInfoReader, LoggerReader, B9ConfigReader, EnvironmentReader, ExcB9, Lift IO] Source #
Definition of the B9 effect list. It encapsulates logging, a reader for the B9.B9Config and access to the current build id, the current build directory and the artifact to build.
This monad is used by the _effectful_ functions in this library.
Since: 0.5.65
type B9 a = Eff B9Eff a Source #
Definition of the B9 monad. See B9Eff
.
This module is used by the _effectful_ functions in this library.
Since: 0.5.65
runB9 :: HasCallStack => B9 a -> B9ConfigAction a Source #
class ToContentGenerator c where Source #
Types whose values can be turned into an Eff
ect that produces
Text
, e.g. ContentGenerator
Since: 0.5.62
toContentGenerator :: (HasCallStack, IsB9 e) => c -> Eff e Text Source #
Instances
ToContentGenerator Content Source # | |
Defined in B9.Artifact.Content.Readable toContentGenerator :: (HasCallStack, IsB9 e) => Content -> Eff e Text Source # |
data SourceFileConversion Source #
Instances
data SourceFile Source #
A wrapper around a file path and a flag indicating if template variable expansion should be performed when reading the file contents.
Instances
readTemplateFile :: (MonadIO (Eff e), '[ExcB9, EnvironmentReader] <:: e) => SourceFile -> Eff e Text Source #
subst :: (Member ExcB9 e, Member EnvironmentReader e) => Text -> Eff e Text Source #
Text
template substitution.
substStr :: (Member ExcB9 e, Member EnvironmentReader e) => String -> Eff e String Source #
String
template substitution
substFile :: (Member EnvironmentReader e, Member ExcB9 e, MonadIO (Eff e)) => FilePath -> FilePath -> Eff e () Source #
substPath :: (Member EnvironmentReader e, Member ExcB9 e) => SystemPath -> Eff e SystemPath Source #
withSubstitutedStringBindings :: (Member EnvironmentReader e, Member ExcB9 e) => [(String, String)] -> Eff e s -> Eff e s Source #
Extend an Environment
with new bindings, where each value may contain
string templates with like "Hello $name, how is life on $planet these days?"
.
Since: 0.5.64
Describe a virtual machine, i.e. a set up disk images to create and a shell script to put things together.
Instances
substVmScript :: forall e. (Member EnvironmentReader e, Member ExcB9 e) => VmScript -> Eff e VmScript Source #
substImageTarget :: forall e. (HasCallStack, Member EnvironmentReader e, Member ExcB9 e) => ImageTarget -> Eff e ImageTarget Source #
Replace $... variables inside an ImageTarget
resolveImageSource :: IsB9 e => ImageSource -> Eff e Image Source #
Resolve an ImageSource to an Image
. The ImageSource might
not exist, as is the case for EmptyImage
.
preferredDestImageTypes :: IsB9 e => ImageSource -> Eff e [ImageType] Source #
Return all valid image types sorted by preference.
preferredSourceImageTypes :: HasCallStack => ImageDestination -> [ImageType] Source #
Return all supported source ImageType
s compatible to a ImageDestinaion
in the preferred order.
ensureAbsoluteImageDirExists :: IsB9 e => Image -> Eff e Image Source #
Create the parent directories for the file that contains the Image
.
If the path to the image file is relative, prepend _projectRoot
from
the B9Config
.
materializeImageSource :: IsB9 e => ImageSource -> Image -> Eff e () Source #
Create an image from an image source. The destination image must have a compatible image type and filesystem. The directory of the image MUST be present and the image file itself MUST NOT alredy exist.
createDestinationImage :: IsB9 e => Image -> ImageDestination -> Eff e () Source #
Convert some Image
, e.g. a temporary image used during the build phase
to the final destination.
resizeImage :: IsB9 e => ImageResize -> Image -> Eff e () Source #
Resize an image, including the file system inside the image.
importImage :: IsB9 e => Image -> Image -> Eff e () Source #
Import a disk image from some external source into the build directory if necessary convert the image.
exportImage :: IsB9 e => Image -> Image -> Eff e () Source #
Export a disk image from the build directory; if necessary convert the image.
exportAndRemoveImage :: IsB9 e => Image -> Image -> Eff e () Source #
Export a disk image from the build directory; if necessary convert the image.
convertImage :: IsB9 e => Image -> Image -> Eff e () Source #
Convert an image in the build directory to another format and return the new image.
shareImage :: IsB9 e => Image -> SharedImageName -> Eff e SharedImage Source #
Publish an sharedImage made from an image and image meta data to the configured repository
class FromAST a where Source #
Types of values that describe content, that can be created from an AST
.
Instances
FromAST YamlObject Source # | |
Defined in B9.Artifact.Content.YamlObject fromAST :: (IsB9 e, ToContentGenerator c) => AST c YamlObject -> Eff e YamlObject Source # | |
FromAST ErlangPropList Source # | |
Defined in B9.Artifact.Content.ErlangPropList fromAST :: (IsB9 e, ToContentGenerator c) => AST c ErlangPropList -> Eff e ErlangPropList Source # | |
FromAST CloudConfigYaml Source # | |
Defined in B9.Artifact.Content.CloudConfigYaml fromAST :: (IsB9 e, ToContentGenerator c) => AST c CloudConfigYaml -> Eff e CloudConfigYaml Source # |
Describe how to create structured content that has a tree-like syntactic
structure, e.g. yaml, JSON and erlang-proplists. The first parameter defines
a context into which the AST
is embedded,
e.g. B9.Artifact.Content'. The second parameter defines a specifix
syntax, e.g ErlangPropList
that the AST
value generates.
ASTObj [(String, AST c a)] | Create an object similar to a Json object. |
ASTArr [AST c a] | An array. |
ASTMerge [AST c a] | Merge the nested elements, this is a very powerful tool that allows to combine |
ASTEmbed c | |
ASTString String | |
ASTInt Int | |
ASTParse SourceFile | |
AST a |
Instances
newtype YamlObject Source #
A wrapper type around yaml values with a Semigroup instance useful for combining yaml documents describing system configuration like e.g. user-data.
Instances
newtype ErlangPropList Source #
A wrapper type around erlang terms with a Semigroup instance useful for combining sys.config files with OTP-application configurations in a list of the form of a proplist.
Instances
textToErlangAst :: Text -> AST c ErlangPropList Source #
Parse a text containing an Erlang
expression ending with a .
and Return
an AST
.
Since: 0.5.67
stringToErlangAst :: String -> AST c ErlangPropList Source #
Parse a string containing an Erlang
expression ending with a .
and Return
an AST
.
Since: 0.5.67
newtype CloudConfigYaml Source #
Cloud-init meta-data
configuration Yaml.
cloud-config
yaml documents contain:
#cloud-config
as first line.
@Since 0.5.62
Instances
cloudConfigFileHeader :: Text Source #
The header line, which must be the first line in the text file containing the cloud-config Yaml document.
@Since 0.5.62
type ErlangAst = AST Content ErlangPropList Source #
An ErlangPropList
AST
with Content
Since: 0.5.67
RenderErlang (AST Content ErlangPropList) | |
RenderYamlObject (AST Content YamlObject) | |
RenderCloudConfig (AST Content CloudConfigYaml) | |
FromByteString ByteString | This data will be passed through unaltered.
This is used during the transition phase from having B9 stuff read from
files via Since: 0.5.62 |
FromString String | Embed a literal string |
FromTextFile SourceFile | Embed the contents of the |
RenderBase64BinaryFile FilePath | The data in the given file will be base64 encoded. |
RenderBase64Binary ByteString | This data will be base64 encoded. |
FromURL String | Download the contents of the URL |
Instances
data ArtifactSource Source #
Describe how input files for artifacts to build are obtained. The general structure of each constructor is FromXXX destination source
FromFile FilePath SourceFile | Copy a |
FromContent FilePath Content | Create a file from some |
SetPermissions Int Int Int [ArtifactSource] | Set the unix file permissions to all files generated
by the nested list of |
FromDirectory FilePath [ArtifactSource] | Assume a local directory as starting point for all
relative source files in the nested |
IntoDirectory FilePath [ArtifactSource] | Specify an output directory for all the files
generated by the nested |
Instances
getArtifactSourceFiles :: ArtifactSource -> [FilePath] Source #
Return all source files generated by an ArtifactSource
.
data AssemblyOutput Source #
The output of an ArtifactAssembly
is either a set of generated files,
or it might be a directory that contains the artifacts sources.
Instances
data CloudInitType Source #
Instances
data ArtifactTarget Source #
Instances
data AssembledArtifact Source #
A symbolic representation of the targets assembled by
assemble
from an ArtifactAssembly
. There is a
list of ArtifactTarget
s because e.g. a single CloudInit
can produce up to
three output files, a directory, an ISO image and a VFAT image.
Instances
data ArtifactAssembly Source #
Define an output of a build. Assemblies are nested into
ArtifactGenerator
s. They contain all the files defined by the Sources
they are nested into.
CloudInit [CloudInitType] FilePath | Generate a cloud-init compatible directory, ISO-
or VFAT image, as specified by the list of
|
VmImages [ImageTarget] VmScript | a set of VM-images that were created by executing a build script on them. |
Instances
newtype InstanceId Source #
Identify an artifact. Deprecated TODO: B9 does not check if all instances IDs are unique.
Instances
data ArtifactGenerator Source #
Artifacts represent the things B9 can build. A generator specifies howto generate parameterized, multiple artifacts. The general structure is:
Let [ ... bindings ... ] [ Sources [ ... list all input files ... ] [ Artifact ... , Artifact ... , Let [ ... ] [ ... ] ] ]
The reasons why Sources
takes a list of ArtifactGenerator
s is that
- this makes the value easier to read/write for humans
- the sources are static files used in all children (e.g. company logo image)
- the sources are parameterized by variables that bound to different values for each artifact, e.g. a template network config file which contains the host IP address.
To bind such variables use Let
, Each
, LetX
or EachT
.
String substitution of these variables is done by B9.Artifact.Content.StringTemplate.
These variables can be used as value in nested Let
s, in most file names/paths
and in source files added with SourceFile
- - @deprecated TODO remove this when switching to Dhall
Sources [ArtifactSource] [ArtifactGenerator] | Add sources available to |
Let [(String, String)] [ArtifactGenerator] | Bind variables, variables are available in nested generators. @deprecated TODO remove this when switching to Dhall |
LetX [(String, [String])] [ArtifactGenerator] | A LetX [("x", ["1","2","3"]), ("y", ["a","b"])] [..] Is equal to: Let [] [ Let [("x", "1"), ("y", "a")] [..] Let [("x", "1"), ("y", "b")] [..] Let [("x", "2"), ("y", "a")] [..] Let [("x", "2"), ("y", "b")] [..] Let [("x", "3"), ("y", "a")] [..] Let [("x", "3"), ("y", "b")] [..] ] @deprecated TODO remove this when switching to Dhall |
Each [(String, [String])] [ArtifactGenerator] | Bind each variable to their first value, then each
variable to the second value, etc ... and execute the
nested generator in every step. |
EachT [String] [[String]] [ArtifactGenerator] | The transposed version of |
Artifact InstanceId ArtifactAssembly | Generate an artifact defined by an
|
EmptyArtifact |
Instances
instanceIdKey :: String Source #
The variable containing the instance id. Deprecated
buildIdKey :: String Source #
The variable containing the buildId that identifies each execution of
B9. For more info about variable substitution in source files see
StringTemplate
buildDateKey :: String Source #
The variable containing the date and time a build was started. For more
info about variable substitution in source files see
StringTemplate
getAssemblyOutput :: ArtifactAssembly -> [AssemblyOutput] Source #
Return the files that the artifact assembly consist of.
buildWithVm :: IsB9 e => InstanceId -> [ImageTarget] -> FilePath -> VmScript -> Eff e Bool Source #
data InstanceGenerator e Source #
Instances
data InstanceSources Source #
Internal data structure. Only exposed for unit testing.
Instances
Eq InstanceSources Source # | |
Defined in B9.Artifact.Readable.Interpreter (==) :: InstanceSources -> InstanceSources -> Bool # (/=) :: InstanceSources -> InstanceSources -> Bool # | |
Show InstanceSources Source # | |
Defined in B9.Artifact.Readable.Interpreter showsPrec :: Int -> InstanceSources -> ShowS # show :: InstanceSources -> String # showList :: [InstanceSources] -> ShowS # |
buildArtifacts :: ArtifactGenerator -> B9 String Source #
Execute an ArtifactGenerator
and return a B9Invocation
that returns
the build id obtained by getBuildId
.
getArtifactOutputFiles :: ArtifactGenerator -> Either SomeException [FilePath] Source #
Return a list of relative paths for the local files to be generated
by the ArtifactGenerator. This excludes Shared
and Transient image targets.
assemble :: ArtifactGenerator -> B9 [AssembledArtifact] Source #
Run an artifact generator to produce the artifacts.
runArtifactGenerator :: Environment -> String -> String -> ArtifactGenerator -> Either SomeException [InstanceGenerator [TextFileWriter]] Source #
Interpret an ArtifactGenerator
into a list of simple commands, i.e. InstanceGenerator
s
Since: 0.5.65
runInstanceGenerator :: IsB9 e => InstanceGenerator FilePath -> Eff e AssembledArtifact Source #
Run an
runArtifactAssembly :: IsB9 e => InstanceId -> FilePath -> ArtifactAssembly -> Eff e [ArtifactTarget] Source #
Create the ArtifactTarget
from an ArtifactAssembly
in the directory instanceDir
Since: 0.5.65