contravariant-extras-0.3.5.1/0000755000000000000000000000000013601652700014223 5ustar0000000000000000contravariant-extras-0.3.5.1/Setup.hs0000644000000000000000000000005613601652700015660 0ustar0000000000000000import Distribution.Simple main = defaultMain contravariant-extras-0.3.5.1/LICENSE0000644000000000000000000000204213601652700015226 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.1/contravariant-extras.cabal0000644000000000000000000000321013601652700021362 0ustar0000000000000000name: contravariant-extras version: 0.3.5.1 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.TH Contravariant.Extras.Prelude build-depends: base >=4.10 && <5, contravariant >=1.3 && <2, template-haskell >=2.8 && <3, template-haskell-compat-v0208 >=0.1.2 && <2 contravariant-extras-0.3.5.1/library/0000755000000000000000000000000013601652700015667 5ustar0000000000000000contravariant-extras-0.3.5.1/library/Contravariant/0000755000000000000000000000000013601652700020502 5ustar0000000000000000contravariant-extras-0.3.5.1/library/Contravariant/Extras.hs0000644000000000000000000000301213601652700022300 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.1/library/Contravariant/Extras/0000755000000000000000000000000013601652700021750 5ustar0000000000000000contravariant-extras-0.3.5.1/library/Contravariant/Extras/ContrazipLifting.hs0000644000000000000000000000432113601652700025572 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.1/library/Contravariant/Extras/Prelude.hs0000644000000000000000000000634713601652700023716 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.1/library/Contravariant/Extras/Contrazip.hs0000644000000000000000000000124213601652700024254 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.divisibleContrazipDecs "contrazip") (reverse [2..42]))) contravariant-extras-0.3.5.1/library/Contravariant/Extras/Op.hs0000644000000000000000000000043013601652700022657 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.1/library/Contravariant/Extras/TH.hs0000644000000000000000000001615513601652700022627 0ustar0000000000000000{-# LANGUAGE CPP #-} module Contravariant.Extras.TH 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 like 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 (PlainTV . mkName) ("a" : bs) where bs = map b (enumFromTo 1 arity) where b index = showString "b" (show index) cxt = [ pred ] where pred = 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 = 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 -- @ divisibleContrazipDecs :: String -> Int -> [Dec] divisibleContrazipDecs baseName arity = [signature, value] where name = mkName (showString baseName (show arity)) signature = SigD name type_ where type_ = ForallT vars cxt type_ where fName = mkName "f" aNames = map aName (enumFromTo 1 arity) where aName index = mkName (showString "a" (show index)) vars = map PlainTV (fName : aNames) cxt = [pred] where pred = 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) value = FunD name clauses where clauses = [clause] where clause = Clause pats body [] where pats = map pat (enumFromTo 1 arity) where pat index = VarP name where name = mkName (showString "f" (show index)) body = NormalB (exp arity) where exp index = case index of 1 -> VarE (mkName (showString "f" (show arity))) _ -> foldl1 AppE [ VarE 'divide , splitTupleAtE index 1 , VarE (mkName (showString "f" (show (arity - index + 1)))) , exp (pred index) ] splitTupleAtE :: Int -> Int -> Exp splitTupleAtE 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 classP :: Name -> [Type] -> Pred #if MIN_VERSION_template_haskell(2,10,0) classP n tl = foldl AppT (ConT n) tl #else classP = ClassP #endif contravariant-extras-0.3.5.1/library/Contravariant/Extras/Op/0000755000000000000000000000000013601652700022326 5ustar0000000000000000contravariant-extras-0.3.5.1/library/Contravariant/Extras/Op/Contrazip.hs0000644000000000000000000000142313601652700024633 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])))