{-# LANGUAGE NoImplicitPrelude #-}
{-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE TupleSections #-}
module Headroom.Ext.PureScript where
import Headroom.Configuration.Types ( CtHeaderConfig )
import Headroom.Ext.Haskell ( extractModuleName )
import Headroom.Types ( TemplateMeta(..) )
import Headroom.Variables ( mkVariables )
import Headroom.Variables.Types ( Variables(..) )
import RIO
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
"_purescript_module_name", ) (Text -> (Text, Text)) -> Maybe Text -> Maybe (Text, Text)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Text -> Maybe Text
extractModuleName Text
text]