Skip to content

Commit 86fb0c2

Browse files
committed
adding meaning introduction to some modules
1 parent b0026b3 commit 86fb0c2

File tree

10 files changed

+17
-7
lines changed

10 files changed

+17
-7
lines changed

src/Nix/Builtins.hs

Lines changed: 1 addition & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -22,6 +22,7 @@
2222
{-# OPTIONS_GHC -Wno-missing-signatures #-}
2323
{-# OPTIONS_GHC -fno-warn-name-shadowing #-}
2424

25+
-- | Code that implements Nix builtins. Lists the functions that are built into the Nix expression evaluator. Some built-ins (aka `derivation`), are always in the scope, so they can be accessed by the name. To keap the namespace clean, most built-ins are inside the `builtins` scope - a set that contains all what is a built-in.
2526
module Nix.Builtins (withNixContext, builtins) where
2627

2728
import Control.Comonad

src/Nix/Cache.hs

Lines changed: 3 additions & 2 deletions
Original file line numberDiff line numberDiff line change
@@ -1,5 +1,6 @@
11
{-# LANGUAGE CPP #-}
22

3+
-- | Reading and writing Nix cache files
34
module Nix.Cache where
45

56
import qualified Data.ByteString.Lazy as BS
@@ -38,11 +39,11 @@ readCache path = do
3839
writeCache :: FilePath -> NExprLoc -> IO ()
3940
writeCache path expr =
4041
#ifdef USE_COMPACT
41-
C.writeCompact path =<< C.compact expr
42+
C.writeCompact path =<< C.compact expr
4243
#else
4344
#ifdef MIN_VERSION_serialise
4445
BS.writeFile path (S.serialise expr)
4546
#else
4647
error "writeCache not implemented for this platform"
4748
#endif
48-
#endif
49+
#endif

src/Nix/Frames.hs

Lines changed: 1 addition & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -4,6 +4,7 @@
44
{-# LANGUAGE FlexibleInstances #-}
55
{-# LANGUAGE ScopedTypeVariables #-}
66

7+
-- | Definitions of Frames. Frames are messages that gather and ship themself with a context related to the message. For example - the message about some exception would also gather, keep and bring with it the tracing information.
78
module Nix.Frames
89
( NixLevel(..)
910
, Frames

src/Nix/Normal.hs

Lines changed: 4 additions & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -9,6 +9,9 @@
99
{-# LANGUAGE TypeApplications #-}
1010
{-# LANGUAGE TypeFamilies #-}
1111

12+
-- | Code for normalization (reduction into a normal form) of Nix expressions.
13+
-- Nix language allows recursion, so some expressions do not converge.
14+
-- And so do not converge into a normal form.
1215
module Nix.Normal where
1316

1417
import Control.Monad
@@ -117,7 +120,7 @@ removeEffects
117120
removeEffects =
118121
iterNValueM
119122
id
120-
(flip queryM (pure opaque))
123+
(`queryM` pure opaque)
121124
(fmap Free . sequenceNValue' id)
122125

123126
opaque :: Applicative f => NValue t f m

src/Nix/Options.hs

Lines changed: 1 addition & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -1,3 +1,4 @@
1+
-- | Definitions & defaults for the CLI options
12
module Nix.Options where
23

34
import Data.Text ( Text )

src/Nix/Options/Parser.hs

Lines changed: 1 addition & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -1,5 +1,6 @@
11
{-# LANGUAGE TemplateHaskell #-}
22

3+
-- | Code that configures presentation parser for the CLI options
34
module Nix.Options.Parser where
45

56
import Control.Arrow ( second )

src/Nix/Parser.hs

Lines changed: 1 addition & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -9,6 +9,7 @@
99
{-# OPTIONS_GHC -fno-warn-name-shadowing #-}
1010
{-# OPTIONS_GHC -Wno-missing-signatures #-}
1111

12+
-- | Main module for parsing Nix expressions.
1213
module Nix.Parser
1314
( parseNixFile
1415
, parseNixFileLoc

src/Nix/Render.hs

Lines changed: 1 addition & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -128,5 +128,5 @@ sourceContext path (unPos -> begLine) (unPos -> _begCol) (unPos -> endLine) (unP
128128
| otherwise = " " ++ n
129129
ls' = zipWith (<+>)
130130
(map (pretty . pad) nums')
131-
(map ((<+>) "| ") ls)
131+
(map ("| " <+>) ls)
132132
pure $ vsep $ ls' ++ [msg]

src/Nix/Render/Frame.hs

Lines changed: 3 additions & 2 deletions
Original file line numberDiff line numberDiff line change
@@ -10,6 +10,8 @@
1010
{-# LANGUAGE TypeApplications #-}
1111
{-# LANGUAGE TypeFamilies #-}
1212

13+
14+
-- | Code for rendering/representation of the messages packaged with their context (Frames).
1315
module Nix.Render.Frame where
1416

1517
import Control.Monad.Reader
@@ -152,8 +154,7 @@ renderExpr _level longLabel shortLabel e@(Fix (Compose (Ann _ x))) = do
152154
| otherwise = prettyNix (Fix (Fix (NSym "<?>") <$ x))
153155
pure $ if verbose opts >= Chatty
154156
then
155-
vsep
156-
$ [pretty (longLabel ++ ":\n>>>>>>>>"), indent 2 rendered, "<<<<<<<<"]
157+
vsep [pretty (longLabel ++ ":\n>>>>>>>>"), indent 2 rendered, "<<<<<<<<"]
157158
else pretty shortLabel <> fillSep [": ", rendered]
158159

159160
renderValueFrame

src/Nix/String.hs

Lines changed: 1 addition & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -205,7 +205,7 @@ principledMakeNixStringWithSingletonContext s c = NixString s (S.singleton c)
205205

206206
-- | Create a NixString from a Text and context
207207
principledMakeNixString :: Text -> S.HashSet StringContext -> NixString
208-
principledMakeNixString s c = NixString s c
208+
principledMakeNixString = NixString
209209

210210
-- | A monad for accumulating string context while producing a result string.
211211
newtype WithStringContextT m a = WithStringContextT (WriterT (S.HashSet StringContext) m a)

0 commit comments

Comments
 (0)