diff --git a/examples/package.toml b/examples/package.toml index 817b6c8..f30badd 100644 --- a/examples/package.toml +++ b/examples/package.toml @@ -6,3 +6,6 @@ minimum_runtime = "0.3.9" [targets.docs] title = "Nirum Examples" + +[targets.rust] +name = "nirum-examples" diff --git a/src/Nirum/Constructs/ModulePath.hs b/src/Nirum/Constructs/ModulePath.hs index bad81cf..0f8579a 100644 --- a/src/Nirum/Constructs/ModulePath.hs +++ b/src/Nirum/Constructs/ModulePath.hs @@ -8,10 +8,14 @@ module Nirum.Constructs.ModulePath ( ModulePath ( ModuleName , fromIdentifiers , hierarchy , hierarchies + , isPrefixOf , replacePrefix + , root + , stripPrefix ) where import Data.Char (toLower) +import qualified Data.List as L import Data.Maybe (fromMaybe, mapMaybe) import GHC.Exts (IsList (Item, fromList, toList)) @@ -64,6 +68,9 @@ hierarchy m@(ModulePath parent _) = m `S.insert` hierarchy parent hierarchies :: S.Set ModulePath -> S.Set ModulePath hierarchies modulePaths = S.unions $ toList $ S.map hierarchy modulePaths +isPrefixOf :: ModulePath -> ModulePath -> Bool +a `isPrefixOf` b = toList a `L.isPrefixOf` toList b + replacePrefix :: ModulePath -> ModulePath -> ModulePath -> ModulePath replacePrefix from to path' | path' == from = to @@ -71,11 +78,22 @@ replacePrefix from to path' ModuleName {} -> path' ModulePath p n -> ModulePath (replacePrefix from to p) n +root :: ModulePath -> Identifier +root = head . toList + +stripPrefix :: ModulePath -> ModulePath -> Maybe ModulePath +stripPrefix a b = do + stripped <- L.stripPrefix (toList a) (toList b) + case stripped of + [] -> Nothing + xs -> Just $ fromList xs instance IsList ModulePath where type Item ModulePath = Identifier fromList identifiers = fromMaybe (error "ModulePath cannot be empty") (fromIdentifiers identifiers) - toList (ModuleName identifier) = [identifier] - toList (ModulePath path' identifier) = toList path' ++ [identifier] + toList mp = toList' mp [] + where + toList' (ModuleName identifier) xs = identifier:xs + toList' (ModulePath path' identifier) xs = toList' path' (identifier:xs) diff --git a/src/Nirum/Targets.hs b/src/Nirum/Targets.hs index 08f9891..2ad630d 100644 --- a/src/Nirum/Targets.hs +++ b/src/Nirum/Targets.hs @@ -39,6 +39,7 @@ import Nirum.Targets.List (targetProxyMapQ) -- docs/target/x.md file too. import Nirum.Targets.Docs () import Nirum.Targets.Python () +import Nirum.Targets.Rust () data BuildError = TargetNameError TargetName | CompileError (M.Map FilePath Text) diff --git a/src/Nirum/Targets/Python/CodeGen.hs b/src/Nirum/Targets/Python/CodeGen.hs index 8c655c1..3600f40 100644 --- a/src/Nirum/Targets/Python/CodeGen.hs +++ b/src/Nirum/Targets/Python/CodeGen.hs @@ -46,7 +46,7 @@ import Data.Text hiding (empty) import qualified Nirum.CodeGen import Nirum.Constructs.Identifier -import Nirum.Constructs.ModulePath +import Nirum.Constructs.ModulePath hiding (isPrefixOf) import Nirum.Constructs.Name minimumRuntime :: Version diff --git a/src/Nirum/Targets/Rust.hs b/src/Nirum/Targets/Rust.hs new file mode 100644 index 0000000..5736477 --- /dev/null +++ b/src/Nirum/Targets/Rust.hs @@ -0,0 +1,128 @@ +{-# LANGUAGE DeriveDataTypeable, ExtendedDefaultRules, OverloadedLists, + QuasiQuotes, TypeFamilies, TypeSynonymInstances, + MultiParamTypeClasses #-} +module Nirum.Targets.Rust ( Rust + , Code + , CompileError + , childModules + ) where + +import qualified Data.Map.Strict as M +import Data.Maybe +import qualified Data.SemVer as SV +import Data.Semigroup +import qualified Data.Set as S +import qualified Data.Text as T +import qualified Data.Text.Lazy as TL +import Data.Text.Encoding (encodeUtf8) +import Data.Text.Lazy (toStrict) +import Data.Typeable (Typeable) +import System.FilePath + +import GHC.Exts (IsList (toList)) + +import Text.Blaze.Renderer.Text +import Text.Heterocephalus (compileText) + +import qualified Nirum.Constructs.Identifier as I +import Nirum.Constructs.ModulePath +import Nirum.Constructs.TypeDeclaration +import Nirum.Package.Metadata +import qualified Nirum.Package.ModuleSet as MS +import Nirum.Targets.Rust.Item +import Nirum.Targets.Rust.Keyword +import Nirum.Targets.Rust.ModuleTree +import Nirum.TypeInstance.BoundModule + +data Rust = Rust { packageName :: T.Text + } + deriving (Eq, Ord, Show, Typeable) + +type Code = T.Text +type CompileError' = () + +genCargoToml :: Package Rust -> Code +genCargoToml Package { metadata = Metadata { version = version' + , target = Rust { packageName = name' } + } + } = + toStrict $ + renderMarkup [compileText|[package] +name = "#{ name' }" +version = "#{ SV.toLazyText version' }" +|] + +buildPrologue :: RustModule -> TL.Text +buildPrologue mod' = + renderMarkup [compileText|%{ forall child <- children mod' } +pub mod #{ toRustIdentifier I.toCamelCaseText child }; +%{ endforall } +|] + +buildBody :: Maybe (BoundModule Rust) -> TL.Text +buildBody (Just m) = + TL.concat [renderItem i | i <- moduleTypes] + where + moduleTypes :: [TypeDeclaration] + moduleTypes = toList $ boundTypes m +buildBody Nothing = TL.empty + +compilePackage' :: Package Rust + -> M.Map FilePath (Either CompileError' Code) +compilePackage' package = + M.fromList $ + [ ( fileName + , Right $ + toStrict $ + TL.append (buildPrologue mod') + (buildBody (resolveWithModulePath mp)) + ) + | mod'@RustModule { filePath = fileName + , modPath = mp + } <- modules' + ] ++ + [ ("Cargo.toml", Right $ genCargoToml package) ] + where + resolveWithModulePath :: ModulePath -> Maybe (BoundModule Rust) + resolveWithModulePath mp = resolveBoundModule mp package + modules' :: [RustModule] + modules' = libModule : map (toRustModule expanded') (toList expanded') + expanded' = hierarchies $ S.fromList $ MS.keys $ modules package + libModule = RustModule { filePath = toFilePath True ["lib"] + , modPath = ["lib"] + , children = S.map root expanded' + } + +childModules :: Foldable f => f ModulePath -> ModulePath -> S.Set I.Identifier +childModules modPaths base = fromMaybe mempty $ getOption $ foldMap f modPaths + where + f = Option . fmap (S.singleton . root) . stripPrefix base + +toFilePath :: Bool -> ModulePath -> FilePath +toFilePath isLeaf p = joinPath ("src" : converted) ++ ".rs" + where + convert = map (toRustIdentifier I.toSnakeCaseText) . toList + converted = map T.unpack $ convert p ++ (if isLeaf then [] else ["mod"]) + +toRustModule :: Foldable f => f ModulePath -> ModulePath -> RustModule +toRustModule modPaths mp = RustModule { filePath = filePath' + , modPath = mp + , children = children' + } + where + children' = childModules modPaths mp + isLeaf = S.null children' + filePath' = toFilePath isLeaf mp + +instance Target Rust where + type CompileResult Rust = Code + type CompileError Rust = CompileError' + + targetName _ = "rust" + parseTarget table = do + name' <- stringField "name" table + return Rust { packageName = name' + } + compilePackage = compilePackage' + showCompileError _ _ = "" + toByteString _ = encodeUtf8 diff --git a/src/Nirum/Targets/Rust/Item.hs b/src/Nirum/Targets/Rust/Item.hs new file mode 100644 index 0000000..e5b9f48 --- /dev/null +++ b/src/Nirum/Targets/Rust/Item.hs @@ -0,0 +1,34 @@ +{-# LANGUAGE ExtendedDefaultRules, OverloadedLists, TypeSynonymInstances, + QuasiQuotes #-} +module Nirum.Targets.Rust.Item ( renderItem + ) where + +import qualified Data.Text.Lazy as TL + +import GHC.Exts (IsList (toList)) + +import Text.Blaze.Renderer.Text +import Text.Heterocephalus (compileText) + +import qualified Nirum.Constructs.Identifier as I +import Nirum.Constructs.Name +import Nirum.Constructs.TypeDeclaration +import Nirum.Targets.Rust.Keyword + +renderItem :: TypeDeclaration -> TL.Text +renderItem TypeDeclaration { typename = moduleName + , type' = ty + } = + renderType ty + where + renderType :: Type -> TL.Text + renderType EnumType { members = members' } = + renderMarkup [compileText| +pub enum #{ toRustIdentifier I.toPascalCaseText $ facialName moduleName } { +%{ forall EnumMember memberName _ <- toList members' } + #{ toRustIdentifier I.toPascalCaseText $ facialName memberName }, +%{ endforall } +} +|] + renderType _ = TL.empty +renderItem _ = TL.empty diff --git a/src/Nirum/Targets/Rust/Keyword.hs b/src/Nirum/Targets/Rust/Keyword.hs new file mode 100644 index 0000000..dc6a58e --- /dev/null +++ b/src/Nirum/Targets/Rust/Keyword.hs @@ -0,0 +1,48 @@ +{-# LANGUAGE ExtendedDefaultRules, OverloadedLists, TypeSynonymInstances #-} +module Nirum.Targets.Rust.Keyword ( isPossibleKeyword + , toRustIdentifier + ) where + +import qualified Data.Set as S +import qualified Data.Text as T + +import qualified Nirum.Constructs.Identifier as I + +-- | The set of Rust keywords. +-- See also: https://doc.rust-lang.org/reference/keywords.html +strictKeywords :: S.Set T.Text +strictKeywords = + [ "as", "box", "break", "const", "continue" + , "crate", "else", "enum", "extern", "false" + , "fn", "for", "if", "impl", "in", "let" + , "loop", "match", "mod", "move", "mut", "pub" + , "ref", "return", "self", "Self", "static" + , "struct", "super", "trait", "true", "type" + , "unsafe", "use", "where", "while" + ] +weakKeywords :: S.Set T.Text +weakKeywords = + [ "catch", "default", "union", "'static" ] +reservedKeywords :: S.Set T.Text +reservedKeywords = + [ "abstract", "alignof", "become", "do" + , "final", "macro", "offsetof", "override" + , "priv", "proc", "pure", "sizeof", "typeof" + , "unsized", "virtual", "yield" + ] + +isPossibleKeyword :: T.Text -> Bool +isPossibleKeyword name' = + (findMember strictKeywords) || + (findMember weakKeywords) || + (findMember reservedKeywords) + where + findMember :: S.Set T.Text -> Bool + findMember = S.member name' + +toRustIdentifier :: (I.Identifier -> T.Text) -> I.Identifier -> T.Text +toRustIdentifier convertIdent identifier = + if isPossibleKeyword attrName then attrName `T.snoc` '_' else attrName + where + attrName :: T.Text + attrName = convertIdent identifier diff --git a/src/Nirum/Targets/Rust/ModuleTree.hs b/src/Nirum/Targets/Rust/ModuleTree.hs new file mode 100644 index 0000000..fa92d9c --- /dev/null +++ b/src/Nirum/Targets/Rust/ModuleTree.hs @@ -0,0 +1,18 @@ +{-# LANGUAGE OverloadedLists, TypeSynonymInstances #-} +module Nirum.Targets.Rust.ModuleTree ( RustModule ( RustModule + , filePath + , modPath + , children + ) + ) where + +import qualified Data.Set as S + +import Nirum.Constructs.Identifier +import Nirum.Constructs.ModulePath (ModulePath) + +data RustModule = RustModule { filePath :: FilePath + , modPath :: ModulePath + , children :: S.Set Identifier + } + deriving (Eq, Show) diff --git a/test/Nirum/Targets/RustSpec.hs b/test/Nirum/Targets/RustSpec.hs new file mode 100644 index 0000000..f5c1e26 --- /dev/null +++ b/test/Nirum/Targets/RustSpec.hs @@ -0,0 +1,33 @@ +{-# LANGUAGE OverloadedLists, PartialTypeSignatures #-} +module Nirum.Targets.RustSpec where + +import qualified Data.Set as S +import Test.Hspec.Meta + +import Nirum.Constructs.ModulePath +import Nirum.Targets.Rust + + +spec :: Spec +spec = parallel $ + describe "childModules" $ do + specify "empty list" $ do + childModules S.empty ["a"] `shouldBe` [] + childModules S.empty ["a", "b"] `shouldBe` [] + specify "singleton" $ do + childModules ([["a"]] :: [ModulePath]) ["a"] `shouldBe` [] + childModules (S.singleton ["foo"]) ["foo"] `shouldBe` [] + childModules ([["foo"]] :: [ModulePath]) ["bar"] `shouldBe` [] + specify "simple" $ do + let input = [ ["a"] + , ["a", "b"] + , ["a", "c", "e"] + , ["b"] + , ["b", "c"] + , ["b", "d"] + ] :: [ModulePath] + childModules input ["a"] `shouldBe` ["b", "c"] + childModules input ["b"] `shouldBe` ["c", "d"] + childModules input ["c"] `shouldBe` [] + childModules input ["a", "b"] `shouldBe` [] + childModules input ["a", "c"] `shouldBe` ["e"] diff --git a/test/nirum_fixture/package.toml b/test/nirum_fixture/package.toml index a567475..fd0def3 100644 --- a/test/nirum_fixture/package.toml +++ b/test/nirum_fixture/package.toml @@ -14,3 +14,6 @@ name = "nirum_fixture" [targets.docs] title = "Fixtures for Nirum tests" + +[targets.rust] +name = "nirum_fixture"