contravariant-extras-0.3.5.3/0000755000000000000000000000000014140163176014230 5ustar0000000000000000contravariant-extras-0.3.5.3/Setup.hs0000644000000000000000000000005614140163176015665 0ustar0000000000000000import Distribution.Simple main = defaultMain contravariant-extras-0.3.5.3/LICENSE0000644000000000000000000000204214140163176015233 0ustar0000000000000000Copyright (c) 2015, Nikita Volkov Permission is hereby granted, free of charge, to any person obtaining a copy of this software and associated documentation files (the "Software"), to deal in the Software without restriction, including without limitation the rights to use, copy, modify, merge, publish, distribute, sublicense, and/or sell copies of the Software, and to permit persons to whom the Software is furnished to do so, subject to the following conditions: The above copyright notice and this permission notice shall be included in all copies or substantial portions of the Software. THE SOFTWARE IS PROVIDED "AS IS", WITHOUT WARRANTY OF ANY KIND, EXPRESS OR IMPLIED, INCLUDING BUT NOT LIMITED TO THE WARRANTIES OF MERCHANTABILITY, FITNESS FOR A PARTICULAR PURPOSE AND NONINFRINGEMENT. IN NO EVENT SHALL THE AUTHORS OR COPYRIGHT HOLDERS BE LIABLE FOR ANY CLAIM, DAMAGES OR OTHER LIABILITY, WHETHER IN AN ACTION OF CONTRACT, TORT OR OTHERWISE, ARISING FROM, OUT OF OR IN CONNECTION WITH THE SOFTWARE OR THE USE OR OTHER DEALINGS IN THE SOFTWARE. contravariant-extras-0.3.5.3/contravariant-extras.cabal0000644000000000000000000000321014140163176021367 0ustar0000000000000000name: contravariant-extras version: 0.3.5.3 category: Control synopsis: Extras for the "contravariant" package homepage: https://github.com/nikita-volkov/contravariant-extras bug-reports: https://github.com/nikita-volkov/contravariant-extras/issues author: Nikita Volkov maintainer: Nikita Volkov copyright: (c) 2015, Nikita Volkov license: MIT license-file: LICENSE build-type: Simple cabal-version: >=1.10 source-repository head type: git location: git://github.com/nikita-volkov/contravariant-extras.git library hs-source-dirs: library default-extensions: Arrows, BangPatterns, ConstraintKinds, DataKinds, DefaultSignatures, DeriveDataTypeable, DeriveFoldable, DeriveFunctor, DeriveGeneric, DeriveTraversable, EmptyDataDecls, FlexibleContexts, FlexibleInstances, FunctionalDependencies, GADTs, GeneralizedNewtypeDeriving, LambdaCase, LiberalTypeSynonyms, MagicHash, MultiParamTypeClasses, MultiWayIf, NoImplicitPrelude, NoMonomorphismRestriction, OverloadedStrings, PatternGuards, ParallelListComp, QuasiQuotes, RankNTypes, RecordWildCards, ScopedTypeVariables, StandaloneDeriving, TemplateHaskell, TupleSections, TypeFamilies, TypeOperators, UnboxedTuples default-language: Haskell2010 exposed-modules: Contravariant.Extras Contravariant.Extras.Contrazip Contravariant.Extras.ContrazipLifting Contravariant.Extras.Op Contravariant.Extras.Op.Contrazip other-modules: Contravariant.Extras.Prelude Contravariant.Extras.TH build-depends: base >=4.10 && <5, contravariant >=1.3 && <2, template-haskell >=2.8 && <3, template-haskell-compat-v0208 >=0.1.7 && <2 contravariant-extras-0.3.5.3/library/0000755000000000000000000000000014140163176015674 5ustar0000000000000000contravariant-extras-0.3.5.3/library/Contravariant/0000755000000000000000000000000014140163176020507 5ustar0000000000000000contravariant-extras-0.3.5.3/library/Contravariant/Extras.hs0000644000000000000000000000301214140163176022305 0ustar0000000000000000module Contravariant.Extras ( {-| @contrazip@ functions of multiple arities. -} module Contravariant.Extras.Contrazip, {-| @contrazipLifting@ functions of multiple arities. -} module Contravariant.Extras.ContrazipLifting, (>*<), contramany, Supplied(..), ) where import Contravariant.Extras.Prelude hiding ((<>)) import Contravariant.Extras.Contrazip import Contravariant.Extras.ContrazipLifting import Data.Functor.Contravariant.Divisible import Data.Semigroup (Semigroup ((<>))) -- | -- An alias to 'divided'. {-# INLINE (>*<) #-} (>*<) :: Divisible f => f a -> f b -> f (a, b) (>*<) = divided contramany :: Decidable f => f a -> f [a] contramany f = loop where loop = choose chooser cons nil where chooser = \case head : tail -> Left (head, tail) _ -> Right () cons = divide id f loop nil = conquer -- | -- A combination of a divisible functor with some input for it. -- Allows to use the 'Monoid' API for composition. data Supplied divisible = forall input. Supplied (divisible input) input instance Divisible divisible => Semigroup (Supplied divisible) where Supplied divisible1 input1 <> Supplied divisible2 input2 = Supplied divisible3 input3 where divisible3 = divide id divisible1 divisible2 input3 = (input1, input2) instance Divisible divisible => Monoid (Supplied divisible) where mempty = Supplied conquer () mappend = (<>) contravariant-extras-0.3.5.3/library/Contravariant/Extras/0000755000000000000000000000000014140163176021755 5ustar0000000000000000contravariant-extras-0.3.5.3/library/Contravariant/Extras/ContrazipLifting.hs0000644000000000000000000000432114140163176025577 0ustar0000000000000000module Contravariant.Extras.ContrazipLifting where import Contravariant.Extras.Prelude import Contravariant.Extras.Contrazip import Data.Functor.Contravariant.Divisible import qualified Contravariant.Extras.TH as TH contrazipLifting2 :: Divisible f => (forall x. g x -> f x) -> g a1 -> g a2 -> f (a1, a2) contrazipLifting2 fn a b = contrazip2 (fn a) (fn b) contrazipLifting3 :: Divisible f => (forall x. g x -> f x) -> g a1 -> g a2 -> g a3 -> f (a1, a2, a3) contrazipLifting3 fn a b c = contrazip3 (fn a) (fn b) (fn c) contrazipLifting4 :: Divisible f => (forall x. g x -> f x) -> g a1 -> g a2 -> g a3 -> g a4 -> f (a1, a2, a3, a4) contrazipLifting4 fn a b c d = contrazip4 (fn a) (fn b) (fn c) (fn d) contrazipLifting5 :: Divisible f => (forall x. g x -> f x) -> g a1 -> g a2 -> g a3 -> g a4 -> g a5 -> f (a1, a2, a3, a4, a5) contrazipLifting5 fn a b c d e = contrazip5 (fn a) (fn b) (fn c) (fn d) (fn e) contrazipLifting6 :: Divisible f => (forall x. g x -> f x) -> g a1 -> g a2 -> g a3 -> g a4 -> g a5 -> g a6 -> f (a1, a2, a3, a4, a5, a6) contrazipLifting6 fn a b c d e f = contrazip6 (fn a) (fn b) (fn c) (fn d) (fn e) (fn f) contrazipLifting7 :: Divisible f => (forall x. g x -> f x) -> g a1 -> g a2 -> g a3 -> g a4 -> g a5 -> g a6 -> g a7 -> f (a1, a2, a3, a4, a5, a6, a7) contrazipLifting7 fn a b c d e f g = contrazip7 (fn a) (fn b) (fn c) (fn d) (fn e) (fn f) (fn g) contrazipLifting8 :: Divisible f => (forall x. g x -> f x) -> g a1 -> g a2 -> g a3 -> g a4 -> g a5 -> g a6 -> g a7 -> g a8 -> f (a1, a2, a3, a4, a5, a6, a7, a8) contrazipLifting8 fn a b c d e f g h = contrazip8 (fn a) (fn b) (fn c) (fn d) (fn e) (fn f) (fn g) (fn h) contrazipLifting9 :: Divisible f => (forall x. g x -> f x) -> g a1 -> g a2 -> g a3 -> g a4 -> g a5 -> g a6 -> g a7 -> g a8 -> g a9 -> f (a1, a2, a3, a4, a5, a6, a7, a8, a9) contrazipLifting9 fn a b c d e f g h i = contrazip9 (fn a) (fn b) (fn c) (fn d) (fn e) (fn f) (fn g) (fn h) (fn i) contrazipLifting10 :: Divisible f => (forall x. g x -> f x) -> g a1 -> g a2 -> g a3 -> g a4 -> g a5 -> g a6 -> g a7 -> g a8 -> g a9 -> g a10 -> f (a1, a2, a3, a4, a5, a6, a7, a8, a9, a10) contrazipLifting10 fn a b c d e f g h i j = contrazip10 (fn a) (fn b) (fn c) (fn d) (fn e) (fn f) (fn g) (fn h) (fn i) (fn j) contravariant-extras-0.3.5.3/library/Contravariant/Extras/Prelude.hs0000644000000000000000000000634714140163176023723 0ustar0000000000000000module Contravariant.Extras.Prelude ( module Exports, ) where -- base ------------------------- import Control.Applicative as Exports import Control.Arrow as Exports hiding (first, second) import Control.Category as Exports import Control.Concurrent as Exports import Control.Exception as Exports import Control.Monad as Exports hiding (fail, mapM_, sequence_, forM_, msum, mapM, sequence, forM) import Control.Monad.IO.Class as Exports import Control.Monad.Fail as Exports import Control.Monad.Fix as Exports hiding (fix) import Control.Monad.ST as Exports import Data.Bifunctor as Exports import Data.Bits as Exports import Data.Bool as Exports import Data.Char as Exports import Data.Coerce as Exports import Data.Complex as Exports import Data.Data as Exports import Data.Dynamic as Exports import Data.Either as Exports import Data.Fixed as Exports import Data.Foldable as Exports hiding (toList) import Data.Function as Exports hiding (id, (.)) import Data.Functor as Exports import Data.Functor.Contravariant as Exports import Data.Functor.Identity as Exports import Data.Int as Exports import Data.IORef as Exports import Data.Ix as Exports import Data.List as Exports hiding (sortOn, isSubsequenceOf, uncons, concat, foldr, foldl1, maximum, minimum, product, sum, all, and, any, concatMap, elem, foldl, foldr1, notElem, or, find, maximumBy, minimumBy, mapAccumL, mapAccumR, foldl') import Data.Maybe as Exports import Data.Monoid as Exports hiding (Last(..), First(..), (<>)) import Data.Ord as Exports import Data.Proxy as Exports import Data.Ratio as Exports import Data.Semigroup as Exports import Data.STRef as Exports import Data.String as Exports import Data.Traversable as Exports import Data.Tuple as Exports import Data.Unique as Exports import Data.Version as Exports import Data.Void as Exports import Data.Word as Exports import Debug.Trace as Exports import Foreign.ForeignPtr as Exports import Foreign.Ptr as Exports import Foreign.StablePtr as Exports import Foreign.Storable as Exports hiding (sizeOf, alignment) import GHC.Conc as Exports hiding (withMVar, threadWaitWriteSTM, threadWaitWrite, threadWaitReadSTM, threadWaitRead) import GHC.Exts as Exports (lazy, inline, sortWith, groupWith, IsList(..)) import GHC.Generics as Exports (Generic, Generic1) import GHC.IO.Exception as Exports import Numeric as Exports import Prelude as Exports hiding (fail, concat, foldr, mapM_, sequence_, foldl1, maximum, minimum, product, sum, all, and, any, concatMap, elem, foldl, foldr1, notElem, or, mapM, sequence, id, (.)) import System.Environment as Exports import System.Exit as Exports import System.IO as Exports import System.IO.Error as Exports import System.IO.Unsafe as Exports import System.Mem as Exports import System.Mem.StableName as Exports import System.Timeout as Exports import Text.ParserCombinators.ReadP as Exports (ReadP, ReadS, readP_to_S, readS_to_P) import Text.ParserCombinators.ReadPrec as Exports (ReadPrec, readPrec_to_P, readP_to_Prec, readPrec_to_S, readS_to_Prec) import Text.Printf as Exports (printf, hPrintf) import Text.Read as Exports (Read(..), readMaybe, readEither) import Unsafe.Coerce as Exports -- contravariant ------------------------- import Data.Functor.Contravariant as Exports import Data.Functor.Contravariant.Divisible as Exports contravariant-extras-0.3.5.3/library/Contravariant/Extras/Contrazip.hs0000644000000000000000000000123114140163176024257 0ustar0000000000000000-- | -- A berserk collection of @contrazip@ functions with arities of up to 42. -- -- Why 42? -- Well, naturally, because it's the answer to the ultimate question of life, -- the universe and everything. -- -- It's exported as a separate module from "Contravariant.Extras" -- only to not pollute its documentation. -- The "Contravariant.Extras" module still reexports this module, -- so you can simply import that only. -- module Contravariant.Extras.Contrazip where import Contravariant.Extras.Prelude import qualified Contravariant.Extras.TH as TH -- Generate the @contrazip@ functions: return (join (map (TH.contrazipDecs "contrazip") (reverse [2..42]))) contravariant-extras-0.3.5.3/library/Contravariant/Extras/Op.hs0000644000000000000000000000043014140163176022664 0ustar0000000000000000-- | -- This module exports functions specialized for the `Op` type. module Contravariant.Extras.Op ( -- | -- A berserk collection of @contrazip@ functions with arities of up to 42. module Contravariant.Extras.Op.Contrazip, ) where import Contravariant.Extras.Op.Contrazip contravariant-extras-0.3.5.3/library/Contravariant/Extras/TH.hs0000644000000000000000000001466714140163176022642 0ustar0000000000000000module Contravariant.Extras.TH ( opContrazipDecs, contrazipDecs, contrazipExp, ) where import Contravariant.Extras.Prelude import Data.Functor.Contravariant import Data.Functor.Contravariant.Divisible import Language.Haskell.TH.Syntax hiding (classP) import qualified TemplateHaskell.Compat.V0208 as Compat {-| Generates declarations in the spirit of the following: @ tuple3 :: Monoid a => Op a b1 -> Op a b2 -> Op a b3 -> Op a ( b1 , b2 , b3 ) tuple3 ( Op op1 ) ( Op op2 ) ( Op op3 ) = Op $ \( v1 , v2 , v3 ) -> mconcat [ op1 v1 , op2 v2 , op3 v3 ] @ -} opContrazipDecs :: String -> Int -> [ Dec ] opContrazipDecs baseName arity = [ signature , value ] where name = mkName (showString baseName (show arity)) signature = SigD name type_ where type_ = ForallT vars cxt type_ where vars = map (Compat.specifiedPlainTV . mkName) ("a" : bs) where bs = map b (enumFromTo 1 arity) where b index = showString "b" (show index) cxt = [ pred ] where pred = Compat.classP ''Monoid [ a ] where a = VarT (mkName "a") type_ = foldr appArrowT result params where appArrowT a b = AppT (AppT ArrowT a) b a = VarT (mkName "a") result = AppT (AppT (ConT ''Op) a) tuple where tuple = foldl AppT (TupleT arity) params where params = map param (enumFromTo 1 arity) where param index = VarT (mkName (showString "b" (show index))) params = map param (enumFromTo 1 arity) where param index = AppT (AppT (ConT ''Op) a) b where b = VarT (mkName (showString "b" (show index))) value = FunD name clauses where clauses = [ clause ] where clause = Clause pats body [] where pats = map pat (enumFromTo 1 arity) where pat index = Compat.conp 'Op pats where pats = [ VarP name ] where name = mkName (showString "op" (show index)) body = NormalB (AppE (ConE 'Op) lambda) where lambda = LamE pats exp where pats = [ TupP pats ] where pats = map pat (enumFromTo 1 arity) where pat index = VarP (mkName (showString "v" (show index))) exp = AppE (VarE 'mconcat) (ListE applications) where applications = map application (enumFromTo 1 arity) where application index = AppE (VarE opName) (VarE varName) where opName = mkName (showString "op" (show index)) varName = mkName (showString "v" (show index)) {-| Generates declarations in the spirit of the following: @ contrazip4 :: Divisible f => f a1 -> f a2 -> f a3 -> f a4 -> f ( a1 , a2 , a3 , a4 ) contrazip4 f1 f2 f3 f4 = divide $(TupleTH.splitTupleAt 4 1) f1 $ divide $(TupleTH.splitTupleAt 3 1) f2 $ divide $(TupleTH.splitTupleAt 2 1) f3 $ f4 @ -} contrazipDecs :: String -> Int -> [Dec] contrazipDecs baseName arity = [signature, value] where name = mkName (showString baseName (show arity)) signature = SigD name (contrazipType arity) value = FunD name clauses where clauses = [clause] where clause = Clause [] body [] where body = NormalB (contrazipExp arity) contrazipType :: Int -> Type contrazipType arity = ForallT vars cxt type_ where fName = mkName "f" aNames = map aName (enumFromTo 1 arity) where aName index = mkName (showString "a" (show index)) vars = map Compat.specifiedPlainTV (fName : aNames) cxt = [pred] where pred = Compat.classP ''Divisible [VarT fName] type_ = foldr appArrowT result params where appArrowT a b = AppT (AppT ArrowT a) b result = AppT (VarT fName) tuple where tuple = foldl AppT (TupleT arity) (map VarT aNames) params = map param aNames where param aName = AppT (VarT fName) (VarT aName) {-| Contrazip lambda expression of specified arity. Allows to create contrazip expressions of any arity: >>>:t $(return (contrazipExp 2)) $(return (contrazipExp 2)) :: Data.Functor.Contravariant.Divisible.Divisible f => f a1 -> f a2 -> f (a1, a2) -} contrazipExp :: Int -> Exp contrazipExp arity = SigE (LamE pats body) (contrazipType arity) where pats = map pat (enumFromTo 1 arity) where pat index = VarP name where name = mkName (showString "f" (show index)) body = exp arity where exp index = case index of 1 -> VarE (mkName (showString "f" (show arity))) _ -> foldl1 AppE [ VarE 'divide , splitTupleAtExp index 1 , VarE (mkName (showString "f" (show (arity - index + 1)))) , exp (pred index) ] splitTupleAtExp :: Int -> Int -> Exp splitTupleAtExp arity position = let nameByIndex index = Name (OccName ('_' : show index)) NameS names = enumFromTo 0 (pred arity) & map nameByIndex pats = names & map VarP pat = TupP pats exps = names & map VarE body = splitAt position exps & \ (a, b) -> Compat.tupE [Compat.tupE a, Compat.tupE b] in LamE [pat] body contravariant-extras-0.3.5.3/library/Contravariant/Extras/Op/0000755000000000000000000000000014140163176022333 5ustar0000000000000000contravariant-extras-0.3.5.3/library/Contravariant/Extras/Op/Contrazip.hs0000644000000000000000000000142314140163176024640 0ustar0000000000000000-- | -- A berserk collection of @contrazip@ functions with arities of up to 42, -- which are specialized to the 'Op' type, -- and jump thru fewer hoops than their 'Divisible'-based siblings. -- -- Why 42? -- Well, naturally, because it's the answer to the ultimate question of life, -- the universe and everything. -- -- It's exported as a separate module from "Contravariant.Extras.Op" -- only to not pollute its documentation. -- The "Contravariant.Extras.Op" module still reexports this module, -- so you can simply import that only. -- module Contravariant.Extras.Op.Contrazip where import Contravariant.Extras.Prelude import qualified Contravariant.Extras.TH as TH -- Generate the @contrazip@ functions: return (join (map (TH.opContrazipDecs "contrazip") (reverse [2..42])))