1
1
{-# LANGUAGE QuasiQuotes #-}
2
+ {-# LANGUAGE ViewPatterns #-}
2
3
3
4
module Garn.CodeGen
4
5
( Garn.CodeGen. run ,
5
- fromToplevelDerivation ,
6
+ PkgInfo (Derivation , Collection , description , path ),
7
+ scanPackages ,
8
+ writePkgFiles ,
6
9
)
7
10
where
8
11
12
+ import Control.Exception (IOException , catch )
13
+ import Control.Monad (forM_ )
9
14
import Cradle (StdoutUntrimmed (.. ), run )
10
15
import Data.Aeson (FromJSON , eitherDecode , toJSON )
11
16
import Data.Aeson.Text (encodeToLazyText )
17
+ import Data.Char (isDigit )
12
18
import Data.Functor ((<&>) )
13
19
import Data.List (intercalate )
14
20
import Data.Map (Map , toAscList )
@@ -19,69 +25,115 @@ import Data.String.Interpolate (i)
19
25
import Data.String.Interpolate.Util (unindent )
20
26
import GHC.Generics (Generic )
21
27
import Garn.Common (currentSystem , nixpkgsInput )
28
+ import System.Directory (createDirectoryIfMissing , removeDirectoryRecursive )
22
29
import WithCli (withCli )
23
30
31
+ -- A nix expression that specifies which packages to include in the final
32
+ -- collection.
33
+ --
34
+ -- All top-level derivations included by default, but everything else excluded.
35
+ -- This can be overridden with the given attribute set.
36
+ pkgSpec :: String
37
+ pkgSpec =
38
+ [i |
39
+ {
40
+ haskellPackages = {};
41
+ nimPackages = {};
42
+ nodePackages = { "@antora/cli" = false; };
43
+ phpPackages = {};
44
+ python2Packages = {};
45
+ python3Packages = {};
46
+ rubyPackages = {};
47
+ rustPackages = {};
48
+ }
49
+ |]
50
+
51
+ pkgs :: String -> String
52
+ pkgs system =
53
+ [i |
54
+ import (builtins.getFlake "#{nixpkgsInput}") {
55
+ system = "#{system}";
56
+ config.allowAliases = false;
57
+ }
58
+ |]
59
+
24
60
run :: IO ()
25
61
run = withCli $ do
26
62
system <- currentSystem
27
- let varName = " pkgs"
28
- nixpkgsExpression =
29
- [i |
30
- import (builtins.getFlake "#{nixpkgsInput}") {
31
- system = "#{system}";
32
- config.allowAliases = false;
33
- }
34
- |]
35
- code <- fromToplevelDerivation " ." varName nixpkgsExpression
36
- writeFile " ts/nixpkgs.ts" code
63
+ let outDir = " ts/internal/nixpkgs"
64
+ removeDirectoryRecursive outDir `catch` \ (_ :: IOException ) -> pure ()
65
+ pkgs <- scanPackages system (pkgs system) pkgSpec
66
+ writePkgFiles outDir " ../.." pkgs
67
+ writeFile " ts/nixpkgs.ts" " export * from \" ./internal/nixpkgs/mod.ts\" ;\n "
68
+
69
+ writePkgFiles :: String -> String -> Map String PkgInfo -> IO ()
70
+ writePkgFiles modulePath garnLibRoot (Map. mapKeys sanitize -> pkgs) = do
71
+ createDirectoryIfMissing True modulePath
72
+ let code =
73
+ unindent
74
+ [i |
75
+ import { mkPackage } from "#{garnLibRoot}/package.ts";
76
+ import { nixRaw } from "#{garnLibRoot}/nix.ts";
77
+
78
+ |]
79
+ <> pkgsString pkgs
80
+ writeFile (modulePath <> " /mod.ts" ) code
81
+ forM_ (Map. assocs pkgs) $ \ (name :: String , pkgInfo :: PkgInfo ) -> do
82
+ case pkgInfo of
83
+ Derivation {} -> pure ()
84
+ Collection {subPkgs} -> writePkgFiles (modulePath <> " /" <> name) (garnLibRoot <> " /.." ) subPkgs
37
85
38
- fromToplevelDerivation :: String -> String -> String -> IO String
39
- fromToplevelDerivation garnLibRoot varName rootExpr = do
40
- system :: String <- do
41
- StdoutUntrimmed json <- Cradle. run " nix" nixArgs (words " eval --impure --json --expr builtins.currentSystem" )
42
- pure $ either error id $ eitherDecode (cs json)
86
+ scanPackages :: String -> String -> String -> IO (Map String PkgInfo )
87
+ scanPackages system pkgs pkgSpec = do
43
88
StdoutUntrimmed json <- Cradle. run " nix" nixArgs " eval" (" .#lib." <> system) " --json" " --apply" nixExpr
44
- pkgs :: Map String PkgInfo <- case eitherDecode (cs json) of
89
+ case eitherDecode (cs json) of
45
90
Right pkgs -> pure pkgs
46
91
Left e -> error (e <> " in " <> cs json)
47
- let sanitizedPkgs = Map. mapKeys sanitize pkgs
48
- pure $
49
- unindent
50
- [i |
51
- import { mkPackage } from "#{garnLibRoot}/package.ts";
52
- import { nixRaw } from "#{garnLibRoot}/nix.ts";
53
-
54
- |]
55
- <> pkgsString varName sanitizedPkgs
56
92
where
57
93
nixExpr =
58
94
[i |
59
- lib :
60
- let mk = name: value: {
61
- attribute = name;
62
- description = if value ? meta.description
63
- then value.meta.description
64
- else null;
65
- };
66
- isNotBroken = value:
67
- let broken = (builtins.tryEval (value.meta.broken or false));
68
- in broken.success && !broken.value;
69
- doesNotThrow = value : (builtins.tryEval value).success;
70
- filterAttrs = lib.attrsets.filterAttrs
71
- (name: value:
72
- doesNotThrow value
73
- && lib.isDerivation value
74
- && isNotBroken value);
75
- in
76
- (lib.mapAttrs mk
77
- (filterAttrs (#{rootExpr}))
78
- )
95
+ lib:
96
+ let
97
+ scan = path: pkgs: pkgSpec:
98
+ if pkgSpec == false then null
99
+ else filterNulls (lib.mapAttrs (k: v:
100
+ let
101
+ newPath = "${path}.${k}";
102
+ in
103
+ if pkgSpec ? ${k}
104
+ then mkCollection (scan newPath v (pkgSpec.${k}))
105
+ else if isWorkingDerivation v then mkDerivation newPath v
106
+ else null
107
+ ) pkgs);
108
+ mkCollection = subPkgs:
109
+ if subPkgs == null then null
110
+ else {
111
+ tag = "Collection";
112
+ inherit subPkgs;
113
+ };
114
+ mkDerivation = path: pkg: {
115
+ tag = "Derivation";
116
+ inherit path;
117
+ description = if pkg ? meta.description
118
+ then pkg.meta.description
119
+ else null;
120
+ };
121
+ filterNulls = lib.filterAttrs (k: v: v != null);
122
+ isWorkingDerivation = value:
123
+ (builtins.tryEval value).success &&
124
+ (let
125
+ evalResult = (builtins.tryEval (value.meta.broken or false));
126
+ in
127
+ evalResult.success &&
128
+ !evalResult.value &&
129
+ lib.isDerivation value);
130
+ in
131
+ scan "pkgs" (#{pkgs}) (#{pkgSpec})
79
132
|]
80
133
81
- data PkgInfo = PkgInfo
82
- { description :: Maybe String ,
83
- attribute :: String
84
- }
134
+ data PkgInfo
135
+ = Derivation { description :: Maybe String , path :: String }
136
+ | Collection { subPkgs :: Map String PkgInfo }
85
137
deriving stock (Eq , Show , Generic )
86
138
deriving anyclass (FromJSON )
87
139
@@ -96,28 +148,40 @@ pkgDoc pkgInfo = case description pkgInfo of
96
148
*/
97
149
|]
98
150
99
- formatPkg :: String -> (String , PkgInfo ) -> String
100
- formatPkg varName (name, pkgInfo) =
101
- let escapedDoc = encodeToLazyText . toJSON $ fromMaybe " " $ description pkgInfo
102
- in pkgDoc pkgInfo
103
- <> unindent
104
- [i |
105
- export const #{name} = mkPackage(
106
- nixRaw`#{varName}.#{attribute pkgInfo}`,
107
- #{escapedDoc},
108
- );
109
- |]
151
+ formatPkg :: (String , PkgInfo ) -> String
152
+ formatPkg (name, pkgInfo) = do
153
+ case pkgInfo of
154
+ Derivation {description, path} ->
155
+ let escapedDoc = encodeToLazyText . toJSON $ fromMaybe " " description
156
+ in pkgDoc pkgInfo
157
+ <> unindent
158
+ [i |
159
+ export const #{name} = mkPackage(
160
+ nixRaw`#{path}`,
161
+ #{escapedDoc},
162
+ );
163
+ |]
164
+ Collection _ ->
165
+ unindent
166
+ [i |
167
+ export * as #{name} from "./#{name}/mod.ts";
168
+ |]
110
169
111
- pkgsString :: String -> Map String PkgInfo -> String
112
- pkgsString varName pkgs =
113
- intercalate " \n " $ formatPkg varName <$> toAscList pkgs
170
+ pkgsString :: Map String PkgInfo -> String
171
+ pkgsString pkgs =
172
+ intercalate " \n " $ formatPkg <$> toAscList pkgs
114
173
115
174
sanitize :: String -> String
116
175
sanitize str
176
+ | isDigit $ head str = sanitize $ " _" <> str
117
177
| str `elem` tsKeywords = str <> " _"
118
178
| otherwise =
119
179
str <&> \ case
180
+ ' +' -> ' _'
120
181
' -' -> ' _'
182
+ ' .' -> ' _'
183
+ ' /' -> ' _'
184
+ ' @' -> ' _'
121
185
x -> x
122
186
123
187
tsKeywords :: [String ]
@@ -145,8 +209,10 @@ tsKeywords =
145
209
" import" ,
146
210
" in" ,
147
211
" instanceOf" ,
212
+ " interface" ,
148
213
" new" ,
149
214
" null" ,
215
+ " private" ,
150
216
" return" ,
151
217
" super" ,
152
218
" switch" ,
@@ -155,6 +221,7 @@ tsKeywords =
155
221
" true" ,
156
222
" try" ,
157
223
" typeOf" ,
224
+ " typeof" ,
158
225
" var" ,
159
226
" void" ,
160
227
" while" ,
0 commit comments