{-# LANGUAGE FlexibleContexts #-}
{-# LANGUAGE TypeFamilies #-}
{-# LANGUAGE ViewPatterns #-}
module HscStats ( ppSourceStats ) where
import GhcPrelude
import Bag
import GHC.Hs
import Outputable
import SrcLoc
import Util
import Data.Char
ppSourceStats :: Bool -> Located (HsModule GhcPs) -> SDoc
ppSourceStats :: Bool -> Located (HsModule GhcPs) -> SDoc
ppSourceStats Bool
short (Located (HsModule GhcPs)
-> Located (SrcSpanLess (Located (HsModule GhcPs)))
forall a. HasSrcSpan a => a -> Located (SrcSpanLess a)
dL->L SrcSpan
_ (HsModule _ exports imports ldecls _ _))
= (if Bool
short then [SDoc] -> SDoc
hcat else [SDoc] -> SDoc
vcat)
(((String, Int) -> SDoc) -> [(String, Int)] -> [SDoc]
forall a b. (a -> b) -> [a] -> [b]
map (String, Int) -> SDoc
pp_val
[(String
"ExportAll ", Int
export_all),
(String
"ExportDecls ", Int
export_ds),
(String
"ExportModules ", Int
export_ms),
(String
"Imports ", Int
imp_no),
(String
" ImpSafe ", Int
imp_safe),
(String
" ImpQual ", Int
imp_qual),
(String
" ImpAs ", Int
imp_as),
(String
" ImpAll ", Int
imp_all),
(String
" ImpPartial ", Int
imp_partial),
(String
" ImpHiding ", Int
imp_hiding),
(String
"FixityDecls ", Int
fixity_sigs),
(String
"DefaultDecls ", Int
default_ds),
(String
"TypeDecls ", Int
type_ds),
(String
"DataDecls ", Int
data_ds),
(String
"NewTypeDecls ", Int
newt_ds),
(String
"TypeFamilyDecls ", Int
type_fam_ds),
(String
"DataConstrs ", Int
data_constrs),
(String
"DataDerivings ", Int
data_derivs),
(String
"ClassDecls ", Int
class_ds),
(String
"ClassMethods ", Int
class_method_ds),
(String
"DefaultMethods ", Int
default_method_ds),
(String
"InstDecls ", Int
inst_ds),
(String
"InstMethods ", Int
inst_method_ds),
(String
"InstType ", Int
inst_type_ds),
(String
"InstData ", Int
inst_data_ds),
(String
"TypeSigs ", Int
bind_tys),
(String
"ClassOpSigs ", Int
generic_sigs),
(String
"ValBinds ", Int
val_bind_ds),
(String
"FunBinds ", Int
fn_bind_ds),
(String
"PatSynBinds ", Int
patsyn_ds),
(String
"InlineMeths ", Int
method_inlines),
(String
"InlineBinds ", Int
bind_inlines),
(String
"SpecialisedMeths ", Int
method_specs),
(String
"SpecialisedBinds ", Int
bind_specs)
])
where
decls :: [HsDecl GhcPs]
decls = (LHsDecl GhcPs -> HsDecl GhcPs)
-> [LHsDecl GhcPs] -> [HsDecl GhcPs]
forall a b. (a -> b) -> [a] -> [b]
map LHsDecl GhcPs -> HsDecl GhcPs
forall a. HasSrcSpan a => a -> SrcSpanLess a
unLoc [LHsDecl GhcPs]
ldecls
pp_val :: (String, Int) -> SDoc
pp_val (String
_, Int
0) = SDoc
empty
pp_val (String
str, Int
n)
| Bool -> Bool
not Bool
short = [SDoc] -> SDoc
hcat [String -> SDoc
text String
str, Int -> SDoc
int Int
n]
| Bool
otherwise = [SDoc] -> SDoc
hcat [String -> SDoc
text (String -> String
trim String
str), SDoc
equals, Int -> SDoc
int Int
n, SDoc
semi]
trim :: String -> String
trim String
ls = (Char -> Bool) -> String -> String
forall a. (a -> Bool) -> [a] -> [a]
takeWhile (Bool -> Bool
not(Bool -> Bool) -> (Char -> Bool) -> Char -> Bool
forall b c a. (b -> c) -> (a -> b) -> a -> c
.Char -> Bool
isSpace) ((Char -> Bool) -> String -> String
forall a. (a -> Bool) -> [a] -> [a]
dropWhile Char -> Bool
isSpace String
ls)
(Int
fixity_sigs, Int
bind_tys, Int
bind_specs, Int
bind_inlines, Int
generic_sigs)
= [Sig GhcPs] -> (Int, Int, Int, Int, Int)
forall pass. [Sig pass] -> (Int, Int, Int, Int, Int)
count_sigs [Sig GhcPs
d | SigD XSigD GhcPs
_ Sig GhcPs
d <- [HsDecl GhcPs]
decls]
tycl_decls :: [TyClDecl GhcPs]
tycl_decls = [TyClDecl GhcPs
d | TyClD XTyClD GhcPs
_ TyClDecl GhcPs
d <- [HsDecl GhcPs]
decls]
(Int
class_ds, Int
type_ds, Int
data_ds, Int
newt_ds, Int
type_fam_ds) =
[TyClDecl GhcPs] -> (Int, Int, Int, Int, Int)
forall pass. [TyClDecl pass] -> (Int, Int, Int, Int, Int)
countTyClDecls [TyClDecl GhcPs]
tycl_decls
inst_decls :: [InstDecl GhcPs]
inst_decls = [InstDecl GhcPs
d | InstD XInstD GhcPs
_ InstDecl GhcPs
d <- [HsDecl GhcPs]
decls]
inst_ds :: Int
inst_ds = [InstDecl GhcPs] -> Int
forall (t :: * -> *) a. Foldable t => t a -> Int
length [InstDecl GhcPs]
inst_decls
default_ds :: Int
default_ds = (HsDecl GhcPs -> Bool) -> [HsDecl GhcPs] -> Int
forall a. (a -> Bool) -> [a] -> Int
count (\ HsDecl GhcPs
x -> case HsDecl GhcPs
x of { DefD{} -> Bool
True; HsDecl GhcPs
_ -> Bool
False}) [HsDecl GhcPs]
decls
val_decls :: [HsBind GhcPs]
val_decls = [HsBind GhcPs
d | ValD XValD GhcPs
_ HsBind GhcPs
d <- [HsDecl GhcPs]
decls]
real_exports :: [LIE GhcPs]
real_exports = case Maybe (Located [LIE GhcPs])
exports of { Maybe (Located [LIE GhcPs])
Nothing -> []; Just (Located [LIE GhcPs] -> Located (SrcSpanLess (Located [LIE GhcPs]))
forall a. HasSrcSpan a => a -> Located (SrcSpanLess a)
dL->L SrcSpan
_ SrcSpanLess (Located [LIE GhcPs])
es) -> [LIE GhcPs]
SrcSpanLess (Located [LIE GhcPs])
es }
n_exports :: Int
n_exports = [LIE GhcPs] -> Int
forall (t :: * -> *) a. Foldable t => t a -> Int
length [LIE GhcPs]
real_exports
export_ms :: Int
export_ms = (LIE GhcPs -> Bool) -> [LIE GhcPs] -> Int
forall a. (a -> Bool) -> [a] -> Int
count (\ LIE GhcPs
e -> case LIE GhcPs -> SrcSpanLess (LIE GhcPs)
forall a. HasSrcSpan a => a -> SrcSpanLess a
unLoc LIE GhcPs
e of { IEModuleContents{} -> Bool
True
; SrcSpanLess (LIE GhcPs)
_ -> Bool
False})
[LIE GhcPs]
real_exports
export_ds :: Int
export_ds = Int
n_exports Int -> Int -> Int
forall a. Num a => a -> a -> a
- Int
export_ms
export_all :: Int
export_all = case Maybe (Located [LIE GhcPs])
exports of { Maybe (Located [LIE GhcPs])
Nothing -> Int
1; Maybe (Located [LIE GhcPs])
_ -> Int
0 }
(Int
val_bind_ds, Int
fn_bind_ds, Int
patsyn_ds)
= [(Int, Int, Int)] -> (Int, Int, Int)
sum3 ((HsBind GhcPs -> (Int, Int, Int))
-> [HsBind GhcPs] -> [(Int, Int, Int)]
forall a b. (a -> b) -> [a] -> [b]
map HsBind GhcPs -> (Int, Int, Int)
forall idL a b c idR p.
(HasSrcSpan (XRec idL Pat), Num a, Num b, Num c,
Outputable (HsBindLR idL idR),
SrcSpanLess (XRec idL Pat) ~ Pat p) =>
HsBindLR idL idR -> (a, b, c)
count_bind [HsBind GhcPs]
val_decls)
(Int
imp_no, Int
imp_safe, Int
imp_qual, Int
imp_as, Int
imp_all, Int
imp_partial, Int
imp_hiding)
= [(Int, Int, Int, Int, Int, Int, Int)]
-> (Int, Int, Int, Int, Int, Int, Int)
sum7 ((LImportDecl GhcPs -> (Int, Int, Int, Int, Int, Int, Int))
-> [LImportDecl GhcPs] -> [(Int, Int, Int, Int, Int, Int, Int)]
forall a b. (a -> b) -> [a] -> [b]
map LImportDecl GhcPs -> (Int, Int, Int, Int, Int, Int, Int)
forall a pass.
(HasSrcSpan a, SrcSpanLess a ~ ImportDecl pass,
XXImportDecl pass ~ NoExtCon) =>
a -> (Int, Int, Int, Int, Int, Int, Int)
import_info [LImportDecl GhcPs]
imports)
(Int
data_constrs, Int
data_derivs)
= [(Int, Int)] -> (Int, Int)
sum2 ((TyClDecl GhcPs -> (Int, Int)) -> [TyClDecl GhcPs] -> [(Int, Int)]
forall a b. (a -> b) -> [a] -> [b]
map TyClDecl GhcPs -> (Int, Int)
forall pass. TyClDecl pass -> (Int, Int)
data_info [TyClDecl GhcPs]
tycl_decls)
(Int
class_method_ds, Int
default_method_ds)
= [(Int, Int)] -> (Int, Int)
sum2 ((TyClDecl GhcPs -> (Int, Int)) -> [TyClDecl GhcPs] -> [(Int, Int)]
forall a b. (a -> b) -> [a] -> [b]
map TyClDecl GhcPs -> (Int, Int)
forall idL p.
(HasSrcSpan (XRec idL Pat), Outputable (HsBindLR idL idL),
SrcSpanLess (XRec idL Pat) ~ Pat p) =>
TyClDecl idL -> (Int, Int)
class_info [TyClDecl GhcPs]
tycl_decls)
(Int
inst_method_ds, Int
method_specs, Int
method_inlines, Int
inst_type_ds, Int
inst_data_ds)
= [(Int, Int, Int, Int, Int)] -> (Int, Int, Int, Int, Int)
sum5 ((InstDecl GhcPs -> (Int, Int, Int, Int, Int))
-> [InstDecl GhcPs] -> [(Int, Int, Int, Int, Int)]
forall a b. (a -> b) -> [a] -> [b]
map InstDecl GhcPs -> (Int, Int, Int, Int, Int)
forall pass p.
(HasSrcSpan (XRec pass Pat), Outputable (HsBindLR pass pass),
XXClsInstDecl pass ~ NoExtCon, SrcSpanLess (XRec pass Pat) ~ Pat p,
XXInstDecl pass ~ NoExtCon) =>
InstDecl pass -> (Int, Int, Int, Int, Int)
inst_info [InstDecl GhcPs]
inst_decls)
count_bind :: HsBindLR idL idR -> (a, b, c)
count_bind (PatBind { pat_lhs :: forall idL idR. HsBindLR idL idR -> LPat idL
pat_lhs = (XRec idL Pat -> Located (SrcSpanLess (XRec idL Pat))
forall a. HasSrcSpan a => a -> Located (SrcSpanLess a)
dL->L SrcSpan
_ (VarPat{})) }) = (a
1,b
0,c
0)
count_bind (PatBind {}) = (a
0,b
1,c
0)
count_bind (FunBind {}) = (a
0,b
1,c
0)
count_bind (PatSynBind {}) = (a
0,b
0,c
1)
count_bind HsBindLR idL idR
b = String -> SDoc -> (a, b, c)
forall a. HasCallStack => String -> SDoc -> a
pprPanic String
"count_bind: Unhandled binder" (HsBindLR idL idR -> SDoc
forall a. Outputable a => a -> SDoc
ppr HsBindLR idL idR
b)
count_sigs :: [Sig pass] -> (Int, Int, Int, Int, Int)
count_sigs [Sig pass]
sigs = [(Int, Int, Int, Int, Int)] -> (Int, Int, Int, Int, Int)
sum5 ((Sig pass -> (Int, Int, Int, Int, Int))
-> [Sig pass] -> [(Int, Int, Int, Int, Int)]
forall a b. (a -> b) -> [a] -> [b]
map Sig pass -> (Int, Int, Int, Int, Int)
forall a b c d e pass.
(Num a, Num b, Num c, Num d, Num e) =>
Sig pass -> (a, b, c, d, e)
sig_info [Sig pass]
sigs)
sig_info :: Sig pass -> (a, b, c, d, e)
sig_info (FixSig {}) = (a
1,b
0,c
0,d
0,e
0)
sig_info (TypeSig {}) = (a
0,b
1,c
0,d
0,e
0)
sig_info (SpecSig {}) = (a
0,b
0,c
1,d
0,e
0)
sig_info (InlineSig {}) = (a
0,b
0,c
0,d
1,e
0)
sig_info (ClassOpSig {}) = (a
0,b
0,c
0,d
0,e
1)
sig_info Sig pass
_ = (a
0,b
0,c
0,d
0,e
0)
import_info :: a -> (Int, Int, Int, Int, Int, Int, Int)
import_info (a -> Located (SrcSpanLess a)
forall a. HasSrcSpan a => a -> Located (SrcSpanLess a)
dL->L SrcSpan
_ (ImportDecl { ideclSafe = safe, ideclQualified = qual
, ideclAs = as, ideclHiding = spec }))
= (Int, Int, Int, Int, Int, Int, Int)
-> (Int, Int, Int, Int, Int, Int, Int)
-> (Int, Int, Int, Int, Int, Int, Int)
add7 (Int
1, Bool -> Int
forall p. Num p => Bool -> p
safe_info Bool
safe, ImportDeclQualifiedStyle -> Int
forall p. Num p => ImportDeclQualifiedStyle -> p
qual_info ImportDeclQualifiedStyle
qual, Maybe (Located ModuleName) -> Int
forall p a. Num p => Maybe a -> p
as_info Maybe (Located ModuleName)
as, Int
0,Int
0,Int
0) (Maybe (Bool, Located [LIE pass])
-> (Int, Int, Int, Int, Int, Int, Int)
forall a b c d e f g b.
(Num a, Num b, Num c, Num d, Num e, Num f, Num g) =>
Maybe (Bool, b) -> (a, b, c, d, e, f, g)
spec_info Maybe (Bool, Located [LIE pass])
spec)
import_info (a -> Located (SrcSpanLess a)
forall a. HasSrcSpan a => a -> Located (SrcSpanLess a)
dL->L SrcSpan
_ (XImportDecl nec)) = NoExtCon -> (Int, Int, Int, Int, Int, Int, Int)
forall a. NoExtCon -> a
noExtCon XXImportDecl pass
NoExtCon
nec
import_info a
_ = String -> (Int, Int, Int, Int, Int, Int, Int)
forall a. String -> a
panic String
" import_info: Impossible Match"
safe_info :: Bool -> p
safe_info Bool
False = p
0
safe_info Bool
True = p
1
qual_info :: ImportDeclQualifiedStyle -> p
qual_info ImportDeclQualifiedStyle
NotQualified = p
0
qual_info ImportDeclQualifiedStyle
_ = p
1
as_info :: Maybe a -> p
as_info Maybe a
Nothing = p
0
as_info (Just a
_) = p
1
spec_info :: Maybe (Bool, b) -> (a, b, c, d, e, f, g)
spec_info Maybe (Bool, b)
Nothing = (a
0,b
0,c
0,d
0,e
1,f
0,g
0)
spec_info (Just (Bool
False, b
_)) = (a
0,b
0,c
0,d
0,e
0,f
1,g
0)
spec_info (Just (Bool
True, b
_)) = (a
0,b
0,c
0,d
0,e
0,f
0,g
1)
data_info :: TyClDecl pass -> (Int, Int)
data_info (DataDecl { tcdDataDefn :: forall pass. TyClDecl pass -> HsDataDefn pass
tcdDataDefn = HsDataDefn
{ dd_cons :: forall pass. HsDataDefn pass -> [LConDecl pass]
dd_cons = [LConDecl pass]
cs
, dd_derivs :: forall pass. HsDataDefn pass -> HsDeriving pass
dd_derivs = (HsDeriving pass -> Located (SrcSpanLess (HsDeriving pass))
forall a. HasSrcSpan a => a -> Located (SrcSpanLess a)
dL->L SrcSpan
_ SrcSpanLess (HsDeriving pass)
derivs)}})
= ( [LConDecl pass] -> Int
forall (t :: * -> *) a. Foldable t => t a -> Int
length [LConDecl pass]
cs
, (Int -> LHsDerivingClause pass -> Int)
-> Int -> [LHsDerivingClause pass] -> Int
forall (t :: * -> *) b a.
Foldable t =>
(b -> a -> b) -> b -> t a -> b
foldl' (\Int
s LHsDerivingClause pass
dc -> GenLocated SrcSpan [LHsSigType pass] -> Int
forall (t :: * -> *) a. Foldable t => t a -> Int
length (HsDerivingClause pass -> GenLocated SrcSpan [LHsSigType pass]
forall pass. HsDerivingClause pass -> Located [LHsSigType pass]
deriv_clause_tys (HsDerivingClause pass -> GenLocated SrcSpan [LHsSigType pass])
-> HsDerivingClause pass -> GenLocated SrcSpan [LHsSigType pass]
forall a b. (a -> b) -> a -> b
$ LHsDerivingClause pass -> SrcSpanLess (LHsDerivingClause pass)
forall a. HasSrcSpan a => a -> SrcSpanLess a
unLoc LHsDerivingClause pass
dc) Int -> Int -> Int
forall a. Num a => a -> a -> a
+ Int
s)
Int
0 [LHsDerivingClause pass]
SrcSpanLess (HsDeriving pass)
derivs )
data_info TyClDecl pass
_ = (Int
0,Int
0)
class_info :: TyClDecl idL -> (Int, Int)
class_info decl :: TyClDecl idL
decl@(ClassDecl {})
= (Int
classops, (Int, Int, Int) -> Int
addpr ([(Int, Int, Int)] -> (Int, Int, Int)
sum3 ((HsBindLR idL idL -> (Int, Int, Int))
-> [HsBindLR idL idL] -> [(Int, Int, Int)]
forall a b. (a -> b) -> [a] -> [b]
map HsBindLR idL idL -> (Int, Int, Int)
forall idL a b c idR p.
(HasSrcSpan (XRec idL Pat), Num a, Num b, Num c,
Outputable (HsBindLR idL idR),
SrcSpanLess (XRec idL Pat) ~ Pat p) =>
HsBindLR idL idR -> (a, b, c)
count_bind [HsBindLR idL idL]
methods)))
where
methods :: [HsBindLR idL idL]
methods = (LHsBindLR idL idL -> HsBindLR idL idL)
-> [LHsBindLR idL idL] -> [HsBindLR idL idL]
forall a b. (a -> b) -> [a] -> [b]
map LHsBindLR idL idL -> HsBindLR idL idL
forall a. HasSrcSpan a => a -> SrcSpanLess a
unLoc ([LHsBindLR idL idL] -> [HsBindLR idL idL])
-> [LHsBindLR idL idL] -> [HsBindLR idL idL]
forall a b. (a -> b) -> a -> b
$ Bag (LHsBindLR idL idL) -> [LHsBindLR idL idL]
forall a. Bag a -> [a]
bagToList (TyClDecl idL -> Bag (LHsBindLR idL idL)
forall pass. TyClDecl pass -> LHsBinds pass
tcdMeths TyClDecl idL
decl)
(Int
_, Int
classops, Int
_, Int
_, Int
_) = [Sig idL] -> (Int, Int, Int, Int, Int)
forall pass. [Sig pass] -> (Int, Int, Int, Int, Int)
count_sigs ((LSig idL -> Sig idL) -> [LSig idL] -> [Sig idL]
forall a b. (a -> b) -> [a] -> [b]
map LSig idL -> Sig idL
forall a. HasSrcSpan a => a -> SrcSpanLess a
unLoc (TyClDecl idL -> [LSig idL]
forall pass. TyClDecl pass -> [LSig pass]
tcdSigs TyClDecl idL
decl))
class_info TyClDecl idL
_ = (Int
0,Int
0)
inst_info :: InstDecl pass -> (Int, Int, Int, Int, Int)
inst_info (TyFamInstD {}) = (Int
0,Int
0,Int
0,Int
1,Int
0)
inst_info (DataFamInstD {}) = (Int
0,Int
0,Int
0,Int
0,Int
1)
inst_info (ClsInstD { cid_inst :: forall pass. InstDecl pass -> ClsInstDecl pass
cid_inst = ClsInstDecl {cid_binds :: forall pass. ClsInstDecl pass -> LHsBinds pass
cid_binds = LHsBinds pass
inst_meths
, cid_sigs :: forall pass. ClsInstDecl pass -> [LSig pass]
cid_sigs = [LSig pass]
inst_sigs
, cid_tyfam_insts :: forall pass. ClsInstDecl pass -> [LTyFamInstDecl pass]
cid_tyfam_insts = [LTyFamInstDecl pass]
ats
, cid_datafam_insts :: forall pass. ClsInstDecl pass -> [LDataFamInstDecl pass]
cid_datafam_insts = [LDataFamInstDecl pass]
adts } })
= case [Sig pass] -> (Int, Int, Int, Int, Int)
forall pass. [Sig pass] -> (Int, Int, Int, Int, Int)
count_sigs ((LSig pass -> Sig pass) -> [LSig pass] -> [Sig pass]
forall a b. (a -> b) -> [a] -> [b]
map LSig pass -> Sig pass
forall a. HasSrcSpan a => a -> SrcSpanLess a
unLoc [LSig pass]
inst_sigs) of
(Int
_,Int
_,Int
ss,Int
is,Int
_) ->
((Int, Int, Int) -> Int
addpr ([(Int, Int, Int)] -> (Int, Int, Int)
sum3 ((HsBindLR pass pass -> (Int, Int, Int))
-> [HsBindLR pass pass] -> [(Int, Int, Int)]
forall a b. (a -> b) -> [a] -> [b]
map HsBindLR pass pass -> (Int, Int, Int)
forall idL a b c idR p.
(HasSrcSpan (XRec idL Pat), Num a, Num b, Num c,
Outputable (HsBindLR idL idR),
SrcSpanLess (XRec idL Pat) ~ Pat p) =>
HsBindLR idL idR -> (a, b, c)
count_bind [HsBindLR pass pass]
methods)),
Int
ss, Int
is, [LTyFamInstDecl pass] -> Int
forall (t :: * -> *) a. Foldable t => t a -> Int
length [LTyFamInstDecl pass]
ats, [LDataFamInstDecl pass] -> Int
forall (t :: * -> *) a. Foldable t => t a -> Int
length [LDataFamInstDecl pass]
adts)
where
methods :: [HsBindLR pass pass]
methods = (LHsBindLR pass pass -> HsBindLR pass pass)
-> [LHsBindLR pass pass] -> [HsBindLR pass pass]
forall a b. (a -> b) -> [a] -> [b]
map LHsBindLR pass pass -> HsBindLR pass pass
forall a. HasSrcSpan a => a -> SrcSpanLess a
unLoc ([LHsBindLR pass pass] -> [HsBindLR pass pass])
-> [LHsBindLR pass pass] -> [HsBindLR pass pass]
forall a b. (a -> b) -> a -> b
$ LHsBinds pass -> [LHsBindLR pass pass]
forall a. Bag a -> [a]
bagToList LHsBinds pass
inst_meths
inst_info (ClsInstD XClsInstD pass
_ (XClsInstDecl XXClsInstDecl pass
nec)) = NoExtCon -> (Int, Int, Int, Int, Int)
forall a. NoExtCon -> a
noExtCon XXClsInstDecl pass
NoExtCon
nec
inst_info (XInstDecl XXInstDecl pass
nec) = NoExtCon -> (Int, Int, Int, Int, Int)
forall a. NoExtCon -> a
noExtCon XXInstDecl pass
NoExtCon
nec
addpr :: (Int,Int,Int) -> Int
sum2 :: [(Int, Int)] -> (Int, Int)
sum3 :: [(Int, Int, Int)] -> (Int, Int, Int)
sum5 :: [(Int, Int, Int, Int, Int)] -> (Int, Int, Int, Int, Int)
sum7 :: [(Int, Int, Int, Int, Int, Int, Int)] -> (Int, Int, Int, Int, Int, Int, Int)
add7 :: (Int, Int, Int, Int, Int, Int, Int) -> (Int, Int, Int, Int, Int, Int, Int)
-> (Int, Int, Int, Int, Int, Int, Int)
addpr :: (Int, Int, Int) -> Int
addpr (Int
x,Int
y,Int
z) = Int
xInt -> Int -> Int
forall a. Num a => a -> a -> a
+Int
yInt -> Int -> Int
forall a. Num a => a -> a -> a
+Int
z
sum2 :: [(Int, Int)] -> (Int, Int)
sum2 = ((Int, Int) -> (Int, Int) -> (Int, Int))
-> (Int, Int) -> [(Int, Int)] -> (Int, Int)
forall (t :: * -> *) a b.
Foldable t =>
(a -> b -> b) -> b -> t a -> b
foldr (Int, Int) -> (Int, Int) -> (Int, Int)
forall a b. (Num a, Num b) => (a, b) -> (a, b) -> (a, b)
add2 (Int
0,Int
0)
where
add2 :: (a, b) -> (a, b) -> (a, b)
add2 (a
x1,b
x2) (a
y1,b
y2) = (a
x1a -> a -> a
forall a. Num a => a -> a -> a
+a
y1,b
x2b -> b -> b
forall a. Num a => a -> a -> a
+b
y2)
sum3 :: [(Int, Int, Int)] -> (Int, Int, Int)
sum3 = ((Int, Int, Int) -> (Int, Int, Int) -> (Int, Int, Int))
-> (Int, Int, Int) -> [(Int, Int, Int)] -> (Int, Int, Int)
forall (t :: * -> *) a b.
Foldable t =>
(a -> b -> b) -> b -> t a -> b
foldr (Int, Int, Int) -> (Int, Int, Int) -> (Int, Int, Int)
forall a b c.
(Num a, Num b, Num c) =>
(a, b, c) -> (a, b, c) -> (a, b, c)
add3 (Int
0,Int
0,Int
0)
where
add3 :: (a, b, c) -> (a, b, c) -> (a, b, c)
add3 (a
x1,b
x2,c
x3) (a
y1,b
y2,c
y3) = (a
x1a -> a -> a
forall a. Num a => a -> a -> a
+a
y1,b
x2b -> b -> b
forall a. Num a => a -> a -> a
+b
y2,c
x3c -> c -> c
forall a. Num a => a -> a -> a
+c
y3)
sum5 :: [(Int, Int, Int, Int, Int)] -> (Int, Int, Int, Int, Int)
sum5 = ((Int, Int, Int, Int, Int)
-> (Int, Int, Int, Int, Int) -> (Int, Int, Int, Int, Int))
-> (Int, Int, Int, Int, Int)
-> [(Int, Int, Int, Int, Int)]
-> (Int, Int, Int, Int, Int)
forall (t :: * -> *) a b.
Foldable t =>
(a -> b -> b) -> b -> t a -> b
foldr (Int, Int, Int, Int, Int)
-> (Int, Int, Int, Int, Int) -> (Int, Int, Int, Int, Int)
forall a b c d e.
(Num a, Num b, Num c, Num d, Num e) =>
(a, b, c, d, e) -> (a, b, c, d, e) -> (a, b, c, d, e)
add5 (Int
0,Int
0,Int
0,Int
0,Int
0)
where
add5 :: (a, b, c, d, e) -> (a, b, c, d, e) -> (a, b, c, d, e)
add5 (a
x1,b
x2,c
x3,d
x4,e
x5) (a
y1,b
y2,c
y3,d
y4,e
y5) = (a
x1a -> a -> a
forall a. Num a => a -> a -> a
+a
y1,b
x2b -> b -> b
forall a. Num a => a -> a -> a
+b
y2,c
x3c -> c -> c
forall a. Num a => a -> a -> a
+c
y3,d
x4d -> d -> d
forall a. Num a => a -> a -> a
+d
y4,e
x5e -> e -> e
forall a. Num a => a -> a -> a
+e
y5)
sum7 :: [(Int, Int, Int, Int, Int, Int, Int)]
-> (Int, Int, Int, Int, Int, Int, Int)
sum7 = ((Int, Int, Int, Int, Int, Int, Int)
-> (Int, Int, Int, Int, Int, Int, Int)
-> (Int, Int, Int, Int, Int, Int, Int))
-> (Int, Int, Int, Int, Int, Int, Int)
-> [(Int, Int, Int, Int, Int, Int, Int)]
-> (Int, Int, Int, Int, Int, Int, Int)
forall (t :: * -> *) a b.
Foldable t =>
(a -> b -> b) -> b -> t a -> b
foldr (Int, Int, Int, Int, Int, Int, Int)
-> (Int, Int, Int, Int, Int, Int, Int)
-> (Int, Int, Int, Int, Int, Int, Int)
add7 (Int
0,Int
0,Int
0,Int
0,Int
0,Int
0,Int
0)
add7 :: (Int, Int, Int, Int, Int, Int, Int)
-> (Int, Int, Int, Int, Int, Int, Int)
-> (Int, Int, Int, Int, Int, Int, Int)
add7 (Int
x1,Int
x2,Int
x3,Int
x4,Int
x5,Int
x6,Int
x7) (Int
y1,Int
y2,Int
y3,Int
y4,Int
y5,Int
y6,Int
y7) = (Int
x1Int -> Int -> Int
forall a. Num a => a -> a -> a
+Int
y1,Int
x2Int -> Int -> Int
forall a. Num a => a -> a -> a
+Int
y2,Int
x3Int -> Int -> Int
forall a. Num a => a -> a -> a
+Int
y3,Int
x4Int -> Int -> Int
forall a. Num a => a -> a -> a
+Int
y4,Int
x5Int -> Int -> Int
forall a. Num a => a -> a -> a
+Int
y5,Int
x6Int -> Int -> Int
forall a. Num a => a -> a -> a
+Int
y6,Int
x7Int -> Int -> Int
forall a. Num a => a -> a -> a
+Int
y7)