{-# LANGUAGE DeriveGeneric #-} {-# LANGUAGE OverloadedStrings #-} {-# LANGUAGE NoImplicitPrelude #-} -- | Skills system for ava agent. -- -- Skills are modular instruction sets that extend ava's capabilities. -- They follow the Claude Skills format: a directory with SKILL.md and -- optional scripts/, references/, and assets/ subdirectories. -- -- Directory structure: -- _/var/ava/skills/ -- ├── shared/ -- Skills available to all users -- │ └── skill-creator/ -- ├── ben/ -- Ben's private skills -- └── alice/ -- Alice's private skills -- -- : out omni-agent-skills -- : dep aeson -- : dep directory module Omni.Agent.Skills ( Skill (..), SkillMetadata (..), loadSkill, loadSkillMetadata, listSkills, listSkillsForUser, publishSkill, skillTool, listSkillsTool, publishSkillTool, skillsDir, main, test, ) where import Alpha import Data.Aeson ((.:), (.=)) import qualified Data.Aeson as Aeson import qualified Data.List as List import qualified Data.Text as Text import qualified Data.Text.IO as TextIO import qualified Omni.Agent.Engine as Engine import qualified Omni.Agent.Paths as Paths import qualified Omni.Test as Test import qualified System.Directory as Directory import qualified System.FilePath as FilePath main :: IO () main = Test.run test test :: Test.Tree test = Test.group "Omni.Agent.Skills" [ Test.unit "skillsDir returns correct path" <| do let dir = skillsDir ("skills" `Text.isSuffixOf` Text.pack dir) Test.@=? True, Test.unit "SkillMetadata parses from YAML frontmatter" <| do let yaml = "name: test-skill\ndescription: A test skill" case parseYamlFrontmatter yaml of Nothing -> Test.assertFailure "Failed to parse frontmatter" Just meta -> do skillMetaName meta Test.@=? "test-skill" skillMetaDescription meta Test.@=? "A test skill", Test.unit "parseSkillMd extracts frontmatter and body" <| do let content = "---\n\ \name: my-skill\n\ \description: Does things\n\ \---\n\ \# My Skill\n\ \\n\ \Instructions here." case parseSkillMd content of Nothing -> Test.assertFailure "Failed to parse SKILL.md" Just (meta, body) -> do skillMetaName meta Test.@=? "my-skill" ("# My Skill" `Text.isInfixOf` body) Test.@=? True, Test.unit "skillTool schema is valid" <| do let schema = Engine.toolJsonSchema (skillTool "test-user") case schema of Aeson.Object _ -> pure () _ -> Test.assertFailure "Schema should be an object", Test.unit "listSkillsTool schema is valid" <| do let schema = Engine.toolJsonSchema (listSkillsTool "test-user") case schema of Aeson.Object _ -> pure () _ -> Test.assertFailure "Schema should be an object" ] -- | Base directory for all skills skillsDir :: FilePath skillsDir = Paths.skillsDir -- | Skill metadata from YAML frontmatter data SkillMetadata = SkillMetadata { skillMetaName :: Text, skillMetaDescription :: Text } deriving (Show, Eq, Generic) instance Aeson.FromJSON SkillMetadata where parseJSON = Aeson.withObject "SkillMetadata" <| \v -> (SkillMetadata (v .: "description") instance Aeson.ToJSON SkillMetadata where toJSON m = Aeson.object [ "name" .= skillMetaName m, "description" .= skillMetaDescription m ] -- | Simple YAML frontmatter parser for skill metadata -- Parses lines like "name: value" and "description: value" parseYamlFrontmatter :: Text -> Maybe SkillMetadata parseYamlFrontmatter yaml = do let kvPairs = parseKvLines (Text.lines yaml) getName = List.lookup "name" kvPairs getDesc = List.lookup "description" kvPairs name' <- getName desc <- getDesc pure SkillMetadata {skillMetaName = name', skillMetaDescription = desc} where parseKvLines :: [Text] -> [(Text, Text)] parseKvLines = mapMaybe parseKvLine parseKvLine :: Text -> Maybe (Text, Text) parseKvLine line = do let (key, rest) = Text.breakOn ":" line guard (not (Text.null rest)) let value = Text.strip (Text.drop 1 rest) guard (not (Text.null key)) pure (Text.strip key, value) -- | Full skill with metadata and content data Skill = Skill { skillName :: Text, skillDescription :: Text, skillBody :: Text, skillPath :: FilePath } deriving (Show, Eq, Generic) instance Aeson.ToJSON Skill where toJSON s = Aeson.object [ "name" .= skillName s, "description" .= skillDescription s, "body" .= skillBody s, "path" .= skillPath s ] -- | Parse SKILL.md content into metadata and body parseSkillMd :: Text -> Maybe (SkillMetadata, Text) parseSkillMd content = do let stripped = Text.strip content guard (Text.isPrefixOf "---" stripped) let afterFirst = Text.drop 3 stripped (yamlPart, rest) = Text.breakOn "---" (Text.stripStart afterFirst) guard (not (Text.null rest)) let body = Text.strip (Text.drop 3 rest) meta <- parseYamlFrontmatter (Text.strip yamlPart) pure (meta, body) -- | Load just the metadata for a skill (for progressive disclosure) loadSkillMetadata :: FilePath -> IO (Maybe SkillMetadata) loadSkillMetadata skillDir = do let skillMd = skillDir FilePath. "SKILL.md" exists <- Directory.doesFileExist skillMd if exists then do content <- TextIO.readFile skillMd pure (fst Text -> IO (Either Text Skill) loadSkill userName skillName' = do let userDir = skillsDir FilePath. Text.unpack userName FilePath. Text.unpack skillName' sharedDir = skillsDir FilePath. "shared" FilePath. Text.unpack skillName' -- Try user's private skills first, then shared userExists <- Directory.doesDirectoryExist userDir sharedExists <- Directory.doesDirectoryExist sharedDir let targetDir | userExists = Just userDir | sharedExists = Just sharedDir | otherwise = Nothing case targetDir of Nothing -> do available <- listSkillsForUser userName pure <| Left <| "Skill not found: " <> skillName' <> ". Available skills: " <> Text.intercalate ", " (map skillMetaName available) Just dir -> do let skillMd = dir FilePath. "SKILL.md" exists <- Directory.doesFileExist skillMd if exists then do content <- TextIO.readFile skillMd case parseSkillMd content of Nothing -> pure <| Left "Failed to parse SKILL.md frontmatter" Just (meta, body) -> pure <| Right <| Skill { skillName = skillMetaName meta, skillDescription = skillMetaDescription meta, skillBody = body, skillPath = dir } else pure <| Left ("SKILL.md not found in " <> Text.pack dir) -- | List all skills in a directory listSkillsInDir :: FilePath -> IO [SkillMetadata] listSkillsInDir dir = do exists <- Directory.doesDirectoryExist dir if exists then do entries <- Directory.listDirectory dir catMaybes do let entryPath = dir FilePath. entry isDir <- Directory.doesDirectoryExist entryPath if isDir then loadSkillMetadata entryPath else pure Nothing ) else pure [] -- | List all available skills (shared only) listSkills :: IO [SkillMetadata] listSkills = listSkillsInDir (skillsDir FilePath. "shared") -- | List skills available to a specific user (their private + shared) listSkillsForUser :: Text -> IO [SkillMetadata] listSkillsForUser userName = do userSkills <- listSkillsInDir (skillsDir FilePath. Text.unpack userName) sharedSkills <- listSkillsInDir (skillsDir FilePath. "shared") -- Dedupe by name, preferring user's version let userNames = map skillMetaName userSkills uniqueShared = filter (\s -> skillMetaName s `notElem` userNames) sharedSkills pure (userSkills <> uniqueShared) -- | Publish a skill from user's private directory to shared publishSkill :: Text -> Text -> IO (Either Text Text) publishSkill userName skillName' = do let userDir = skillsDir FilePath. Text.unpack userName FilePath. Text.unpack skillName' sharedDir = skillsDir FilePath. "shared" FilePath. Text.unpack skillName' userExists <- Directory.doesDirectoryExist userDir if not userExists then pure <| Left ("Skill not found in your directory: " <> skillName') else do -- Copy recursively Directory.createDirectoryIfMissing True sharedDir copyDirectory userDir sharedDir pure <| Right ("Published " <> skillName' <> " to shared skills") -- | Recursively copy a directory copyDirectory :: FilePath -> FilePath -> IO () copyDirectory src dst = do entries <- Directory.listDirectory src forM_ entries ( \entry -> do let srcPath = src FilePath. entry dstPath = dst FilePath. entry isDir <- Directory.doesDirectoryExist srcPath if isDir then do Directory.createDirectoryIfMissing True dstPath copyDirectory srcPath dstPath else Directory.copyFile srcPath dstPath ) -- Tool result helpers mkSuccess :: Text -> Aeson.Value mkSuccess output = Aeson.object [ "success" .= True, "output" .= output ] mkError :: Text -> Aeson.Value mkError err = Aeson.object [ "success" .= False, "error" .= err ] -- | Tool to load a skill's instructions skillTool :: Text -> Engine.Tool skillTool userName = Engine.Tool { Engine.toolName = "skill", Engine.toolDescription = "Load specialized instructions for a domain or task. " <> "Skills provide expert workflows, scripts, and context. " <> "Use list_skills to see available skills.", Engine.toolJsonSchema = Aeson.object [ "type" .= ("object" :: Text), "properties" .= Aeson.object [ "name" .= Aeson.object [ "type" .= ("string" :: Text), "description" .= ("Name of the skill to load" :: Text) ] ], "required" .= (["name"] :: [Text]) ], Engine.toolExecute = executeSkill userName } newtype SkillArgs = SkillArgs {skillArgsName :: Text} deriving (Show, Eq, Generic) instance Aeson.FromJSON SkillArgs where parseJSON = Aeson.withObject "SkillArgs" <| \v -> SkillArgs Aeson.Value -> IO Aeson.Value executeSkill userName v = case Aeson.fromJSON v of Aeson.Error e -> pure <| mkError (Text.pack e) Aeson.Success args -> do result <- loadSkill userName (skillArgsName args) case result of Left err -> pure <| mkError err Right skill -> pure <| Aeson.object [ "success" .= True, "skill" .= skillName skill, "description" .= skillDescription skill, "instructions" .= skillBody skill, "path" .= skillPath skill ] -- | Tool to list available skills listSkillsTool :: Text -> Engine.Tool listSkillsTool userName = Engine.Tool { Engine.toolName = "list_skills", Engine.toolDescription = "List all available skills you can load.", Engine.toolJsonSchema = Aeson.object [ "type" .= ("object" :: Text), "properties" .= Aeson.object [] ], Engine.toolExecute = \_ -> executeListSkills userName } executeListSkills :: Text -> IO Aeson.Value executeListSkills userName = do skills <- listSkillsForUser userName let formatted = Text.unlines <| map formatSkillMeta skills pure <| Aeson.object [ "success" .= True, "count" .= length skills, "skills" .= skills, "formatted" .= formatted ] where formatSkillMeta m = "- " <> skillMetaName m <> ": " <> skillMetaDescription m -- | Tool to publish a skill to shared publishSkillTool :: Text -> Engine.Tool publishSkillTool userName = Engine.Tool { Engine.toolName = "publish_skill", Engine.toolDescription = "Publish one of your private skills to the shared skills directory " <> "so other users can access it.", Engine.toolJsonSchema = Aeson.object [ "type" .= ("object" :: Text), "properties" .= Aeson.object [ "name" .= Aeson.object [ "type" .= ("string" :: Text), "description" .= ("Name of the skill to publish" :: Text) ] ], "required" .= (["name"] :: [Text]) ], Engine.toolExecute = executePublishSkill userName } executePublishSkill :: Text -> Aeson.Value -> IO Aeson.Value executePublishSkill userName v = case Aeson.fromJSON v of Aeson.Error e -> pure <| mkError (Text.pack e) Aeson.Success args -> do result <- publishSkill userName (skillArgsName args) case result of Left err -> pure <| mkError err Right msg -> pure <| mkSuccess msg