-
Notifications
You must be signed in to change notification settings - Fork 3
Commit
This commit does not belong to any branch on this repository, and may belong to a fork outside of the repository.
- Loading branch information
1 parent
38f5232
commit 0cefffe
Showing
6 changed files
with
176 additions
and
2 deletions.
There are no files selected for viewing
This file contains bidirectional Unicode text that may be interpreted or compiled differently than what appears below. To review, open the file in an editor that reveals hidden Unicode characters.
Learn more about bidirectional Unicode characters
This file contains bidirectional Unicode text that may be interpreted or compiled differently than what appears below. To review, open the file in an editor that reveals hidden Unicode characters.
Learn more about bidirectional Unicode characters
This file contains bidirectional Unicode text that may be interpreted or compiled differently than what appears below. To review, open the file in an editor that reveals hidden Unicode characters.
Learn more about bidirectional Unicode characters
This file contains bidirectional Unicode text that may be interpreted or compiled differently than what appears below. To review, open the file in an editor that reveals hidden Unicode characters.
Learn more about bidirectional Unicode characters
Original file line number | Diff line number | Diff line change |
---|---|---|
@@ -0,0 +1,118 @@ | ||
{-# LANGUAGE LambdaCase #-} | ||
{-# LANGUAGE NoImplicitPrelude #-} | ||
{-# LANGUAGE OverloadedStrings #-} | ||
{-# LANGUAGE QuasiQuotes #-} | ||
{-# LANGUAGE StrictData #-} | ||
{-# LANGUAGE TypeApplications #-} | ||
{-# LANGUAGE ViewPatterns #-} | ||
|
||
{-| | ||
Module : Headroom.Template.TemplateRef | ||
Description : Representation of reference to template file | ||
Copyright : (c) 2019-2021 Vaclav Svejcar | ||
License : BSD-3-Clause | ||
Maintainer : [email protected] | ||
Stability : experimental | ||
Portability : POSIX | ||
'TemplateRef' data type represents reference to template file, either local or | ||
remote, which can be later opened/downloaded and parsed into template. | ||
-} | ||
|
||
module Headroom.Template.TemplateRef | ||
( -- * Data Types | ||
TemplateSource(..) | ||
, TemplateRef(..) | ||
-- * Constructor Functions | ||
, mkTemplateRef | ||
-- * Error Types | ||
, TemplateRefError(..) | ||
) | ||
where | ||
|
||
import Data.String.Interpolate ( iii ) | ||
import Headroom.Data.EnumExtra ( textToEnum ) | ||
import Headroom.Data.Regex ( match | ||
, re | ||
) | ||
import Headroom.FileType.Types ( FileType ) | ||
import Headroom.Meta ( TemplateType ) | ||
import Headroom.Template ( Template(..) ) | ||
import Headroom.Types ( fromHeadroomError | ||
, toHeadroomError | ||
) | ||
import RIO | ||
import qualified RIO.Text as T | ||
import Text.URI ( URI(..) | ||
, mkURI | ||
) | ||
|
||
|
||
--------------------------------- DATA TYPES --------------------------------- | ||
|
||
-- | Source of the template (e.g. local file, URI address). | ||
data TemplateSource | ||
= LocalTemplateSource FilePath -- ^ template path on local file system | ||
| UriTemplateSource URI -- ^ remote template URI adress | ||
deriving (Eq, Show) | ||
|
||
|
||
-- | Reference to the template. Later this reference is used to get and parse | ||
-- the content of the actual template. | ||
data TemplateRef = TemplateRef | ||
{ trFileType :: FileType -- ^ type of files which this template is for | ||
, trSource :: TemplateSource -- ^ source of the template | ||
} | ||
deriving (Eq, Show) | ||
|
||
|
||
------------------------------ PUBLIC FUNCTIONS ------------------------------ | ||
|
||
-- | Creates a 'TemplateRef' from given text. If the raw text appears to be | ||
-- valid URL with either @http@ or @https@ as protocol, it considers it as | ||
-- 'UriTemplateSource', otherwise it creates 'LocalTemplateSource'. | ||
mkTemplateRef :: MonadThrow m | ||
=> Text -- ^ input text | ||
-> m TemplateRef -- ^ created 'TemplateRef' (or error) | ||
mkTemplateRef raw = do | ||
fileType <- extractFileType | ||
source <- detectSource | ||
pure TemplateRef { trFileType = fileType, trSource = source } | ||
where | ||
exts = templateExtensions @TemplateType | ||
detectSource = case match [re|(^\w+):\/\/|] raw of | ||
Just (_ : p : _) | ||
| p `elem` ["http", "https"] -> UriTemplateSource <$> mkURI raw | ||
| otherwise -> throwM $ UnsupportedUriProtocol p raw | ||
_ -> pure . LocalTemplateSource . T.unpack $ raw | ||
extractFileType = case match [re|(\w+)\.(\w+)$|] raw of | ||
Just (_ : (textToEnum -> (Just ft )) : e : _) | e `elem` exts -> pure ft | ||
_ -> throwM $ UnrecognizedTemplateName raw | ||
|
||
|
||
--------------------------------- ERROR TYPES -------------------------------- | ||
|
||
-- | Error related to template references. | ||
data TemplateRefError | ||
= UnrecognizedTemplateName Text -- ^ not a valid format for template name | ||
| UnsupportedUriProtocol Text Text -- ^ URI protocol not supported | ||
deriving (Eq, Show) | ||
|
||
|
||
instance Exception TemplateRefError where | ||
displayException = displayException' | ||
toException = toHeadroomError | ||
fromException = fromHeadroomError | ||
|
||
|
||
displayException' :: TemplateRefError -> String | ||
displayException' = \case | ||
UnrecognizedTemplateName raw -> [iii| | ||
Cannot extract file type and template type from path #{raw}. Please make | ||
sure that the path ends with '<FILE_TYPE>.<TEMPLATE_TYPE>', for example | ||
'/path/to/haskell.mustache'. | ||
|] | ||
UnsupportedUriProtocol protocol raw -> [iii| | ||
Protocol '#{protocol}' of in URI '#{raw}' is not supported. Make sure that | ||
you use either HTTP or HTTPS URIs. | ||
|] |
This file contains bidirectional Unicode text that may be interpreted or compiled differently than what appears below. To review, open the file in an editor that reveals hidden Unicode characters.
Learn more about bidirectional Unicode characters
This file contains bidirectional Unicode text that may be interpreted or compiled differently than what appears below. To review, open the file in an editor that reveals hidden Unicode characters.
Learn more about bidirectional Unicode characters
Original file line number | Diff line number | Diff line change |
---|---|---|
@@ -0,0 +1,44 @@ | ||
{-# LANGUAGE LambdaCase #-} | ||
{-# LANGUAGE NoImplicitPrelude #-} | ||
{-# LANGUAGE OverloadedStrings #-} | ||
{-# LANGUAGE QuasiQuotes #-} | ||
|
||
module Headroom.Template.TemplateRefSpec | ||
( spec | ||
) | ||
where | ||
|
||
|
||
import Headroom.FileType.Types ( FileType(..) ) | ||
import Headroom.Template.TemplateRef | ||
import RIO | ||
import Test.Hspec | ||
import Text.URI.QQ ( uri ) | ||
|
||
|
||
spec :: Spec | ||
spec = do | ||
|
||
describe "mkTemplateRef" $ do | ||
it "creates valid reference to local Haskell template" $ do | ||
let raw = "/path/to/some/haskell.mustache" | ||
expected = TemplateRef | ||
{ trFileType = Haskell | ||
, trSource = LocalTemplateSource "/path/to/some/haskell.mustache" | ||
} | ||
mkTemplateRef raw `shouldBe` Just expected | ||
|
||
it "creates valid reference to HTTP Haskell template" $ do | ||
let raw = "http://foo/haskell.mustache" | ||
expected = TemplateRef | ||
{ trFileType = Haskell | ||
, trSource = UriTemplateSource [uri|http://foo/haskell.mustache|] | ||
} | ||
mkTemplateRef raw `shouldBe` Just expected | ||
|
||
it "throws error if URI is valid but protocol is not supported" $ do | ||
let raw = "foo://foo/haskell.mustache" | ||
mkTemplateRef raw `shouldThrow` \case | ||
(UnsupportedUriProtocol _ _) -> True | ||
_ -> False | ||
|