1
1
{-# LANGUAGE BangPatterns #-}
2
+ {-# LANGUAGE LambdaCase #-}
2
3
{-# LANGUAGE MultiWayIf #-}
3
4
4
5
-- | Create a package.dhall from files and directory contents.
@@ -15,6 +16,7 @@ import Data.List.NonEmpty (NonEmpty (..))
15
16
import Data.Maybe (fromMaybe )
16
17
import Data.Text (Text )
17
18
import qualified Data.Text as Text
19
+ import Data.Traversable (for )
18
20
import Dhall.Core
19
21
( Directory (.. )
20
22
, Expr (.. )
@@ -24,12 +26,13 @@ import Dhall.Core
24
26
, ImportHashed (.. )
25
27
, ImportMode (.. )
26
28
, ImportType (.. )
27
- , RecordField
29
+ , RecordField ( .. )
28
30
, makeRecordField
29
31
)
30
32
import Dhall.Map (Map )
31
33
import qualified Dhall.Map as Map
32
34
import Dhall.Pretty (CharacterSet (.. ))
35
+ import qualified Dhall.Pretty
33
36
import Dhall.Util (_ERROR , renderExpression )
34
37
import System.Directory
35
38
import System.FilePath
@@ -44,72 +47,152 @@ writePackage characterSet outputFn inputs = do
44
47
45
48
-- | Get the path and the Dhall expression for a package file.
46
49
--
47
- -- The inputs provided as the second argument are processed depending on whether
50
+ -- The location of the resulting package file is determined by the first path of the second argument:
51
+ --
52
+ -- * If it is a directory, it is also the output directory and the package
53
+ -- file will be placed there.
54
+ --
55
+ -- * If it is a file, then the directory that file resides in is the output
56
+ -- directory and the package file will be placed there.
57
+ --
58
+ -- All inputs provided as the second argument must be either in the output
59
+ -- directory or below it. They are processed depending on whether
48
60
-- the path points to a directory or a file:
49
61
--
50
62
-- * If the path points to a directory, all files with a @.dhall@ extensions
51
63
-- in that directory are included in the package.
52
- -- The package file will be located in that directory.
53
64
--
54
65
-- * If the path points to a regular file, it is included in the package
55
66
-- unless it is the path of the package file itself.
56
- -- All files passed as input must reside in the same directory.
57
- -- The package file will be located in the (shared) parent directory of the
58
- -- files passed as input to this function.
59
67
--
60
68
getPackagePathAndContent :: Maybe String -> NonEmpty FilePath -> IO (FilePath , Expr s Import )
61
69
getPackagePathAndContent outputFn (path :| paths) = do
62
70
outputDir <- do
63
71
isDirectory <- doesDirectoryExist path
64
72
return $ if isDirectory then path else takeDirectory path
65
- outputDir' <- makeAbsolute $ normalise outputDir
73
+ outputDir' <- addTrailingPathSeparator <$> makeAbsolute ( normalise outputDir)
66
74
75
+ -- Check if the supplied @dir@ argument points to a filesystem entry below
76
+ -- the output directory and return the path relative to the output directory.
67
77
let checkOutputDir dir = do
68
- dir' <- makeAbsolute $ normalise dir
69
- when (dir' /= outputDir') $
78
+ absoluteDir <- addTrailingPathSeparator <$> makeAbsolute (normalise dir)
79
+ let relativeDir = makeRelative outputDir' absoluteDir
80
+ unless (isRelative relativeDir) $
70
81
throwIO $ AmbiguousOutputDirectory outputDir dir
82
+ return relativeDir
71
83
72
84
resultMap <- go Map. empty checkOutputDir (path: paths)
73
- return (outputDir </> outputFn', RecordLit resultMap)
85
+ return (outputDir </> outputFn', RecordLit $ Map. sort resultMap)
74
86
where
75
- go :: Map Text (RecordField s Import ) -> (FilePath -> IO () ) -> [FilePath ] -> IO (Map Text (RecordField s Import ))
87
+ go :: Map Text (RecordField s Import ) -> (FilePath -> IO FilePath ) -> [FilePath ] -> IO (Map Text (RecordField s Import ))
76
88
go ! acc _checkOutputDir [] = return acc
77
89
go ! acc checkOutputDir (p: ps) = do
78
90
isDirectory <- doesDirectoryExist p
79
91
isFile <- doesFileExist p
80
92
if | isDirectory -> do
81
- checkOutputDir p
93
+ void $ checkOutputDir p
82
94
entries <- listDirectory p
83
95
let entries' = filter (\ entry -> takeExtension entry == " .dhall" ) entries
84
96
go acc checkOutputDir (map (p </> ) entries' <> ps)
85
97
| isFile -> do
86
- checkOutputDir $ takeDirectory p
98
+ dir <- checkOutputDir $ takeDirectory p
99
+
100
+ let p' = normalise $ dir </> takeFileName p
101
+
102
+ let resultMap = if p' == outputFn'
103
+ then Map. empty
104
+ else filepathToMap outputFn' p'
105
+
106
+ acc' <- mergeMaps acc resultMap
107
+ go acc' checkOutputDir ps
108
+ | otherwise -> throwIO $ InvalidPath p
87
109
88
- let key = Text. pack $ dropExtension $ takeFileName p
110
+ outputFn' = fromMaybe " package.dhall " outputFn
89
111
112
+ -- | Construct a nested 'Map' from a 'FilePath'.
113
+ -- For example, the filepath @some/file/path.dhall@ will result in something
114
+ -- similar to the following:
115
+ --
116
+ -- fromList
117
+ -- [ ("some", fromList
118
+ -- [ ("file", fromList
119
+ -- [ ("path", ./some/file/path.dhall)
120
+ -- ])
121
+ -- ])
122
+ -- ])
123
+ --
124
+ -- ... where ./some/file/path.dhall is a Dhall import. If the last component
125
+ -- equals the value passed in the @outputFn@ argument we produce a slightly
126
+ -- different result. Consider for example the Dhall Prelude: We have some
127
+ -- sub-packages there like @List/package.dhall@. If we want to construct the
128
+ -- top-level @package.dhall@ we want an entry like
129
+ --
130
+ -- > List = ./List/package.dhall
131
+ --
132
+ -- in there and not:
133
+ --
134
+ -- > List = { package = ./List/package.dhall }
135
+ --
136
+ filepathToMap :: FilePath -> FilePath -> Map Text (RecordField s Import )
137
+ filepathToMap outputFn = go [] . splitDirectories
138
+ where
139
+ go acc [] = go acc [" ." ]
140
+ go ! acc [x] =
90
141
let import_ = Import
91
142
{ importHashed = ImportHashed
92
143
{ hash = Nothing
93
144
, importType = Local Here File
94
- { directory = Directory []
95
- , file = Text. pack (takeFileName p)
145
+ { directory = Directory acc
146
+ , file = Text. pack x
96
147
}
97
148
}
98
149
, importMode = Code
99
150
}
151
+ in Map. singleton (Text. pack $ dropExtension x) $ makeRecordField $ Embed import_
152
+ go ! acc [x, y] | y == outputFn =
153
+ let import_ = Import
154
+ { importHashed = ImportHashed
155
+ { hash = Nothing
156
+ , importType = Local Here File
157
+ { directory = Directory (Text. pack x : acc)
158
+ , file = Text. pack y
159
+ }
160
+ }
161
+ , importMode = Code
162
+ }
163
+ in Map. singleton (Text. pack x) $ makeRecordField $ Embed import_
164
+ go ! acc (x: xs) = Map. singleton (Text. pack x) $ makeRecordField $ RecordLit $ go (Text. pack x : acc) xs
100
165
101
- let resultMap = if takeFileName p == outputFn'
102
- then Map. empty
103
- else Map. singleton key (makeRecordField $ Embed import_)
104
-
105
- go (resultMap <> acc) checkOutputDir ps
106
- | otherwise -> throwIO $ InvalidPath p
166
+ -- | Merge two 'Map's constructed with 'filepathToMap'.
167
+ -- It will throw an error if the arguments are not compatible with each other, e.g.
168
+ -- we cannot merge the following two maps:
169
+ --
170
+ -- > fromList [ ("file", ./file.dhall) ]
171
+ -- > fromList [ ("file", fromList [("nested", ./file/nested.dhall)]) ]
172
+ --
173
+ mergeMaps :: Map Text (RecordField s Import ) -> Map Text (RecordField s Import ) -> IO (Map Text (RecordField s Import ))
174
+ mergeMaps x y = do
175
+ let x' = fmap (:| [] ) x
176
+ y' = fmap (:| [] ) y
177
+ z = Map. unionWith (<>) x' y'
178
+ for z $ \ case
179
+ v@ RecordField {recordFieldValue = Embed {}} :| [] -> return v
180
+ vs | Just rs <- traverse extractRecordLit vs -> makeRecordField . RecordLit . Map. sort <$> foldM mergeMaps Map. empty rs
181
+ | otherwise -> throwIO $ IncompatiblePaths $ foldMap extractEmbeds vs
182
+ where
183
+ extractEmbeds :: RecordField s Import -> [Import ]
184
+ extractEmbeds RecordField {recordFieldValue = Embed import_} = [import_]
185
+ extractEmbeds RecordField {recordFieldValue = RecordLit xs} = foldMap extractEmbeds xs
186
+ extractEmbeds _ = mempty
107
187
108
- outputFn' = fromMaybe " package.dhall" outputFn
188
+ extractRecordLit :: RecordField s Import -> Maybe (Map Text (RecordField s Import ))
189
+ extractRecordLit RecordField {recordFieldValue = RecordLit xs} = Just xs
190
+ extractRecordLit _ = Nothing
109
191
110
192
-- | Exception thrown when creating a package file.
111
193
data PackageError
112
194
= AmbiguousOutputDirectory FilePath FilePath
195
+ | IncompatiblePaths [Import ]
113
196
| InvalidPath FilePath
114
197
115
198
instance Exception PackageError
@@ -125,6 +208,11 @@ instance Show PackageError where
125
208
\Although those paths might point to the same location they are not lexically the\n \
126
209
\same."
127
210
211
+ show (IncompatiblePaths imports) =
212
+ _ERROR <> " : ❰dhall package❱ failed because some inputs are not compatible with\n \
213
+ \each other:\n \
214
+ \\n " <> unlines (map (show . Dhall.Pretty. prettyExpr . Embed ) imports)
215
+
128
216
show (InvalidPath fp) =
129
217
_ERROR <> " : ❰dhall package❱ failed because the input does not exist or is\n \
130
218
\neither a directory nor a regular file:\n \
0 commit comments