commit 611b65f (2025-10-08 10:55:50 -0400) Torsten Scholak: wip
Tagged as: ai strategy economics cost-analysis
Posted on Aug 21, 2025
31 min read
WIPThis is a computational essay about enterprise AI strategy and the commoditization trap. It uses code to model the economics of AI outsourcing and internal capability development. Code snippets are executable examples that demonstrate the concepts discussed.
Below some boilerplate code for this module that you can skip over if you just want to read the essay:
{-# LANGUAGE DataKinds #-}
{-# LANGUAGE DeriveGeneric #-}
{-# LANGUAGE DerivingStrategies #-}
{-# LANGUAGE GeneralizedNewtypeDeriving #-}
{-# LANGUAGE KindSignatures #-}
{-# LANGUAGE NumericUnderscores #-}
{-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE RecordWildCards #-}
{-# LANGUAGE TypeSynonymInstances #-}
{-# LANGUAGE FlexibleInstances #-}
{-# LANGUAGE MultiParamTypeClasses #-}
{-# LANGUAGE ScopedTypeVariables #-}
module OutsourcedAI where
import GHC.Generics (Generic)
import Text.Printf (printf)
import Data.Ratio (Ratio, (%))
import Quantity
Quantity (Q, magnitude, units),
(
unQ,Unit,
convert,
one,
inUnit,
scalar,
qCeiling,
qFromIntegral,
second,
hour,
month,
year,
dollar,
unit,*@),
(./),
(
qExp,
qScale,
qClamp,
)import Data.Ord (clamp)
import Graphics.Rendering.Chart.Easy
import Graphics.Rendering.Chart.Backend.Diagrams
import Control.Monad (forM_)
type Scalar = Double
-- import System.Directory (getTemporaryDirectory)
-- import System.FilePath ((</>))
-- import qualified Data.Text.IO as T
The most dangerous assumption in enterprise AI strategy is that you must choose between competing on cost or on differentiation. This false dichotomy misses how competitive advantage actually works in the AI era. In reality, predictable unit cost and pricing power are themselves differentiators once you control your AI stack.
We are comparing two deployment strategies for enterprise use:
data Deployment =
External -- Use third-party APIs (OpenAI, Anthropic, etc.)
| Internal -- Build and serve models in-house
deriving (Eq, Show)
Our primary goal is a simple, clear economic comparison:
Which deployment strategy delivers greater long-term profitability?
To answer this, we use a simple macroeconomic model that balances two key quantities:
-- | Expected revenue (from successfully completed AI tasks)
type Revenue = Quantity Scalar
-- | Operational cost (to perform AI tasks)
type Cost = Quantity Scalar
A task is an abstract unit of AI work (e.g., a completed chat interaction, a document processed, typical of your business use case):
task :: Unit
= unit "task" task
For our macroeconomic treatment of platform AI economics, we make simplifying assumptions:
TaskUnit
.
Complexity, structure, and purpose are absorbed into this abstract
type.The key economic differentiator between strategies is how the success rate and the cost structure evolve over time. We model this evolution explicitly as a time series:
type SuccessRate = Scalar -- dimensionless, between 0 and 1 (0% to 100%)
type DataAdvantage = Scalar -- dimensionless, between 0 and 1 (0% to 100%)
type Throughput = Quantity Scalar -- tasks per time unit
-- | Usage is the number of tasks per time unit
type Usage = Quantity Scalar
data State = State
deployment :: !Deployment -- ^ current deployment strategy
{ usage :: !Usage -- ^ current usage in tasks per time unit
, successRate :: !SuccessRate -- ^ current success rate (0 to 1)
, dataAdvantage :: !DataAdvantage -- ^ current data advantage (0 to 1)
, }
A deployment strategy is a function that cleanly decouples decision-making from the simulation dynamics. This allows us to write strategies without touching the core engine.
type DeploymentStrategy = Exogenous -> State -> Deployment
data Exogenous = Exogenous
-- external
{ externalCost :: !Cost -- ^ $ / task for external API
externalSuccessRateCeiling :: !SuccessRate -- ^ success rate for external API (at asymptote)
, externalImprovementRate :: !(Quantity Scalar) -- ^ improvement rate for external API (1 / time unit)
,
-- internal cost structure
internalFixedCost :: !Cost -- ^ internal fixed cost / time unit (R&D, baseline infra)
, internalVariableCost :: !Cost -- ^ cost / time unit / active node
, internalThroughput :: !Throughput -- ^ tasks / time unit / node
, internalBaseNodes :: !(Quantity Scalar) -- ^ minimum nodes kept warm
, internalSuccessRateCeiling :: !SuccessRate -- ^ success rate for internal model (at asymptote)
, internalLearningRate :: !(Quantity Scalar) -- ^ demand increase due to learning effects (1 / time unit)
, internalDataAccumulationRate :: !(Quantity Scalar) -- ^ data accumulation rate (1 / task)
,
-- demand side
marketCapacity :: !Usage -- ^ maximum market size in tasks / time unit
, qualitySensitivity :: !(Quantity Scalar) -- ^ demand increase due to quality improvements (1 / time unit)
, qualitySuccessRateThreshold :: !SuccessRate -- ^ success rate threshold for demand increase
, profitabilitySensitivity :: !(Quantity Scalar) -- ^ demand increase due to profitability improvements (task / $ / time unit)
, profitabilityMarginCap :: !(Quantity Scalar) -- ^ cap on margin effect to prevent runaway growth (1 / time unit)
, crowdingOutPressure :: !(Quantity Scalar) -- ^ demand reduction due to market saturation (1 / time unit)
,
-- cost drift
driftExternalCost :: !(Quantity Scalar) -- ^ external cost drift (1 / time unit)
, driftInternalFixedCost :: !(Quantity Scalar) -- ^ internal fixed cost drift (1 / time unit)
, driftInternalVariableCost :: !(Quantity Scalar) -- ^ internal variable cost drift (1 / time unit)
,
-- financial
discountPerStep :: !Scalar -- ^ discount rate for NPV calculations
, }
-- | Expected revenue per successful task.
-- Calibrate to a concrete use case.
-- Here: piecewise toy curve: 0 until 0.6, then linear; bonus after 0.9.
expectedRevenue :: SuccessRate -> Revenue
= (retention successRate) *@ dollar ./ task
expectedRevenue successRate where
| sr < 0.6 = 0
retention sr | sr < 0.9 = 5 * (sr - 0.6)
| otherwise = 1.5 + 2 * (sr - 0.9)
Demand increase due to quality improvements models the idea that better outcomes directly attract more usage. When the success rate rises above a baseline threshold, customers are more likely to adopt the service, stick with it, and recommend it, which drives future demand. Below the threshold, improvements may have little effect on adoption, as the product is still perceived as unreliable.
-- | Demand increase due to quality improvements
qualityDrivenDemand :: Exogenous -> SuccessRate -> Quantity Scalar
Exogenous{..} successRate =
qualityDrivenDemand - qualitySuccessRateThreshold) `qScale` qualitySensitivity (successRate
The exogenous qualitySensitivity
constant determines how
strongly usage grows as success rate improves beyond the
qualitySuccessRateThreshold
. Above this threshold (set near
the point where the product delivers consistently acceptable results,
i.e. 0.6
to 0.7
for probabilistic AI systems)
each 0.1
improvement in success rate typically yields an
additional 1 to 3 percent annual usage growth if
qualitySensitivity
is in the 0.1
to
0.3
range.
Usage change due to profitability captures the idea that healthy unit economics create both the means and the incentive to scale. When each unit of work generates a positive margin, a business can reinvest in marketing, infrastructure, and customer acquisition, which increases future usage. Conversely, negative margins force contraction, either by actively limiting work to high-value cases or through customer churn as prices rise or quality drops. In this way, profitability directly influences the rate at which demand grows or shrinks over time.
-- | Demand change due to profitability
profitabilityDrivenDemand :: Exogenous -> Usage -> Deployment -> SuccessRate -> Quantity Scalar
@Exogenous{..} usage deployment successRate =
profitabilityDrivenDemand exogenous- profitabilityMarginCap, profitabilityMarginCap) $ profitabilitySensitivity * margin
qClamp (where
= case deployment of
cost External -> externalCost
Internal -> internalCost exogenous usage / processingCapacity exogenous usage
= expectedRevenue successRate - cost margin
The exogenous profitabilitySensitivity
constant controls
how strongly margins translate into usage growth: if one step represents
a year, values in the 0.05
to 0.2
range for
USD 0.01 per task margin are typical. The
profitabilityMarginCap
constant should be low enough (e.g.,
0.1
for plus/minus 10 percent per year) to avoid
implausibly large swings from a single year's profitability spike. With
0.1
, extreme margins (e.g., USD 0.05 per task) still only
change usage 10 percent per year, which is reasonable for a mature
enterprise platform.
Demand reduction due to market saturation reflects the slowdown that occurs as usage approaches the total addressable capacity of the market. Early growth is easy when there are many untapped customers, but as adoption nears the market's limit, each additional unit of demand is harder to capture. This "crowding out" effect models the natural tapering of growth under saturation, where further expansion requires disproportionate effort and yields diminishing returns.
-- | Demand reduction due to market saturation
crowdingOut :: Exogenous -> Usage -> Quantity Scalar
Exogenous{..} usage =
crowdingOut * usage / marketCapacity crowdingOutPressure
The exogenous crowdingOutPressure
constant sets the
strength of this drag: a value near 1.0
ensures that growth
falls to zero as we hit marketCapacity
, producing a
realistic plateau. Smaller values let growth continue even past nominal
capacity, and the plateau will be softer. Choosing
marketCapacity
so that the initial usage is only a few
percent of capacity ensures saturation effects appear later in the
simulation, not immediately.
Putting this all together, we can define the usage update rule as follows:
-- | Usage update
updateUsage ::
Duration ->
Exogenous ->
State ->
Usage
@Exogenous {..} State {..} =
updateUsage dt exogenouslet
= qualityDrivenDemand exogenous successRate
q = profitabilityDrivenDemand exogenous usage deployment successRate
p = crowdingOut exogenous usage
c = qExp $ (q + p - c) * dt
factor in qClamp (0 *@ task ./ second, marketCapacity) $ factor `qScale` usage
We distinguish two deployment modes:
External (exogenous improvement).: Vendors do
not learn from our traffic. Their models improve through global
R&D, independent of our usage. We model this as a drift toward an
asymptote externalSuccessRateCeiling
, closing a fixed
fraction of the remaining gap each time step to model diminishing
returns. The externalImprovementRate
controls how quickly
this happens. This leads to a rapid initial improvement that slows as we
approach the vendor's success rate. There is no
dataAdvantage
term here since external vendors do not learn
from our data.
Internal (data flywheel).: In-house deployment
compounds proprietary signal. Each step, completed tasks contribute to a
dataAdvantage
. The more successful tasks are served, the
more proprietary data is accumulated. This data advantage then
accelerates improvements in success rate, with diminishing returns as we
approach the upper bound 1
. This captures the slow start,
rapid mid-phase, and natural plateau characteristic of internal learning
curves.
-- | Learning update
updateLearning ::
Duration ->
Exogenous ->
State ->
SuccessRate, DataAdvantage)
(Exogenous{..} State{..} =
updateLearning dt case deployment of
External ->
-- asymptotic drift toward vendor's success rate
let improve = 1 - qExp (- externalImprovementRate * dt)
= clamp (0,1) $ successRate + improve * (externalSuccessRateCeiling - successRate)
successRate' in (successRate', dataAdvantage) -- no data advantage growth
Internal ->
-- saturating growth driven by accumulated advantage
let delta = clamp (0,1) $ scalar (internalDataAccumulationRate * usage * dt) * successRate
= clamp (0,1) $ dataAdvantage + (1 - dataAdvantage) * delta
dataAdvantage' = 1 - qExp (- internalLearningRate * dt)
improve = clamp (0,1) $ successRate + improve * dataAdvantage' * (internalSuccessRateCeiling - successRate)
successRate' in (successRate', dataAdvantage')
-- | Update the exogenous parameters over time (due to cost reductions)
updateExogenous ::
Duration ->
Exogenous ->
Exogenous
@Exogenous {..} =
updateExogenous dt exogenouslet fec = qExp (driftExternalCost * dt)
= qExp (driftInternalFixedCost * dt)
fifc = qExp (driftInternalVariableCost * dt)
fivc in exogenous
= fec `qScale` externalCost
{ externalCost = fifc `qScale` internalFixedCost
, internalFixedCost = fivc `qScale` internalVariableCost
, internalVariableCost }
type Time = Quantity Scalar
type Duration = Quantity Scalar
data Clock = Clock { now :: !Time, dt :: !Duration }
-- | Update the state by one time step
step :: Clock -> Exogenous -> State -> (Exogenous, State)
Clock{..} exogenous state@State{..} =
step let
= updateExogenous dt exogenous
exogenous' = updateUsage dt exogenous' state
usage' = updateLearning dt exogenous' state
(successRate', dataAdvantage') = state { usage = usage', successRate = successRate', dataAdvantage = dataAdvantage' }
state' in (exogenous', state')
alwaysInternal :: DeploymentStrategy
alwaysExternal,= External
alwaysExternal _ _ = Internal
alwaysInternal _ _
-- | Break-even strategy: start external; switch to internal when (rev - c_int) > (rev - c_ext) + eps AND usage above threshold
-- Problem: you need to know the future to do this optimally
-- Problem: you may never break even if no investment in internal capabilities
breakEven :: DeploymentStrategy
@Exogenous{..} State{..}
breakEven exogenous| usage < thresholdUsage = External
| marginInternal > marginExternal + epsilonPerTime = Internal
| otherwise = External
where
= 1.0e7 *@ task ./ second -- minimum usage to consider
thresholdUsage = 0.01 *@ dollar ./ task -- minimum margin improvement to switch
epsilonPerTask = epsilonPerTask * usage
epsilonPerTime = expectedRevenue successRate * usage
revenue = revenue - internalCost exogenous usage
marginInternal = revenue - externalCost * usage
marginExternal
-- total number of nodes needed to handle the given usage
totalNodes :: Exogenous -> Usage -> Quantity Scalar
Exogenous {..} usage =
totalNodes let neededNodes = qFromIntegral . qCeiling $ usage / internalThroughput
in max internalBaseNodes neededNodes
-- total processing capacity in tasks per time unit
processingCapacity :: Exogenous -> Usage -> Quantity Scalar
@Exogenous{..} usage =
processingCapacity exogenous* totalNodes exogenous usage
internalThroughput
-- internal cost per time unit
internalCost :: Exogenous -> Usage -> Cost
@Exogenous {..} usage =
internalCost exogenous+ totalNodes exogenous usage * internalVariableCost
internalFixedCost
baseState :: State
= State {
baseState = External,
deployment = 5.0e8 *@ task ./ second,
usage = 0.65,
successRate = 0
dataAdvantage
}
baseExogenousFor :: Duration -> Exogenous
=
baseExogenousFor dt Exogenous
= 0.02 *@ dollar ./ task,
{ externalCost = 0.75,
externalSuccessRateCeiling = 0.01 *@ one ./ month,
externalImprovementRate = 120_000 *@ dollar ./ month,
internalFixedCost = 1.0e2 *@ dollar ./ hour ./ node,
internalVariableCost = 1.0e6 *@ task ./ second ./ node,
internalThroughput = 1 *@ node,
internalBaseNodes = 0.90,
internalSuccessRateCeiling = 0.05 *@ one ./ month,
internalLearningRate = 0.01 *@ one ./ task,
internalDataAccumulationRate = 1.0e10 *@ task ./ second,
marketCapacity = 0.2 *@ one ./ month,
qualitySensitivity = 0.6,
qualitySuccessRateThreshold = 5 *@ task ./ dollar ./ month,
profitabilitySensitivity = 0.1 *@ one ./ month,
profitabilityMarginCap = 0.5 *@ one ./ month,
crowdingOutPressure = log 0.99 *@ one ./ month,
driftExternalCost = log 1.005 *@ one ./ month,
driftInternalFixedCost = log 0.995 *@ one ./ month,
driftInternalVariableCost = let annualDiscountRate = 0.08 in exp (-annualDiscountRate * (inUnit dt year))
discountPerStep
}
node :: Unit
= unit "node" node
data Row = Row
time :: !Time,
{ deploymentBeforeStep :: !Deployment,
-- | tasks / time
usageBeforeStep :: !Usage,
-- | 0..1
successRateBeforeStep :: !SuccessRate,
-- | 0..1
dataAdvantageBeforeStep :: !DataAdvantage,
-- | \$ / task
unitCostPerTask :: !(Quantity Scalar),
-- | \$ / time
revenueRate :: !(Quantity Scalar),
-- | \$ / time
costRate :: !(Quantity Scalar),
-- | \$ / time
profitRate :: !(Quantity Scalar),
-- | \$ over this dt
cashFlowForPeriod :: !(Quantity Scalar),
-- | discounted $
presentValueOfCashFlowForPeriod :: !(Quantity Scalar),
-- | discounted $, cumulative
cumulativePresentValueOfCashFlow :: !(Quantity Scalar)
}deriving (Show)
simulate ::
DeploymentStrategy ->
Clock ->
Exogenous ->
State ->
Row]
[=
simulate strategy clock0 exogenous0 state0 0 *@ dollar) clock0 1 exogenous0 state0
go (where
go ::
Quantity Scalar ->
Clock ->
Scalar ->
Exogenous ->
State ->
Row]
[@Clock {..} discountMultiplierBeforeStep exogenousBeforeStep stateBeforeStep =
go cumulativePresentValueBeforeStep clockBeforeSteplet -- decide deployment for this step. state is still "before step"
= strategy exogenousBeforeStep stateBeforeStep
deploymentBeforeStep = stateBeforeStep {deployment = deploymentBeforeStep}
stateBeforeStep'
-- snapshot some "before step" observables we want to emit in the Row
= now
time = usage stateBeforeStep'
usageBeforeStep = successRate stateBeforeStep'
successRateBeforeStep = dataAdvantage stateBeforeStep'
dataAdvantageBeforeStep
-- per-time economics for this step
= expectedRevenue successRateBeforeStep * usageBeforeStep
revenueRate = case deploymentBeforeStep of
costRate External -> externalCost exogenousBeforeStep * usageBeforeStep
Internal -> internalCost exogenousBeforeStep usageBeforeStep
= revenueRate - costRate
profitRate
-- cash flow and NPV for this step
= profitRate * dt
cashFlowForPeriod = (1 - discountPerStep exogenousBeforeStep) / (- log (discountPerStep exogenousBeforeStep))
averageDiscountWithinStep = (discountMultiplierBeforeStep * averageDiscountWithinStep) `qScale` cashFlowForPeriod
presentValueOfCashFlowForPeriod = cumulativePresentValueBeforeStep + presentValueOfCashFlowForPeriod
cumulativePresentValueOfCashFlow
-- unit cost snapshot for this step
= case deploymentBeforeStep of
unitCostPerTask External -> externalCost exogenousBeforeStep
Internal ->
internalCost exogenousBeforeStep usageBeforeStep/ processingCapacity exogenousBeforeStep usageBeforeStep
= Row {..}
row
= step clockBeforeStep exogenousBeforeStep stateBeforeStep'
(exogenousNextStep, stateNextStep) = clockBeforeStep {now = now + dt}
clockNextStep = discountMultiplierBeforeStep * discountPerStep exogenousBeforeStep
discountMultiplierNextStep in row : go cumulativePresentValueOfCashFlow clockNextStep discountMultiplierNextStep exogenousNextStep stateNextStep
pointsSuccessRateBeforeStep :: [Row] -> [(Scalar, Scalar)]
=
pointsSuccessRateBeforeStep map (\Row{..} -> (inUnit time month, successRateBeforeStep))
pointsUnitCostPerTask :: [Row] -> [(Scalar, Scalar)]
=
pointsUnitCostPerTask map (\Row{..} -> (inUnit time month, inUnit unitCostPerTask (dollar ./ task)))
pointsCumulativePresentValueOfCashFlow :: [Row] -> [(Scalar, Scalar)]
=
pointsCumulativePresentValueOfCashFlow map (\Row{..} -> (inUnit time month, inUnit cumulativePresentValueOfCashFlow dollar))
main :: IO ()
= do
main let strategies =
"alwaysExternal", alwaysExternal)
[ ("alwaysInternal", alwaysInternal)
, ("breakEven", breakEven)
, (
]
= Clock { now = 0 *@ month, dt = 1 *@ month }
monthlyClock
= 60
horizonMonths
= baseExogenousFor (dt monthlyClock)
baseExogenous
=
takeH (name, strat) take horizonMonths (simulate strat monthlyClock baseExogenous baseState))
(name,
= map takeH strategies
runs
= FileOptions { _fo_size = (800, 600), _fo_format = SVG, _fo_fonts = loadSansSerifFonts }
fileOptions
-- Success rate plot
"success_rate.svg" $ do
toFile fileOptions .= "Success Rate over Time"
layout_title . laxis_title .= "Month"
layout_x_axis . laxis_title .= "Success rate"
layout_y_axis $ \(name, rows) ->
forM_ runs
plot (line name [pointsSuccessRateBeforeStep rows])
-- Unit cost plot
"unit_cost_per_task.svg" $ do
toFile fileOptions .= "Unit Cost per Task ($)"
layout_title . laxis_title .= "Month"
layout_x_axis . laxis_title .= "USD per task"
layout_y_axis $ \(name, rows) ->
forM_ runs
plot (line name [pointsUnitCostPerTask rows])
-- Cumulative NPV plot
"cumulative_present_value_of_profit.svg" $ do
toFile fileOptions .= "Cumulative Present Value of Profit ($)"
layout_title . laxis_title .= "Month"
layout_x_axis . laxis_title .= "USD"
layout_y_axis $ \(name, rows) ->
forM_ runs plot (line name [pointsCumulativePresentValueOfCashFlow rows])
CC BY 4.0 — Please attribute "Torsten Scholak" with a link to the original. Code blocks are BSD-3-Clause unless noted.
Oct 8, 2025
OpenAI shipped AgentKit this week, a platform with a visual workflow editor, versioned agents, governed connectors, and evals infrastructure. The internet immediately split into two camps: people dunking on it ("this isn't AGI!") and people defending visual editors as necessary for non-technical users. Both camps are arguing about the wrong thing.
Aug 20, 2025
Enterprises are told they have to choose between cost or differentiation. But that's a false choice. If you outsource all AI, your costs stay volatile and your upside is capped. The winners will own enough of the stack to control both unit cost and quality.