summaryrefslogtreecommitdiff
path: root/src
diff options
context:
space:
mode:
authorAndrew Cady <d@jerkface.net>2018-07-10 06:29:05 -0400
committerAndrew Cady <d@jerkface.net>2018-07-10 06:29:05 -0400
commit0af33cecec5d0a9a23fb4b1758455cef3840db88 (patch)
treec41069c895929efbbb8512c1680f6b752e6028a1 /src
parente6d7f0fcc5475b7cbd6b675fc2d4954838410c21 (diff)
separate module ConfigFile
Diffstat (limited to 'src')
-rw-r--r--src/ConfigFile.hs77
1 files changed, 77 insertions, 0 deletions
diff --git a/src/ConfigFile.hs b/src/ConfigFile.hs
new file mode 100644
index 0000000..8b23582
--- /dev/null
+++ b/src/ConfigFile.hs
@@ -0,0 +1,77 @@
1{-# OPTIONS_GHC -fno-warn-type-defaults #-}
2{-# LANGUAGE ExtendedDefaultRules #-}
3{-# LANGUAGE LambdaCase #-}
4{-# LANGUAGE NamedFieldPuns #-}
5{-# LANGUAGE NoImplicitPrelude #-}
6{-# LANGUAGE OverloadedStrings #-}
7{-# LANGUAGE RecordWildCards #-}
8{-# LANGUAGE ScopedTypeVariables #-}
9
10module ConfigFile where
11import Rebase.Prelude hiding (bool, hash, (<.>))
12
13import Data.Yaml.Combinators
14import Development.Shake hiding (getEnv)
15import Development.Shake.Command ()
16import qualified Rebase.Data.Set as Set
17import Rebase.Data.Text (pack, unpack)
18import Rebase.Data.Text.Encoding
19import qualified Rebase.Data.Vector as Vector
20{-
21
22Basic idea is to have a fs.yaml that specifies the build procedure. Analogous to
23stack.yaml, it should specify everything (every source) directly or indirectly.
24
25We want to make new images from CoW copies of old ones. We want to build these
26things incrementally, but still end up with something that will be reproducible
27from scratch.
28
29Anyway, what we'll have is a list of packages, which will be unpacked first.
30Then a list of debconf values, which will be applied. Then we will have the rest
31of the other, slower changes to the image (including dpkg --configure -a). Some
32changes can be assumed to produce the same results out of order. Oh right, and
33the zeroeth step is to generate the empty (or just initial) filesystem image.
34The initial filesystem image, if nonempty, is specified by filename (otherwise,
35by size), while the hash of the configuration determines the output filename.
36
37--
38
39'Parent' param should be a config file, not hash. The hash will only be used to
40determine whether we need to build it.
41
42-}
43
44newtype DebconfConfig = DebconfConfig Text deriving (Show, Read, Eq, Ord)
45newtype Package = Package Text deriving (Show, Read, Eq, Ord)
46data Patch = Patch deriving (Show, Read)
47
48data BaseImageSpecification
49 = EmptyImageOfBytes Int
50 | ParentImageConfigFile FilePath
51 deriving (Show, Read)
52
53data DiskImageConfig = DiskImageConfig {
54 initialImage :: BaseImageSpecification
55, packages :: Set Package
56, debconfConfig :: Maybe FilePath
57, unpackOnly :: Bool
58, binaries :: Vector Text
59, chrootCommands :: Vector Text
60} deriving (Show, Read)
61
62parsePackageName :: Text -> Package
63parsePackageName = Package -- TODO
64
65diskImageConfigParser :: Parser DiskImageConfig
66diskImageConfigParser = object $
67 DiskImageConfig
68 <$> field "parent" ((EmptyImageOfBytes <$> integer) <> (ParentImageConfigFile . unpack <$> string))
69 <*> (Set.fromList . toList . fmap parsePackageName <$> defaultField "packages" Vector.empty (array string))
70 <*> (fmap unpack <$> optField "debconf" string)
71 <*> defaultField "unpack-only" False bool
72 <*> defaultField "binaries" Vector.empty (array string)
73 <*> defaultField "chroot-commands" Vector.empty (array string)
74
75readCfg :: FilePath -> Action DiskImageConfig
76readCfg yaml = either error id . parse diskImageConfigParser . encodeUtf8 . pack <$> readFile' yaml
77