Skip to content

Commit

Permalink
Minikube demo working now with minio S3 server
Browse files Browse the repository at this point in the history
  • Loading branch information
thomasjm committed Aug 2, 2024
1 parent fdced4e commit 0dd50c7
Show file tree
Hide file tree
Showing 8 changed files with 40 additions and 25 deletions.
7 changes: 4 additions & 3 deletions demos/demo-kubernetes-kind/app/Main.hs
Original file line number Diff line number Diff line change
Expand Up @@ -37,14 +37,15 @@ spec = describe "Introducing a Kubernetes cluster" $ do
images <- getLoadedImages
forM_ images $ \image -> info [i|Image: #{image}|]

introduceBinaryViaNixPackage @"kubectl" "kubectl" $
withKubernetesNamespace "foo" $
introduceBinaryViaNixPackage @"kubectl" "kubectl" $
introduceBinaryViaNixDerivation @"kubectl-minio" kubectlMinioDerivation $
introduceMinioOperator $ do
introduceMinioOperator defaultMinioOperatorOptions $ do
it "Has a MinIO operator" $ do
moc <- getContext minioOperator
info [i|Got MinIO operator: #{moc}|]

withKubernetesNamespace "foo" $ introduceK8SMinioS3Server "foo" $ do
withKubernetesNamespace "foo" $ introduceK8SMinioS3Server (defaultMinioS3ServerOptions "foo") $ do
it "has a MinIO S3 server" $ do
serv <- getContext testS3Server
info [i|Got test S3 server: #{serv}|]
Expand Down
18 changes: 3 additions & 15 deletions demos/demo-kubernetes-minikube/app/Main.hs
Original file line number Diff line number Diff line change
Expand Up @@ -23,7 +23,6 @@ import Test.Sandwich.Contexts.Kubernetes.MinioS3Server
import Test.Sandwich.Contexts.Kubernetes.Namespace
import Test.Sandwich.Contexts.Nix
import Test.Sandwich.Contexts.Waits
import UnliftIO.Concurrent
import UnliftIO.Environment
import UnliftIO.Process

Expand All @@ -35,6 +34,7 @@ spec = describe "Introducing a Kubernetes cluster" $ do
introduceMinikubeClusterViaNix defaultMinikubeClusterOptions $ do
it "prints the cluster info" $ do
kcc <- getContext kubernetesCluster
info [i|export KUBECONFIG='#{kubernetesClusterKubeConfigPath kcc}'|]
info [i|Got Kubernetes cluster context: #{kcc}|]

it "prints the loaded images" $ do
Expand All @@ -48,25 +48,13 @@ spec = describe "Introducing a Kubernetes cluster" $ do
info [i|Got MinIO operator: #{moc}|]

withKubernetesNamespace "foo" $ do
it "creates a service account" $ do
kubectlBinary <- askFile @"kubectl"

KubernetesClusterContext {..} <- getContext kubernetesCluster
baseEnv <- getEnvironment
let env = L.nubBy (\x y -> fst x == fst y) (("KUBECONFIG", kubernetesClusterKubeConfigPath) : baseEnv)

let args = ["create", "serviceaccount", "default", "--namespace", "foo"]

p <- createProcessWithLogging ((proc kubectlBinary args) { env = Just env, delegate_ctlc = True })
waitForProcess p >>= (`shouldBe` ExitSuccess)

introduceK8SMinioS3Server (defaultMinioS3ServerOptions "foo") $ do
it "has a MinIO S3 server" $ do
serv <- getContext testS3Server
info [i|Got test S3 server: #{serv}|]

it "pauses" $ do
threadDelay 9999999999999
-- it "pauses" $ do
-- threadDelay 9999999999999


main :: IO ()
Expand Down
Original file line number Diff line number Diff line change
Expand Up @@ -10,11 +10,14 @@ module Test.Sandwich.Contexts.Kubernetes.FindImages (

import Control.Lens
import Data.Aeson (FromJSON)
import qualified Data.Aeson as A
import Data.Aeson.Lens
import Data.Text as T
import qualified Data.Yaml as Yaml
import Kubernetes.OpenAPI.Model as Kubernetes
import Kubernetes.OpenAPI.ModelLens as Kubernetes
import Relude
import Test.Sandwich.Contexts.Kubernetes.Util.Aeson


-- | Find all image references in a chunk of YAML containing multiple sections
Expand All @@ -36,6 +39,12 @@ findAllImages' (decode -> Right x@(V1DaemonSet {})) = maybe [] imagesFromPodSpec
where
maybePodSpec :: Maybe V1PodSpec
maybePodSpec = x ^? (v1DaemonSetSpecL . _Just . v1DaemonSetSpecTemplateL . v1PodTemplateSpecSpecL . _Just)

-- Pick up images in MinIO "Tenant" CRDs
findAllImages' (decode -> Right x@(A.Object obj))
| Just (A.String "Tenant") <- aesonLookup "kind" obj
, Just (A.String img) <- x ^? (_Object . ix "spec" . _Object . ix "image") = [img]

findAllImages' _ = []

imagesFromPodSpec :: V1PodSpec -> [Text]
Expand Down
Original file line number Diff line number Diff line change
Expand Up @@ -116,9 +116,7 @@ loadImageIfNecessary' :: (
-- | The transformed image name
-> m ()
loadImageIfNecessary' kcc imageLoadSpec = do
image <- imageLoadSpecToImageName imageLoadSpec

whenM (clusterContainsImage' kcc image) $
unlessM (imageLoadSpecToImageName imageLoadSpec >>= clusterContainsImage' kcc) $
void $ loadImage' kcc imageLoadSpec

-- | Load an image into a Kubernetes cluster. The image you pass may be an absolute path to a .tar or .tar.gz
Expand Down
Original file line number Diff line number Diff line change
Expand Up @@ -37,7 +37,6 @@ import Test.Sandwich.Contexts.Kubernetes.Util.UUID
import Test.Sandwich.Contexts.MinIO
import Test.Sandwich.Contexts.Nix
import Test.Sandwich.Contexts.Waits
import UnliftIO.Concurrent
import UnliftIO.Exception
import UnliftIO.Process
import UnliftIO.Timeout
Expand Down Expand Up @@ -151,9 +150,11 @@ withK8SMinioS3Server' kubectlBinary kcc@(KubernetesClusterContext {..}) MinioOpe
when minioS3ServerPreloadImages $ do
let images = findAllImages (toText allYaml)

forM_ images $ \image ->
forM_ images $ \image -> do
debug [i|Preloading image: #{image}|]
loadImageIfNecessary' kcc (ImageLoadSpecDocker image IfNotPresent)

debug [i|Preloading image: #{busyboxImage}|]
loadImageIfNecessary' kcc (ImageLoadSpecDocker busyboxImage IfNotPresent)

(userAndPassword@(username, password), finalYaml) <- case transformKustomizeChunks (toString minioS3ServerNamespace) (T.splitOn "---\n" (toText allYaml)) of
Expand Down Expand Up @@ -191,6 +192,7 @@ withK8SMinioS3Server' kubectlBinary kcc@(KubernetesClusterContext {..}) MinioOpe
, "--rm", "-i"
, "--attach"
, [i|--image=#{busyboxImage}|]
, "--image-pull-policy=IfNotPresent"
, "--restart=Never"
, "--command"
, "--namespace", toString minioS3ServerNamespace
Expand All @@ -208,7 +210,6 @@ withK8SMinioS3Server' kubectlBinary kcc@(KubernetesClusterContext {..}) MinioOpe

withKubectlPortForward' kubectlBinary kubernetesClusterKubeConfigPath minioS3ServerNamespace (const True) Nothing "service/minio" port $ \(KubectlPortForwardContext {..}) -> do
info [i|Did forward to localhost:#{kubectlPortForwardPort}|]
-- liftIO $ threadDelay 999999999999

let bucket = "bucket1"

Expand Down
Original file line number Diff line number Diff line change
Expand Up @@ -5,15 +5,17 @@ module Test.Sandwich.Contexts.Kubernetes.MinioS3Server.Parsing (
, transformKustomizeChunks
) where

import Control.Lens
import Data.Aeson (FromJSON)
import qualified Data.Aeson as A
import Data.Aeson.Lens
import qualified Data.Map as M
import Data.String.Interpolate
import Data.Text as T
import qualified Data.Yaml as Yaml
import Kubernetes.OpenAPI.Model as Kubernetes
import Relude
import Safe
import Safe (headMay)
import Test.Sandwich.Contexts.Kubernetes.Util.Aeson
import Text.Regex.TDFA

Expand Down Expand Up @@ -41,8 +43,12 @@ transformKustomizeChunks namespace initialChunks = do
-- Don't include a kind: Namespace
& Relude.filter (not . isNamespace)

-- Set metadata.namespace on all values
& fmap (setMetaNamespace namespace)

-- Disable TLS
& fmap disableTLS

-- Combine everything into multi-document Yaml
& T.intercalate "---\n"

Expand Down Expand Up @@ -73,5 +79,15 @@ setMetaNamespace namespace (decode -> Right (A.Object obj1@(aesonLookup "metadat
obj2' = A.Object (aesonInsert "namespace" (A.String (toText namespace)) obj2)
setMetaNamespace _ t = t

-- Do the steps to disable TLS in the tenant CRD.
-- See https://min.io/docs/minio/kubernetes/upstream/reference/operator-crd.html#tenantspec
disableTLS :: Text -> Text
disableTLS (decode -> Right x@(A.Object (aesonLookup "kind" -> Just (A.String "Tenant")))) = decodeUtf8 (Yaml.encode x')
where
x' = x
& set (_Object . ix "spec" . _Object . ix "requestAutoCert") (A.Bool False)
& set (_Object . ix "spec" . _Object . at "externalCertSecret") Nothing
disableTLS t = t

decode :: FromJSON a => Text -> Either Yaml.ParseException a
decode = Yaml.decodeEither' . encodeUtf8
1 change: 1 addition & 0 deletions sandwich-contexts-kubernetes/package.yaml
Original file line number Diff line number Diff line change
Expand Up @@ -58,6 +58,7 @@ library:
- kubernetes-client
- kubernetes-client-core
- lens
- lens-aeson
- minio-hs
- monad-logger
- network
Expand Down
Original file line number Diff line number Diff line change
Expand Up @@ -79,6 +79,7 @@ library
, kubernetes-client
, kubernetes-client-core
, lens
, lens-aeson
, minio-hs
, monad-logger
, network
Expand Down

0 comments on commit 0dd50c7

Please sign in to comment.