SJW/src/SJW/Source.hs

59 lines
1.7 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 ConstraintKinds #-}
module SJW.Source (
CodePath(..)
, Source(..)
, HasSource
, Path(..)
, source
) where
import Control.Monad.Reader (MonadReader)
import Data.List (intercalate)
import Text.ParserCombinators.ReadP (char, munch, sepBy)
import Text.ParserCombinators.ReadPrec (lift)
import Text.Read (readPrec)
newtype Path = Path [String] deriving (Eq, Ord)
newtype CodePath = CodePath [FilePath]
data Source = Source {
code :: CodePath
, mainModule :: Path
}
type HasSource = MonadReader Source
instance Show Path where
show (Path components) = intercalate "." components
instance Read Path where
readPrec = fmap Path . lift $
munch (/= '.') `sepBy` char '.'
instance Show CodePath where
show (CodePath dirs) = intercalate ":" dirs
source :: [String] -> Source
source paths = Source {
code = CodePath paths
, mainModule = Path ["Main"]
}