SJW/src/SJW/Module.hs

90 lines
3.1 KiB
Haskell

--- SJW -- Clean Javascript modules for front-end development
--- Copyright © 2022 Tissevert <tissevert+devel@marvid.fr>
---
--- This file is part of SJW.
---
--- SJW is free software: you can redistribute it and/or modify it under the
--- terms of the GNU General Public License as published by the Free Software
--- Foundation, either version 3 of the License, or (at your option) any later
--- version.
---
--- SJW is distributed in the hope that it will be useful, but WITHOUT ANY
--- WARRANTY; without even the implied warranty of MERCHANTABILITY or FITNESS
--- FOR A PARTICULAR PURPOSE. See the GNU General Public License for more
--- details.
---
--- You should have received a copy of the GNU General Public License along
--- with this program. If not, see <http://www.gnu.org/licenses/>.
{-# LANGUAGE NamedFieldPuns #-}
{-# LANGUAGE ConstraintKinds #-}
{-# LANGUAGE FlexibleContexts #-}
module SJW.Module (
Environment
, Log
, Module(..)
, Modules(..)
, parse
, register
) where
import SJW.Source (CodePath(..), Source(..), HasSource, Path(..))
import Control.Monad.Except (MonadError(..))
import Control.Monad.IO.Class (MonadIO(..))
import Control.Monad.RWS (MonadState, MonadWriter, asks, modify)
import Data.Attoparsec.Text (parseOnly)
import Data.Map (Map)
import qualified Data.Map as Map (insert)
import Data.Set (Set)
import qualified Data.Set as Set (empty, insert)
import qualified Data.Text as Text (pack)
import SJW.Dependencies (Failable)
import SJW.Module.File (File(..))
import qualified SJW.Module.File as File (parser)
import SJW.Module.Imports (Reference(..), recurse)
import Prelude hiding (takeWhile)
import System.Directory (doesFileExist)
import System.FilePath ((</>), (<.>))
import Text.Printf (printf)
data Module = Module {
file :: File
, dependencies :: Set Path
}
newtype Modules = Modules {
modules :: Map Path Module
}
type Environment = MonadState Modules
type Log = MonadWriter [String]
register :: Environment m => Path -> Module -> m ()
register path module_ = modify $
\(Modules modules) -> Modules $ Map.insert path module_ modules
build :: File -> Module
build file = Module {file, dependencies}
where
dependencies = recurse pushDependency Set.empty $ imports file
pushDependency set _ ref = Set.insert (modulePath ref) set
parse :: (HasSource m, MonadIO m, Failable m) => Bool -> Path -> m Module
parse isMain path = do
searchPath <- asks code
filePath <- find (CodePath [], searchPath) path
source <- Text.pack <$> liftIO (readFile filePath)
either throwError (return . build) $
parseOnly (File.parser isMain) source
find :: (Failable m, MonadIO m) => (CodePath, CodePath) -> Path -> m FilePath
find (stack, CodePath []) path = throwError $
printf "Module %s not found in paths : %s" (show path) (show $ stack)
find (CodePath stackedDirs, CodePath (dir:otherDirs)) path@(Path components) = do
fileExists <- liftIO $ doesFileExist filePath
if fileExists
then return filePath
else find (CodePath (dir:stackedDirs), CodePath otherDirs) path
where
filePath = foldl (</>) dir components <.> "js"