summaryrefslogtreecommitdiff
path: root/Coalpit.hs
blob: 4d3bdd0ff88295abecf90bd22e463cf784d5ae05 (plain)
1
2
3
4
5
6
7
8
9
10
11
12
13
14
15
16
17
18
19
20
21
22
23
24
25
26
27
28
29
30
31
32
33
34
35
36
37
38
39
40
41
42
43
44
45
46
47
48
49
50
51
52
53
54
55
56
57
58
59
60
61
62
63
64
65
66
67
68
69
70
71
72
73
74
75
76
77
78
79
80
81
82
83
84
85
86
87
88
89
90
91
92
93
94
95
96
97
98
99
100
101
102
103
104
105
106
107
108
109
110
111
112
113
114
115
116
117
118
119
120
121
122
123
124
125
126
127
128
129
130
131
132
133
134
135
136
137
138
139
140
141
142
143
144
145
146
147
148
149
150
151
152
153
154
{-# LANGUAGE TypeOperators #-}
{-# LANGUAGE DefaultSignatures #-}
{-# LANGUAGE DeriveGeneric #-}
{-# LANGUAGE FlexibleContexts #-}
{-# LANGUAGE FlexibleInstances #-}
{-# LANGUAGE ScopedTypeVariables #-}

module Coalpit where

import Data.List
import GHC.Generics
import Text.Megaparsec
import Text.Megaparsec.Char
import Data.Maybe

type Parser = Parsec String String

args :: ToArgs a => a -> String
args = intercalate " " . toArgs

class ArgParser a where
  argParser :: Parser a
  default argParser :: (Generic a, GArgParser (Rep a)) => Parser a
  argParser = to <$> gArgParser

class GArgParser f where
  gArgParser :: Parser (f a)

class ToArgs a where
  toArgs :: a -> [String]
  default toArgs :: (Generic a, GToArgs (Rep a)) => a -> [String]
  toArgs a = gToArgs (from a)

class GToArgs f where
  gToArgs :: f a -> [String]


instance GArgParser U1 where
  gArgParser = pure U1

instance GToArgs U1 where
  gToArgs U1 = []

instance (GArgParser a, GArgParser b) => GArgParser (a :*: b) where
  gArgParser = (:*:) <$> gArgParser <* space <*> gArgParser

instance (GToArgs a, GToArgs b) => GToArgs (a :*: b) where
  gToArgs (a :*: b) = gToArgs a ++ gToArgs b

instance (Constructor c1, GArgParser f1, GArgParser (f :+: g)) =>
  GArgParser ((f :+: g) :+: C1 c1 f1) where
  gArgParser =
    L1 <$> gArgParser
    <|>
    R1 <$> (string (conName (undefined :: C1 c1 f a)) *> space *> gArgParser)

instance (Constructor c1, GArgParser f1, GArgParser (f :+: g)) =>
  GArgParser (C1 c1 f1 :+: (f :+: g)) where
  gArgParser =
    L1 <$> (string (conName (undefined :: C1 c1 f a)) *> space *> gArgParser)
    <|>
    R1 <$> gArgParser

instance (Constructor c1, Constructor c2, GArgParser f1, GArgParser f2) =>
  GArgParser (C1 c1 f1 :+: C1 c2 f2) where
  gArgParser =
    L1 <$> (string (conName (undefined :: C1 c1 f a)) *> space *> gArgParser)
    <|>
    R1 <$> (string (conName (undefined :: C1 c2 f a)) *> space *> gArgParser)

instance (Constructor c1, GToArgs f1, GToArgs (f :+: g)) =>
  GToArgs ((f :+: g) :+: C1 c1 f1) where
  gToArgs (L1 x) = gToArgs x
  gToArgs (R1 x) = conName x : gToArgs x

instance (Constructor c1, GToArgs f1, GToArgs (f :+: g)) =>
  GToArgs (C1 c1 f1 :+: (f :+: g)) where
  gToArgs (L1 x) = conName x : gToArgs x
  gToArgs (R1 x) = gToArgs x

instance (Constructor c1, Constructor c2, GToArgs f1, GToArgs f2) =>
  GToArgs (C1 c1 f1 :+: C1 c2 f2) where
  gToArgs (L1 x) = conName x : gToArgs x
  gToArgs (R1 x) = conName x : gToArgs x

instance {-#OVERLAPPING#-}
  (ArgParser a, Selector c) => GArgParser (S1 c (Rec0 (Maybe a))) where
  gArgParser = do
    case selName (undefined :: S1 c (Rec0 (Maybe a)) f) of
           "" -> M1 <$> gArgParser
           name -> do
             x <- optional $ string ("--" ++ name) *> space *> argParser
             pure $ M1 $ K1 x

instance (GArgParser a, Selector c) => GArgParser (S1 c a) where
  gArgParser = M1 <$> do
    let sname = case selName (undefined :: S1 c a f) of
          "" -> pure ()
          name -> string ("--" ++ name) *> space
    sname *> gArgParser

-- record selectors
instance {-#OVERLAPPING#-}
  (ToArgs a, Selector c) => GToArgs (S1 c (Rec0 (Maybe a))) where
  gToArgs s@(M1 (K1 x)) = case (selName s, x) of
                       ("", _) -> toArgs x
                       (_, Nothing) -> []
                       (name, Just x') -> ("--" ++ selName s) : toArgs x'

instance (GToArgs a, Selector c) => GToArgs (S1 c a) where
  gToArgs s@(M1 x) = case selName s of
                         "" -> gToArgs x
                         name -> ("--" ++ name) : gToArgs x

instance (GArgParser a, Constructor c) => GArgParser (C1 c a) where
  gArgParser = M1 <$> gArgParser

instance (GToArgs a, Constructor c) => GToArgs (C1 c a) where
  gToArgs c@(M1 x) = gToArgs x


instance (GArgParser a, Datatype c) => GArgParser (D1 c a) where
  gArgParser = M1 <$> gArgParser

instance (GToArgs a, Datatype c) => GToArgs (D1 c a) where
  gToArgs d@(M1 x) = gToArgs x

instance (ArgParser a) => GArgParser (K1 i a) where
  gArgParser = K1 <$> argParser

instance (ToArgs a) => GToArgs (K1 i a) where
  gToArgs (K1 x) = toArgs x


instance ArgParser Int where
  argParser = read <$> some digitChar

instance ToArgs Int where
  toArgs i = [show i]

instance ArgParser String where
  argParser = char '"' *> manyTill anyChar (char '"')

instance ToArgs String where
  toArgs i = [show i]

instance ArgParser Double where
  argParser = read <$> some (digitChar <|> char '.')

instance ToArgs Double where
  toArgs i = [show i]

instance ArgParser a => ArgParser (Maybe a)
instance ToArgs a => ToArgs (Maybe a)