github-actions: Github Actions

[ bsd3, language, library ] [ Propose Tags ] [ Report a vulnerability ]
Versions [RSS] 0.1.0.0
Dependencies aeson (>=2.2.3.0 && <2.3), base (>=4.14 && <4.22), containers (>=0.6.7 && <0.9), hedgehog (>=1.5 && <1.6), hoist-error (>=0.3 && <0.4), string-interpolate (>=0.3.3 && <0.4), text (>=1.2.4.1 && <1.3 || >=2.0.2 && <2.1 || >=2.1.1 && <2.2), vector (>=0.13.0.0 && <0.14) [details]
Tested with ghc ==9.6.6 || ==9.8.2 || ==9.10.1
License BSD-3-Clause
Copyright Copyright (C) 2025 Bellroy Pty Ltd
Author Bellroy Tech Team <haskell@bellroy.com>
Maintainer Bellroy Tech Team <haskell@bellroy.com>
Revised Revision 1 made by jack at 2025-07-04T06:35:13Z
Category Language
Home page http://github.com/bellroy/github-actions
Bug tracker http://github.com/bellroy/github-actions/issues
Source repo head: git clone https://github.com/bellroy/github-actions.git
Uploaded by michaelwebb76 at 2025-07-01T13:01:23Z
Distributions
Downloads 4 total (4 in the last 30 days)
Rating (no votes yet) [estimated by Bayesian average]
Your Rating
  • λ
  • λ
  • λ
Status Docs available [build log]
Last success reported on 2025-07-01 [all 1 reports]

Readme for github-actions-0.1.0.0

[back to package description]

Github Actions

Haskell-CI

This library provides types and instances for serializing and deserializing GitHub Actions YAML, so that workflows can be built and maintained in Haskell.

As specified here: https://docs.github.com/en/actions/writing-workflows/workflow-syntax-for-github-actions

Usage Examples

1. Exporting a Workflow to YAML

You can create a workflow in Haskell and export it to YAML format:

{-# LANGUAGE OverloadedStrings #-}

import qualified Data.Yaml as Yaml
import qualified Data.Map as Map
import qualified Data.Set as Set
import Data.List.NonEmpty (NonEmpty(..))
import Language.Github.Actions.Workflow
import qualified Language.Github.Actions.Job as Job
import qualified Language.Github.Actions.Job.Id as JobId
import qualified Language.Github.Actions.Step as Step
import qualified Language.Github.Actions.Workflow.Trigger as Trigger

-- Create a simple CI workflow
myWorkflow :: Workflow
myWorkflow = new
  { workflowName = Just "CI"
  , on = Set.singleton (Trigger.PushTrigger Trigger.pushTriggerDefaults)
  , jobs = Map.singleton (JobId.JobId "build") buildJob
  }

buildJob :: Job.Job
buildJob = Job.new
  { Job.jobName = Just "Build and Test"
  , Job.runsOn = Just "ubuntu-latest"
  , Job.steps = Just $ checkoutStep :| [buildStep, testStep]
  }

checkoutStep :: Step.Step
checkoutStep = Step.new
  { Step.name = Just "Checkout repository"
  , Step.uses = Just "actions/checkout@v4"
  }

buildStep :: Step.Step
buildStep = Step.new
  { Step.name = Just "Build project"
  , Step.run = Just "npm install && npm run build"
  }

testStep :: Step.Step
testStep = Step.new
  { Step.name = Just "Run tests"
  , Step.run = Just "npm test"
  }

-- Export to YAML
exportWorkflow :: IO ()
exportWorkflow = Yaml.encodeFile "workflow.yml" myWorkflow

2. Importing a YAML file into a Workflow representation

You can load an existing GitHub Actions YAML file into a Haskell Workflow type:

{-# LANGUAGE TypeApplications #-}

import qualified Data.Yaml as Yaml
import Language.Github.Actions.Workflow (Workflow)

-- Import from YAML file
importWorkflow :: FilePath -> IO (Either String Workflow)
importWorkflow yamlFilePath = do
  result <- Yaml.decodeFileEither @Workflow yamlFilePath
  case result of
    Left parseException ->
      return $ Left $ Yaml.prettyPrintParseException parseException
    Right workflow ->
      return $ Right workflow

-- Example usage
main :: IO ()
main = do
  result <- importWorkflow ".github/workflows/ci.yml"
  case result of
    Left errorMsg -> putStrLn $ "Failed to parse workflow: " ++ errorMsg
    Right workflow -> do
      putStrLn "Successfully parsed workflow!"
      print workflow