{-# LANGUAGE NoImplicitPrelude #-}
{-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE QuasiQuotes #-}
{-# LANGUAGE TupleSections #-}
module Headroom.Ext.Java
( extractVariables
, extractPackageName
)
where
import Headroom.Configuration.Types ( CtHeaderConfig )
import Headroom.Data.Regex ( match
, re
)
import Headroom.Data.TextExtra ( toLines )
import Headroom.Types ( TemplateMeta(..) )
import Headroom.Variables ( mkVariables )
import Headroom.Variables.Types ( Variables(..) )
import RIO
import RIO.Lens ( ix )
extractPackageName :: Text
-> Maybe Text
= [Text] -> Maybe Text
go ([Text] -> Maybe Text) -> (Text -> [Text]) -> Text -> Maybe Text
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Text -> [Text]
toLines
where
go :: [Text] -> Maybe Text
go [] = Maybe Text
forall a. Maybe a
Nothing
go (Text
x : [Text]
xs) = Maybe Text -> ([Text] -> Maybe Text) -> Maybe [Text] -> Maybe Text
forall b a. b -> (a -> b) -> Maybe a -> b
maybe ([Text] -> Maybe Text
go [Text]
xs) ([Text] -> Getting (First Text) [Text] Text -> Maybe Text
forall s a. s -> Getting (First a) s a -> Maybe a
^? Index [Text] -> Traversal' [Text] (IxValue [Text])
forall m. Ixed m => Index m -> Traversal' m (IxValue m)
ix Index [Text]
1) (Regex -> Text -> Maybe [Text]
match [re|^package (.*);$|] Text
x)
extractVariables :: CtHeaderConfig
-> Maybe TemplateMeta
-> Maybe (Int, Int)
-> Text
-> Variables
CtHeaderConfig
_ Maybe TemplateMeta
_ Maybe (Int, Int)
_ Text
text = ([(Text, Text)] -> Variables
mkVariables ([(Text, Text)] -> Variables)
-> ([Maybe (Text, Text)] -> [(Text, Text)])
-> [Maybe (Text, Text)]
-> Variables
forall b c a. (b -> c) -> (a -> b) -> a -> c
. [Maybe (Text, Text)] -> [(Text, Text)]
forall a. [Maybe a] -> [a]
catMaybes)
[(Text
"_java_package_name", ) (Text -> (Text, Text)) -> Maybe Text -> Maybe (Text, Text)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Text -> Maybe Text
extractPackageName Text
text]