Skip to content

Instantly share code, notes, and snippets.

@masaeedu
Forked from parsonsmatt/overlays.hs
Last active July 16, 2021 04:08
Show Gist options
  • Star 0 You must be signed in to star a gist
  • Fork 0 You must be signed in to fork a gist
  • Save masaeedu/4f86aef80c9abbbe408b54eee549a2b8 to your computer and use it in GitHub Desktop.
Save masaeedu/4f86aef80c9abbbe408b54eee549a2b8 to your computer and use it in GitHub Desktop.
{-# LANGUAGE NamedFieldPuns #-}
{-# LANGUAGE OverloadedLists #-}
{-# OPTIONS_GHC -Wall #-}
module Lib where
import Control.Category ((<<<))
import Data.Function (fix)
import Data.Map (Map)
import qualified Data.Map.Lazy as Map
import Data.Monoid
import GHC.Stack (HasCallStack)
import Prelude hiding ((.))
type PkgSet = Map String Derivation
type Derivation = Int
(=:) :: a -> b -> (a, b)
a =: b = (a, b)
infixr 0 =:
nixpkgs :: PkgSet
nixpkgs =
[ "gcc" =: 1,
"ghc" =: 2
]
augment :: Semigroup a => (a -> a) -> a -> a
augment f i = f i <> i
augmentations :: Semigroup a => [a -> a] -> a -> a
augmentations = appEndo <<< getDual <<< foldMap (Dual <<< Endo <<< augment)
fix1 :: (a -> a -> a) -> a -> a
fix1 = (fix <<<)
overlays :: Semigroup a => (a -> [a -> a]) -> a -> a
overlays = fix1 <<< flip <<< fmap augmentations
myPackage :: HasCallStack => PkgSet
myPackage =
flip overlays nixpkgs $ \self ->
[ \super ->
[ "hello" =: self . "gcc" + 1
],
\super ->
[ "hello" =: super . "hello" + 4,
"helloOld" =: super . "hello",
"helloSelf" =: self . "hello",
"dang" =: self . "hello" + 1
],
\super ->
[ "hello" =: 1234,
"finalHello" =: self . "hello"
]
]
infixr 9 .
(.) :: PkgSet -> String -> Derivation
pkgSet . attr =
case Map.lookup attr pkgSet of
Nothing ->
error $
mconcat
( [ "The attribute ",
attr,
" was not found in the package set: ",
show pkgSet
] ::
[String]
)
Just a ->
a
Sign up for free to join this conversation on GitHub. Already have an account? Sign in to comment