{-# OPTIONS_GHC -Wall #-} module Text.Pandoc.Z.Columns where import Control.Lens ( Lens', Prism' ) import Text.Pandoc.Options(ReaderOptions(..), WriterOptions(..)) class HasColumns a where columns :: Lens' a Int instance HasColumns Int where columns :: Lens' Int Int columns = (Int -> f Int) -> Int -> f Int forall a. a -> a id class AsColumns a where _Columns :: Prism' a Int instance AsColumns Int where _Columns :: Prism' Int Int _Columns = p Int (f Int) -> p Int (f Int) forall a. a -> a id instance HasColumns ReaderOptions where columns :: Lens' ReaderOptions Int columns Int -> f Int f (ReaderOptions Extensions e Bool s Int c Int t [Text] i Set Text a Text g TrackChanges h Bool m) = (Int -> ReaderOptions) -> f Int -> f ReaderOptions forall a b. (a -> b) -> f a -> f b forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b fmap (\Int c' -> Extensions -> Bool -> Int -> Int -> [Text] -> Set Text -> Text -> TrackChanges -> Bool -> ReaderOptions ReaderOptions Extensions e Bool s Int c' Int t [Text] i Set Text a Text g TrackChanges h Bool m) (Int -> f Int f Int c) instance HasColumns WriterOptions where columns :: Lens' WriterOptions Int columns Int -> f Int f (WriterOptions Maybe (Template Text) a00 Context Text a01 Int a02 Bool a03 Bool a04 HTMLMathMethod a05 Bool a06 [Int] a07 Bool a08 Extensions a09 Bool a10 Int a11 WrapOption a12 Int a13 ObfuscationMethod a14 Text a15 CiteMethod a16 Bool a17 Maybe Int a18 TopLevelDivision a19 Bool a20 Maybe Style a21 Bool a22 Bool a23 Text a24 Maybe Text a25 [FilePath] a26 Bool a27 Int a28 PathTemplate a29 Int a30 Maybe FilePath a31 ReferenceLocation a32 SyntaxMap a33 Bool a34) = (Int -> WriterOptions) -> f Int -> f WriterOptions forall a b. (a -> b) -> f a -> f b forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b fmap (\Int a13' -> Maybe (Template Text) -> Context Text -> Int -> Bool -> Bool -> HTMLMathMethod -> Bool -> [Int] -> Bool -> Extensions -> Bool -> Int -> WrapOption -> Int -> ObfuscationMethod -> Text -> CiteMethod -> Bool -> Maybe Int -> TopLevelDivision -> Bool -> Maybe Style -> Bool -> Bool -> Text -> Maybe Text -> [FilePath] -> Bool -> Int -> PathTemplate -> Int -> Maybe FilePath -> ReferenceLocation -> SyntaxMap -> Bool -> WriterOptions WriterOptions Maybe (Template Text) a00 Context Text a01 Int a02 Bool a03 Bool a04 HTMLMathMethod a05 Bool a06 [Int] a07 Bool a08 Extensions a09 Bool a10 Int a11 WrapOption a12 Int a13' ObfuscationMethod a14 Text a15 CiteMethod a16 Bool a17 Maybe Int a18 TopLevelDivision a19 Bool a20 Maybe Style a21 Bool a22 Bool a23 Text a24 Maybe Text a25 [FilePath] a26 Bool a27 Int a28 PathTemplate a29 Int a30 Maybe FilePath a31 ReferenceLocation a32 SyntaxMap a33 Bool a34) (Int -> f Int f Int a13)