{-# LANGUAGE LambdaCase #-} {-# LANGUAGE RecordWildCards #-} {-# LANGUAGE NoImplicitPrelude #-} -- | Small module for extracting metadata from the comments of modules. module Biz.Bild.Meta where import Alpha import qualified Data.Aeson as Aeson import qualified Data.Char as Char import qualified Data.Set as Set import qualified Data.Text as Text import qualified Text.Regex.Applicative as Regex -- | A third-party dependency. This gets mapped to some name in nixpkgs, -- prefixed by package set like @haskellPackages@ or -- @python3Packages@. type Dep = String -- | This is a system-level requirement, the string gets mapped to a name in -- nixpkgs at the top level, like @pkgs.thing@. type Sys = String -- | A run-time dependency. This is some executable that will be placed on -- @PATH@. This gets selected from @bild.pkgs@, so it must be exported there. type Run = String -- | An arbitrary compiler argument that may get added to the compilation -- command. Should be used sparingly, and not all builds will support this. type Arg = String data Out = Lib String | Bin String | None deriving (Show, Eq) instance Aeson.ToJSON Out where toJSON = Aeson.String <. Text.pack <. \case Bin a -> a Lib a -> a None -> "" data Parsed = Parsed { pdep :: Set Dep, parg :: Set Arg, pout :: Out, psys :: Set Sys, prun :: Set Run } detect :: (Ord a) => Regex.RE Char a -> [Text] -> Set a detect m cl = cl /> Text.unpack /> Regex.match m |> catMaybes |> Set.fromList -- | 'Out' is always singular, so it gets a special function detectOut :: Regex.RE Char Out -> [Text] -> Out detectOut m cl = cl /> Text.unpack /> Regex.match m |> catMaybes |> head |> fromMaybe None detectAll :: [Char] -> [Text] -> Parsed detectAll m cl = Parsed {..} where pout = detectOut (out m <|> lib m) cl detect_ re = detect (re m) cl pdep = detect_ dep psys = detect_ sys parg = detect_ arg prun = detect_ run dep :: [Char] -> Regex.RE Char Dep dep comment = Regex.string (comment ++ " : dep ") *> Regex.many (Regex.psym (not <. Char.isSpace)) sys :: [Char] -> Regex.RE Char Dep sys comment = Regex.string (comment ++ " : sys ") *> Regex.many (Regex.psym (not <. Char.isSpace)) out :: [Char] -> Regex.RE Char Out out comment = Regex.string (comment ++ " : out ") *> Regex.many (Regex.psym (/= ' ')) /> Bin lib :: [Char] -> Regex.RE Char Out lib comment = Regex.string (comment ++ " : lib ") *> Regex.many (Regex.psym (/= ' ')) /> Lib arg :: [Char] -> Regex.RE Char Arg arg comment = Regex.string (comment ++ " : arg ") *> Regex.many Regex.anySym run :: [Char] -> Regex.RE Char Run run comment = Regex.string (comment ++ " : run ") *> Regex.many Regex.anySym