module Buffet.Assemble.LocalBuildStages ( get ) where import qualified Buffet.Assemble.ConditionInstructionsInContext as ConditionInstructionsInContext import qualified Buffet.Ir.Ir as Ir import qualified Data.Map.Strict as Map import Prelude (($), (.), concatMap, fmap, uncurry) get :: Ir.Buffet -> [Ir.DockerfilePart] get :: Buffet -> [DockerfilePart] get Buffet buffet = ((Option, Dish) -> [DockerfilePart]) -> [(Option, Dish)] -> [DockerfilePart] forall (t :: * -> *) a b. Foldable t => (a -> [b]) -> t a -> [b] concatMap ((Option -> Dish -> [DockerfilePart]) -> (Option, Dish) -> [DockerfilePart] forall a b c. (a -> b -> c) -> (a, b) -> c uncurry ((Option -> Dish -> [DockerfilePart]) -> (Option, Dish) -> [DockerfilePart]) -> (Option -> Dish -> [DockerfilePart]) -> (Option, Dish) -> [DockerfilePart] forall a b. (a -> b) -> a -> b $ Buffet -> Option -> Dish -> [DockerfilePart] dishBuildStages Buffet buffet) ([(Option, Dish)] -> [DockerfilePart]) -> (Map Option Dish -> [(Option, Dish)]) -> Map Option Dish -> [DockerfilePart] forall b c a. (b -> c) -> (a -> b) -> a -> c . Map Option Dish -> [(Option, Dish)] forall k a. Map k a -> [(k, a)] Map.toAscList (Map Option Dish -> [DockerfilePart]) -> Map Option Dish -> [DockerfilePart] forall a b. (a -> b) -> a -> b $ Buffet -> Map Option Dish Ir.optionToDish Buffet buffet dishBuildStages :: Ir.Buffet -> Ir.Option -> Ir.Dish -> [Ir.DockerfilePart] dishBuildStages :: Buffet -> Option -> Dish -> [DockerfilePart] dishBuildStages Buffet buffet Option option = (DockerfilePart -> DockerfilePart) -> [DockerfilePart] -> [DockerfilePart] forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b fmap (Buffet -> Option -> DockerfilePart -> DockerfilePart ConditionInstructionsInContext.get Buffet buffet Option option) ([DockerfilePart] -> [DockerfilePart]) -> (Dish -> [DockerfilePart]) -> Dish -> [DockerfilePart] forall b c a. (b -> c) -> (a -> b) -> a -> c . Dish -> [DockerfilePart] Ir.localBuildStages