{-# LANGUAGE FlexibleInstances #-}
{-# LANGUAGE GeneralizedNewtypeDeriving #-}
{-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE TemplateHaskell #-}
{-# OPTIONS_GHC -fno-warn-missing-fields #-}

-- | This module is the twin brother of module Text.Cassius.
-- The difference is that these parsers preserv the given order of attributes and mixin blocks.
--
-- > let bams = [cassiusMixin|
-- >               bam1:bam2
-- >               ^{bins}
-- >               bam3:bam4
-- >            |] :: Mixin
-- >     bins = [cassiusMixin|
-- >               bin1:bin2
-- >            |] :: Mixin
-- >  in renderCss ([Text.Ordered.lucius|foo{bar1:bar2;^{bams};bar3:bar4;}|] undefined)
-- > "foo{bar1:bar2;bam1:bam2;bin1:bin2;bam3:bam4;bar3:bar4}"

module Text.Cassius.Ordered
    ( -- * Datatypes
      Css
    , CssUrl
      -- * Type class
    , ToCss (..)
      -- * Rendering
    , renderCss
    , renderCssUrl
      -- * Parsing
    , cassius
    , cassiusFile
    , cassiusFileDebug
    , cassiusFileReload
      -- ** Mixims
    , cassiusMixin
    , Mixin
      -- * ToCss instances
      -- ** Color
    , Color (..)
    , colorRed
    , colorBlack
      -- ** Size
    , mkSize
    , AbsoluteUnit (..)
    , AbsoluteSize (..)
    , absoluteSize
    , EmSize (..)
    , ExSize (..)
    , PercentageSize (..)
    , percentageSize
    , PixelSize (..)
      -- * Internal
    , cassiusUsedIdentifiers
    ) where

import Language.Haskell.TH.Quote (QuasiQuoter (..))
import Language.Haskell.TH.Syntax
import Text.IndentToBrace (i2b)
import Text.Internal.Cassius (i2bMixin)
import Text.Internal.Css
import Text.Internal.CssCommon
import Text.Internal.Lucius (parseTopLevels)
import qualified Text.Lucius.Ordered as Lucius.Ordered
import Text.Shakespeare (VarType)
import Text.Shakespeare.Base

-- | @since 2.0.30
cassius :: QuasiQuoter
cassius :: QuasiQuoter
cassius = QuasiQuoter :: (String -> Q Exp)
-> (String -> Q Pat)
-> (String -> Q Type)
-> (String -> Q [Dec])
-> QuasiQuoter
QuasiQuoter { quoteExp :: String -> Q Exp
quoteExp = QuasiQuoter -> String -> Q Exp
quoteExp QuasiQuoter
Lucius.Ordered.lucius (String -> Q Exp) -> (String -> String) -> String -> Q Exp
forall b c a. (b -> c) -> (a -> b) -> a -> c
. String -> String
i2b }

-- | @since 2.0.30
cassiusFile :: FilePath -> Q Exp
cassiusFile :: String -> Q Exp
cassiusFile String
fp = do
    String
contents <- String -> Q String
readFileRecompileQ String
fp
    QuasiQuoter -> String -> Q Exp
quoteExp QuasiQuoter
cassius String
contents

-- | @since 2.0.30
cassiusFileDebug :: FilePath -> Q Exp
cassiusFileDebug :: String -> Q Exp
cassiusFileDebug = Bool -> Q Exp -> Parser [TopLevel 'Unresolved] -> String -> Q Exp
cssFileDebug Bool
True [|parseTopLevels Ordered|] (Order -> Parser [TopLevel 'Unresolved]
parseTopLevels Order
Ordered)

-- | @since 2.0.30
cassiusFileReload :: FilePath -> Q Exp
cassiusFileReload :: String -> Q Exp
cassiusFileReload = String -> Q Exp
cassiusFileDebug

-- | Determine which identifiers are used by the given template, useful for
-- creating systems like yesod devel.
-- | @since 2.0.30
cassiusUsedIdentifiers :: String -> [(Deref, VarType)]
cassiusUsedIdentifiers :: String -> [(Deref, VarType)]
cassiusUsedIdentifiers = Bool
-> Parser [TopLevel 'Unresolved] -> String -> [(Deref, VarType)]
cssUsedIdentifiers Bool
True (Order -> Parser [TopLevel 'Unresolved]
parseTopLevels Order
Ordered)

-- | Create a mixin with Cassius syntax.
--
-- | @since 2.0.30
cassiusMixin :: QuasiQuoter
cassiusMixin :: QuasiQuoter
cassiusMixin = QuasiQuoter :: (String -> Q Exp)
-> (String -> Q Pat)
-> (String -> Q Type)
-> (String -> Q [Dec])
-> QuasiQuoter
QuasiQuoter
    { quoteExp :: String -> Q Exp
quoteExp = QuasiQuoter -> String -> Q Exp
quoteExp QuasiQuoter
Lucius.Ordered.luciusMixin (String -> Q Exp) -> (String -> String) -> String -> Q Exp
forall b c a. (b -> c) -> (a -> b) -> a -> c
. String -> String
i2bMixin
    }