-- SPDX-FileCopyrightText: 2022 Oxhead Alpha -- SPDX-License-Identifier: LicenseRef-MIT-OA {-# OPTIONS_HADDOCK not-home #-} -- | Actual decision implementation for 'NumChildren'. module Morley.Michelson.Typed.ClassifiedInstr.Internal.Classifiers.NumChildren ( module Morley.Michelson.Typed.ClassifiedInstr.Internal.Classifiers.NumChildren ) where import Prelude hiding (Type) import Language.Haskell.TH (Type(..)) import Morley.Michelson.Typed.ClassifiedInstr.Internal.Types import Morley.Michelson.Typed.Instr (ExtInstr, Instr) -- | Given a list of constructor arguments, count how many of those arguments -- are instructions (i.e. 'Instr'), and return the corresponding classification. -- There is one unfortunate case of ambiguity in 'ExtInstr' we have to handle -- manually. If arguments mention 'Instr' indirectly, e.g. @Value' Instr t@ -- 'HasIndirectChildren' is returned instead. numChildren :: [Type] -> NumChildren numChildren args | any isExtInstr args = MayHaveChildren | any (isAppToInstr && not . isInstr) args = HasIndirectChildren | otherwise = case countInstrArgs args of 0 -> NoChildren 1 -> OneChild 2 -> TwoChildren x -> error $ "Instruction has too many children: " <> show x countInstrArgs :: [Type] -> Int countInstrArgs = go 0 where go !n = \case [] -> n (x:xs) | isInstr x -> go (n + 1) xs | otherwise -> go n xs isExtInstr :: Type -> Bool isExtInstr = \case AppT x _ -> isExtInstr x ConT n | n == ''ExtInstr -> True _ -> False isInstr :: Type -> Bool isInstr = \case AppT x _ -> isInstr x ConT n | n == ''Instr -> True _ -> False isAppToInstr :: Type -> Bool isAppToInstr = \case AppT x y -> isAppToInstr x || isAppToInstr y ConT n | n == ''Instr -> True _ -> False